OSDN Git Service

* genemit.c (gen_insn): Call gen_exp with a non-null used
[pf3gnuchains/gcc-fork.git] / gcc / ada / exp_ch5.adb
1 ------------------------------------------------------------------------------
2 --                                                                          --
3 --                         GNAT COMPILER COMPONENTS                         --
4 --                                                                          --
5 --                              E X P _ C H 5                               --
6 --                                                                          --
7 --                                 B o d y                                  --
8 --                                                                          --
9 --          Copyright (C) 1992-2006, Free Software Foundation, Inc.         --
10 --                                                                          --
11 -- GNAT is free software;  you can  redistribute it  and/or modify it under --
12 -- terms of the  GNU General Public License as published  by the Free Soft- --
13 -- ware  Foundation;  either version 2,  or (at your option) any later ver- --
14 -- sion.  GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY;  without even the  implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License --
17 -- for  more details.  You should have  received  a copy of the GNU General --
18 -- Public License  distributed with GNAT;  see file COPYING.  If not, write --
19 -- to  the  Free Software Foundation,  51  Franklin  Street,  Fifth  Floor, --
20 -- Boston, MA 02110-1301, USA.                                              --
21 --                                                                          --
22 -- GNAT was originally developed  by the GNAT team at  New York University. --
23 -- Extensive contributions were provided by Ada Core Technologies Inc.      --
24 --                                                                          --
25 ------------------------------------------------------------------------------
26
27 with Atree;    use Atree;
28 with Checks;   use Checks;
29 with Debug;    use Debug;
30 with Einfo;    use Einfo;
31 with Elists;   use Elists;
32 with Exp_Aggr; use Exp_Aggr;
33 with Exp_Ch6;  use Exp_Ch6;
34 with Exp_Ch7;  use Exp_Ch7;
35 with Exp_Ch11; use Exp_Ch11;
36 with Exp_Dbug; use Exp_Dbug;
37 with Exp_Pakd; use Exp_Pakd;
38 with Exp_Tss;  use Exp_Tss;
39 with Exp_Util; use Exp_Util;
40 with Hostparm; use Hostparm;
41 with Nlists;   use Nlists;
42 with Nmake;    use Nmake;
43 with Opt;      use Opt;
44 with Restrict; use Restrict;
45 with Rident;   use Rident;
46 with Rtsfind;  use Rtsfind;
47 with Sinfo;    use Sinfo;
48 with Sem;      use Sem;
49 with Sem_Ch3;  use Sem_Ch3;
50 with Sem_Ch8;  use Sem_Ch8;
51 with Sem_Ch13; use Sem_Ch13;
52 with Sem_Eval; use Sem_Eval;
53 with Sem_Res;  use Sem_Res;
54 with Sem_Util; use Sem_Util;
55 with Snames;   use Snames;
56 with Stand;    use Stand;
57 with Stringt;  use Stringt;
58 with Tbuild;   use Tbuild;
59 with Ttypes;   use Ttypes;
60 with Uintp;    use Uintp;
61 with Validsw;  use Validsw;
62
63 package body Exp_Ch5 is
64
65    Enable_New_Return_Processing : constant Boolean := True;
66    --  ??? This flag is temporary. False causes the compiler to use the old
67    --  version of Analyze_Return_Statement; True, the new version, which does
68    --  not yet work. We probably want this to match the corresponding thing
69    --  in sem_ch6.adb.
70
71    function Change_Of_Representation (N : Node_Id) return Boolean;
72    --  Determine if the right hand side of the assignment N is a type
73    --  conversion which requires a change of representation. Called
74    --  only for the array and record cases.
75
76    procedure Expand_Assign_Array (N : Node_Id; Rhs : Node_Id);
77    --  N is an assignment which assigns an array value. This routine process
78    --  the various special cases and checks required for such assignments,
79    --  including change of representation. Rhs is normally simply the right
80    --  hand side of the assignment, except that if the right hand side is
81    --  a type conversion or a qualified expression, then the Rhs is the
82    --  actual expression inside any such type conversions or qualifications.
83
84    function Expand_Assign_Array_Loop
85      (N      : Node_Id;
86       Larray : Entity_Id;
87       Rarray : Entity_Id;
88       L_Type : Entity_Id;
89       R_Type : Entity_Id;
90       Ndim   : Pos;
91       Rev    : Boolean) return Node_Id;
92    --  N is an assignment statement which assigns an array value. This routine
93    --  expands the assignment into a loop (or nested loops for the case of a
94    --  multi-dimensional array) to do the assignment component by component.
95    --  Larray and Rarray are the entities of the actual arrays on the left
96    --  hand and right hand sides. L_Type and R_Type are the types of these
97    --  arrays (which may not be the same, due to either sliding, or to a
98    --  change of representation case). Ndim is the number of dimensions and
99    --  the parameter Rev indicates if the loops run normally (Rev = False),
100    --  or reversed (Rev = True). The value returned is the constructed
101    --  loop statement. Auxiliary declarations are inserted before node N
102    --  using the standard Insert_Actions mechanism.
103
104    procedure Expand_Assign_Record (N : Node_Id);
105    --  N is an assignment of a non-tagged record value. This routine handles
106    --  the case where the assignment must be made component by component,
107    --  either because the target is not byte aligned, or there is a change
108    --  of representation.
109
110    procedure Expand_Non_Function_Return (N : Node_Id);
111    --  Called by Expand_Simple_Return in case we're returning from a procedure
112    --  body, entry body, accept statement, or extended returns statement.
113    --  Note that all non-function returns are simple return statements.
114
115    procedure Expand_Simple_Function_Return (N : Node_Id);
116    --  Expand simple return from function. Called by Expand_Simple_Return in
117    --  case we're returning from a function body.
118
119    procedure Expand_Simple_Return (N : Node_Id);
120    --  Expansion for simple return statements. Calls either
121    --  Expand_Simple_Function_Return or Expand_Non_Function_Return.
122
123    function Make_Tag_Ctrl_Assignment (N : Node_Id) return List_Id;
124    --  Generate the necessary code for controlled and tagged assignment,
125    --  that is to say, finalization of the target before, adjustement of
126    --  the target after and save and restore of the tag and finalization
127    --  pointers which are not 'part of the value' and must not be changed
128    --  upon assignment. N is the original Assignment node.
129
130    procedure No_Secondary_Stack_Case (N : Node_Id);
131    --  Obsolete code to deal with functions for which
132    --  Function_Returns_With_DSP is True.
133
134    function Possible_Bit_Aligned_Component (N : Node_Id) return Boolean;
135    --  This function is used in processing the assignment of a record or
136    --  indexed component. The argument N is either the left hand or right
137    --  hand side of an assignment, and this function determines if there
138    --  is a record component reference where the record may be bit aligned
139    --  in a manner that causes trouble for the back end (see description
140    --  of Exp_Util.Component_May_Be_Bit_Aligned for further details).
141
142    ------------------------------
143    -- Change_Of_Representation --
144    ------------------------------
145
146    function Change_Of_Representation (N : Node_Id) return Boolean is
147       Rhs : constant Node_Id := Expression (N);
148    begin
149       return
150         Nkind (Rhs) = N_Type_Conversion
151           and then
152             not Same_Representation (Etype (Rhs), Etype (Expression (Rhs)));
153    end Change_Of_Representation;
154
155    -------------------------
156    -- Expand_Assign_Array --
157    -------------------------
158
159    --  There are two issues here. First, do we let Gigi do a block move, or
160    --  do we expand out into a loop? Second, we need to set the two flags
161    --  Forwards_OK and Backwards_OK which show whether the block move (or
162    --  corresponding loops) can be legitimately done in a forwards (low to
163    --  high) or backwards (high to low) manner.
164
165    procedure Expand_Assign_Array (N : Node_Id; Rhs : Node_Id) is
166       Loc : constant Source_Ptr := Sloc (N);
167
168       Lhs : constant Node_Id := Name (N);
169
170       Act_Lhs : constant Node_Id := Get_Referenced_Object (Lhs);
171       Act_Rhs : Node_Id          := Get_Referenced_Object (Rhs);
172
173       L_Type : constant Entity_Id :=
174                  Underlying_Type (Get_Actual_Subtype (Act_Lhs));
175       R_Type : Entity_Id :=
176                  Underlying_Type (Get_Actual_Subtype (Act_Rhs));
177
178       L_Slice : constant Boolean := Nkind (Act_Lhs) = N_Slice;
179       R_Slice : constant Boolean := Nkind (Act_Rhs) = N_Slice;
180
181       Crep : constant Boolean := Change_Of_Representation (N);
182
183       Larray  : Node_Id;
184       Rarray  : Node_Id;
185
186       Ndim : constant Pos := Number_Dimensions (L_Type);
187
188       Loop_Required : Boolean := False;
189       --  This switch is set to True if the array move must be done using
190       --  an explicit front end generated loop.
191
192       procedure Apply_Dereference (Arg : in out Node_Id);
193       --  If the argument is an access to an array, and the assignment is
194       --  converted into a procedure call, apply explicit dereference.
195
196       function Has_Address_Clause (Exp : Node_Id) return Boolean;
197       --  Test if Exp is a reference to an array whose declaration has
198       --  an address clause, or it is a slice of such an array.
199
200       function Is_Formal_Array (Exp : Node_Id) return Boolean;
201       --  Test if Exp is a reference to an array which is either a formal
202       --  parameter or a slice of a formal parameter. These are the cases
203       --  where hidden aliasing can occur.
204
205       function Is_Non_Local_Array (Exp : Node_Id) return Boolean;
206       --  Determine if Exp is a reference to an array variable which is other
207       --  than an object defined in the current scope, or a slice of such
208       --  an object. Such objects can be aliased to parameters (unlike local
209       --  array references).
210
211       -----------------------
212       -- Apply_Dereference --
213       -----------------------
214
215       procedure Apply_Dereference (Arg : in out Node_Id) is
216          Typ : constant Entity_Id := Etype (Arg);
217       begin
218          if Is_Access_Type (Typ) then
219             Rewrite (Arg, Make_Explicit_Dereference (Loc,
220               Prefix => Relocate_Node (Arg)));
221             Analyze_And_Resolve (Arg, Designated_Type (Typ));
222          end if;
223       end Apply_Dereference;
224
225       ------------------------
226       -- Has_Address_Clause --
227       ------------------------
228
229       function Has_Address_Clause (Exp : Node_Id) return Boolean is
230       begin
231          return
232            (Is_Entity_Name (Exp) and then
233                               Present (Address_Clause (Entity (Exp))))
234              or else
235            (Nkind (Exp) = N_Slice and then Has_Address_Clause (Prefix (Exp)));
236       end Has_Address_Clause;
237
238       ---------------------
239       -- Is_Formal_Array --
240       ---------------------
241
242       function Is_Formal_Array (Exp : Node_Id) return Boolean is
243       begin
244          return
245            (Is_Entity_Name (Exp) and then Is_Formal (Entity (Exp)))
246              or else
247            (Nkind (Exp) = N_Slice and then Is_Formal_Array (Prefix (Exp)));
248       end Is_Formal_Array;
249
250       ------------------------
251       -- Is_Non_Local_Array --
252       ------------------------
253
254       function Is_Non_Local_Array (Exp : Node_Id) return Boolean is
255       begin
256          return (Is_Entity_Name (Exp)
257                    and then Scope (Entity (Exp)) /= Current_Scope)
258             or else (Nkind (Exp) = N_Slice
259                        and then Is_Non_Local_Array (Prefix (Exp)));
260       end Is_Non_Local_Array;
261
262       --  Determine if Lhs, Rhs are formal arrays or nonlocal arrays
263
264       Lhs_Formal : constant Boolean := Is_Formal_Array (Act_Lhs);
265       Rhs_Formal : constant Boolean := Is_Formal_Array (Act_Rhs);
266
267       Lhs_Non_Local_Var : constant Boolean := Is_Non_Local_Array (Act_Lhs);
268       Rhs_Non_Local_Var : constant Boolean := Is_Non_Local_Array (Act_Rhs);
269
270    --  Start of processing for Expand_Assign_Array
271
272    begin
273       --  Deal with length check, note that the length check is done with
274       --  respect to the right hand side as given, not a possible underlying
275       --  renamed object, since this would generate incorrect extra checks.
276
277       Apply_Length_Check (Rhs, L_Type);
278
279       --  We start by assuming that the move can be done in either
280       --  direction, i.e. that the two sides are completely disjoint.
281
282       Set_Forwards_OK  (N, True);
283       Set_Backwards_OK (N, True);
284
285       --  Normally it is only the slice case that can lead to overlap,
286       --  and explicit checks for slices are made below. But there is
287       --  one case where the slice can be implicit and invisible to us
288       --  and that is the case where we have a one dimensional array,
289       --  and either both operands are parameters, or one is a parameter
290       --  and the other is a global variable. In this case the parameter
291       --  could be a slice that overlaps with the other parameter.
292
293       --  Check for the case of slices requiring an explicit loop. Normally
294       --  it is only the explicit slice cases that bother us, but in the
295       --  case of one dimensional arrays, parameters can be slices that
296       --  are passed by reference, so we can have aliasing for assignments
297       --  from one parameter to another, or assignments between parameters
298       --  and nonlocal variables. However, if the array subtype is a
299       --  constrained first subtype in the parameter case, then we don't
300       --  have to worry about overlap, since slice assignments aren't
301       --  possible (other than for a slice denoting the whole array).
302
303       --  Note: overlap is never possible if there is a change of
304       --  representation, so we can exclude this case.
305
306       if Ndim = 1
307         and then not Crep
308         and then
309            ((Lhs_Formal and Rhs_Formal)
310               or else
311             (Lhs_Formal and Rhs_Non_Local_Var)
312               or else
313             (Rhs_Formal and Lhs_Non_Local_Var))
314         and then
315            (not Is_Constrained (Etype (Lhs))
316              or else not Is_First_Subtype (Etype (Lhs)))
317
318          --  In the case of compiling for the Java Virtual Machine,
319          --  slices are always passed by making a copy, so we don't
320          --  have to worry about overlap. We also want to prevent
321          --  generation of "<" comparisons for array addresses,
322          --  since that's a meaningless operation on the JVM.
323
324         and then not Java_VM
325       then
326          Set_Forwards_OK  (N, False);
327          Set_Backwards_OK (N, False);
328
329          --  Note: the bit-packed case is not worrisome here, since if
330          --  we have a slice passed as a parameter, it is always aligned
331          --  on a byte boundary, and if there are no explicit slices, the
332          --  assignment can be performed directly.
333       end if;
334
335       --  We certainly must use a loop for change of representation
336       --  and also we use the operand of the conversion on the right
337       --  hand side as the effective right hand side (the component
338       --  types must match in this situation).
339
340       if Crep then
341          Act_Rhs := Get_Referenced_Object (Rhs);
342          R_Type  := Get_Actual_Subtype (Act_Rhs);
343          Loop_Required := True;
344
345       --  We require a loop if the left side is possibly bit unaligned
346
347       elsif Possible_Bit_Aligned_Component (Lhs)
348               or else
349             Possible_Bit_Aligned_Component (Rhs)
350       then
351          Loop_Required := True;
352
353       --  Arrays with controlled components are expanded into a loop
354       --  to force calls to adjust at the component level.
355
356       elsif Has_Controlled_Component (L_Type) then
357          Loop_Required := True;
358
359          --  If object is atomic, we cannot tolerate a loop
360
361       elsif Is_Atomic_Object (Act_Lhs)
362               or else
363             Is_Atomic_Object (Act_Rhs)
364       then
365          return;
366
367       --  Loop is required if we have atomic components since we have to
368       --  be sure to do any accesses on an element by element basis.
369
370       elsif Has_Atomic_Components (L_Type)
371         or else Has_Atomic_Components (R_Type)
372         or else Is_Atomic (Component_Type (L_Type))
373         or else Is_Atomic (Component_Type (R_Type))
374       then
375          Loop_Required := True;
376
377       --  Case where no slice is involved
378
379       elsif not L_Slice and not R_Slice then
380
381          --  The following code deals with the case of unconstrained bit
382          --  packed arrays. The problem is that the template for such
383          --  arrays contains the bounds of the actual source level array,
384
385          --  But the copy of an entire array requires the bounds of the
386          --  underlying array. It would be nice if the back end could take
387          --  care of this, but right now it does not know how, so if we
388          --  have such a type, then we expand out into a loop, which is
389          --  inefficient but works correctly. If we don't do this, we
390          --  get the wrong length computed for the array to be moved.
391          --  The two cases we need to worry about are:
392
393          --  Explicit deference of an unconstrained packed array type as
394          --  in the following example:
395
396          --    procedure C52 is
397          --       type BITS is array(INTEGER range <>) of BOOLEAN;
398          --       pragma PACK(BITS);
399          --       type A is access BITS;
400          --       P1,P2 : A;
401          --    begin
402          --       P1 := new BITS (1 .. 65_535);
403          --       P2 := new BITS (1 .. 65_535);
404          --       P2.ALL := P1.ALL;
405          --    end C52;
406
407          --  A formal parameter reference with an unconstrained bit
408          --  array type is the other case we need to worry about (here
409          --  we assume the same BITS type declared above):
410
411          --    procedure Write_All (File : out BITS; Contents : BITS);
412          --    begin
413          --       File.Storage := Contents;
414          --    end Write_All;
415
416          --  We expand to a loop in either of these two cases
417
418          --  Question for future thought. Another potentially more efficient
419          --  approach would be to create the actual subtype, and then do an
420          --  unchecked conversion to this actual subtype ???
421
422          Check_Unconstrained_Bit_Packed_Array : declare
423
424             function Is_UBPA_Reference (Opnd : Node_Id) return Boolean;
425             --  Function to perform required test for the first case,
426             --  above (dereference of an unconstrained bit packed array)
427
428             -----------------------
429             -- Is_UBPA_Reference --
430             -----------------------
431
432             function Is_UBPA_Reference (Opnd : Node_Id) return Boolean is
433                Typ      : constant Entity_Id := Underlying_Type (Etype (Opnd));
434                P_Type   : Entity_Id;
435                Des_Type : Entity_Id;
436
437             begin
438                if Present (Packed_Array_Type (Typ))
439                  and then Is_Array_Type (Packed_Array_Type (Typ))
440                  and then not Is_Constrained (Packed_Array_Type (Typ))
441                then
442                   return True;
443
444                elsif Nkind (Opnd) = N_Explicit_Dereference then
445                   P_Type := Underlying_Type (Etype (Prefix (Opnd)));
446
447                   if not Is_Access_Type (P_Type) then
448                      return False;
449
450                   else
451                      Des_Type := Designated_Type (P_Type);
452                      return
453                        Is_Bit_Packed_Array (Des_Type)
454                          and then not Is_Constrained (Des_Type);
455                   end if;
456
457                else
458                   return False;
459                end if;
460             end Is_UBPA_Reference;
461
462          --  Start of processing for Check_Unconstrained_Bit_Packed_Array
463
464          begin
465             if Is_UBPA_Reference (Lhs)
466                  or else
467                Is_UBPA_Reference (Rhs)
468             then
469                Loop_Required := True;
470
471             --  Here if we do not have the case of a reference to a bit
472             --  packed unconstrained array case. In this case gigi can
473             --  most certainly handle the assignment if a forwards move
474             --  is allowed.
475
476             --  (could it handle the backwards case also???)
477
478             elsif Forwards_OK (N) then
479                return;
480             end if;
481          end Check_Unconstrained_Bit_Packed_Array;
482
483       --  The back end can always handle the assignment if the right side is a
484       --  string literal (note that overlap is definitely impossible in this
485       --  case). If the type is packed, a string literal is always converted
486       --  into aggregate, except in the case of a null slice, for which no
487       --  aggregate can be written. In that case, rewrite the assignment as a
488       --  null statement, a length check has already been emitted to verify
489       --  that the range of the left-hand side is empty.
490
491       --  Note that this code is not executed if we had an assignment of
492       --  a string literal to a non-bit aligned component of a record, a
493       --  case which cannot be handled by the backend
494
495       elsif Nkind (Rhs) = N_String_Literal then
496          if String_Length (Strval (Rhs)) = 0
497            and then Is_Bit_Packed_Array (L_Type)
498          then
499             Rewrite (N, Make_Null_Statement (Loc));
500             Analyze (N);
501          end if;
502
503          return;
504
505       --  If either operand is bit packed, then we need a loop, since we
506       --  can't be sure that the slice is byte aligned. Similarly, if either
507       --  operand is a possibly unaligned slice, then we need a loop (since
508       --  the back end cannot handle unaligned slices).
509
510       elsif Is_Bit_Packed_Array (L_Type)
511         or else Is_Bit_Packed_Array (R_Type)
512         or else Is_Possibly_Unaligned_Slice (Lhs)
513         or else Is_Possibly_Unaligned_Slice (Rhs)
514       then
515          Loop_Required := True;
516
517       --  If we are not bit-packed, and we have only one slice, then no
518       --  overlap is possible except in the parameter case, so we can let
519       --  the back end handle things.
520
521       elsif not (L_Slice and R_Slice) then
522          if Forwards_OK (N) then
523             return;
524          end if;
525       end if;
526
527       --  If the right-hand side is a string literal, introduce a temporary
528       --  for it, for use in the generated loop that will follow.
529
530       if Nkind (Rhs) = N_String_Literal then
531          declare
532             Temp : constant Entity_Id :=
533                      Make_Defining_Identifier (Loc, New_Internal_Name ('T'));
534             Decl : Node_Id;
535
536          begin
537             Decl :=
538               Make_Object_Declaration (Loc,
539                  Defining_Identifier => Temp,
540                  Object_Definition => New_Occurrence_Of (L_Type, Loc),
541                  Expression => Relocate_Node (Rhs));
542
543             Insert_Action (N, Decl);
544             Rewrite (Rhs, New_Occurrence_Of (Temp, Loc));
545             R_Type := Etype (Temp);
546          end;
547       end if;
548
549       --  Come here to complete the analysis
550
551       --    Loop_Required: Set to True if we know that a loop is required
552       --                   regardless of overlap considerations.
553
554       --    Forwards_OK:   Set to False if we already know that a forwards
555       --                   move is not safe, else set to True.
556
557       --    Backwards_OK:  Set to False if we already know that a backwards
558       --                   move is not safe, else set to True
559
560       --  Our task at this stage is to complete the overlap analysis, which
561       --  can result in possibly setting Forwards_OK or Backwards_OK to
562       --  False, and then generating the final code, either by deciding
563       --  that it is OK after all to let Gigi handle it, or by generating
564       --  appropriate code in the front end.
565
566       declare
567          L_Index_Typ : constant Node_Id := Etype (First_Index (L_Type));
568          R_Index_Typ : constant Node_Id := Etype (First_Index (R_Type));
569
570          Left_Lo  : constant Node_Id := Type_Low_Bound  (L_Index_Typ);
571          Left_Hi  : constant Node_Id := Type_High_Bound (L_Index_Typ);
572          Right_Lo : constant Node_Id := Type_Low_Bound  (R_Index_Typ);
573          Right_Hi : constant Node_Id := Type_High_Bound (R_Index_Typ);
574
575          Act_L_Array : Node_Id;
576          Act_R_Array : Node_Id;
577
578          Cleft_Lo  : Node_Id;
579          Cright_Lo : Node_Id;
580          Condition : Node_Id;
581
582          Cresult : Compare_Result;
583
584       begin
585          --  Get the expressions for the arrays. If we are dealing with a
586          --  private type, then convert to the underlying type. We can do
587          --  direct assignments to an array that is a private type, but
588          --  we cannot assign to elements of the array without this extra
589          --  unchecked conversion.
590
591          if Nkind (Act_Lhs) = N_Slice then
592             Larray := Prefix (Act_Lhs);
593          else
594             Larray := Act_Lhs;
595
596             if Is_Private_Type (Etype (Larray)) then
597                Larray :=
598                  Unchecked_Convert_To
599                    (Underlying_Type (Etype (Larray)), Larray);
600             end if;
601          end if;
602
603          if Nkind (Act_Rhs) = N_Slice then
604             Rarray := Prefix (Act_Rhs);
605          else
606             Rarray := Act_Rhs;
607
608             if Is_Private_Type (Etype (Rarray)) then
609                Rarray :=
610                  Unchecked_Convert_To
611                    (Underlying_Type (Etype (Rarray)), Rarray);
612             end if;
613          end if;
614
615          --  If both sides are slices, we must figure out whether
616          --  it is safe to do the move in one direction or the other
617          --  It is always safe if there is a change of representation
618          --  since obviously two arrays with different representations
619          --  cannot possibly overlap.
620
621          if (not Crep) and L_Slice and R_Slice then
622             Act_L_Array := Get_Referenced_Object (Prefix (Act_Lhs));
623             Act_R_Array := Get_Referenced_Object (Prefix (Act_Rhs));
624
625             --  If both left and right hand arrays are entity names, and
626             --  refer to different entities, then we know that the move
627             --  is safe (the two storage areas are completely disjoint).
628
629             if Is_Entity_Name (Act_L_Array)
630               and then Is_Entity_Name (Act_R_Array)
631               and then Entity (Act_L_Array) /= Entity (Act_R_Array)
632             then
633                null;
634
635             --  Otherwise, we assume the worst, which is that the two
636             --  arrays are the same array. There is no need to check if
637             --  we know that is the case, because if we don't know it,
638             --  we still have to assume it!
639
640             --  Generally if the same array is involved, then we have
641             --  an overlapping case. We will have to really assume the
642             --  worst (i.e. set neither of the OK flags) unless we can
643             --  determine the lower or upper bounds at compile time and
644             --  compare them.
645
646             else
647                Cresult := Compile_Time_Compare (Left_Lo, Right_Lo);
648
649                if Cresult = Unknown then
650                   Cresult := Compile_Time_Compare (Left_Hi, Right_Hi);
651                end if;
652
653                case Cresult is
654                   when LT | LE | EQ => Set_Backwards_OK (N, False);
655                   when GT | GE      => Set_Forwards_OK  (N, False);
656                   when NE | Unknown => Set_Backwards_OK (N, False);
657                                        Set_Forwards_OK  (N, False);
658                end case;
659             end if;
660          end if;
661
662          --  If after that analysis, Forwards_OK is still True, and
663          --  Loop_Required is False, meaning that we have not discovered
664          --  some non-overlap reason for requiring a loop, then we can
665          --  still let gigi handle it.
666
667          if not Loop_Required then
668             if Forwards_OK (N) then
669                return;
670             else
671                null;
672                --  Here is where a memmove would be appropriate ???
673             end if;
674          end if;
675
676          --  At this stage we have to generate an explicit loop, and
677          --  we have the following cases:
678
679          --  Forwards_OK = True
680
681          --    Rnn : right_index := right_index'First;
682          --    for Lnn in left-index loop
683          --       left (Lnn) := right (Rnn);
684          --       Rnn := right_index'Succ (Rnn);
685          --    end loop;
686
687          --    Note: the above code MUST be analyzed with checks off,
688          --    because otherwise the Succ could overflow. But in any
689          --    case this is more efficient!
690
691          --  Forwards_OK = False, Backwards_OK = True
692
693          --    Rnn : right_index := right_index'Last;
694          --    for Lnn in reverse left-index loop
695          --       left (Lnn) := right (Rnn);
696          --       Rnn := right_index'Pred (Rnn);
697          --    end loop;
698
699          --    Note: the above code MUST be analyzed with checks off,
700          --    because otherwise the Pred could overflow. But in any
701          --    case this is more efficient!
702
703          --  Forwards_OK = Backwards_OK = False
704
705          --    This only happens if we have the same array on each side. It is
706          --    possible to create situations using overlays that violate this,
707          --    but we simply do not promise to get this "right" in this case.
708
709          --    There are two possible subcases. If the No_Implicit_Conditionals
710          --    restriction is set, then we generate the following code:
711
712          --      declare
713          --        T : constant <operand-type> := rhs;
714          --      begin
715          --        lhs := T;
716          --      end;
717
718          --    If implicit conditionals are permitted, then we generate:
719
720          --      if Left_Lo <= Right_Lo then
721          --         <code for Forwards_OK = True above>
722          --      else
723          --         <code for Backwards_OK = True above>
724          --      end if;
725
726          --  Cases where either Forwards_OK or Backwards_OK is true
727
728          if Forwards_OK (N) or else Backwards_OK (N) then
729             if Controlled_Type (Component_Type (L_Type))
730               and then Base_Type (L_Type) = Base_Type (R_Type)
731               and then Ndim = 1
732               and then not No_Ctrl_Actions (N)
733             then
734                declare
735                   Proc : constant Entity_Id :=
736                            TSS (Base_Type (L_Type), TSS_Slice_Assign);
737                   Actuals : List_Id;
738
739                begin
740                   Apply_Dereference (Larray);
741                   Apply_Dereference (Rarray);
742                   Actuals := New_List (
743                     Duplicate_Subexpr (Larray,   Name_Req => True),
744                     Duplicate_Subexpr (Rarray,   Name_Req => True),
745                     Duplicate_Subexpr (Left_Lo,  Name_Req => True),
746                     Duplicate_Subexpr (Left_Hi,  Name_Req => True),
747                     Duplicate_Subexpr (Right_Lo, Name_Req => True),
748                     Duplicate_Subexpr (Right_Hi, Name_Req => True));
749
750                   Append_To (Actuals,
751                     New_Occurrence_Of (
752                       Boolean_Literals (not Forwards_OK (N)), Loc));
753
754                   Rewrite (N,
755                     Make_Procedure_Call_Statement (Loc,
756                       Name => New_Reference_To (Proc, Loc),
757                       Parameter_Associations => Actuals));
758                end;
759
760             else
761                Rewrite (N,
762                  Expand_Assign_Array_Loop
763                    (N, Larray, Rarray, L_Type, R_Type, Ndim,
764                     Rev => not Forwards_OK (N)));
765             end if;
766
767          --  Case of both are false with No_Implicit_Conditionals
768
769          elsif Restriction_Active (No_Implicit_Conditionals) then
770             declare
771                   T : constant Entity_Id :=
772                         Make_Defining_Identifier (Loc, Chars => Name_T);
773
774             begin
775                Rewrite (N,
776                  Make_Block_Statement (Loc,
777                   Declarations => New_List (
778                     Make_Object_Declaration (Loc,
779                       Defining_Identifier => T,
780                       Constant_Present  => True,
781                       Object_Definition =>
782                         New_Occurrence_Of (Etype (Rhs), Loc),
783                       Expression        => Relocate_Node (Rhs))),
784
785                     Handled_Statement_Sequence =>
786                       Make_Handled_Sequence_Of_Statements (Loc,
787                         Statements => New_List (
788                           Make_Assignment_Statement (Loc,
789                             Name       => Relocate_Node (Lhs),
790                             Expression => New_Occurrence_Of (T, Loc))))));
791             end;
792
793          --  Case of both are false with implicit conditionals allowed
794
795          else
796             --  Before we generate this code, we must ensure that the
797             --  left and right side array types are defined. They may
798             --  be itypes, and we cannot let them be defined inside the
799             --  if, since the first use in the then may not be executed.
800
801             Ensure_Defined (L_Type, N);
802             Ensure_Defined (R_Type, N);
803
804             --  We normally compare addresses to find out which way round
805             --  to do the loop, since this is realiable, and handles the
806             --  cases of parameters, conversions etc. But we can't do that
807             --  in the bit packed case or the Java VM case, because addresses
808             --  don't work there.
809
810             if not Is_Bit_Packed_Array (L_Type) and then not Java_VM then
811                Condition :=
812                  Make_Op_Le (Loc,
813                    Left_Opnd =>
814                      Unchecked_Convert_To (RTE (RE_Integer_Address),
815                        Make_Attribute_Reference (Loc,
816                          Prefix =>
817                            Make_Indexed_Component (Loc,
818                              Prefix =>
819                                Duplicate_Subexpr_Move_Checks (Larray, True),
820                              Expressions => New_List (
821                                Make_Attribute_Reference (Loc,
822                                  Prefix =>
823                                    New_Reference_To
824                                      (L_Index_Typ, Loc),
825                                  Attribute_Name => Name_First))),
826                          Attribute_Name => Name_Address)),
827
828                    Right_Opnd =>
829                      Unchecked_Convert_To (RTE (RE_Integer_Address),
830                        Make_Attribute_Reference (Loc,
831                          Prefix =>
832                            Make_Indexed_Component (Loc,
833                              Prefix =>
834                                Duplicate_Subexpr_Move_Checks (Rarray, True),
835                              Expressions => New_List (
836                                Make_Attribute_Reference (Loc,
837                                  Prefix =>
838                                    New_Reference_To
839                                      (R_Index_Typ, Loc),
840                                  Attribute_Name => Name_First))),
841                          Attribute_Name => Name_Address)));
842
843             --  For the bit packed and Java VM cases we use the bounds.
844             --  That's OK, because we don't have to worry about parameters,
845             --  since they cannot cause overlap. Perhaps we should worry
846             --  about weird slice conversions ???
847
848             else
849                --  Copy the bounds and reset the Analyzed flag, because the
850                --  bounds of the index type itself may be universal, and must
851                --  must be reaanalyzed to acquire the proper type for Gigi.
852
853                Cleft_Lo  := New_Copy_Tree (Left_Lo);
854                Cright_Lo := New_Copy_Tree (Right_Lo);
855                Set_Analyzed (Cleft_Lo, False);
856                Set_Analyzed (Cright_Lo, False);
857
858                Condition :=
859                  Make_Op_Le (Loc,
860                    Left_Opnd  => Cleft_Lo,
861                    Right_Opnd => Cright_Lo);
862             end if;
863
864             if Controlled_Type (Component_Type (L_Type))
865               and then Base_Type (L_Type) = Base_Type (R_Type)
866               and then Ndim = 1
867               and then not No_Ctrl_Actions (N)
868             then
869
870                --  Call TSS procedure for array assignment, passing the
871                --  the explicit bounds of right and left hand sides.
872
873                declare
874                   Proc    : constant Node_Id :=
875                               TSS (Base_Type (L_Type), TSS_Slice_Assign);
876                   Actuals : List_Id;
877
878                begin
879                   Apply_Dereference (Larray);
880                   Apply_Dereference (Rarray);
881                   Actuals := New_List (
882                     Duplicate_Subexpr (Larray,   Name_Req => True),
883                     Duplicate_Subexpr (Rarray,   Name_Req => True),
884                     Duplicate_Subexpr (Left_Lo,  Name_Req => True),
885                     Duplicate_Subexpr (Left_Hi,  Name_Req => True),
886                     Duplicate_Subexpr (Right_Lo, Name_Req => True),
887                     Duplicate_Subexpr (Right_Hi, Name_Req => True));
888
889                   Append_To (Actuals,
890                      Make_Op_Not (Loc,
891                        Right_Opnd => Condition));
892
893                   Rewrite (N,
894                     Make_Procedure_Call_Statement (Loc,
895                       Name => New_Reference_To (Proc, Loc),
896                       Parameter_Associations => Actuals));
897                end;
898
899             else
900                Rewrite (N,
901                  Make_Implicit_If_Statement (N,
902                    Condition => Condition,
903
904                    Then_Statements => New_List (
905                      Expand_Assign_Array_Loop
906                       (N, Larray, Rarray, L_Type, R_Type, Ndim,
907                        Rev => False)),
908
909                    Else_Statements => New_List (
910                      Expand_Assign_Array_Loop
911                       (N, Larray, Rarray, L_Type, R_Type, Ndim,
912                        Rev => True))));
913             end if;
914          end if;
915
916          Analyze (N, Suppress => All_Checks);
917       end;
918
919    exception
920       when RE_Not_Available =>
921          return;
922    end Expand_Assign_Array;
923
924    ------------------------------
925    -- Expand_Assign_Array_Loop --
926    ------------------------------
927
928    --  The following is an example of the loop generated for the case of
929    --  a two-dimensional array:
930
931    --    declare
932    --       R2b : Tm1X1 := 1;
933    --    begin
934    --       for L1b in 1 .. 100 loop
935    --          declare
936    --             R4b : Tm1X2 := 1;
937    --          begin
938    --             for L3b in 1 .. 100 loop
939    --                vm1 (L1b, L3b) := vm2 (R2b, R4b);
940    --                R4b := Tm1X2'succ(R4b);
941    --             end loop;
942    --          end;
943    --          R2b := Tm1X1'succ(R2b);
944    --       end loop;
945    --    end;
946
947    --  Here Rev is False, and Tm1Xn are the subscript types for the right
948    --  hand side. The declarations of R2b and R4b are inserted before the
949    --  original assignment statement.
950
951    function Expand_Assign_Array_Loop
952      (N      : Node_Id;
953       Larray : Entity_Id;
954       Rarray : Entity_Id;
955       L_Type : Entity_Id;
956       R_Type : Entity_Id;
957       Ndim   : Pos;
958       Rev    : Boolean) return Node_Id
959    is
960       Loc  : constant Source_Ptr := Sloc (N);
961
962       Lnn : array (1 .. Ndim) of Entity_Id;
963       Rnn : array (1 .. Ndim) of Entity_Id;
964       --  Entities used as subscripts on left and right sides
965
966       L_Index_Type : array (1 .. Ndim) of Entity_Id;
967       R_Index_Type : array (1 .. Ndim) of Entity_Id;
968       --  Left and right index types
969
970       Assign : Node_Id;
971
972       F_Or_L : Name_Id;
973       S_Or_P : Name_Id;
974
975    begin
976       if Rev then
977          F_Or_L := Name_Last;
978          S_Or_P := Name_Pred;
979       else
980          F_Or_L := Name_First;
981          S_Or_P := Name_Succ;
982       end if;
983
984       --  Setup index types and subscript entities
985
986       declare
987          L_Index : Node_Id;
988          R_Index : Node_Id;
989
990       begin
991          L_Index := First_Index (L_Type);
992          R_Index := First_Index (R_Type);
993
994          for J in 1 .. Ndim loop
995             Lnn (J) :=
996               Make_Defining_Identifier (Loc,
997                 Chars => New_Internal_Name ('L'));
998
999             Rnn (J) :=
1000               Make_Defining_Identifier (Loc,
1001                 Chars => New_Internal_Name ('R'));
1002
1003             L_Index_Type (J) := Etype (L_Index);
1004             R_Index_Type (J) := Etype (R_Index);
1005
1006             Next_Index (L_Index);
1007             Next_Index (R_Index);
1008          end loop;
1009       end;
1010
1011       --  Now construct the assignment statement
1012
1013       declare
1014          ExprL : constant List_Id := New_List;
1015          ExprR : constant List_Id := New_List;
1016
1017       begin
1018          for J in 1 .. Ndim loop
1019             Append_To (ExprL, New_Occurrence_Of (Lnn (J), Loc));
1020             Append_To (ExprR, New_Occurrence_Of (Rnn (J), Loc));
1021          end loop;
1022
1023          Assign :=
1024            Make_Assignment_Statement (Loc,
1025              Name =>
1026                Make_Indexed_Component (Loc,
1027                  Prefix      => Duplicate_Subexpr (Larray, Name_Req => True),
1028                  Expressions => ExprL),
1029              Expression =>
1030                Make_Indexed_Component (Loc,
1031                  Prefix      => Duplicate_Subexpr (Rarray, Name_Req => True),
1032                  Expressions => ExprR));
1033
1034          --  We set assignment OK, since there are some cases, e.g. in object
1035          --  declarations, where we are actually assigning into a constant.
1036          --  If there really is an illegality, it was caught long before now,
1037          --  and was flagged when the original assignment was analyzed.
1038
1039          Set_Assignment_OK (Name (Assign));
1040
1041          --  Propagate the No_Ctrl_Actions flag to individual assignments
1042
1043          Set_No_Ctrl_Actions (Assign, No_Ctrl_Actions (N));
1044       end;
1045
1046       --  Now construct the loop from the inside out, with the last subscript
1047       --  varying most rapidly. Note that Assign is first the raw assignment
1048       --  statement, and then subsequently the loop that wraps it up.
1049
1050       for J in reverse 1 .. Ndim loop
1051          Assign :=
1052            Make_Block_Statement (Loc,
1053              Declarations => New_List (
1054               Make_Object_Declaration (Loc,
1055                 Defining_Identifier => Rnn (J),
1056                 Object_Definition =>
1057                   New_Occurrence_Of (R_Index_Type (J), Loc),
1058                 Expression =>
1059                   Make_Attribute_Reference (Loc,
1060                     Prefix => New_Occurrence_Of (R_Index_Type (J), Loc),
1061                     Attribute_Name => F_Or_L))),
1062
1063            Handled_Statement_Sequence =>
1064              Make_Handled_Sequence_Of_Statements (Loc,
1065                Statements => New_List (
1066                  Make_Implicit_Loop_Statement (N,
1067                    Iteration_Scheme =>
1068                      Make_Iteration_Scheme (Loc,
1069                        Loop_Parameter_Specification =>
1070                          Make_Loop_Parameter_Specification (Loc,
1071                            Defining_Identifier => Lnn (J),
1072                            Reverse_Present => Rev,
1073                            Discrete_Subtype_Definition =>
1074                              New_Reference_To (L_Index_Type (J), Loc))),
1075
1076                    Statements => New_List (
1077                      Assign,
1078
1079                      Make_Assignment_Statement (Loc,
1080                        Name => New_Occurrence_Of (Rnn (J), Loc),
1081                        Expression =>
1082                          Make_Attribute_Reference (Loc,
1083                            Prefix =>
1084                              New_Occurrence_Of (R_Index_Type (J), Loc),
1085                            Attribute_Name => S_Or_P,
1086                            Expressions => New_List (
1087                              New_Occurrence_Of (Rnn (J), Loc)))))))));
1088       end loop;
1089
1090       return Assign;
1091    end Expand_Assign_Array_Loop;
1092
1093    --------------------------
1094    -- Expand_Assign_Record --
1095    --------------------------
1096
1097    --  The only processing required is in the change of representation
1098    --  case, where we must expand the assignment to a series of field
1099    --  by field assignments.
1100
1101    procedure Expand_Assign_Record (N : Node_Id) is
1102       Lhs : constant Node_Id := Name (N);
1103       Rhs : Node_Id          := Expression (N);
1104
1105    begin
1106       --  If change of representation, then extract the real right hand
1107       --  side from the type conversion, and proceed with component-wise
1108       --  assignment, since the two types are not the same as far as the
1109       --  back end is concerned.
1110
1111       if Change_Of_Representation (N) then
1112          Rhs := Expression (Rhs);
1113
1114       --  If this may be a case of a large bit aligned component, then
1115       --  proceed with component-wise assignment, to avoid possible
1116       --  clobbering of other components sharing bits in the first or
1117       --  last byte of the component to be assigned.
1118
1119       elsif Possible_Bit_Aligned_Component (Lhs)
1120               or
1121             Possible_Bit_Aligned_Component (Rhs)
1122       then
1123          null;
1124
1125       --  If neither condition met, then nothing special to do, the back end
1126       --  can handle assignment of the entire component as a single entity.
1127
1128       else
1129          return;
1130       end if;
1131
1132       --  At this stage we know that we must do a component wise assignment
1133
1134       declare
1135          Loc   : constant Source_Ptr := Sloc (N);
1136          R_Typ : constant Entity_Id  := Base_Type (Etype (Rhs));
1137          L_Typ : constant Entity_Id  := Base_Type (Etype (Lhs));
1138          Decl  : constant Node_Id    := Declaration_Node (R_Typ);
1139          RDef  : Node_Id;
1140          F     : Entity_Id;
1141
1142          function Find_Component
1143            (Typ  : Entity_Id;
1144             Comp : Entity_Id) return Entity_Id;
1145          --  Find the component with the given name in the underlying record
1146          --  declaration for Typ. We need to use the actual entity because
1147          --  the type may be private and resolution by identifier alone would
1148          --  fail.
1149
1150          function Make_Component_List_Assign
1151            (CL  : Node_Id;
1152             U_U : Boolean := False) return List_Id;
1153          --  Returns a sequence of statements to assign the components that
1154          --  are referenced in the given component list. The flag U_U is
1155          --  used to force the usage of the inferred value of the variant
1156          --  part expression as the switch for the generated case statement.
1157
1158          function Make_Field_Assign
1159            (C : Entity_Id;
1160             U_U : Boolean := False) return Node_Id;
1161          --  Given C, the entity for a discriminant or component, build an
1162          --  assignment for the corresponding field values. The flag U_U
1163          --  signals the presence of an Unchecked_Union and forces the usage
1164          --  of the inferred discriminant value of C as the right hand side
1165          --  of the assignment.
1166
1167          function Make_Field_Assigns (CI : List_Id) return List_Id;
1168          --  Given CI, a component items list, construct series of statements
1169          --  for fieldwise assignment of the corresponding components.
1170
1171          --------------------
1172          -- Find_Component --
1173          --------------------
1174
1175          function Find_Component
1176            (Typ  : Entity_Id;
1177             Comp : Entity_Id) return Entity_Id
1178          is
1179             Utyp : constant Entity_Id := Underlying_Type (Typ);
1180             C    : Entity_Id;
1181
1182          begin
1183             C := First_Entity (Utyp);
1184
1185             while Present (C) loop
1186                if Chars (C) = Chars (Comp) then
1187                   return C;
1188                end if;
1189                Next_Entity (C);
1190             end loop;
1191
1192             raise Program_Error;
1193          end Find_Component;
1194
1195          --------------------------------
1196          -- Make_Component_List_Assign --
1197          --------------------------------
1198
1199          function Make_Component_List_Assign
1200            (CL  : Node_Id;
1201             U_U : Boolean := False) return List_Id
1202          is
1203             CI : constant List_Id := Component_Items (CL);
1204             VP : constant Node_Id := Variant_Part (CL);
1205
1206             Alts   : List_Id;
1207             DC     : Node_Id;
1208             DCH    : List_Id;
1209             Expr   : Node_Id;
1210             Result : List_Id;
1211             V      : Node_Id;
1212
1213          begin
1214             Result := Make_Field_Assigns (CI);
1215
1216             if Present (VP) then
1217
1218                V := First_Non_Pragma (Variants (VP));
1219                Alts := New_List;
1220                while Present (V) loop
1221
1222                   DCH := New_List;
1223                   DC := First (Discrete_Choices (V));
1224                   while Present (DC) loop
1225                      Append_To (DCH, New_Copy_Tree (DC));
1226                      Next (DC);
1227                   end loop;
1228
1229                   Append_To (Alts,
1230                     Make_Case_Statement_Alternative (Loc,
1231                       Discrete_Choices => DCH,
1232                       Statements =>
1233                         Make_Component_List_Assign (Component_List (V))));
1234                   Next_Non_Pragma (V);
1235                end loop;
1236
1237                --  If we have an Unchecked_Union, use the value of the inferred
1238                --  discriminant of the variant part expression as the switch
1239                --  for the case statement. The case statement may later be
1240                --  folded.
1241
1242                if U_U then
1243                   Expr :=
1244                     New_Copy (Get_Discriminant_Value (
1245                       Entity (Name (VP)),
1246                       Etype (Rhs),
1247                       Discriminant_Constraint (Etype (Rhs))));
1248                else
1249                   Expr :=
1250                     Make_Selected_Component (Loc,
1251                       Prefix => Duplicate_Subexpr (Rhs),
1252                       Selector_Name =>
1253                         Make_Identifier (Loc, Chars (Name (VP))));
1254                end if;
1255
1256                Append_To (Result,
1257                  Make_Case_Statement (Loc,
1258                    Expression => Expr,
1259                    Alternatives => Alts));
1260             end if;
1261
1262             return Result;
1263          end Make_Component_List_Assign;
1264
1265          -----------------------
1266          -- Make_Field_Assign --
1267          -----------------------
1268
1269          function Make_Field_Assign
1270            (C : Entity_Id;
1271             U_U : Boolean := False) return Node_Id
1272          is
1273             A    : Node_Id;
1274             Expr : Node_Id;
1275
1276          begin
1277             --  In the case of an Unchecked_Union, use the discriminant
1278             --  constraint value as on the right hand side of the assignment.
1279
1280             if U_U then
1281                Expr :=
1282                  New_Copy (Get_Discriminant_Value (C,
1283                    Etype (Rhs),
1284                    Discriminant_Constraint (Etype (Rhs))));
1285             else
1286                Expr :=
1287                  Make_Selected_Component (Loc,
1288                    Prefix => Duplicate_Subexpr (Rhs),
1289                    Selector_Name => New_Occurrence_Of (C, Loc));
1290             end if;
1291
1292             A :=
1293               Make_Assignment_Statement (Loc,
1294                 Name =>
1295                   Make_Selected_Component (Loc,
1296                     Prefix => Duplicate_Subexpr (Lhs),
1297                     Selector_Name =>
1298                       New_Occurrence_Of (Find_Component (L_Typ, C), Loc)),
1299                 Expression => Expr);
1300
1301             --  Set Assignment_OK, so discriminants can be assigned
1302
1303             Set_Assignment_OK (Name (A), True);
1304             return A;
1305          end Make_Field_Assign;
1306
1307          ------------------------
1308          -- Make_Field_Assigns --
1309          ------------------------
1310
1311          function Make_Field_Assigns (CI : List_Id) return List_Id is
1312             Item   : Node_Id;
1313             Result : List_Id;
1314
1315          begin
1316             Item := First (CI);
1317             Result := New_List;
1318             while Present (Item) loop
1319                if Nkind (Item) = N_Component_Declaration then
1320                   Append_To
1321                     (Result, Make_Field_Assign (Defining_Identifier (Item)));
1322                end if;
1323
1324                Next (Item);
1325             end loop;
1326
1327             return Result;
1328          end Make_Field_Assigns;
1329
1330       --  Start of processing for Expand_Assign_Record
1331
1332       begin
1333          --  Note that we use the base types for this processing. This results
1334          --  in some extra work in the constrained case, but the change of
1335          --  representation case is so unusual that it is not worth the effort.
1336
1337          --  First copy the discriminants. This is done unconditionally. It
1338          --  is required in the unconstrained left side case, and also in the
1339          --  case where this assignment was constructed during the expansion
1340          --  of a type conversion (since initialization of discriminants is
1341          --  suppressed in this case). It is unnecessary but harmless in
1342          --  other cases.
1343
1344          if Has_Discriminants (L_Typ) then
1345             F := First_Discriminant (R_Typ);
1346             while Present (F) loop
1347
1348                if Is_Unchecked_Union (Base_Type (R_Typ)) then
1349                   Insert_Action (N, Make_Field_Assign (F, True));
1350                else
1351                   Insert_Action (N, Make_Field_Assign (F));
1352                end if;
1353
1354                Next_Discriminant (F);
1355             end loop;
1356          end if;
1357
1358          --  We know the underlying type is a record, but its current view
1359          --  may be private. We must retrieve the usable record declaration.
1360
1361          if Nkind (Decl) = N_Private_Type_Declaration
1362            and then Present (Full_View (R_Typ))
1363          then
1364             RDef := Type_Definition (Declaration_Node (Full_View (R_Typ)));
1365          else
1366             RDef := Type_Definition (Decl);
1367          end if;
1368
1369          if Nkind (RDef) = N_Record_Definition
1370            and then Present (Component_List (RDef))
1371          then
1372
1373             if Is_Unchecked_Union (R_Typ) then
1374                Insert_Actions (N,
1375                  Make_Component_List_Assign (Component_List (RDef), True));
1376             else
1377                Insert_Actions
1378                  (N, Make_Component_List_Assign (Component_List (RDef)));
1379             end if;
1380
1381             Rewrite (N, Make_Null_Statement (Loc));
1382          end if;
1383
1384       end;
1385    end Expand_Assign_Record;
1386
1387    -----------------------------------
1388    -- Expand_N_Assignment_Statement --
1389    -----------------------------------
1390
1391    --  This procedure implements various cases where an assignment statement
1392    --  cannot just be passed on to the back end in untransformed state.
1393
1394    procedure Expand_N_Assignment_Statement (N : Node_Id) is
1395       Loc  : constant Source_Ptr := Sloc (N);
1396       Lhs  : constant Node_Id    := Name (N);
1397       Rhs  : constant Node_Id    := Expression (N);
1398       Typ  : constant Entity_Id  := Underlying_Type (Etype (Lhs));
1399       Exp  : Node_Id;
1400
1401    begin
1402       --  Ada 2005 (AI-327): Handle assignment to priority of protected object
1403
1404       --  Rewrite an assignment to X'Priority into a run-time call.
1405
1406       --   For example:         X'Priority := New_Prio_Expr;
1407       --   ...is expanded into  Set_Ceiling (X._Object, New_Prio_Expr);
1408
1409       --  Note that although X'Priority is notionally an object, it is quite
1410       --  deliberately not defined as an aliased object in the RM. This means
1411       --  that it works fine to rewrite it as a call, without having to worry
1412       --  about complications that would other arise from X'Priority'Access,
1413       --  which is illegal, because of the lack of aliasing.
1414
1415       if Ada_Version >= Ada_05 then
1416          declare
1417             Call           : Node_Id;
1418             Conctyp        : Entity_Id;
1419             Ent            : Entity_Id;
1420             Object_Parm    : Node_Id;
1421             Subprg         : Entity_Id;
1422             RT_Subprg_Name : Node_Id;
1423
1424          begin
1425             --  Handle chains of renamings
1426
1427             Ent := Name (N);
1428             while Nkind (Ent) in N_Has_Entity
1429               and then Present (Entity (Ent))
1430               and then Present (Renamed_Object (Entity (Ent)))
1431             loop
1432                Ent := Renamed_Object (Entity (Ent));
1433             end loop;
1434
1435             --  The attribute Priority applied to protected objects has been
1436             --  previously expanded into calls to the Get_Ceiling run-time
1437             --  subprogram.
1438
1439             if Nkind (Ent) = N_Function_Call
1440               and then (Entity (Name (Ent)) = RTE (RE_Get_Ceiling)
1441                           or else
1442                         Entity (Name (Ent)) = RTE (RO_PE_Get_Ceiling))
1443             then
1444                --  Look for the enclosing concurrent type
1445
1446                Conctyp := Current_Scope;
1447                while not Is_Concurrent_Type (Conctyp) loop
1448                   Conctyp := Scope (Conctyp);
1449                end loop;
1450
1451                pragma Assert (Is_Protected_Type (Conctyp));
1452
1453                --  Generate the first actual of the call
1454
1455                Subprg := Current_Scope;
1456                while not Present (Protected_Body_Subprogram (Subprg)) loop
1457                   Subprg := Scope (Subprg);
1458                end loop;
1459
1460                Object_Parm :=
1461                  Make_Attribute_Reference (Loc,
1462                    Prefix =>
1463                      Make_Selected_Component (Loc,
1464                        Prefix => New_Reference_To
1465                                    (First_Entity
1466                                      (Protected_Body_Subprogram (Subprg)),
1467                                     Loc),
1468                      Selector_Name =>
1469                        Make_Identifier (Loc, Name_uObject)),
1470                    Attribute_Name => Name_Unchecked_Access);
1471
1472                --  Select the appropriate run-time call
1473
1474                if Number_Entries (Conctyp) = 0 then
1475                   RT_Subprg_Name :=
1476                     New_Reference_To (RTE (RE_Set_Ceiling), Loc);
1477                else
1478                   RT_Subprg_Name :=
1479                     New_Reference_To (RTE (RO_PE_Set_Ceiling), Loc);
1480                end if;
1481
1482                Call :=
1483                  Make_Procedure_Call_Statement (Loc,
1484                    Name => RT_Subprg_Name,
1485                    Parameter_Associations =>
1486                      New_List (Object_Parm,
1487                                Relocate_Node (Expression (N))));
1488
1489                Rewrite (N, Call);
1490                Analyze (N);
1491                return;
1492             end if;
1493          end;
1494       end if;
1495
1496       --  First deal with generation of range check if required. For now we do
1497       --  this only for discrete types.
1498
1499       if Do_Range_Check (Rhs)
1500         and then Is_Discrete_Type (Typ)
1501       then
1502          Set_Do_Range_Check (Rhs, False);
1503          Generate_Range_Check (Rhs, Typ, CE_Range_Check_Failed);
1504       end if;
1505
1506       --  Check for a special case where a high level transformation is
1507       --  required. If we have either of:
1508
1509       --    P.field := rhs;
1510       --    P (sub) := rhs;
1511
1512       --  where P is a reference to a bit packed array, then we have to unwind
1513       --  the assignment. The exact meaning of being a reference to a bit
1514       --  packed array is as follows:
1515
1516       --    An indexed component whose prefix is a bit packed array is a
1517       --     reference to a bit packed array.
1518
1519       --    An indexed component or selected component whose prefix is a
1520       --     reference to a bit packed array is itself a reference ot a
1521       --     bit packed array.
1522
1523       --  The required transformation is
1524
1525       --     Tnn : prefix_type := P;
1526       --     Tnn.field := rhs;
1527       --     P := Tnn;
1528
1529       --  or
1530
1531       --     Tnn : prefix_type := P;
1532       --     Tnn (subscr) := rhs;
1533       --     P := Tnn;
1534
1535       --  Since P is going to be evaluated more than once, any subscripts
1536       --  in P must have their evaluation forced.
1537
1538       if (Nkind (Lhs) = N_Indexed_Component
1539            or else
1540           Nkind (Lhs) = N_Selected_Component)
1541         and then Is_Ref_To_Bit_Packed_Array (Prefix (Lhs))
1542       then
1543          declare
1544             BPAR_Expr : constant Node_Id   := Relocate_Node (Prefix (Lhs));
1545             BPAR_Typ  : constant Entity_Id := Etype (BPAR_Expr);
1546             Tnn       : constant Entity_Id :=
1547                           Make_Defining_Identifier (Loc,
1548                             Chars => New_Internal_Name ('T'));
1549
1550          begin
1551             --  Insert the post assignment first, because we want to copy
1552             --  the BPAR_Expr tree before it gets analyzed in the context
1553             --  of the pre assignment. Note that we do not analyze the
1554             --  post assignment yet (we cannot till we have completed the
1555             --  analysis of the pre assignment). As usual, the analysis
1556             --  of this post assignment will happen on its own when we
1557             --  "run into" it after finishing the current assignment.
1558
1559             Insert_After (N,
1560               Make_Assignment_Statement (Loc,
1561                 Name       => New_Copy_Tree (BPAR_Expr),
1562                 Expression => New_Occurrence_Of (Tnn, Loc)));
1563
1564             --  At this stage BPAR_Expr is a reference to a bit packed
1565             --  array where the reference was not expanded in the original
1566             --  tree, since it was on the left side of an assignment. But
1567             --  in the pre-assignment statement (the object definition),
1568             --  BPAR_Expr will end up on the right hand side, and must be
1569             --  reexpanded. To achieve this, we reset the analyzed flag
1570             --  of all selected and indexed components down to the actual
1571             --  indexed component for the packed array.
1572
1573             Exp := BPAR_Expr;
1574             loop
1575                Set_Analyzed (Exp, False);
1576
1577                if Nkind (Exp) = N_Selected_Component
1578                     or else
1579                   Nkind (Exp) = N_Indexed_Component
1580                then
1581                   Exp := Prefix (Exp);
1582                else
1583                   exit;
1584                end if;
1585             end loop;
1586
1587             --  Now we can insert and analyze the pre-assignment
1588
1589             --  If the right-hand side requires a transient scope, it has
1590             --  already been placed on the stack. However, the declaration is
1591             --  inserted in the tree outside of this scope, and must reflect
1592             --  the proper scope for its variable. This awkward bit is forced
1593             --  by the stricter scope discipline imposed by GCC 2.97.
1594
1595             declare
1596                Uses_Transient_Scope : constant Boolean :=
1597                                         Scope_Is_Transient
1598                                           and then N = Node_To_Be_Wrapped;
1599
1600             begin
1601                if Uses_Transient_Scope then
1602                   New_Scope (Scope (Current_Scope));
1603                end if;
1604
1605                Insert_Before_And_Analyze (N,
1606                  Make_Object_Declaration (Loc,
1607                    Defining_Identifier => Tnn,
1608                    Object_Definition   => New_Occurrence_Of (BPAR_Typ, Loc),
1609                    Expression          => BPAR_Expr));
1610
1611                if Uses_Transient_Scope then
1612                   Pop_Scope;
1613                end if;
1614             end;
1615
1616             --  Now fix up the original assignment and continue processing
1617
1618             Rewrite (Prefix (Lhs),
1619               New_Occurrence_Of (Tnn, Loc));
1620
1621             --  We do not need to reanalyze that assignment, and we do not need
1622             --  to worry about references to the temporary, but we do need to
1623             --  make sure that the temporary is not marked as a true constant
1624             --  since we now have a generate assignment to it!
1625
1626             Set_Is_True_Constant (Tnn, False);
1627          end;
1628       end if;
1629
1630       --  When we have the appropriate type of aggregate in the
1631       --  expression (it has been determined during analysis of the
1632       --  aggregate by setting the delay flag), let's perform in place
1633       --  assignment and thus avoid creating a temporay.
1634
1635       if Is_Delayed_Aggregate (Rhs) then
1636          Convert_Aggr_In_Assignment (N);
1637          Rewrite (N, Make_Null_Statement (Loc));
1638          Analyze (N);
1639          return;
1640       end if;
1641
1642       --  Apply discriminant check if required. If Lhs is an access type
1643       --  to a designated type with discriminants, we must always check.
1644
1645       if Has_Discriminants (Etype (Lhs)) then
1646
1647          --  Skip discriminant check if change of representation. Will be
1648          --  done when the change of representation is expanded out.
1649
1650          if not Change_Of_Representation (N) then
1651             Apply_Discriminant_Check (Rhs, Etype (Lhs), Lhs);
1652          end if;
1653
1654       --  If the type is private without discriminants, and the full type
1655       --  has discriminants (necessarily with defaults) a check may still be
1656       --  necessary if the Lhs is aliased. The private determinants must be
1657       --  visible to build the discriminant constraints.
1658
1659       --  Only an explicit dereference that comes from source indicates
1660       --  aliasing. Access to formals of protected operations and entries
1661       --  create dereferences but are not semantic aliasings.
1662
1663       elsif Is_Private_Type (Etype (Lhs))
1664         and then Has_Discriminants (Typ)
1665         and then Nkind (Lhs) = N_Explicit_Dereference
1666         and then Comes_From_Source (Lhs)
1667       then
1668          declare
1669             Lt : constant Entity_Id := Etype (Lhs);
1670          begin
1671             Set_Etype (Lhs, Typ);
1672             Rewrite (Rhs, OK_Convert_To (Base_Type (Typ), Rhs));
1673             Apply_Discriminant_Check (Rhs, Typ, Lhs);
1674             Set_Etype (Lhs, Lt);
1675          end;
1676
1677          --  If the Lhs has a private type with unknown discriminants, it
1678          --  may have a full view with discriminants, but those are nameable
1679          --  only in the underlying type, so convert the Rhs to it before
1680          --  potential checking.
1681
1682       elsif Has_Unknown_Discriminants (Base_Type (Etype (Lhs)))
1683         and then Has_Discriminants (Typ)
1684       then
1685          Rewrite (Rhs, OK_Convert_To (Base_Type (Typ), Rhs));
1686          Apply_Discriminant_Check (Rhs, Typ, Lhs);
1687
1688       --  In the access type case, we need the same discriminant check,
1689       --  and also range checks if we have an access to constrained array.
1690
1691       elsif Is_Access_Type (Etype (Lhs))
1692         and then Is_Constrained (Designated_Type (Etype (Lhs)))
1693       then
1694          if Has_Discriminants (Designated_Type (Etype (Lhs))) then
1695
1696             --  Skip discriminant check if change of representation. Will be
1697             --  done when the change of representation is expanded out.
1698
1699             if not Change_Of_Representation (N) then
1700                Apply_Discriminant_Check (Rhs, Etype (Lhs));
1701             end if;
1702
1703          elsif Is_Array_Type (Designated_Type (Etype (Lhs))) then
1704             Apply_Range_Check (Rhs, Etype (Lhs));
1705
1706             if Is_Constrained (Etype (Lhs)) then
1707                Apply_Length_Check (Rhs, Etype (Lhs));
1708             end if;
1709
1710             if Nkind (Rhs) = N_Allocator then
1711                declare
1712                   Target_Typ : constant Entity_Id := Etype (Expression (Rhs));
1713                   C_Es       : Check_Result;
1714
1715                begin
1716                   C_Es :=
1717                     Range_Check
1718                       (Lhs,
1719                        Target_Typ,
1720                        Etype (Designated_Type (Etype (Lhs))));
1721
1722                   Insert_Range_Checks
1723                     (C_Es,
1724                      N,
1725                      Target_Typ,
1726                      Sloc (Lhs),
1727                      Lhs);
1728                end;
1729             end if;
1730          end if;
1731
1732       --  Apply range check for access type case
1733
1734       elsif Is_Access_Type (Etype (Lhs))
1735         and then Nkind (Rhs) = N_Allocator
1736         and then Nkind (Expression (Rhs)) = N_Qualified_Expression
1737       then
1738          Analyze_And_Resolve (Expression (Rhs));
1739          Apply_Range_Check
1740            (Expression (Rhs), Designated_Type (Etype (Lhs)));
1741       end if;
1742
1743       --  Ada 2005 (AI-231): Generate the run-time check
1744
1745       if Is_Access_Type (Typ)
1746         and then Can_Never_Be_Null (Etype (Lhs))
1747         and then not Can_Never_Be_Null (Etype (Rhs))
1748       then
1749          Apply_Constraint_Check (Rhs, Etype (Lhs));
1750       end if;
1751
1752       --  Case of assignment to a bit packed array element
1753
1754       if Nkind (Lhs) = N_Indexed_Component
1755         and then Is_Bit_Packed_Array (Etype (Prefix (Lhs)))
1756       then
1757          Expand_Bit_Packed_Element_Set (N);
1758          return;
1759
1760       --  Build-in-place function call case. Note that we're not yet doing
1761       --  build-in-place for user-written assignment statements; the
1762       --  assignment here came from can aggregate.
1763
1764       elsif Ada_Version >= Ada_05
1765         and then Is_Build_In_Place_Function_Call (Rhs)
1766       then
1767          Make_Build_In_Place_Call_In_Assignment (N, Rhs);
1768
1769       elsif Is_Tagged_Type (Typ)
1770         or else (Controlled_Type (Typ) and then not Is_Array_Type (Typ))
1771       then
1772          Tagged_Case : declare
1773             L                   : List_Id := No_List;
1774             Expand_Ctrl_Actions : constant Boolean := not No_Ctrl_Actions (N);
1775
1776          begin
1777             --  In the controlled case, we need to make sure that function
1778             --  calls are evaluated before finalizing the target. In all
1779             --  cases, it makes the expansion easier if the side-effects
1780             --  are removed first.
1781
1782             Remove_Side_Effects (Lhs);
1783             Remove_Side_Effects (Rhs);
1784
1785             --  Avoid recursion in the mechanism
1786
1787             Set_Analyzed (N);
1788
1789             --  If dispatching assignment, we need to dispatch to _assign
1790
1791             if Is_Class_Wide_Type (Typ)
1792
1793                --  If the type is tagged, we may as well use the predefined
1794                --  primitive assignment. This avoids inlining a lot of code
1795                --  and in the class-wide case, the assignment is replaced by
1796                --  dispatch call to _assign. Note that this cannot be done
1797                --  when discriminant checks are locally suppressed (as in
1798                --  extension aggregate expansions) because otherwise the
1799                --  discriminant check will be performed within the _assign
1800                --  call. It is also suppressed for assignmments created by the
1801                --  expander that correspond to initializations, where we do
1802                --  want to copy the tag (No_Ctrl_Actions flag set True).
1803                --  by the expander and we do not need to mess with tags ever
1804                --  (Expand_Ctrl_Actions flag is set True in this case).
1805
1806                or else (Is_Tagged_Type (Typ)
1807                           and then Chars (Current_Scope) /= Name_uAssign
1808                           and then Expand_Ctrl_Actions
1809                           and then not Discriminant_Checks_Suppressed (Empty))
1810             then
1811                --  Fetch the primitive op _assign and proper type to call
1812                --  it. Because of possible conflits between private and
1813                --  full view the proper type is fetched directly from the
1814                --  operation profile.
1815
1816                declare
1817                   Op    : constant Entity_Id :=
1818                             Find_Prim_Op (Typ, Name_uAssign);
1819                   F_Typ : Entity_Id := Etype (First_Formal (Op));
1820
1821                begin
1822                   --  If the assignment is dispatching, make sure to use the
1823                   --  proper type.
1824
1825                   if Is_Class_Wide_Type (Typ) then
1826                      F_Typ := Class_Wide_Type (F_Typ);
1827                   end if;
1828
1829                   L := New_List;
1830
1831                   --  In case of assignment to a class-wide tagged type, before
1832                   --  the assignment we generate run-time check to ensure that
1833                   --  the tag of the Target is covered by the tag of the source
1834
1835                   if Is_Class_Wide_Type (Typ)
1836                     and then Is_Tagged_Type (Typ)
1837                     and then Is_Tagged_Type (Underlying_Type (Etype (Rhs)))
1838                   then
1839                      Append_To (L,
1840                        Make_Raise_Constraint_Error (Loc,
1841                          Condition =>
1842                            Make_Op_Not (Loc,
1843                              Make_Function_Call (Loc,
1844                                Name => New_Reference_To
1845                                          (RTE (RE_CW_Membership), Loc),
1846                                Parameter_Associations => New_List (
1847                                  Make_Selected_Component (Loc,
1848                                    Prefix =>
1849                                      Duplicate_Subexpr (Lhs),
1850                                    Selector_Name =>
1851                                      Make_Identifier (Loc, Name_uTag)),
1852                                  Make_Selected_Component (Loc,
1853                                    Prefix =>
1854                                      Duplicate_Subexpr (Rhs),
1855                                    Selector_Name =>
1856                                      Make_Identifier (Loc, Name_uTag))))),
1857                          Reason => CE_Tag_Check_Failed));
1858                   end if;
1859
1860                   Append_To (L,
1861                     Make_Procedure_Call_Statement (Loc,
1862                       Name => New_Reference_To (Op, Loc),
1863                       Parameter_Associations => New_List (
1864                         Unchecked_Convert_To (F_Typ, Duplicate_Subexpr (Lhs)),
1865                         Unchecked_Convert_To (F_Typ,
1866                           Duplicate_Subexpr (Rhs)))));
1867                end;
1868
1869             else
1870                L := Make_Tag_Ctrl_Assignment (N);
1871
1872                --  We can't afford to have destructive Finalization Actions
1873                --  in the Self assignment case, so if the target and the
1874                --  source are not obviously different, code is generated to
1875                --  avoid the self assignment case
1876                --
1877                --    if lhs'address /= rhs'address then
1878                --       <code for controlled and/or tagged assignment>
1879                --    end if;
1880
1881                if not Statically_Different (Lhs, Rhs)
1882                  and then Expand_Ctrl_Actions
1883                then
1884                   L := New_List (
1885                     Make_Implicit_If_Statement (N,
1886                       Condition =>
1887                         Make_Op_Ne (Loc,
1888                           Left_Opnd =>
1889                             Make_Attribute_Reference (Loc,
1890                               Prefix         => Duplicate_Subexpr (Lhs),
1891                               Attribute_Name => Name_Address),
1892
1893                            Right_Opnd =>
1894                             Make_Attribute_Reference (Loc,
1895                               Prefix         => Duplicate_Subexpr (Rhs),
1896                               Attribute_Name => Name_Address)),
1897
1898                       Then_Statements => L));
1899                end if;
1900
1901                --  We need to set up an exception handler for implementing
1902                --  7.6.1 (18). The remaining adjustments are tackled by the
1903                --  implementation of adjust for record_controllers (see
1904                --  s-finimp.adb)
1905
1906                --  This is skipped if we have no finalization
1907
1908                if Expand_Ctrl_Actions
1909                  and then not Restriction_Active (No_Finalization)
1910                then
1911                   L := New_List (
1912                     Make_Block_Statement (Loc,
1913                       Handled_Statement_Sequence =>
1914                         Make_Handled_Sequence_Of_Statements (Loc,
1915                           Statements => L,
1916                           Exception_Handlers => New_List (
1917                             Make_Exception_Handler (Loc,
1918                               Exception_Choices =>
1919                                 New_List (Make_Others_Choice (Loc)),
1920                               Statements        => New_List (
1921                                 Make_Raise_Program_Error (Loc,
1922                                   Reason =>
1923                                     PE_Finalize_Raised_Exception)
1924                               ))))));
1925                end if;
1926             end if;
1927
1928             Rewrite (N,
1929               Make_Block_Statement (Loc,
1930                 Handled_Statement_Sequence =>
1931                   Make_Handled_Sequence_Of_Statements (Loc, Statements => L)));
1932
1933             --  If no restrictions on aborts, protect the whole assignement
1934             --  for controlled objects as per 9.8(11)
1935
1936             if Controlled_Type (Typ)
1937               and then Expand_Ctrl_Actions
1938               and then Abort_Allowed
1939             then
1940                declare
1941                   Blk : constant Entity_Id :=
1942                           New_Internal_Entity
1943                             (E_Block, Current_Scope, Sloc (N), 'B');
1944
1945                begin
1946                   Set_Scope (Blk, Current_Scope);
1947                   Set_Etype (Blk, Standard_Void_Type);
1948                   Set_Identifier (N, New_Occurrence_Of (Blk, Sloc (N)));
1949
1950                   Prepend_To (L, Build_Runtime_Call (Loc, RE_Abort_Defer));
1951                   Set_At_End_Proc (Handled_Statement_Sequence (N),
1952                     New_Occurrence_Of (RTE (RE_Abort_Undefer_Direct), Loc));
1953                   Expand_At_End_Handler
1954                     (Handled_Statement_Sequence (N), Blk);
1955                end;
1956             end if;
1957
1958             --  N has been rewritten to a block statement for which it is
1959             --  known by construction that no checks are necessary: analyze
1960             --  it with all checks suppressed.
1961
1962             Analyze (N, Suppress => All_Checks);
1963             return;
1964          end Tagged_Case;
1965
1966       --  Array types
1967
1968       elsif Is_Array_Type (Typ) then
1969          declare
1970             Actual_Rhs : Node_Id := Rhs;
1971
1972          begin
1973             while Nkind (Actual_Rhs) = N_Type_Conversion
1974               or else
1975                   Nkind (Actual_Rhs) = N_Qualified_Expression
1976             loop
1977                Actual_Rhs := Expression (Actual_Rhs);
1978             end loop;
1979
1980             Expand_Assign_Array (N, Actual_Rhs);
1981             return;
1982          end;
1983
1984       --  Record types
1985
1986       elsif Is_Record_Type (Typ) then
1987          Expand_Assign_Record (N);
1988          return;
1989
1990       --  Scalar types. This is where we perform the processing related
1991       --  to the requirements of (RM 13.9.1(9-11)) concerning the handling
1992       --  of invalid scalar values.
1993
1994       elsif Is_Scalar_Type (Typ) then
1995
1996          --  Case where right side is known valid
1997
1998          if Expr_Known_Valid (Rhs) then
1999
2000             --  Here the right side is valid, so it is fine. The case to
2001             --  deal with is when the left side is a local variable reference
2002             --  whose value is not currently known to be valid. If this is
2003             --  the case, and the assignment appears in an unconditional
2004             --  context, then we can mark the left side as now being valid.
2005
2006             if Is_Local_Variable_Reference (Lhs)
2007               and then not Is_Known_Valid (Entity (Lhs))
2008               and then In_Unconditional_Context (N)
2009             then
2010                Set_Is_Known_Valid (Entity (Lhs), True);
2011             end if;
2012
2013          --  Case where right side may be invalid in the sense of the RM
2014          --  reference above. The RM does not require that we check for
2015          --  the validity on an assignment, but it does require that the
2016          --  assignment of an invalid value not cause erroneous behavior.
2017
2018          --  The general approach in GNAT is to use the Is_Known_Valid flag
2019          --  to avoid the need for validity checking on assignments. However
2020          --  in some cases, we have to do validity checking in order to make
2021          --  sure that the setting of this flag is correct.
2022
2023          else
2024             --  Validate right side if we are validating copies
2025
2026             if Validity_Checks_On
2027               and then Validity_Check_Copies
2028             then
2029                --  Skip this if left hand side is an array or record component
2030                --  and elementary component validity checks are suppressed.
2031
2032                if (Nkind (Lhs) = N_Selected_Component
2033                     or else
2034                    Nkind (Lhs) = N_Indexed_Component)
2035                  and then not Validity_Check_Components
2036                then
2037                   null;
2038                else
2039                   Ensure_Valid (Rhs);
2040                end if;
2041
2042                --  We can propagate this to the left side where appropriate
2043
2044                if Is_Local_Variable_Reference (Lhs)
2045                  and then not Is_Known_Valid (Entity (Lhs))
2046                  and then In_Unconditional_Context (N)
2047                then
2048                   Set_Is_Known_Valid (Entity (Lhs), True);
2049                end if;
2050
2051             --  Otherwise check to see what should be done
2052
2053             --  If left side is a local variable, then we just set its
2054             --  flag to indicate that its value may no longer be valid,
2055             --  since we are copying a potentially invalid value.
2056
2057             elsif Is_Local_Variable_Reference (Lhs) then
2058                Set_Is_Known_Valid (Entity (Lhs), False);
2059
2060             --  Check for case of a nonlocal variable on the left side
2061             --  which is currently known to be valid. In this case, we
2062             --  simply ensure that the right side is valid. We only play
2063             --  the game of copying validity status for local variables,
2064             --  since we are doing this statically, not by tracing the
2065             --  full flow graph.
2066
2067             elsif Is_Entity_Name (Lhs)
2068               and then Is_Known_Valid (Entity (Lhs))
2069             then
2070                --  Note that the Ensure_Valid call is ignored if the
2071                --  Validity_Checking mode is set to none so we do not
2072                --  need to worry about that case here.
2073
2074                Ensure_Valid (Rhs);
2075
2076             --  In all other cases, we can safely copy an invalid value
2077             --  without worrying about the status of the left side. Since
2078             --  it is not a variable reference it will not be considered
2079             --  as being known to be valid in any case.
2080
2081             else
2082                null;
2083             end if;
2084          end if;
2085       end if;
2086
2087       --  Defend against invalid subscripts on left side if we are in
2088       --  standard validity checking mode. No need to do this if we
2089       --  are checking all subscripts.
2090
2091       if Validity_Checks_On
2092         and then Validity_Check_Default
2093         and then not Validity_Check_Subscripts
2094       then
2095          Check_Valid_Lvalue_Subscripts (Lhs);
2096       end if;
2097
2098    exception
2099       when RE_Not_Available =>
2100          return;
2101    end Expand_N_Assignment_Statement;
2102
2103    ------------------------------
2104    -- Expand_N_Block_Statement --
2105    ------------------------------
2106
2107    --  Encode entity names defined in block statement
2108
2109    procedure Expand_N_Block_Statement (N : Node_Id) is
2110    begin
2111       Qualify_Entity_Names (N);
2112    end Expand_N_Block_Statement;
2113
2114    -----------------------------
2115    -- Expand_N_Case_Statement --
2116    -----------------------------
2117
2118    procedure Expand_N_Case_Statement (N : Node_Id) is
2119       Loc    : constant Source_Ptr := Sloc (N);
2120       Expr   : constant Node_Id    := Expression (N);
2121       Alt    : Node_Id;
2122       Len    : Nat;
2123       Cond   : Node_Id;
2124       Choice : Node_Id;
2125       Chlist : List_Id;
2126
2127    begin
2128       --  Check for the situation where we know at compile time which
2129       --  branch will be taken
2130
2131       if Compile_Time_Known_Value (Expr) then
2132          Alt := Find_Static_Alternative (N);
2133
2134          --  Move the statements from this alternative after the case
2135          --  statement. They are already analyzed, so will be skipped
2136          --  by the analyzer.
2137
2138          Insert_List_After (N, Statements (Alt));
2139
2140          --  That leaves the case statement as a shell. So now we can kill all
2141          --  other alternatives in the case statement.
2142
2143          Kill_Dead_Code (Expression (N));
2144
2145          declare
2146             A : Node_Id;
2147
2148          begin
2149             --  Loop through case alternatives, skipping pragmas, and skipping
2150             --  the one alternative that we select (and therefore retain).
2151
2152             A := First (Alternatives (N));
2153             while Present (A) loop
2154                if A /= Alt
2155                  and then Nkind (A) = N_Case_Statement_Alternative
2156                then
2157                   Kill_Dead_Code (Statements (A), Warn_On_Deleted_Code);
2158                end if;
2159
2160                Next (A);
2161             end loop;
2162          end;
2163
2164          Rewrite (N, Make_Null_Statement (Loc));
2165          return;
2166       end if;
2167
2168       --  Here if the choice is not determined at compile time
2169
2170       declare
2171          Last_Alt : constant Node_Id := Last (Alternatives (N));
2172
2173          Others_Present : Boolean;
2174          Others_Node    : Node_Id;
2175
2176          Then_Stms : List_Id;
2177          Else_Stms : List_Id;
2178
2179       begin
2180          if Nkind (First (Discrete_Choices (Last_Alt))) = N_Others_Choice then
2181             Others_Present := True;
2182             Others_Node    := Last_Alt;
2183          else
2184             Others_Present := False;
2185          end if;
2186
2187          --  First step is to worry about possible invalid argument. The RM
2188          --  requires (RM 5.4(13)) that if the result is invalid (e.g. it is
2189          --  outside the base range), then Constraint_Error must be raised.
2190
2191          --  Case of validity check required (validity checks are on, the
2192          --  expression is not known to be valid, and the case statement
2193          --  comes from source -- no need to validity check internally
2194          --  generated case statements).
2195
2196          if Validity_Check_Default then
2197             Ensure_Valid (Expr);
2198          end if;
2199
2200          --  If there is only a single alternative, just replace it with
2201          --  the sequence of statements since obviously that is what is
2202          --  going to be executed in all cases.
2203
2204          Len := List_Length (Alternatives (N));
2205
2206          if Len = 1 then
2207             --  We still need to evaluate the expression if it has any
2208             --  side effects.
2209
2210             Remove_Side_Effects (Expression (N));
2211
2212             Insert_List_After (N, Statements (First (Alternatives (N))));
2213
2214             --  That leaves the case statement as a shell. The alternative
2215             --  that will be executed is reset to a null list. So now we can
2216             --  kill the entire case statement.
2217
2218             Kill_Dead_Code (Expression (N));
2219             Rewrite (N, Make_Null_Statement (Loc));
2220             return;
2221          end if;
2222
2223          --  An optimization. If there are only two alternatives, and only
2224          --  a single choice, then rewrite the whole case statement as an
2225          --  if statement, since this can result in susbequent optimizations.
2226          --  This helps not only with case statements in the source of a
2227          --  simple form, but also with generated code (discriminant check
2228          --  functions in particular)
2229
2230          if Len = 2 then
2231             Chlist := Discrete_Choices (First (Alternatives (N)));
2232
2233             if List_Length (Chlist) = 1 then
2234                Choice := First (Chlist);
2235
2236                Then_Stms := Statements (First (Alternatives (N)));
2237                Else_Stms := Statements (Last  (Alternatives (N)));
2238
2239                --  For TRUE, generate "expression", not expression = true
2240
2241                if Nkind (Choice) = N_Identifier
2242                  and then Entity (Choice) = Standard_True
2243                then
2244                   Cond := Expression (N);
2245
2246                --  For FALSE, generate "expression" and switch then/else
2247
2248                elsif Nkind (Choice) = N_Identifier
2249                  and then Entity (Choice) = Standard_False
2250                then
2251                   Cond := Expression (N);
2252                   Else_Stms := Statements (First (Alternatives (N)));
2253                   Then_Stms := Statements (Last  (Alternatives (N)));
2254
2255                --  For a range, generate "expression in range"
2256
2257                elsif Nkind (Choice) = N_Range
2258                  or else (Nkind (Choice) = N_Attribute_Reference
2259                            and then Attribute_Name (Choice) = Name_Range)
2260                  or else (Is_Entity_Name (Choice)
2261                            and then Is_Type (Entity (Choice)))
2262                  or else Nkind (Choice) = N_Subtype_Indication
2263                then
2264                   Cond :=
2265                     Make_In (Loc,
2266                       Left_Opnd  => Expression (N),
2267                       Right_Opnd => Relocate_Node (Choice));
2268
2269                --  For any other subexpression "expression = value"
2270
2271                else
2272                   Cond :=
2273                     Make_Op_Eq (Loc,
2274                       Left_Opnd  => Expression (N),
2275                       Right_Opnd => Relocate_Node (Choice));
2276                end if;
2277
2278                --  Now rewrite the case as an IF
2279
2280                Rewrite (N,
2281                  Make_If_Statement (Loc,
2282                    Condition => Cond,
2283                    Then_Statements => Then_Stms,
2284                    Else_Statements => Else_Stms));
2285                Analyze (N);
2286                return;
2287             end if;
2288          end if;
2289
2290          --  If the last alternative is not an Others choice, replace it
2291          --  with an N_Others_Choice. Note that we do not bother to call
2292          --  Analyze on the modified case statement, since it's only effect
2293          --  would be to compute the contents of the Others_Discrete_Choices
2294          --  which is not needed by the back end anyway.
2295
2296          --  The reason we do this is that the back end always needs some
2297          --  default for a switch, so if we have not supplied one in the
2298          --  processing above for validity checking, then we need to
2299          --  supply one here.
2300
2301          if not Others_Present then
2302             Others_Node := Make_Others_Choice (Sloc (Last_Alt));
2303             Set_Others_Discrete_Choices
2304               (Others_Node, Discrete_Choices (Last_Alt));
2305             Set_Discrete_Choices (Last_Alt, New_List (Others_Node));
2306          end if;
2307       end;
2308    end Expand_N_Case_Statement;
2309
2310    -----------------------------
2311    -- Expand_N_Exit_Statement --
2312    -----------------------------
2313
2314    --  The only processing required is to deal with a possible C/Fortran
2315    --  boolean value used as the condition for the exit statement.
2316
2317    procedure Expand_N_Exit_Statement (N : Node_Id) is
2318    begin
2319       Adjust_Condition (Condition (N));
2320    end Expand_N_Exit_Statement;
2321
2322    ----------------------------------------
2323    -- Expand_N_Extended_Return_Statement --
2324    ----------------------------------------
2325
2326    --  If there is a Handled_Statement_Sequence, we rewrite this:
2327
2328    --     return Result : T := <expression> do
2329    --        <handled_seq_of_stms>
2330    --     end return;
2331
2332    --  to be:
2333
2334    --     declare
2335    --        Result : T := <expression>;
2336    --     begin
2337    --        <handled_seq_of_stms>
2338    --        return Result;
2339    --     end;
2340
2341    --  Otherwise (no Handled_Statement_Sequence), we rewrite this:
2342
2343    --     return Result : T := <expression>;
2344
2345    --  to be:
2346
2347    --     return <expression>;
2348
2349    --  unless it's build-in-place or there's no <expression>, in which case
2350    --  we generate:
2351
2352    --     declare
2353    --        Result : T := <expression>;
2354    --     begin
2355    --        return Result;
2356    --     end;
2357
2358    --  Note that this case could have been written by the user as an extended
2359    --  return statement, or could have been transformed to this from a simple
2360    --  return statement.
2361
2362    --  That is, we need to have a reified return object if there are statements
2363    --  (which might refer to it) or if we're doing build-in-place (so we can
2364    --  set its address to the final resting place -- but that key part is not
2365    --  yet implemented) or if there is no expression (in which case default
2366    --  initial values might need to be set).
2367
2368    procedure Expand_N_Extended_Return_Statement (N : Node_Id) is
2369
2370       function Is_Build_In_Place_Function (Fun : Entity_Id) return Boolean;
2371       --  F must be of type E_Function or E_Generic_Function. Return True if it
2372       --  uses build-in-place for the result object. In Ada 95, this must be
2373       --  False for inherently limited result type. In Ada 2005, this must be
2374       --  True for inherently limited result type. For other types, we have a
2375       --  choice -- build-in-place is usually more efficient for large things,
2376       --  and less efficient for small things. However, we had better not use
2377       --  build-in-place if the Convention is other than Ada, because that
2378       --  would disturb mixed-language programs.
2379       --
2380       --  Note that for the non-inherently-limited cases, we must make the same
2381       --  decision for Ada 95 and 2005, so that mixed-dialect programs work.
2382       --
2383       --  ???This function will be needed when compiling the call sites;
2384       --  we will have to move it to a more global place.
2385
2386       --------------------------------
2387       -- Is_Build_In_Place_Function --
2388       --------------------------------
2389
2390       function Is_Build_In_Place_Function (Fun : Entity_Id) return Boolean is
2391          R_Type : constant Entity_Id := Underlying_Type (Etype (Fun));
2392
2393       begin
2394          --  First, the cases that matter for correctness
2395
2396          if Is_Inherently_Limited_Type (R_Type) then
2397             return Ada_Version >= Ada_05 and then not Debug_Flag_Dot_L;
2398
2399             --  Note: If you have Convention (C) on an inherently limited
2400             --  type, you're on your own. That is, the C code will have to be
2401             --  carefully written to know about the Ada conventions.
2402
2403          elsif
2404            Has_Foreign_Convention (R_Type)
2405              or else
2406            Has_Foreign_Convention (Fun)
2407          then
2408             return False;
2409
2410          --  Second, the efficiency-related decisions. It would be obnoxiously
2411          --  inefficient to use build-in-place for elementary types. For
2412          --  composites, we could return False if the subtype is known to be
2413          --  small (<= one or two words?) but we don't bother with that yet.
2414
2415          else
2416             return Is_Composite_Type (R_Type);
2417          end if;
2418       end Is_Build_In_Place_Function;
2419
2420       ------------------------
2421       -- Local Declarations --
2422       ------------------------
2423
2424       Loc : constant Source_Ptr := Sloc (N);
2425
2426       Return_Object_Entity : constant Entity_Id :=
2427                                First_Entity (Return_Statement_Entity (N));
2428       Return_Object_Decl   : constant Node_Id :=
2429                                Parent (Return_Object_Entity);
2430       Parent_Function      : constant Entity_Id :=
2431                                Return_Applies_To (Return_Statement_Entity (N));
2432       Is_Build_In_Place    : constant Boolean :=
2433                                Is_Build_In_Place_Function (Parent_Function);
2434
2435       Return_Stm      : Node_Id;
2436       Handled_Stm_Seq : Node_Id;
2437       Result          : Node_Id;
2438       Exp             : Node_Id;
2439
2440    --  Start of processing for Expand_N_Extended_Return_Statement
2441
2442    begin
2443       if Nkind (Return_Object_Decl) = N_Object_Declaration then
2444          Exp := Expression (Return_Object_Decl);
2445       else
2446          Exp := Empty;
2447       end if;
2448
2449       Handled_Stm_Seq := Handled_Statement_Sequence (N);
2450
2451       if Present (Handled_Stm_Seq)
2452         or else Is_Build_In_Place
2453         or else No (Exp)
2454       then
2455          --  Build simple_return_statement that returns the return object
2456
2457          Return_Stm :=
2458            Make_Return_Statement (Loc,
2459              Expression => New_Occurrence_Of (Return_Object_Entity, Loc));
2460
2461          if Present (Handled_Stm_Seq) then
2462             Handled_Stm_Seq :=
2463               Make_Handled_Sequence_Of_Statements (Loc,
2464                 Statements => New_List (Handled_Stm_Seq, Return_Stm));
2465          else
2466             Handled_Stm_Seq :=
2467               Make_Handled_Sequence_Of_Statements (Loc,
2468                 Statements => New_List (Return_Stm));
2469          end if;
2470
2471          pragma Assert (Present (Handled_Stm_Seq));
2472       end if;
2473
2474       --  Case where we build a block
2475
2476       if Present (Handled_Stm_Seq) then
2477          Result :=
2478            Make_Block_Statement (Loc,
2479              Declarations => Return_Object_Declarations (N),
2480              Handled_Statement_Sequence => Handled_Stm_Seq);
2481
2482          if Is_Build_In_Place then
2483
2484             --  Locate the implicit access parameter associated with the
2485             --  the caller-supplied return object and convert the return
2486             --  statement's return object declaration to a renaming of a
2487             --  dereference of the access parameter. If the return object's
2488             --  declaration includes an expression that has not already been
2489             --  expanded as separate assignments, then add an assignment
2490             --  statement to ensure the return object gets initialized.
2491
2492             --  declare
2493             --     Result : T [:= <expression>];
2494             --  begin
2495             --     ...
2496
2497             --  is converted to
2498
2499             --  declare
2500             --     Result : T renames FuncRA.all;
2501             --     [Result := <expression;]
2502             --  begin
2503             --     ...
2504
2505             declare
2506                Return_Obj_Id   : constant Entity_Id :=
2507                                    Defining_Identifier (Return_Object_Decl);
2508                Return_Obj_Typ  : constant Entity_Id := Etype (Return_Obj_Id);
2509                Return_Obj_Expr : constant Node_Id :=
2510                                    Expression (Return_Object_Decl);
2511                Obj_Acc_Formal  : Entity_Id := Extra_Formals (Parent_Function);
2512                Obj_Acc_Deref   : Node_Id;
2513                Init_Assignment : Node_Id;
2514
2515             begin
2516                --  Build-in-place results must be returned by reference
2517
2518                Set_By_Ref (Return_Stm);
2519
2520                --  Locate the implicit access parameter passed by the caller.
2521                --  It might be better to search for that with a symbol table
2522                --  lookup, but for now we traverse the extra actuals to find
2523                --  the access parameter (currently there can only be one).
2524
2525                while Present (Obj_Acc_Formal) loop
2526                   exit when
2527                     Ekind (Etype (Obj_Acc_Formal)) = E_Anonymous_Access_Type;
2528                   Next_Formal_With_Extras (Obj_Acc_Formal);
2529                end loop;
2530
2531                --  ??? pragma Assert (Present (Obj_Acc_Formal));
2532
2533                --  For now we only rewrite the object if we can locate the
2534                --  implicit access parameter. Normally there should be one
2535                --  if Build_In_Place is true, but at the moment it's only
2536                --  created in the more restrictive case of constrained
2537                --  inherently limited result subtypes. ???
2538
2539                if Present (Obj_Acc_Formal) then
2540
2541                   --  If the return object's declaration includes an expression
2542                   --  and the declaration isn't marked as No_Initialization,
2543                   --  then we need to generate an assignment to the object and
2544                   --  insert it after the declaration before rewriting it as
2545                   --  a renaming (otherwise we'll lose the initialization).
2546
2547                   if Present (Return_Obj_Expr)
2548                     and then not No_Initialization (Return_Object_Decl)
2549                   then
2550                      Init_Assignment :=
2551                        Make_Assignment_Statement (Loc,
2552                          Name       => New_Reference_To (Return_Obj_Id, Loc),
2553                          Expression => Relocate_Node (Return_Obj_Expr));
2554                      Set_Assignment_OK (Name (Init_Assignment));
2555                      Set_No_Ctrl_Actions (Init_Assignment);
2556
2557                      --  ??? Should we be setting the parent of the expression
2558                      --  here?
2559                      --  Set_Parent
2560                      --    (Expression (Init_Assignment), Init_Assignment);
2561
2562                      Set_Expression (Return_Object_Decl, Empty);
2563
2564                      Insert_After (Return_Object_Decl, Init_Assignment);
2565                   end if;
2566
2567                   --  Replace the return object declaration with a renaming
2568                   --  of a dereference of the implicit access formal.
2569
2570                   Obj_Acc_Deref :=
2571                     Make_Explicit_Dereference (Loc,
2572                       Prefix => New_Reference_To (Obj_Acc_Formal, Loc));
2573
2574                   Rewrite (Return_Object_Decl,
2575                     Make_Object_Renaming_Declaration (Loc,
2576                       Defining_Identifier => Return_Obj_Id,
2577                       Access_Definition   => Empty,
2578                       Subtype_Mark        => New_Occurrence_Of
2579                                                (Return_Obj_Typ, Loc),
2580                       Name                => Obj_Acc_Deref));
2581
2582                   Set_Renamed_Object (Return_Obj_Id, Obj_Acc_Deref);
2583                end if;
2584             end;
2585          end if;
2586
2587       --  Case where we do not build a block
2588
2589       else
2590          --  We're about to drop Return_Object_Declarations on the floor, so
2591          --  we need to insert it, in case it got expanded into useful code.
2592
2593          Insert_List_Before (N, Return_Object_Declarations (N));
2594
2595          --  Build simple_return_statement that returns the expression directly
2596
2597          Return_Stm := Make_Return_Statement (Loc, Expression => Exp);
2598
2599          Result := Return_Stm;
2600       end if;
2601
2602       --  Set the flag to prevent infinite recursion
2603
2604       Set_Comes_From_Extended_Return_Statement (Return_Stm);
2605
2606       Rewrite (N, Result);
2607       Analyze (N);
2608    end Expand_N_Extended_Return_Statement;
2609
2610    -----------------------------
2611    -- Expand_N_Goto_Statement --
2612    -----------------------------
2613
2614    --  Add poll before goto if polling active
2615
2616    procedure Expand_N_Goto_Statement (N : Node_Id) is
2617    begin
2618       Generate_Poll_Call (N);
2619    end Expand_N_Goto_Statement;
2620
2621    ---------------------------
2622    -- Expand_N_If_Statement --
2623    ---------------------------
2624
2625    --  First we deal with the case of C and Fortran convention boolean
2626    --  values, with zero/non-zero semantics.
2627
2628    --  Second, we deal with the obvious rewriting for the cases where the
2629    --  condition of the IF is known at compile time to be True or False.
2630
2631    --  Third, we remove elsif parts which have non-empty Condition_Actions
2632    --  and rewrite as independent if statements. For example:
2633
2634    --     if x then xs
2635    --     elsif y then ys
2636    --     ...
2637    --     end if;
2638
2639    --  becomes
2640    --
2641    --     if x then xs
2642    --     else
2643    --        <<condition actions of y>>
2644    --        if y then ys
2645    --        ...
2646    --        end if;
2647    --     end if;
2648
2649    --  This rewriting is needed if at least one elsif part has a non-empty
2650    --  Condition_Actions list. We also do the same processing if there is
2651    --  a constant condition in an elsif part (in conjunction with the first
2652    --  processing step mentioned above, for the recursive call made to deal
2653    --  with the created inner if, this deals with properly optimizing the
2654    --  cases of constant elsif conditions).
2655
2656    procedure Expand_N_If_Statement (N : Node_Id) is
2657       Loc    : constant Source_Ptr := Sloc (N);
2658       Hed    : Node_Id;
2659       E      : Node_Id;
2660       New_If : Node_Id;
2661
2662    begin
2663       Adjust_Condition (Condition (N));
2664
2665       --  The following loop deals with constant conditions for the IF. We
2666       --  need a loop because as we eliminate False conditions, we grab the
2667       --  first elsif condition and use it as the primary condition.
2668
2669       while Compile_Time_Known_Value (Condition (N)) loop
2670
2671          --  If condition is True, we can simply rewrite the if statement
2672          --  now by replacing it by the series of then statements.
2673
2674          if Is_True (Expr_Value (Condition (N))) then
2675
2676             --  All the else parts can be killed
2677
2678             Kill_Dead_Code (Elsif_Parts (N), Warn_On_Deleted_Code);
2679             Kill_Dead_Code (Else_Statements (N), Warn_On_Deleted_Code);
2680
2681             Hed := Remove_Head (Then_Statements (N));
2682             Insert_List_After (N, Then_Statements (N));
2683             Rewrite (N, Hed);
2684             return;
2685
2686          --  If condition is False, then we can delete the condition and
2687          --  the Then statements
2688
2689          else
2690             --  We do not delete the condition if constant condition
2691             --  warnings are enabled, since otherwise we end up deleting
2692             --  the desired warning. Of course the backend will get rid
2693             --  of this True/False test anyway, so nothing is lost here.
2694
2695             if not Constant_Condition_Warnings then
2696                Kill_Dead_Code (Condition (N));
2697             end if;
2698
2699             Kill_Dead_Code (Then_Statements (N), Warn_On_Deleted_Code);
2700
2701             --  If there are no elsif statements, then we simply replace
2702             --  the entire if statement by the sequence of else statements.
2703
2704             if No (Elsif_Parts (N)) then
2705                if No (Else_Statements (N))
2706                  or else Is_Empty_List (Else_Statements (N))
2707                then
2708                   Rewrite (N,
2709                     Make_Null_Statement (Sloc (N)));
2710                else
2711                   Hed := Remove_Head (Else_Statements (N));
2712                   Insert_List_After (N, Else_Statements (N));
2713                   Rewrite (N, Hed);
2714                end if;
2715
2716                return;
2717
2718             --  If there are elsif statements, the first of them becomes
2719             --  the if/then section of the rebuilt if statement This is
2720             --  the case where we loop to reprocess this copied condition.
2721
2722             else
2723                Hed := Remove_Head (Elsif_Parts (N));
2724                Insert_Actions      (N, Condition_Actions (Hed));
2725                Set_Condition       (N, Condition (Hed));
2726                Set_Then_Statements (N, Then_Statements (Hed));
2727
2728                --  Hed might have been captured as the condition determining
2729                --  the current value for an entity. Now it is detached from
2730                --  the tree, so a Current_Value pointer in the condition might
2731                --  need to be updated.
2732
2733                Set_Current_Value_Condition (N);
2734
2735                if Is_Empty_List (Elsif_Parts (N)) then
2736                   Set_Elsif_Parts (N, No_List);
2737                end if;
2738             end if;
2739          end if;
2740       end loop;
2741
2742       --  Loop through elsif parts, dealing with constant conditions and
2743       --  possible expression actions that are present.
2744
2745       if Present (Elsif_Parts (N)) then
2746          E := First (Elsif_Parts (N));
2747          while Present (E) loop
2748             Adjust_Condition (Condition (E));
2749
2750             --  If there are condition actions, then we rewrite the if
2751             --  statement as indicated above. We also do the same rewrite
2752             --  if the condition is True or False. The further processing
2753             --  of this constant condition is then done by the recursive
2754             --  call to expand the newly created if statement
2755
2756             if Present (Condition_Actions (E))
2757               or else Compile_Time_Known_Value (Condition (E))
2758             then
2759                --  Note this is not an implicit if statement, since it is
2760                --  part of an explicit if statement in the source (or of an
2761                --  implicit if statement that has already been tested).
2762
2763                New_If :=
2764                  Make_If_Statement (Sloc (E),
2765                    Condition       => Condition (E),
2766                    Then_Statements => Then_Statements (E),
2767                    Elsif_Parts     => No_List,
2768                    Else_Statements => Else_Statements (N));
2769
2770                --  Elsif parts for new if come from remaining elsif's of parent
2771
2772                while Present (Next (E)) loop
2773                   if No (Elsif_Parts (New_If)) then
2774                      Set_Elsif_Parts (New_If, New_List);
2775                   end if;
2776
2777                   Append (Remove_Next (E), Elsif_Parts (New_If));
2778                end loop;
2779
2780                Set_Else_Statements (N, New_List (New_If));
2781
2782                if Present (Condition_Actions (E)) then
2783                   Insert_List_Before (New_If, Condition_Actions (E));
2784                end if;
2785
2786                Remove (E);
2787
2788                if Is_Empty_List (Elsif_Parts (N)) then
2789                   Set_Elsif_Parts (N, No_List);
2790                end if;
2791
2792                Analyze (New_If);
2793                return;
2794
2795             --  No special processing for that elsif part, move to next
2796
2797             else
2798                Next (E);
2799             end if;
2800          end loop;
2801       end if;
2802
2803       --  Some more optimizations applicable if we still have an IF statement
2804
2805       if Nkind (N) /= N_If_Statement then
2806          return;
2807       end if;
2808
2809       --  Another optimization, special cases that can be simplified
2810
2811       --     if expression then
2812       --        return true;
2813       --     else
2814       --        return false;
2815       --     end if;
2816
2817       --  can be changed to:
2818
2819       --     return expression;
2820
2821       --  and
2822
2823       --     if expression then
2824       --        return false;
2825       --     else
2826       --        return true;
2827       --     end if;
2828
2829       --  can be changed to:
2830
2831       --     return not (expression);
2832
2833       if Nkind (N) = N_If_Statement
2834          and then No (Elsif_Parts (N))
2835          and then Present (Else_Statements (N))
2836          and then List_Length (Then_Statements (N)) = 1
2837          and then List_Length (Else_Statements (N)) = 1
2838       then
2839          declare
2840             Then_Stm : constant Node_Id := First (Then_Statements (N));
2841             Else_Stm : constant Node_Id := First (Else_Statements (N));
2842
2843          begin
2844             if Nkind (Then_Stm) = N_Return_Statement
2845                  and then
2846                Nkind (Else_Stm) = N_Return_Statement
2847             then
2848                declare
2849                   Then_Expr : constant Node_Id := Expression (Then_Stm);
2850                   Else_Expr : constant Node_Id := Expression (Else_Stm);
2851
2852                begin
2853                   if Nkind (Then_Expr) = N_Identifier
2854                        and then
2855                      Nkind (Else_Expr) = N_Identifier
2856                   then
2857                      if Entity (Then_Expr) = Standard_True
2858                        and then Entity (Else_Expr) = Standard_False
2859                      then
2860                         Rewrite (N,
2861                           Make_Return_Statement (Loc,
2862                             Expression => Relocate_Node (Condition (N))));
2863                         Analyze (N);
2864                         return;
2865
2866                      elsif Entity (Then_Expr) = Standard_False
2867                        and then Entity (Else_Expr) = Standard_True
2868                      then
2869                         Rewrite (N,
2870                           Make_Return_Statement (Loc,
2871                             Expression =>
2872                               Make_Op_Not (Loc,
2873                                 Right_Opnd => Relocate_Node (Condition (N)))));
2874                         Analyze (N);
2875                         return;
2876                      end if;
2877                   end if;
2878                end;
2879             end if;
2880          end;
2881       end if;
2882    end Expand_N_If_Statement;
2883
2884    -----------------------------
2885    -- Expand_N_Loop_Statement --
2886    -----------------------------
2887
2888    --  1. Deal with while condition for C/Fortran boolean
2889    --  2. Deal with loops with a non-standard enumeration type range
2890    --  3. Deal with while loops where Condition_Actions is set
2891    --  4. Insert polling call if required
2892
2893    procedure Expand_N_Loop_Statement (N : Node_Id) is
2894       Loc  : constant Source_Ptr := Sloc (N);
2895       Isc  : constant Node_Id    := Iteration_Scheme (N);
2896
2897    begin
2898       if Present (Isc) then
2899          Adjust_Condition (Condition (Isc));
2900       end if;
2901
2902       if Is_Non_Empty_List (Statements (N)) then
2903          Generate_Poll_Call (First (Statements (N)));
2904       end if;
2905
2906       --  Nothing more to do for plain loop with no iteration scheme
2907
2908       if No (Isc) then
2909          return;
2910       end if;
2911
2912       --  Note: we do not have to worry about validity chekcing of the for loop
2913       --  range bounds here, since they were frozen with constant declarations
2914       --  and it is during that process that the validity checking is done.
2915
2916       --  Handle the case where we have a for loop with the range type being
2917       --  an enumeration type with non-standard representation. In this case
2918       --  we expand:
2919
2920       --    for x in [reverse] a .. b loop
2921       --       ...
2922       --    end loop;
2923
2924       --  to
2925
2926       --    for xP in [reverse] integer
2927       --                          range etype'Pos (a) .. etype'Pos (b) loop
2928       --       declare
2929       --          x : constant etype := Pos_To_Rep (xP);
2930       --       begin
2931       --          ...
2932       --       end;
2933       --    end loop;
2934
2935       if Present (Loop_Parameter_Specification (Isc)) then
2936          declare
2937             LPS     : constant Node_Id   := Loop_Parameter_Specification (Isc);
2938             Loop_Id : constant Entity_Id := Defining_Identifier (LPS);
2939             Ltype   : constant Entity_Id := Etype (Loop_Id);
2940             Btype   : constant Entity_Id := Base_Type (Ltype);
2941             Expr    : Node_Id;
2942             New_Id  : Entity_Id;
2943
2944          begin
2945             if not Is_Enumeration_Type (Btype)
2946               or else No (Enum_Pos_To_Rep (Btype))
2947             then
2948                return;
2949             end if;
2950
2951             New_Id :=
2952               Make_Defining_Identifier (Loc,
2953                 Chars => New_External_Name (Chars (Loop_Id), 'P'));
2954
2955             --  If the type has a contiguous representation, successive
2956             --  values can be generated as offsets from the first literal.
2957
2958             if Has_Contiguous_Rep (Btype) then
2959                Expr :=
2960                   Unchecked_Convert_To (Btype,
2961                     Make_Op_Add (Loc,
2962                       Left_Opnd =>
2963                          Make_Integer_Literal (Loc,
2964                            Enumeration_Rep (First_Literal (Btype))),
2965                       Right_Opnd => New_Reference_To (New_Id, Loc)));
2966             else
2967                --  Use the constructed array Enum_Pos_To_Rep
2968
2969                Expr :=
2970                  Make_Indexed_Component (Loc,
2971                    Prefix => New_Reference_To (Enum_Pos_To_Rep (Btype), Loc),
2972                    Expressions => New_List (New_Reference_To (New_Id, Loc)));
2973             end if;
2974
2975             Rewrite (N,
2976               Make_Loop_Statement (Loc,
2977                 Identifier => Identifier (N),
2978
2979                 Iteration_Scheme =>
2980                   Make_Iteration_Scheme (Loc,
2981                     Loop_Parameter_Specification =>
2982                       Make_Loop_Parameter_Specification (Loc,
2983                         Defining_Identifier => New_Id,
2984                         Reverse_Present => Reverse_Present (LPS),
2985
2986                         Discrete_Subtype_Definition =>
2987                           Make_Subtype_Indication (Loc,
2988
2989                             Subtype_Mark =>
2990                               New_Reference_To (Standard_Natural, Loc),
2991
2992                             Constraint =>
2993                               Make_Range_Constraint (Loc,
2994                                 Range_Expression =>
2995                                   Make_Range (Loc,
2996
2997                                     Low_Bound =>
2998                                       Make_Attribute_Reference (Loc,
2999                                         Prefix =>
3000                                           New_Reference_To (Btype, Loc),
3001
3002                                         Attribute_Name => Name_Pos,
3003
3004                                         Expressions => New_List (
3005                                           Relocate_Node
3006                                             (Type_Low_Bound (Ltype)))),
3007
3008                                     High_Bound =>
3009                                       Make_Attribute_Reference (Loc,
3010                                         Prefix =>
3011                                           New_Reference_To (Btype, Loc),
3012
3013                                         Attribute_Name => Name_Pos,
3014
3015                                         Expressions => New_List (
3016                                           Relocate_Node
3017                                             (Type_High_Bound (Ltype))))))))),
3018
3019                 Statements => New_List (
3020                   Make_Block_Statement (Loc,
3021                     Declarations => New_List (
3022                       Make_Object_Declaration (Loc,
3023                         Defining_Identifier => Loop_Id,
3024                         Constant_Present    => True,
3025                         Object_Definition   => New_Reference_To (Ltype, Loc),
3026                         Expression          => Expr)),
3027
3028                     Handled_Statement_Sequence =>
3029                       Make_Handled_Sequence_Of_Statements (Loc,
3030                         Statements => Statements (N)))),
3031
3032                 End_Label => End_Label (N)));
3033             Analyze (N);
3034          end;
3035
3036       --  Second case, if we have a while loop with Condition_Actions set,
3037       --  then we change it into a plain loop:
3038
3039       --    while C loop
3040       --       ...
3041       --    end loop;
3042
3043       --  changed to:
3044
3045       --    loop
3046       --       <<condition actions>>
3047       --       exit when not C;
3048       --       ...
3049       --    end loop
3050
3051       elsif Present (Isc)
3052         and then Present (Condition_Actions (Isc))
3053       then
3054          declare
3055             ES : Node_Id;
3056
3057          begin
3058             ES :=
3059               Make_Exit_Statement (Sloc (Condition (Isc)),
3060                 Condition =>
3061                   Make_Op_Not (Sloc (Condition (Isc)),
3062                     Right_Opnd => Condition (Isc)));
3063
3064             Prepend (ES, Statements (N));
3065             Insert_List_Before (ES, Condition_Actions (Isc));
3066
3067             --  This is not an implicit loop, since it is generated in
3068             --  response to the loop statement being processed. If this
3069             --  is itself implicit, the restriction has already been
3070             --  checked. If not, it is an explicit loop.
3071
3072             Rewrite (N,
3073               Make_Loop_Statement (Sloc (N),
3074                 Identifier => Identifier (N),
3075                 Statements => Statements (N),
3076                 End_Label  => End_Label  (N)));
3077
3078             Analyze (N);
3079          end;
3080       end if;
3081    end Expand_N_Loop_Statement;
3082
3083    -------------------------------
3084    -- Expand_N_Return_Statement --
3085    -------------------------------
3086
3087    procedure Expand_N_Return_Statement (N : Node_Id) is
3088       Loc         : constant Source_Ptr := Sloc (N);
3089       Exp         : constant Node_Id    := Expression (N);
3090       Exptyp      : Entity_Id;
3091       T           : Entity_Id;
3092       Utyp        : Entity_Id;
3093       Scope_Id    : Entity_Id;
3094       Kind        : Entity_Kind;
3095       Call        : Node_Id;
3096       Acc_Stat    : Node_Id;
3097       Goto_Stat   : Node_Id;
3098       Lab_Node    : Node_Id;
3099       Cur_Idx     : Nat;
3100       Return_Type : Entity_Id;
3101       Result_Exp  : Node_Id;
3102       Result_Id   : Entity_Id;
3103       Result_Obj  : Node_Id;
3104
3105    begin
3106       if Enable_New_Return_Processing then --  ???Temporary hack
3107          Expand_Simple_Return (N);
3108          return;
3109       end if;
3110
3111       --  Case where returned expression is present
3112
3113       if Present (Exp) then
3114
3115          --  Always normalize C/Fortran boolean result. This is not always
3116          --  necessary, but it seems a good idea to minimize the passing
3117          --  around of non-normalized values, and in any case this handles
3118          --  the processing of barrier functions for protected types, which
3119          --  turn the condition into a return statement.
3120
3121          Exptyp := Etype (Exp);
3122
3123          if Is_Boolean_Type (Exptyp)
3124            and then Nonzero_Is_True (Exptyp)
3125          then
3126             Adjust_Condition (Exp);
3127             Adjust_Result_Type (Exp, Exptyp);
3128          end if;
3129
3130          --  Do validity check if enabled for returns
3131
3132          if Validity_Checks_On
3133            and then Validity_Check_Returns
3134          then
3135             Ensure_Valid (Exp);
3136          end if;
3137       end if;
3138
3139       --  Find relevant enclosing scope from which return is returning
3140
3141       Cur_Idx := Scope_Stack.Last;
3142       loop
3143          Scope_Id := Scope_Stack.Table (Cur_Idx).Entity;
3144
3145          if Ekind (Scope_Id) /= E_Block
3146            and then Ekind (Scope_Id) /= E_Loop
3147          then
3148             exit;
3149
3150          else
3151             Cur_Idx := Cur_Idx - 1;
3152             pragma Assert (Cur_Idx >= 0);
3153          end if;
3154       end loop;
3155       --  ???I believe the above code is no longer necessary
3156       pragma Assert (Scope_Id =
3157                        Return_Applies_To (Return_Statement_Entity (N)));
3158
3159       if No (Exp) then
3160          Kind := Ekind (Scope_Id);
3161
3162          --  If it is a return from procedures do no extra steps
3163
3164          if Kind = E_Procedure or else Kind = E_Generic_Procedure then
3165             return;
3166          end if;
3167
3168          pragma Assert (Is_Entry (Scope_Id));
3169
3170          --  Look at the enclosing block to see whether the return is from
3171          --  an accept statement or an entry body.
3172
3173          for J in reverse 0 .. Cur_Idx loop
3174             Scope_Id := Scope_Stack.Table (J).Entity;
3175             exit when Is_Concurrent_Type (Scope_Id);
3176          end loop;
3177
3178          --  If it is a return from accept statement it should be expanded
3179          --  as a call to RTS Complete_Rendezvous and a goto to the end of
3180          --  the accept body.
3181
3182          --  (cf : Expand_N_Accept_Statement, Expand_N_Selective_Accept,
3183          --   Expand_N_Accept_Alternative in exp_ch9.adb)
3184
3185          if Is_Task_Type (Scope_Id) then
3186
3187             Call := (Make_Procedure_Call_Statement (Loc,
3188                       Name => New_Reference_To
3189                         (RTE (RE_Complete_Rendezvous), Loc)));
3190             Insert_Before (N, Call);
3191             --  why not insert actions here???
3192             Analyze (Call);
3193
3194             Acc_Stat := Parent (N);
3195             while Nkind (Acc_Stat) /= N_Accept_Statement loop
3196                Acc_Stat := Parent (Acc_Stat);
3197             end loop;
3198
3199             Lab_Node := Last (Statements
3200               (Handled_Statement_Sequence (Acc_Stat)));
3201
3202             Goto_Stat := Make_Goto_Statement (Loc,
3203               Name => New_Occurrence_Of
3204                 (Entity (Identifier (Lab_Node)), Loc));
3205
3206             Set_Analyzed (Goto_Stat);
3207
3208             Rewrite (N, Goto_Stat);
3209             Analyze (N);
3210
3211          --  If it is a return from an entry body, put a Complete_Entry_Body
3212          --  call in front of the return.
3213
3214          elsif Is_Protected_Type (Scope_Id) then
3215
3216             Call :=
3217               Make_Procedure_Call_Statement (Loc,
3218                 Name => New_Reference_To
3219                   (RTE (RE_Complete_Entry_Body), Loc),
3220                 Parameter_Associations => New_List
3221                   (Make_Attribute_Reference (Loc,
3222                     Prefix =>
3223                       New_Reference_To
3224                         (Object_Ref
3225                            (Corresponding_Body (Parent (Scope_Id))),
3226                         Loc),
3227                     Attribute_Name => Name_Unchecked_Access)));
3228
3229             Insert_Before (N, Call);
3230             Analyze (Call);
3231          end if;
3232
3233          return;
3234       end if;
3235
3236       T := Etype (Exp);
3237       Return_Type := Etype (Scope_Id);
3238       Utyp := Underlying_Type (Return_Type);
3239
3240       --  Check the result expression of a scalar function against the subtype
3241       --  of the function by inserting a conversion. This conversion must
3242       --  eventually be performed for other classes of types, but for now it's
3243       --  only done for scalars. ???
3244
3245       if Is_Scalar_Type (T) then
3246          Rewrite (Exp, Convert_To (Return_Type, Exp));
3247          Analyze (Exp);
3248       end if;
3249
3250       --  Deal with returning variable length objects and controlled types
3251
3252       --  Nothing to do if we are returning by reference, or this is not a
3253       --  type that requires special processing (indicated by the fact that
3254       --  it requires a cleanup scope for the secondary stack case).
3255
3256       if Is_Inherently_Limited_Type (T) then
3257          null;
3258
3259       elsif not Requires_Transient_Scope (Return_Type) then
3260
3261          --  Mutable records with no variable length components are not
3262          --  returned on the sec-stack, so we need to make sure that the
3263          --  backend will only copy back the size of the actual value, and not
3264          --  the maximum size. We create an actual subtype for this purpose.
3265
3266          declare
3267             Ubt  : constant Entity_Id := Underlying_Type (Base_Type (T));
3268             Decl : Node_Id;
3269             Ent  : Entity_Id;
3270
3271          begin
3272             if Has_Discriminants (Ubt)
3273               and then not Is_Constrained (Ubt)
3274               and then not Has_Unchecked_Union (Ubt)
3275             then
3276                Decl := Build_Actual_Subtype (Ubt, Exp);
3277                Ent := Defining_Identifier (Decl);
3278                Insert_Action (Exp, Decl);
3279
3280                Rewrite (Exp, Unchecked_Convert_To (Ent, Exp));
3281                Analyze_And_Resolve (Exp);
3282             end if;
3283          end;
3284
3285       --  Case of secondary stack not used
3286
3287       elsif Function_Returns_With_DSP (Scope_Id) then
3288
3289          --  The DSP method is no longer in use. We would like to ignore DSP
3290          --  while implementing AI-318; hence the raise below.
3291
3292          if True then
3293             raise Program_Error;
3294          end if;
3295
3296          --  Here what we need to do is to always return by reference, since
3297          --  we will return with the stack pointer depressed. We may need to
3298          --  do a copy to a local temporary before doing this return.
3299
3300          No_Secondary_Stack_Case : declare
3301             Local_Copy_Required : Boolean := False;
3302             --  Set to True if a local copy is required
3303
3304             Copy_Ent : Entity_Id;
3305             --  Used for the target entity if a copy is required
3306
3307             Decl : Node_Id;
3308             --  Declaration used to create copy if needed
3309
3310             procedure Test_Copy_Required (Expr : Node_Id);
3311             --  Determines if Expr represents a return value for which a
3312             --  copy is required. More specifically, a copy is not required
3313             --  if Expr represents an object or component of an object that
3314             --  is either in the local subprogram frame, or is constant.
3315             --  If a copy is required, then Local_Copy_Required is set True.
3316
3317             ------------------------
3318             -- Test_Copy_Required --
3319             ------------------------
3320
3321             procedure Test_Copy_Required (Expr : Node_Id) is
3322                Ent : Entity_Id;
3323
3324             begin
3325                --  If component, test prefix (object containing component)
3326
3327                if Nkind (Expr) = N_Indexed_Component
3328                     or else
3329                   Nkind (Expr) = N_Selected_Component
3330                then
3331                   Test_Copy_Required (Prefix (Expr));
3332                   return;
3333
3334                --  See if we have an entity name
3335
3336                elsif Is_Entity_Name (Expr) then
3337                   Ent := Entity (Expr);
3338
3339                   --  Constant entity is always OK, no copy required
3340
3341                   if Ekind (Ent) = E_Constant then
3342                      return;
3343
3344                   --  No copy required for local variable
3345
3346                   elsif Ekind (Ent) = E_Variable
3347                     and then Scope (Ent) = Current_Subprogram
3348                   then
3349                      return;
3350                   end if;
3351                end if;
3352
3353                --  All other cases require a copy
3354
3355                Local_Copy_Required := True;
3356             end Test_Copy_Required;
3357
3358          --  Start of processing for No_Secondary_Stack_Case
3359
3360          begin
3361             --  No copy needed if result is from a function call.
3362             --  In this case the result is already being returned by
3363             --  reference with the stack pointer depressed.
3364
3365             --  To make up for a gcc 2.8.1 deficiency (???), we perform
3366             --  the copy for array types if the constrained status of the
3367             --  target type is different from that of the expression.
3368
3369             if Requires_Transient_Scope (T)
3370               and then
3371                 (not Is_Array_Type (T)
3372                    or else Is_Constrained (T) = Is_Constrained (Return_Type)
3373                    or else Controlled_Type (T))
3374               and then Nkind (Exp) = N_Function_Call
3375             then
3376                Set_By_Ref (N);
3377
3378             --  We always need a local copy for a controlled type, since
3379             --  we are required to finalize the local value before return.
3380             --  The copy will automatically include the required finalize.
3381             --  Moreover, gigi cannot make this copy, since we need special
3382             --  processing to ensure proper behavior for finalization.
3383
3384             --  Note: the reason we are returning with a depressed stack
3385             --  pointer in the controlled case (even if the type involved
3386             --  is constrained) is that we must make a local copy to deal
3387             --  properly with the requirement that the local result be
3388             --  finalized.
3389
3390             elsif Controlled_Type (Utyp) then
3391                Copy_Ent :=
3392                  Make_Defining_Identifier (Loc,
3393                    Chars => New_Internal_Name ('R'));
3394
3395                --  Build declaration to do the copy, and insert it, setting
3396                --  Assignment_OK, because we may be copying a limited type.
3397                --  In addition we set the special flag to inhibit finalize
3398                --  attachment if this is a controlled type (since this attach
3399                --  must be done by the caller, otherwise if we attach it here
3400                --  we will finalize the returned result prematurely).
3401
3402                Decl :=
3403                  Make_Object_Declaration (Loc,
3404                    Defining_Identifier => Copy_Ent,
3405                    Object_Definition   => New_Occurrence_Of (Return_Type, Loc),
3406                    Expression          => Relocate_Node (Exp));
3407
3408                Set_Assignment_OK (Decl);
3409                Set_Delay_Finalize_Attach (Decl);
3410                Insert_Action (N, Decl);
3411
3412                --  Now the actual return uses the copied value
3413
3414                Rewrite (Exp, New_Occurrence_Of (Copy_Ent, Loc));
3415                Analyze_And_Resolve (Exp, Return_Type);
3416
3417                --  Since we have made the copy, gigi does not have to, so
3418                --  we set the By_Ref flag to prevent another copy being made.
3419
3420                Set_By_Ref (N);
3421
3422             --  Non-controlled cases
3423
3424             else
3425                Test_Copy_Required (Exp);
3426
3427                --  If a local copy is required, then gigi will make the
3428                --  copy, otherwise, we can return the result directly,
3429                --  so set By_Ref to suppress the gigi copy.
3430
3431                if not Local_Copy_Required then
3432                   Set_By_Ref (N);
3433                end if;
3434             end if;
3435          end No_Secondary_Stack_Case;
3436
3437       --  Here if secondary stack is used
3438
3439       else
3440          --  Make sure that no surrounding block will reclaim the secondary
3441          --  stack on which we are going to put the result. Not only may this
3442          --  introduce secondary stack leaks but worse, if the reclamation is
3443          --  done too early, then the result we are returning may get
3444          --  clobbered. See example in 7417-003.
3445
3446          declare
3447             S : Entity_Id := Current_Scope;
3448
3449          begin
3450             while Ekind (S) = E_Block or else Ekind (S) = E_Loop loop
3451                Set_Sec_Stack_Needed_For_Return (S, True);
3452                S := Enclosing_Dynamic_Scope (S);
3453             end loop;
3454          end;
3455
3456          --  Optimize the case where the result is a function call. In this
3457          --  case either the result is already on the secondary stack, or is
3458          --  already being returned with the stack pointer depressed and no
3459          --  further processing is required except to set the By_Ref flag to
3460          --  ensure that gigi does not attempt an extra unnecessary copy.
3461          --  (actually not just unnecessary but harmfully wrong in the case
3462          --  of a controlled type, where gigi does not know how to do a copy).
3463          --  To make up for a gcc 2.8.1 deficiency (???), we perform
3464          --  the copy for array types if the constrained status of the
3465          --  target type is different from that of the expression.
3466
3467          if Requires_Transient_Scope (T)
3468            and then
3469               (not Is_Array_Type (T)
3470                 or else Is_Constrained (T) = Is_Constrained (Return_Type)
3471                 or else Is_Class_Wide_Type (Utyp)
3472                 or else Controlled_Type (T))
3473            and then Nkind (Exp) = N_Function_Call
3474          then
3475             Set_By_Ref (N);
3476
3477             --  Remove side effects from the expression now so that
3478             --  other part of the expander do not have to reanalyze
3479             --  this node without this optimization
3480
3481             Rewrite (Exp, Duplicate_Subexpr_No_Checks (Exp));
3482
3483          --  For controlled types, do the allocation on the secondary stack
3484          --  manually in order to call adjust at the right time:
3485          --    type Anon1 is access Return_Type;
3486          --    for Anon1'Storage_pool use ss_pool;
3487          --    Anon2 : anon1 := new Return_Type'(expr);
3488          --    return Anon2.all;
3489          --  We do the same for classwide types that are not potentially
3490          --  controlled (by the virtue of restriction No_Finalization) because
3491          --  gigi is not able to properly allocate class-wide types.
3492
3493          elsif Is_Class_Wide_Type (Utyp)
3494            or else Controlled_Type (Utyp)
3495          then
3496             declare
3497                Loc        : constant Source_Ptr := Sloc (N);
3498                Temp       : constant Entity_Id :=
3499                               Make_Defining_Identifier (Loc,
3500                                 Chars => New_Internal_Name ('R'));
3501                Acc_Typ    : constant Entity_Id :=
3502                               Make_Defining_Identifier (Loc,
3503                                 Chars => New_Internal_Name ('A'));
3504                Alloc_Node : Node_Id;
3505
3506             begin
3507                Set_Ekind (Acc_Typ, E_Access_Type);
3508
3509                Set_Associated_Storage_Pool (Acc_Typ, RTE (RE_SS_Pool));
3510
3511                Alloc_Node :=
3512                  Make_Allocator (Loc,
3513                    Expression =>
3514                      Make_Qualified_Expression (Loc,
3515                        Subtype_Mark => New_Reference_To (Etype (Exp), Loc),
3516                        Expression => Relocate_Node (Exp)));
3517
3518                Insert_List_Before_And_Analyze (N, New_List (
3519                  Make_Full_Type_Declaration (Loc,
3520                    Defining_Identifier => Acc_Typ,
3521                    Type_Definition     =>
3522                      Make_Access_To_Object_Definition (Loc,
3523                        Subtype_Indication =>
3524                           New_Reference_To (Return_Type, Loc))),
3525
3526                  Make_Object_Declaration (Loc,
3527                    Defining_Identifier => Temp,
3528                    Object_Definition   => New_Reference_To (Acc_Typ, Loc),
3529                    Expression          => Alloc_Node)));
3530
3531                Rewrite (Exp,
3532                  Make_Explicit_Dereference (Loc,
3533                  Prefix => New_Reference_To (Temp, Loc)));
3534
3535                Analyze_And_Resolve (Exp, Return_Type);
3536             end;
3537
3538          --  Otherwise use the gigi mechanism to allocate result on the
3539          --  secondary stack.
3540
3541          else
3542             Set_Storage_Pool      (N, RTE (RE_SS_Pool));
3543
3544             --  If we are generating code for the Java VM do not use
3545             --  SS_Allocate since everything is heap-allocated anyway.
3546
3547             if not Java_VM then
3548                Set_Procedure_To_Call (N, RTE (RE_SS_Allocate));
3549             end if;
3550          end if;
3551       end if;
3552
3553       --  Implement the rules of 6.5(8-10), which require a tag check in
3554       --  the case of a limited tagged return type, and tag reassignment
3555       --  for nonlimited tagged results. These actions are needed when
3556       --  the return type is a specific tagged type and the result
3557       --  expression is a conversion or a formal parameter, because in
3558       --  that case the tag of the expression might differ from the tag
3559       --  of the specific result type.
3560
3561       if Is_Tagged_Type (Utyp)
3562         and then not Is_Class_Wide_Type (Utyp)
3563         and then (Nkind (Exp) = N_Type_Conversion
3564                     or else Nkind (Exp) = N_Unchecked_Type_Conversion
3565                     or else (Is_Entity_Name (Exp)
3566                                and then Ekind (Entity (Exp)) in Formal_Kind))
3567       then
3568          --  When the return type is limited, perform a check that the
3569          --  tag of the result is the same as the tag of the return type.
3570
3571          if Is_Limited_Type (Return_Type) then
3572             Insert_Action (Exp,
3573               Make_Raise_Constraint_Error (Loc,
3574                 Condition =>
3575                   Make_Op_Ne (Loc,
3576                     Left_Opnd =>
3577                       Make_Selected_Component (Loc,
3578                         Prefix => Duplicate_Subexpr (Exp),
3579                         Selector_Name =>
3580                           New_Reference_To (First_Tag_Component (Utyp), Loc)),
3581                     Right_Opnd =>
3582                       Unchecked_Convert_To (RTE (RE_Tag),
3583                         New_Reference_To
3584                           (Node (First_Elmt
3585                                   (Access_Disp_Table (Base_Type (Utyp)))),
3586                            Loc))),
3587                 Reason => CE_Tag_Check_Failed));
3588
3589          --  If the result type is a specific nonlimited tagged type,
3590          --  then we have to ensure that the tag of the result is that
3591          --  of the result type. This is handled by making a copy of the
3592          --  expression in the case where it might have a different tag,
3593          --  namely when the expression is a conversion or a formal
3594          --  parameter. We create a new object of the result type and
3595          --  initialize it from the expression, which will implicitly
3596          --  force the tag to be set appropriately.
3597
3598          else
3599             Result_Id :=
3600               Make_Defining_Identifier (Loc, New_Internal_Name ('R'));
3601             Result_Exp := New_Reference_To (Result_Id, Loc);
3602
3603             Result_Obj :=
3604               Make_Object_Declaration (Loc,
3605                 Defining_Identifier => Result_Id,
3606                 Object_Definition   => New_Reference_To (Return_Type, Loc),
3607                 Constant_Present    => True,
3608                 Expression          => Relocate_Node (Exp));
3609
3610             Set_Assignment_OK (Result_Obj);
3611             Insert_Action (Exp, Result_Obj);
3612
3613             Rewrite (Exp, Result_Exp);
3614             Analyze_And_Resolve (Exp, Return_Type);
3615          end if;
3616
3617       --  Ada 2005 (AI-344): If the result type is class-wide, then insert
3618       --  a check that the level of the return expression's underlying type
3619       --  is not deeper than the level of the master enclosing the function.
3620       --  Always generate the check when the type of the return expression
3621       --  is class-wide, when it's a type conversion, or when it's a formal
3622       --  parameter. Otherwise, suppress the check in the case where the
3623       --  return expression has a specific type whose level is known not to
3624       --  be statically deeper than the function's result type.
3625
3626       elsif Ada_Version >= Ada_05
3627         and then Is_Class_Wide_Type (Return_Type)
3628         and then not Scope_Suppress (Accessibility_Check)
3629         and then
3630           (Is_Class_Wide_Type (Etype (Exp))
3631             or else Nkind (Exp) = N_Type_Conversion
3632             or else Nkind (Exp) = N_Unchecked_Type_Conversion
3633             or else (Is_Entity_Name (Exp)
3634                        and then Ekind (Entity (Exp)) in Formal_Kind)
3635             or else Scope_Depth (Enclosing_Dynamic_Scope (Etype (Exp))) >
3636                       Scope_Depth (Enclosing_Dynamic_Scope (Scope_Id)))
3637       then
3638          Insert_Action (Exp,
3639            Make_Raise_Program_Error (Loc,
3640              Condition =>
3641                Make_Op_Gt (Loc,
3642                  Left_Opnd =>
3643                    Make_Function_Call (Loc,
3644                      Name =>
3645                        New_Reference_To
3646                          (RTE (RE_Get_Access_Level), Loc),
3647                      Parameter_Associations =>
3648                        New_List (Make_Attribute_Reference (Loc,
3649                                    Prefix         =>
3650                                       Duplicate_Subexpr (Exp),
3651                                    Attribute_Name =>
3652                                       Name_Tag))),
3653                  Right_Opnd =>
3654                    Make_Integer_Literal (Loc,
3655                      Scope_Depth (Enclosing_Dynamic_Scope (Scope_Id)))),
3656              Reason => PE_Accessibility_Check_Failed));
3657       end if;
3658
3659    exception
3660       when RE_Not_Available =>
3661          return;
3662    end Expand_N_Return_Statement;
3663
3664    --------------------------------
3665    -- Expand_Non_Function_Return --
3666    --------------------------------
3667
3668    procedure Expand_Non_Function_Return (N : Node_Id) is
3669       pragma Assert (No (Expression (N)));
3670
3671       Loc         : constant Source_Ptr := Sloc (N);
3672       Scope_Id    : Entity_Id :=
3673                       Return_Applies_To (Return_Statement_Entity (N));
3674       Kind        : constant Entity_Kind := Ekind (Scope_Id);
3675       Call        : Node_Id;
3676       Acc_Stat    : Node_Id;
3677       Goto_Stat   : Node_Id;
3678       Lab_Node    : Node_Id;
3679
3680    begin
3681       --  If it is a return from procedures do no extra steps
3682
3683       if Kind = E_Procedure or else Kind = E_Generic_Procedure then
3684          return;
3685
3686       --  If it is a nested return within an extended one, replace it
3687       --  with a return of the previously declared return object.
3688
3689       elsif Kind = E_Return_Statement then
3690          Rewrite (N,
3691            Make_Return_Statement (Loc,
3692              Expression =>
3693                New_Occurrence_Of (First_Entity (Scope_Id), Loc)));
3694          Set_Comes_From_Extended_Return_Statement (N);
3695          Set_Return_Statement_Entity (N, Scope_Id);
3696          Expand_Simple_Function_Return (N);
3697          return;
3698       end if;
3699
3700       pragma Assert (Is_Entry (Scope_Id));
3701
3702       --  Look at the enclosing block to see whether the return is from
3703       --  an accept statement or an entry body.
3704
3705       for J in reverse 0 .. Scope_Stack.Last loop
3706          Scope_Id := Scope_Stack.Table (J).Entity;
3707          exit when Is_Concurrent_Type (Scope_Id);
3708       end loop;
3709
3710       --  If it is a return from accept statement it is expanded as call to
3711       --  RTS Complete_Rendezvous and a goto to the end of the accept body.
3712
3713       --  (cf : Expand_N_Accept_Statement, Expand_N_Selective_Accept,
3714       --  Expand_N_Accept_Alternative in exp_ch9.adb)
3715
3716       if Is_Task_Type (Scope_Id) then
3717
3718          Call :=
3719            Make_Procedure_Call_Statement (Loc,
3720              Name => New_Reference_To
3721                        (RTE (RE_Complete_Rendezvous), Loc));
3722          Insert_Before (N, Call);
3723          --  why not insert actions here???
3724          Analyze (Call);
3725
3726          Acc_Stat := Parent (N);
3727          while Nkind (Acc_Stat) /= N_Accept_Statement loop
3728             Acc_Stat := Parent (Acc_Stat);
3729          end loop;
3730
3731          Lab_Node := Last (Statements
3732            (Handled_Statement_Sequence (Acc_Stat)));
3733
3734          Goto_Stat := Make_Goto_Statement (Loc,
3735            Name => New_Occurrence_Of
3736              (Entity (Identifier (Lab_Node)), Loc));
3737
3738          Set_Analyzed (Goto_Stat);
3739
3740          Rewrite (N, Goto_Stat);
3741          Analyze (N);
3742
3743       --  If it is a return from an entry body, put a Complete_Entry_Body
3744       --  call in front of the return.
3745
3746       elsif Is_Protected_Type (Scope_Id) then
3747          Call :=
3748            Make_Procedure_Call_Statement (Loc,
3749              Name => New_Reference_To
3750                (RTE (RE_Complete_Entry_Body), Loc),
3751              Parameter_Associations => New_List
3752                (Make_Attribute_Reference (Loc,
3753                  Prefix =>
3754                    New_Reference_To
3755                      (Object_Ref
3756                         (Corresponding_Body (Parent (Scope_Id))),
3757                      Loc),
3758                  Attribute_Name => Name_Unchecked_Access)));
3759
3760          Insert_Before (N, Call);
3761          Analyze (Call);
3762       end if;
3763    end Expand_Non_Function_Return;
3764
3765    --------------------------
3766    -- Expand_Simple_Return --
3767    --------------------------
3768
3769    procedure Expand_Simple_Return (N : Node_Id) is
3770    begin
3771       --  Distinguish the function and non-function cases:
3772
3773       case Ekind (Return_Applies_To (Return_Statement_Entity (N))) is
3774
3775          when E_Function          |
3776               E_Generic_Function  =>
3777             Expand_Simple_Function_Return (N);
3778
3779          when E_Procedure         |
3780               E_Generic_Procedure |
3781               E_Entry             |
3782               E_Entry_Family      |
3783               E_Return_Statement =>
3784             Expand_Non_Function_Return (N);
3785
3786          when others =>
3787             raise Program_Error;
3788       end case;
3789
3790    exception
3791       when RE_Not_Available =>
3792          return;
3793    end Expand_Simple_Return;
3794
3795    -----------------------------------
3796    -- Expand_Simple_Function_Return --
3797    -----------------------------------
3798
3799    --  The "simple" comes from the syntax rule simple_return_statement.
3800    --  The semantics are not at all simple!
3801
3802    procedure Expand_Simple_Function_Return (N : Node_Id) is
3803       Loc : constant Source_Ptr := Sloc (N);
3804
3805       Scope_Id : constant Entity_Id :=
3806                    Return_Applies_To (Return_Statement_Entity (N));
3807       --  The function we are returning from
3808
3809       R_Type : constant Entity_Id := Etype (Scope_Id);
3810       --  The result type of the function
3811
3812       Utyp : constant Entity_Id := Underlying_Type (R_Type);
3813
3814       Exp : constant Node_Id := Expression (N);
3815       pragma Assert (Present (Exp));
3816
3817       Exptyp : constant Entity_Id := Etype (Exp);
3818       --  The type of the expression (not necessarily the same as R_Type)
3819
3820    begin
3821       --  The DSP method is no longer in use
3822
3823       pragma Assert (not Function_Returns_With_DSP (Scope_Id));
3824
3825       --  We rewrite "return <expression>;" to be:
3826
3827       --    return _anon_ : <return_subtype> := <expression>
3828
3829       --  The expansion produced by Expand_N_Extended_Return_Statement will
3830       --  contain simple return statements (for example, a block containing a
3831       --  simple return of the return object), which brings us back here with
3832       --  Comes_From_Extended_Return_Statement set. To avoid infinite
3833       --  recursion, we do not transform into an extended return if
3834       --  Comes_From_Extended_Return_Statement is True.
3835
3836       --  The reason for this design is that for Ada 2005 limited returns, we
3837       --  need to reify the return object, so we can build it "in place",
3838       --  and we need a block statement to hang finalization and tasking stuff
3839       --  off of.
3840
3841       --  ??? In order to avoid disruption, we avoid translating to extended
3842       --  return except in the cases where we really need to (Ada 2005
3843       --  inherently limited). We would prefer eventually to do this
3844       --  translation in all cases except perhaps for the case of Ada 95
3845       --  inherently limited, in order to fully exercise the code in
3846       --  Expand_N_Extended_Return_Statement, and in order to do
3847       --  build-in-place for efficiency when it is not required.
3848
3849       if not Comes_From_Extended_Return_Statement (N)
3850         and then Is_Inherently_Limited_Type (R_Type) --  ???
3851         and then Ada_Version >= Ada_05 --  ???
3852         and then not Debug_Flag_Dot_L
3853       then
3854          declare
3855             Return_Object_Entity : constant Entity_Id :=
3856                                      Make_Defining_Identifier (Loc,
3857                                        New_Internal_Name ('R'));
3858
3859             Subtype_Ind : constant Node_Id := New_Occurrence_Of (R_Type, Loc);
3860
3861             Obj_Decl : constant Node_Id :=
3862                          Make_Object_Declaration (Loc,
3863                            Defining_Identifier => Return_Object_Entity,
3864                            Object_Definition   => Subtype_Ind,
3865                            Expression          => Exp);
3866
3867             Ext : constant Node_Id := Make_Extended_Return_Statement (Loc,
3868                     Return_Object_Declarations => New_List (Obj_Decl));
3869
3870          begin
3871             Rewrite (N, Ext);
3872             Analyze (N);
3873             return;
3874          end;
3875       end if;
3876
3877       --  Here we have a simple return statement that is part of the expansion
3878       --  of an extended return statement (either written by the user, or
3879       --  generated by the above code).
3880
3881       --  Always normalize C/Fortran boolean result. This is not always
3882       --  necessary, but it seems a good idea to minimize the passing
3883       --  around of non-normalized values, and in any case this handles
3884       --  the processing of barrier functions for protected types, which
3885       --  turn the condition into a return statement.
3886
3887       if Is_Boolean_Type (Exptyp)
3888         and then Nonzero_Is_True (Exptyp)
3889       then
3890          Adjust_Condition (Exp);
3891          Adjust_Result_Type (Exp, Exptyp);
3892       end if;
3893
3894       --  Do validity check if enabled for returns
3895
3896       if Validity_Checks_On
3897         and then Validity_Check_Returns
3898       then
3899          Ensure_Valid (Exp);
3900       end if;
3901
3902       --  Check the result expression of a scalar function against the subtype
3903       --  of the function by inserting a conversion. This conversion must
3904       --  eventually be performed for other classes of types, but for now it's
3905       --  only done for scalars.
3906       --  ???
3907
3908       if Is_Scalar_Type (Exptyp) then
3909          Rewrite (Exp, Convert_To (R_Type, Exp));
3910          Analyze (Exp);
3911       end if;
3912
3913       --  Deal with returning variable length objects and controlled types
3914
3915       --  Nothing to do if we are returning by reference, or this is not a
3916       --  type that requires special processing (indicated by the fact that
3917       --  it requires a cleanup scope for the secondary stack case).
3918
3919       if Is_Inherently_Limited_Type (Exptyp) then
3920          null;
3921
3922       elsif not Requires_Transient_Scope (R_Type) then
3923
3924          --  Mutable records with no variable length components are not
3925          --  returned on the sec-stack, so we need to make sure that the
3926          --  backend will only copy back the size of the actual value, and not
3927          --  the maximum size. We create an actual subtype for this purpose.
3928
3929          declare
3930             Ubt  : constant Entity_Id := Underlying_Type (Base_Type (Exptyp));
3931             Decl : Node_Id;
3932             Ent  : Entity_Id;
3933          begin
3934             if Has_Discriminants (Ubt)
3935               and then not Is_Constrained (Ubt)
3936               and then not Has_Unchecked_Union (Ubt)
3937             then
3938                Decl := Build_Actual_Subtype (Ubt, Exp);
3939                Ent := Defining_Identifier (Decl);
3940                Insert_Action (Exp, Decl);
3941                Rewrite (Exp, Unchecked_Convert_To (Ent, Exp));
3942                Analyze_And_Resolve (Exp);
3943             end if;
3944          end;
3945
3946       --  Case of secondary stack not used
3947
3948       elsif Function_Returns_With_DSP (Scope_Id) then
3949
3950          --  The DSP method is no longer in use. We would like to ignore DSP
3951          --  while implementing AI-318; hence the following assertion. Keep the
3952          --  old code around in case DSP is revived someday.
3953
3954          pragma Assert (False);
3955
3956          No_Secondary_Stack_Case (N);
3957
3958       --  Here if secondary stack is used
3959
3960       else
3961          --  Make sure that no surrounding block will reclaim the secondary
3962          --  stack on which we are going to put the result. Not only may this
3963          --  introduce secondary stack leaks but worse, if the reclamation is
3964          --  done too early, then the result we are returning may get
3965          --  clobbered. See example in 7417-003.
3966
3967          declare
3968             S : Entity_Id;
3969          begin
3970             S := Current_Scope;
3971             while Ekind (S) = E_Block or else Ekind (S) = E_Loop loop
3972                Set_Sec_Stack_Needed_For_Return (S, True);
3973                S := Enclosing_Dynamic_Scope (S);
3974             end loop;
3975          end;
3976
3977          --  Optimize the case where the result is a function call. In this
3978          --  case either the result is already on the secondary stack, or is
3979          --  already being returned with the stack pointer depressed and no
3980          --  further processing is required except to set the By_Ref flag to
3981          --  ensure that gigi does not attempt an extra unnecessary copy.
3982          --  (actually not just unnecessary but harmfully wrong in the case
3983          --  of a controlled type, where gigi does not know how to do a copy).
3984          --  To make up for a gcc 2.8.1 deficiency (???), we perform
3985          --  the copy for array types if the constrained status of the
3986          --  target type is different from that of the expression.
3987
3988          if Requires_Transient_Scope (Exptyp)
3989            and then
3990               (not Is_Array_Type (Exptyp)
3991                 or else Is_Constrained (Exptyp) = Is_Constrained (R_Type)
3992                 or else Is_Class_Wide_Type (Utyp)
3993                 or else Controlled_Type (Exptyp))
3994            and then Nkind (Exp) = N_Function_Call
3995          then
3996             Set_By_Ref (N);
3997
3998             --  Remove side effects from the expression now so that
3999             --  other part of the expander do not have to reanalyze
4000             --  this node without this optimization
4001
4002             Rewrite (Exp, Duplicate_Subexpr_No_Checks (Exp));
4003
4004          --  For controlled types, do the allocation on the secondary stack
4005          --  manually in order to call adjust at the right time:
4006
4007          --    type Anon1 is access R_Type;
4008          --    for Anon1'Storage_pool use ss_pool;
4009          --    Anon2 : anon1 := new R_Type'(expr);
4010          --    return Anon2.all;
4011
4012          --  We do the same for classwide types that are not potentially
4013          --  controlled (by the virtue of restriction No_Finalization) because
4014          --  gigi is not able to properly allocate class-wide types.
4015
4016          elsif Is_Class_Wide_Type (Utyp)
4017            or else Controlled_Type (Utyp)
4018          then
4019             declare
4020                Loc        : constant Source_Ptr := Sloc (N);
4021                Temp       : constant Entity_Id :=
4022                               Make_Defining_Identifier (Loc,
4023                                 Chars => New_Internal_Name ('R'));
4024                Acc_Typ    : constant Entity_Id :=
4025                               Make_Defining_Identifier (Loc,
4026                                 Chars => New_Internal_Name ('A'));
4027                Alloc_Node : Node_Id;
4028
4029             begin
4030                Set_Ekind (Acc_Typ, E_Access_Type);
4031
4032                Set_Associated_Storage_Pool (Acc_Typ, RTE (RE_SS_Pool));
4033
4034                Alloc_Node :=
4035                  Make_Allocator (Loc,
4036                    Expression =>
4037                      Make_Qualified_Expression (Loc,
4038                        Subtype_Mark => New_Reference_To (Etype (Exp), Loc),
4039                        Expression => Relocate_Node (Exp)));
4040
4041                Insert_List_Before_And_Analyze (N, New_List (
4042                  Make_Full_Type_Declaration (Loc,
4043                    Defining_Identifier => Acc_Typ,
4044                    Type_Definition     =>
4045                      Make_Access_To_Object_Definition (Loc,
4046                        Subtype_Indication =>
4047                           New_Reference_To (R_Type, Loc))),
4048
4049                  Make_Object_Declaration (Loc,
4050                    Defining_Identifier => Temp,
4051                    Object_Definition   => New_Reference_To (Acc_Typ, Loc),
4052                    Expression          => Alloc_Node)));
4053
4054                Rewrite (Exp,
4055                  Make_Explicit_Dereference (Loc,
4056                  Prefix => New_Reference_To (Temp, Loc)));
4057
4058                Analyze_And_Resolve (Exp, R_Type);
4059             end;
4060
4061          --  Otherwise use the gigi mechanism to allocate result on the
4062          --  secondary stack.
4063
4064          else
4065             Set_Storage_Pool      (N, RTE (RE_SS_Pool));
4066
4067             --  If we are generating code for the Java VM do not use
4068             --  SS_Allocate since everything is heap-allocated anyway.
4069
4070             if not Java_VM then
4071                Set_Procedure_To_Call (N, RTE (RE_SS_Allocate));
4072             end if;
4073          end if;
4074       end if;
4075
4076       --  Implement the rules of 6.5(8-10), which require a tag check in
4077       --  the case of a limited tagged return type, and tag reassignment
4078       --  for nonlimited tagged results. These actions are needed when
4079       --  the return type is a specific tagged type and the result
4080       --  expression is a conversion or a formal parameter, because in
4081       --  that case the tag of the expression might differ from the tag
4082       --  of the specific result type.
4083
4084       if Is_Tagged_Type (Utyp)
4085         and then not Is_Class_Wide_Type (Utyp)
4086         and then (Nkind (Exp) = N_Type_Conversion
4087                     or else Nkind (Exp) = N_Unchecked_Type_Conversion
4088                     or else (Is_Entity_Name (Exp)
4089                                and then Ekind (Entity (Exp)) in Formal_Kind))
4090       then
4091          --  When the return type is limited, perform a check that the
4092          --  tag of the result is the same as the tag of the return type.
4093
4094          if Is_Limited_Type (R_Type) then
4095             Insert_Action (Exp,
4096               Make_Raise_Constraint_Error (Loc,
4097                 Condition =>
4098                   Make_Op_Ne (Loc,
4099                     Left_Opnd =>
4100                       Make_Selected_Component (Loc,
4101                         Prefix => Duplicate_Subexpr (Exp),
4102                         Selector_Name =>
4103                           New_Reference_To (First_Tag_Component (Utyp), Loc)),
4104                     Right_Opnd =>
4105                       Unchecked_Convert_To (RTE (RE_Tag),
4106                         New_Reference_To
4107                           (Node (First_Elmt
4108                                   (Access_Disp_Table (Base_Type (Utyp)))),
4109                            Loc))),
4110                 Reason => CE_Tag_Check_Failed));
4111
4112          --  If the result type is a specific nonlimited tagged type,
4113          --  then we have to ensure that the tag of the result is that
4114          --  of the result type. This is handled by making a copy of the
4115          --  expression in the case where it might have a different tag,
4116          --  namely when the expression is a conversion or a formal
4117          --  parameter. We create a new object of the result type and
4118          --  initialize it from the expression, which will implicitly
4119          --  force the tag to be set appropriately.
4120
4121          else
4122             declare
4123                Result_Id  : constant Entity_Id :=
4124                               Make_Defining_Identifier (Loc,
4125                                 Chars => New_Internal_Name ('R'));
4126                Result_Exp : constant Node_Id :=
4127                               New_Reference_To (Result_Id, Loc);
4128                Result_Obj : constant Node_Id :=
4129                               Make_Object_Declaration (Loc,
4130                                 Defining_Identifier => Result_Id,
4131                                 Object_Definition   =>
4132                                   New_Reference_To (R_Type, Loc),
4133                                 Constant_Present    => True,
4134                                 Expression          => Relocate_Node (Exp));
4135
4136             begin
4137                Set_Assignment_OK (Result_Obj);
4138                Insert_Action (Exp, Result_Obj);
4139
4140                Rewrite (Exp, Result_Exp);
4141                Analyze_And_Resolve (Exp, R_Type);
4142             end;
4143          end if;
4144
4145       --  Ada 2005 (AI-344): If the result type is class-wide, then insert
4146       --  a check that the level of the return expression's underlying type
4147       --  is not deeper than the level of the master enclosing the function.
4148       --  Always generate the check when the type of the return expression
4149       --  is class-wide, when it's a type conversion, or when it's a formal
4150       --  parameter. Otherwise, suppress the check in the case where the
4151       --  return expression has a specific type whose level is known not to
4152       --  be statically deeper than the function's result type.
4153
4154       elsif Ada_Version >= Ada_05
4155         and then Is_Class_Wide_Type (R_Type)
4156         and then not Scope_Suppress (Accessibility_Check)
4157         and then
4158           (Is_Class_Wide_Type (Etype (Exp))
4159             or else Nkind (Exp) = N_Type_Conversion
4160             or else Nkind (Exp) = N_Unchecked_Type_Conversion
4161             or else (Is_Entity_Name (Exp)
4162                        and then Ekind (Entity (Exp)) in Formal_Kind)
4163             or else Scope_Depth (Enclosing_Dynamic_Scope (Etype (Exp))) >
4164                       Scope_Depth (Enclosing_Dynamic_Scope (Scope_Id)))
4165       then
4166          Insert_Action (Exp,
4167            Make_Raise_Program_Error (Loc,
4168              Condition =>
4169                Make_Op_Gt (Loc,
4170                  Left_Opnd =>
4171                    Make_Function_Call (Loc,
4172                      Name =>
4173                        New_Reference_To
4174                          (RTE (RE_Get_Access_Level), Loc),
4175                      Parameter_Associations =>
4176                        New_List (Make_Attribute_Reference (Loc,
4177                                    Prefix         =>
4178                                       Duplicate_Subexpr (Exp),
4179                                    Attribute_Name =>
4180                                       Name_Tag))),
4181                  Right_Opnd =>
4182                    Make_Integer_Literal (Loc,
4183                      Scope_Depth (Enclosing_Dynamic_Scope (Scope_Id)))),
4184              Reason => PE_Accessibility_Check_Failed));
4185       end if;
4186    end Expand_Simple_Function_Return;
4187
4188    ------------------------------
4189    -- Make_Tag_Ctrl_Assignment --
4190    ------------------------------
4191
4192    function Make_Tag_Ctrl_Assignment (N : Node_Id) return List_Id is
4193       Loc : constant Source_Ptr := Sloc (N);
4194       L   : constant Node_Id    := Name (N);
4195       T   : constant Entity_Id  := Underlying_Type (Etype (L));
4196
4197       Ctrl_Act : constant Boolean := Controlled_Type (T)
4198                                        and then not No_Ctrl_Actions (N);
4199
4200       Save_Tag : constant Boolean := Is_Tagged_Type (T)
4201                                        and then not No_Ctrl_Actions (N)
4202                                        and then not Java_VM;
4203       --  Tags are not saved and restored when Java_VM because JVM tags
4204       --  are represented implicitly in objects.
4205
4206       Res       : List_Id;
4207       Tag_Tmp   : Entity_Id;
4208
4209    begin
4210       Res := New_List;
4211
4212       --  Finalize the target of the assignment when controlled.
4213       --  We have two exceptions here:
4214
4215       --   1. If we are in an init proc since it is an initialization
4216       --      more than an assignment
4217
4218       --   2. If the left-hand side is a temporary that was not initialized
4219       --      (or the parent part of a temporary since it is the case in
4220       --      extension aggregates). Such a temporary does not come from
4221       --      source. We must examine the original node for the prefix, because
4222       --      it may be a component of an entry formal, in which case it has
4223       --      been rewritten and does not appear to come from source either.
4224
4225       --  Case of init proc
4226
4227       if not Ctrl_Act then
4228          null;
4229
4230       --  The left hand side is an uninitialized temporary
4231
4232       elsif Nkind (L) = N_Type_Conversion
4233         and then Is_Entity_Name (Expression (L))
4234         and then No_Initialization (Parent (Entity (Expression (L))))
4235       then
4236          null;
4237       else
4238          Append_List_To (Res,
4239            Make_Final_Call (
4240              Ref         => Duplicate_Subexpr_No_Checks (L),
4241              Typ         => Etype (L),
4242              With_Detach => New_Reference_To (Standard_False, Loc)));
4243       end if;
4244
4245       --  Save the Tag in a local variable Tag_Tmp
4246
4247       if Save_Tag then
4248          Tag_Tmp :=
4249            Make_Defining_Identifier (Loc, New_Internal_Name ('A'));
4250
4251          Append_To (Res,
4252            Make_Object_Declaration (Loc,
4253              Defining_Identifier => Tag_Tmp,
4254              Object_Definition => New_Reference_To (RTE (RE_Tag), Loc),
4255              Expression =>
4256                Make_Selected_Component (Loc,
4257                  Prefix        => Duplicate_Subexpr_No_Checks (L),
4258                  Selector_Name => New_Reference_To (First_Tag_Component (T),
4259                                                     Loc))));
4260
4261       --  Otherwise Tag_Tmp not used
4262
4263       else
4264          Tag_Tmp := Empty;
4265       end if;
4266
4267       --  Processing for controlled types and types with controlled components
4268
4269       --  Variables of such types contain pointers used to chain them in
4270       --  finalization lists, in addition to user data. These pointers are
4271       --  specific to each object of the type, not to the value being assigned.
4272       --  Thus they need to be left intact during the assignment. We achieve
4273       --  this by constructing a Storage_Array subtype, and by overlaying
4274       --  objects of this type on the source and target of the assignment.
4275       --  The assignment is then rewritten to assignments of slices of these
4276       --  arrays, copying the user data, and leaving the pointers untouched.
4277
4278       if Ctrl_Act then
4279          Controlled_Actions : declare
4280             Prev_Ref : Node_Id;
4281             --  A reference to the Prev component of the record controller
4282
4283             First_After_Root : Node_Id := Empty;
4284             --  Index of first byte to be copied (used to skip
4285             --  Root_Controlled in controlled objects).
4286
4287             Last_Before_Hole : Node_Id := Empty;
4288             --  Index of last byte to be copied before outermost record
4289             --  controller data.
4290
4291             Hole_Length      : Node_Id := Empty;
4292             --  Length of record controller data (Prev and Next pointers)
4293
4294             First_After_Hole : Node_Id := Empty;
4295             --  Index of first byte to be copied after outermost record
4296             --  controller data.
4297
4298             Expr, Source_Size     : Node_Id;
4299             Source_Actual_Subtype : Entity_Id;
4300             --  Used for computation of the size of the data to be copied
4301
4302             Range_Type  : Entity_Id;
4303             Opaque_Type : Entity_Id;
4304
4305             function Build_Slice
4306               (Rec : Entity_Id;
4307                Lo  : Node_Id;
4308                Hi  : Node_Id) return Node_Id;
4309             --  Build and return a slice of an array of type S overlaid
4310             --  on object Rec, with bounds specified by Lo and Hi. If either
4311             --  bound is empty, a default of S'First (respectively S'Last)
4312             --  is used.
4313
4314             -----------------
4315             -- Build_Slice --
4316             -----------------
4317
4318             function Build_Slice
4319               (Rec : Node_Id;
4320                Lo  : Node_Id;
4321                Hi  : Node_Id) return Node_Id
4322             is
4323                Lo_Bound : Node_Id;
4324                Hi_Bound : Node_Id;
4325
4326                Opaque : constant Node_Id :=
4327                           Unchecked_Convert_To (Opaque_Type,
4328                             Make_Attribute_Reference (Loc,
4329                               Prefix         => Rec,
4330                               Attribute_Name => Name_Address));
4331                --  Access value designating an opaque storage array of
4332                --  type S overlaid on record Rec.
4333
4334             begin
4335                --  Compute slice bounds using S'First (1) and S'Last
4336                --  as default values when not specified by the caller.
4337
4338                if No (Lo) then
4339                   Lo_Bound := Make_Integer_Literal (Loc, 1);
4340                else
4341                   Lo_Bound := Lo;
4342                end if;
4343
4344                if No (Hi) then
4345                   Hi_Bound := Make_Attribute_Reference (Loc,
4346                     Prefix => New_Occurrence_Of (Range_Type, Loc),
4347                     Attribute_Name => Name_Last);
4348                else
4349                   Hi_Bound := Hi;
4350                end if;
4351
4352                return Make_Slice (Loc,
4353                  Prefix =>
4354                    Opaque,
4355                  Discrete_Range => Make_Range (Loc,
4356                    Lo_Bound, Hi_Bound));
4357             end Build_Slice;
4358
4359          --  Start of processing for Controlled_Actions
4360
4361          begin
4362             --  Create a constrained subtype of Storage_Array whose size
4363             --  corresponds to the value being assigned.
4364
4365             --  subtype G is Storage_Offset range
4366             --    1 .. (Expr'Size + Storage_Unit - 1) / Storage_Unit
4367
4368             Expr := Duplicate_Subexpr_No_Checks (Expression (N));
4369
4370             if Nkind (Expr) = N_Qualified_Expression then
4371                Expr := Expression (Expr);
4372             end if;
4373
4374             Source_Actual_Subtype := Etype (Expr);
4375
4376             if Has_Discriminants (Source_Actual_Subtype)
4377               and then not Is_Constrained (Source_Actual_Subtype)
4378             then
4379                Append_To (Res,
4380                  Build_Actual_Subtype (Source_Actual_Subtype, Expr));
4381                Source_Actual_Subtype := Defining_Identifier (Last (Res));
4382             end if;
4383
4384             Source_Size :=
4385               Make_Op_Add (Loc,
4386                 Left_Opnd =>
4387                   Make_Attribute_Reference (Loc,
4388                     Prefix =>
4389                       New_Occurrence_Of (Source_Actual_Subtype, Loc),
4390                     Attribute_Name =>
4391                       Name_Size),
4392                 Right_Opnd =>
4393                   Make_Integer_Literal (Loc,
4394                   System_Storage_Unit - 1));
4395             Source_Size :=
4396               Make_Op_Divide (Loc,
4397                 Left_Opnd => Source_Size,
4398                 Right_Opnd =>
4399                   Make_Integer_Literal (Loc,
4400                     Intval => System_Storage_Unit));
4401
4402             Range_Type :=
4403               Make_Defining_Identifier (Loc,
4404                 New_Internal_Name ('G'));
4405
4406             Append_To (Res,
4407               Make_Subtype_Declaration (Loc,
4408                 Defining_Identifier => Range_Type,
4409                 Subtype_Indication =>
4410                   Make_Subtype_Indication (Loc,
4411                     Subtype_Mark =>
4412                       New_Reference_To (RTE (RE_Storage_Offset), Loc),
4413                     Constraint   => Make_Range_Constraint (Loc,
4414                       Range_Expression =>
4415                         Make_Range (Loc,
4416                           Low_Bound  => Make_Integer_Literal (Loc, 1),
4417                           High_Bound => Source_Size)))));
4418
4419             --  subtype S is Storage_Array (G)
4420
4421             Append_To (Res,
4422               Make_Subtype_Declaration (Loc,
4423                 Defining_Identifier =>
4424                   Make_Defining_Identifier (Loc,
4425                     New_Internal_Name ('S')),
4426                 Subtype_Indication  =>
4427                   Make_Subtype_Indication (Loc,
4428                     Subtype_Mark =>
4429                       New_Reference_To (RTE (RE_Storage_Array), Loc),
4430                     Constraint =>
4431                       Make_Index_Or_Discriminant_Constraint (Loc,
4432                         Constraints =>
4433                           New_List (New_Reference_To (Range_Type, Loc))))));
4434
4435             --  type A is access S
4436
4437             Opaque_Type :=
4438               Make_Defining_Identifier (Loc,
4439                 Chars => New_Internal_Name ('A'));
4440
4441             Append_To (Res,
4442               Make_Full_Type_Declaration (Loc,
4443                 Defining_Identifier => Opaque_Type,
4444                 Type_Definition     =>
4445                   Make_Access_To_Object_Definition (Loc,
4446                     Subtype_Indication =>
4447                       New_Occurrence_Of (
4448                         Defining_Identifier (Last (Res)), Loc))));
4449
4450             --  Generate appropriate slice assignments
4451
4452             First_After_Root := Make_Integer_Literal (Loc, 1);
4453
4454             --  For the case of a controlled object, skip the
4455             --  Root_Controlled part.
4456
4457             if Is_Controlled (T) then
4458                First_After_Root :=
4459                  Make_Op_Add (Loc,
4460                    First_After_Root,
4461                    Make_Op_Divide (Loc,
4462                      Make_Attribute_Reference (Loc,
4463                        Prefix =>
4464                          New_Occurrence_Of (RTE (RE_Root_Controlled), Loc),
4465                        Attribute_Name => Name_Size),
4466                      Make_Integer_Literal (Loc, System_Storage_Unit)));
4467             end if;
4468
4469             --  For the case of a record with controlled components, skip
4470             --  the Prev and Next components of the record controller.
4471             --  These components constitute a 'hole' in the middle of the
4472             --  data to be copied.
4473
4474             if Has_Controlled_Component (T) then
4475                Prev_Ref :=
4476                  Make_Selected_Component (Loc,
4477                    Prefix =>
4478                      Make_Selected_Component (Loc,
4479                        Prefix => Duplicate_Subexpr_No_Checks (L),
4480                        Selector_Name =>
4481                          New_Reference_To (Controller_Component (T), Loc)),
4482                    Selector_Name =>  Make_Identifier (Loc, Name_Prev));
4483
4484                --  Last index before hole: determined by position of
4485                --  the _Controller.Prev component.
4486
4487                Last_Before_Hole :=
4488                  Make_Defining_Identifier (Loc,
4489                    New_Internal_Name ('L'));
4490
4491                Append_To (Res,
4492                  Make_Object_Declaration (Loc,
4493                    Defining_Identifier => Last_Before_Hole,
4494                    Object_Definition   => New_Occurrence_Of (
4495                      RTE (RE_Storage_Offset), Loc),
4496                    Constant_Present    => True,
4497                    Expression          => Make_Op_Add (Loc,
4498                        Make_Attribute_Reference (Loc,
4499                          Prefix => Prev_Ref,
4500                          Attribute_Name => Name_Position),
4501                        Make_Attribute_Reference (Loc,
4502                          Prefix => New_Copy_Tree (Prefix (Prev_Ref)),
4503                          Attribute_Name => Name_Position))));
4504
4505                --  Hole length: size of the Prev and Next components
4506
4507                Hole_Length :=
4508                  Make_Op_Multiply (Loc,
4509                    Left_Opnd  => Make_Integer_Literal (Loc, Uint_2),
4510                    Right_Opnd =>
4511                      Make_Op_Divide (Loc,
4512                        Left_Opnd =>
4513                          Make_Attribute_Reference (Loc,
4514                            Prefix         => New_Copy_Tree (Prev_Ref),
4515                            Attribute_Name => Name_Size),
4516                        Right_Opnd =>
4517                          Make_Integer_Literal (Loc,
4518                            Intval => System_Storage_Unit)));
4519
4520                --  First index after hole
4521
4522                First_After_Hole :=
4523                  Make_Defining_Identifier (Loc,
4524                    New_Internal_Name ('F'));
4525
4526                Append_To (Res,
4527                  Make_Object_Declaration (Loc,
4528                    Defining_Identifier => First_After_Hole,
4529                    Object_Definition   => New_Occurrence_Of (
4530                      RTE (RE_Storage_Offset), Loc),
4531                    Constant_Present    => True,
4532                    Expression          =>
4533                      Make_Op_Add (Loc,
4534                        Left_Opnd  =>
4535                          Make_Op_Add (Loc,
4536                            Left_Opnd  =>
4537                              New_Occurrence_Of (Last_Before_Hole, Loc),
4538                            Right_Opnd => Hole_Length),
4539                        Right_Opnd => Make_Integer_Literal (Loc, 1))));
4540
4541                Last_Before_Hole := New_Occurrence_Of (Last_Before_Hole, Loc);
4542                First_After_Hole := New_Occurrence_Of (First_After_Hole, Loc);
4543             end if;
4544
4545             --  Assign the first slice (possibly skipping Root_Controlled,
4546             --  up to the beginning of the record controller if present,
4547             --  up to the end of the object if not).
4548
4549             Append_To (Res, Make_Assignment_Statement (Loc,
4550               Name       => Build_Slice (
4551                 Rec => Duplicate_Subexpr_No_Checks (L),
4552                 Lo  => First_After_Root,
4553                 Hi  => Last_Before_Hole),
4554
4555               Expression => Build_Slice (
4556                 Rec => Expression (N),
4557                 Lo  => First_After_Root,
4558                 Hi  => New_Copy_Tree (Last_Before_Hole))));
4559
4560             if Present (First_After_Hole) then
4561
4562                --  If a record controller is present, copy the second slice,
4563                --  from right after the _Controller.Next component up to the
4564                --  end of the object.
4565
4566                Append_To (Res, Make_Assignment_Statement (Loc,
4567                  Name       => Build_Slice (
4568                    Rec => Duplicate_Subexpr_No_Checks (L),
4569                    Lo  => First_After_Hole,
4570                    Hi  => Empty),
4571                  Expression => Build_Slice (
4572                    Rec => Duplicate_Subexpr_No_Checks (Expression (N)),
4573                    Lo  => New_Copy_Tree (First_After_Hole),
4574                    Hi  => Empty)));
4575             end if;
4576          end Controlled_Actions;
4577
4578       else
4579          Append_To (Res, Relocate_Node (N));
4580       end if;
4581
4582       --  Restore the tag
4583
4584       if Save_Tag then
4585          Append_To (Res,
4586            Make_Assignment_Statement (Loc,
4587              Name =>
4588                Make_Selected_Component (Loc,
4589                  Prefix        => Duplicate_Subexpr_No_Checks (L),
4590                  Selector_Name => New_Reference_To (First_Tag_Component (T),
4591                                                     Loc)),
4592              Expression => New_Reference_To (Tag_Tmp, Loc)));
4593       end if;
4594
4595       --  Adjust the target after the assignment when controlled (not in the
4596       --  init proc since it is an initialization more than an assignment).
4597
4598       if Ctrl_Act then
4599          Append_List_To (Res,
4600            Make_Adjust_Call (
4601              Ref         => Duplicate_Subexpr_Move_Checks (L),
4602              Typ         => Etype (L),
4603              Flist_Ref   => New_Reference_To (RTE (RE_Global_Final_List), Loc),
4604              With_Attach => Make_Integer_Literal (Loc, 0)));
4605       end if;
4606
4607       return Res;
4608
4609    exception
4610       --  Could use comment here ???
4611
4612       when RE_Not_Available =>
4613          return Empty_List;
4614    end Make_Tag_Ctrl_Assignment;
4615
4616    -----------------------------
4617    -- No_Secondary_Stack_Case --
4618    -----------------------------
4619
4620    procedure No_Secondary_Stack_Case (N : Node_Id) is
4621       pragma Assert (False); --  DSP method no longer in use
4622
4623       Loc         : constant Source_Ptr := Sloc (N);
4624       Exp         : constant Node_Id    := Expression (N);
4625       T           : constant Entity_Id  := Etype (Exp);
4626       Scope_Id    : constant Entity_Id  :=
4627                       Return_Applies_To (Return_Statement_Entity (N));
4628       Return_Type : constant Entity_Id  := Etype (Scope_Id);
4629       Utyp        : constant Entity_Id  := Underlying_Type (Return_Type);
4630
4631       --  Here what we need to do is to always return by reference, since
4632       --  we will return with the stack pointer depressed. We may need to
4633       --  do a copy to a local temporary before doing this return.
4634
4635       Local_Copy_Required : Boolean := False;
4636       --  Set to True if a local copy is required
4637
4638       Copy_Ent : Entity_Id;
4639       --  Used for the target entity if a copy is required
4640
4641       Decl : Node_Id;
4642       --  Declaration used to create copy if needed
4643
4644       procedure Test_Copy_Required (Expr : Node_Id);
4645       --  Determines if Expr represents a return value for which a
4646       --  copy is required. More specifically, a copy is not required
4647       --  if Expr represents an object or component of an object that
4648       --  is either in the local subprogram frame, or is constant.
4649       --  If a copy is required, then Local_Copy_Required is set True.
4650
4651       ------------------------
4652       -- Test_Copy_Required --
4653       ------------------------
4654
4655       procedure Test_Copy_Required (Expr : Node_Id) is
4656          Ent : Entity_Id;
4657
4658       begin
4659          --  If component, test prefix (object containing component)
4660
4661          if Nkind (Expr) = N_Indexed_Component
4662               or else
4663             Nkind (Expr) = N_Selected_Component
4664          then
4665             Test_Copy_Required (Prefix (Expr));
4666             return;
4667
4668          --  See if we have an entity name
4669
4670          elsif Is_Entity_Name (Expr) then
4671             Ent := Entity (Expr);
4672
4673             --  Constant entity is always OK, no copy required
4674
4675             if Ekind (Ent) = E_Constant then
4676                return;
4677
4678             --  No copy required for local variable
4679
4680             elsif Ekind (Ent) = E_Variable
4681               and then Scope (Ent) = Current_Subprogram
4682             then
4683                return;
4684             end if;
4685          end if;
4686
4687          --  All other cases require a copy
4688
4689          Local_Copy_Required := True;
4690       end Test_Copy_Required;
4691
4692    --  Start of processing for No_Secondary_Stack_Case
4693
4694    begin
4695       --  No copy needed if result is from a function call.
4696       --  In this case the result is already being returned by
4697       --  reference with the stack pointer depressed.
4698
4699       --  To make up for a gcc 2.8.1 deficiency (???), we perform
4700       --  the copy for array types if the constrained status of the
4701       --  target type is different from that of the expression.
4702
4703       if Requires_Transient_Scope (T)
4704         and then
4705           (not Is_Array_Type (T)
4706              or else Is_Constrained (T) = Is_Constrained (Return_Type)
4707              or else Controlled_Type (T))
4708         and then Nkind (Exp) = N_Function_Call
4709       then
4710          Set_By_Ref (N);
4711
4712       --  We always need a local copy for a controlled type, since
4713       --  we are required to finalize the local value before return.
4714       --  The copy will automatically include the required finalize.
4715       --  Moreover, gigi cannot make this copy, since we need special
4716       --  processing to ensure proper behavior for finalization.
4717
4718       --  Note: the reason we are returning with a depressed stack
4719       --  pointer in the controlled case (even if the type involved
4720       --  is constrained) is that we must make a local copy to deal
4721       --  properly with the requirement that the local result be
4722       --  finalized.
4723
4724       elsif Controlled_Type (Utyp) then
4725          Copy_Ent :=
4726            Make_Defining_Identifier (Loc,
4727              Chars => New_Internal_Name ('R'));
4728
4729          --  Build declaration to do the copy, and insert it, setting
4730          --  Assignment_OK, because we may be copying a limited type.
4731          --  In addition we set the special flag to inhibit finalize
4732          --  attachment if this is a controlled type (since this attach
4733          --  must be done by the caller, otherwise if we attach it here
4734          --  we will finalize the returned result prematurely).
4735
4736          Decl :=
4737            Make_Object_Declaration (Loc,
4738              Defining_Identifier => Copy_Ent,
4739              Object_Definition   => New_Occurrence_Of (Return_Type, Loc),
4740              Expression          => Relocate_Node (Exp));
4741
4742          Set_Assignment_OK (Decl);
4743          Set_Delay_Finalize_Attach (Decl);
4744          Insert_Action (N, Decl);
4745
4746          --  Now the actual return uses the copied value
4747
4748          Rewrite (Exp, New_Occurrence_Of (Copy_Ent, Loc));
4749          Analyze_And_Resolve (Exp, Return_Type);
4750
4751          --  Since we have made the copy, gigi does not have to, so
4752          --  we set the By_Ref flag to prevent another copy being made.
4753
4754          Set_By_Ref (N);
4755
4756       --  Non-controlled cases
4757
4758       else
4759          Test_Copy_Required (Exp);
4760
4761          --  If a local copy is required, then gigi will make the
4762          --  copy, otherwise, we can return the result directly,
4763          --  so set By_Ref to suppress the gigi copy.
4764
4765          if not Local_Copy_Required then
4766             Set_By_Ref (N);
4767          end if;
4768       end if;
4769    end No_Secondary_Stack_Case;
4770
4771    ------------------------------------
4772    -- Possible_Bit_Aligned_Component --
4773    ------------------------------------
4774
4775    function Possible_Bit_Aligned_Component (N : Node_Id) return Boolean is
4776    begin
4777       case Nkind (N) is
4778
4779          --  Case of indexed component
4780
4781          when N_Indexed_Component =>
4782             declare
4783                P    : constant Node_Id   := Prefix (N);
4784                Ptyp : constant Entity_Id := Etype (P);
4785
4786             begin
4787                --  If we know the component size and it is less than 64, then
4788                --  we are definitely OK. The back end always does assignment
4789                --  of misaligned small objects correctly.
4790
4791                if Known_Static_Component_Size (Ptyp)
4792                  and then Component_Size (Ptyp) <= 64
4793                then
4794                   return False;
4795
4796                --  Otherwise, we need to test the prefix, to see if we are
4797                --  indexing from a possibly unaligned component.
4798
4799                else
4800                   return Possible_Bit_Aligned_Component (P);
4801                end if;
4802             end;
4803
4804          --  Case of selected component
4805
4806          when N_Selected_Component =>
4807             declare
4808                P    : constant Node_Id   := Prefix (N);
4809                Comp : constant Entity_Id := Entity (Selector_Name (N));
4810
4811             begin
4812                --  If there is no component clause, then we are in the clear
4813                --  since the back end will never misalign a large component
4814                --  unless it is forced to do so. In the clear means we need
4815                --  only the recursive test on the prefix.
4816
4817                if Component_May_Be_Bit_Aligned (Comp) then
4818                   return True;
4819                else
4820                   return Possible_Bit_Aligned_Component (P);
4821                end if;
4822             end;
4823
4824          --  If we have neither a record nor array component, it means that
4825          --  we have fallen off the top testing prefixes recursively, and
4826          --  we now have a stand alone object, where we don't have a problem
4827
4828          when others =>
4829             return False;
4830
4831       end case;
4832    end Possible_Bit_Aligned_Component;
4833
4834 end Exp_Ch5;