OSDN Git Service

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