OSDN Git Service

2011-08-29 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-2011, Free Software Foundation, Inc.         --
10 --                                                                          --
11 -- GNAT is free software;  you can  redistribute it  and/or modify it under --
12 -- terms of the  GNU General Public License as published  by the Free Soft- --
13 -- ware  Foundation;  either version 3,  or (at your option) any later ver- --
14 -- sion.  GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY;  without even the  implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License --
17 -- for  more details.  You should have  received  a copy of the GNU General --
18 -- Public License  distributed with GNAT; see file COPYING3.  If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license.          --
20 --                                                                          --
21 -- GNAT was originally developed  by the GNAT team at  New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc.      --
23 --                                                                          --
24 ------------------------------------------------------------------------------
25
26 with Atree;    use Atree;
27 with Checks;   use Checks;
28 with Debug;    use Debug;
29 with Einfo;    use Einfo;
30 with Exp_Aggr; use Exp_Aggr;
31 with Exp_Ch6;  use Exp_Ch6;
32 with Exp_Ch7;  use Exp_Ch7;
33 with Exp_Ch11; use Exp_Ch11;
34 with Exp_Dbug; use Exp_Dbug;
35 with Exp_Pakd; use Exp_Pakd;
36 with Exp_Tss;  use Exp_Tss;
37 with Exp_Util; use Exp_Util;
38 with Namet;    use Namet;
39 with Nlists;   use Nlists;
40 with Nmake;    use Nmake;
41 with Opt;      use Opt;
42 with Restrict; use Restrict;
43 with Rident;   use Rident;
44 with Rtsfind;  use Rtsfind;
45 with Sinfo;    use Sinfo;
46 with Sem;      use Sem;
47 with Sem_Aux;  use Sem_Aux;
48 with Sem_Ch3;  use Sem_Ch3;
49 with Sem_Ch8;  use Sem_Ch8;
50 with Sem_Ch13; use Sem_Ch13;
51 with Sem_Eval; use Sem_Eval;
52 with Sem_Res;  use Sem_Res;
53 with Sem_Util; use Sem_Util;
54 with Snames;   use Snames;
55 with Stand;    use Stand;
56 with Stringt;  use Stringt;
57 with Targparm; use Targparm;
58 with Tbuild;   use Tbuild;
59 with Validsw;  use Validsw;
60
61 package body Exp_Ch5 is
62
63    function Change_Of_Representation (N : Node_Id) return Boolean;
64    --  Determine if the right hand side of the assignment N is a type
65    --  conversion which requires a change of representation. Called
66    --  only for the array and record cases.
67
68    procedure Expand_Assign_Array (N : Node_Id; Rhs : Node_Id);
69    --  N is an assignment which assigns an array value. This routine process
70    --  the various special cases and checks required for such assignments,
71    --  including change of representation. Rhs is normally simply the right
72    --  hand side of the assignment, except that if the right hand side is
73    --  a type conversion or a qualified expression, then the Rhs is the
74    --  actual expression inside any such type conversions or qualifications.
75
76    function Expand_Assign_Array_Loop
77      (N      : Node_Id;
78       Larray : Entity_Id;
79       Rarray : Entity_Id;
80       L_Type : Entity_Id;
81       R_Type : Entity_Id;
82       Ndim   : Pos;
83       Rev    : Boolean) return Node_Id;
84    --  N is an assignment statement which assigns an array value. This routine
85    --  expands the assignment into a loop (or nested loops for the case of a
86    --  multi-dimensional array) to do the assignment component by component.
87    --  Larray and Rarray are the entities of the actual arrays on the left
88    --  hand and right hand sides. L_Type and R_Type are the types of these
89    --  arrays (which may not be the same, due to either sliding, or to a
90    --  change of representation case). Ndim is the number of dimensions and
91    --  the parameter Rev indicates if the loops run normally (Rev = False),
92    --  or reversed (Rev = True). The value returned is the constructed
93    --  loop statement. Auxiliary declarations are inserted before node N
94    --  using the standard Insert_Actions mechanism.
95
96    procedure Expand_Assign_Record (N : Node_Id);
97    --  N is an assignment of a non-tagged record value. This routine handles
98    --  the case where the assignment must be made component by component,
99    --  either because the target is not byte aligned, or there is a change
100    --  of representation, or when we have a tagged type with a representation
101    --  clause (this last case is required because holes in the tagged type
102    --  might be filled with components from child types).
103
104    procedure Expand_Iterator_Loop (N : Node_Id);
105    --  Expand loop over arrays and containers that uses the form "for X of C"
106    --  with an optional subtype mark, or "for Y in C".
107
108    procedure Expand_Predicated_Loop (N : Node_Id);
109    --  Expand for loop over predicated subtype
110
111    function Make_Tag_Ctrl_Assignment (N : Node_Id) return List_Id;
112    --  Generate the necessary code for controlled and tagged assignment, that
113    --  is to say, finalization of the target before, adjustment of the target
114    --  after and save and restore of the tag and finalization pointers which
115    --  are not 'part of the value' and must not be changed upon assignment. N
116    --  is the original Assignment node.
117
118    ------------------------------
119    -- Change_Of_Representation --
120    ------------------------------
121
122    function Change_Of_Representation (N : Node_Id) return Boolean is
123       Rhs : constant Node_Id := Expression (N);
124    begin
125       return
126         Nkind (Rhs) = N_Type_Conversion
127           and then
128             not Same_Representation (Etype (Rhs), Etype (Expression (Rhs)));
129    end Change_Of_Representation;
130
131    -------------------------
132    -- Expand_Assign_Array --
133    -------------------------
134
135    --  There are two issues here. First, do we let Gigi do a block move, or
136    --  do we expand out into a loop? Second, we need to set the two flags
137    --  Forwards_OK and Backwards_OK which show whether the block move (or
138    --  corresponding loops) can be legitimately done in a forwards (low to
139    --  high) or backwards (high to low) manner.
140
141    procedure Expand_Assign_Array (N : Node_Id; Rhs : Node_Id) is
142       Loc : constant Source_Ptr := Sloc (N);
143
144       Lhs : constant Node_Id := Name (N);
145
146       Act_Lhs : constant Node_Id := Get_Referenced_Object (Lhs);
147       Act_Rhs : Node_Id          := Get_Referenced_Object (Rhs);
148
149       L_Type : constant Entity_Id :=
150                  Underlying_Type (Get_Actual_Subtype (Act_Lhs));
151       R_Type : Entity_Id :=
152                  Underlying_Type (Get_Actual_Subtype (Act_Rhs));
153
154       L_Slice : constant Boolean := Nkind (Act_Lhs) = N_Slice;
155       R_Slice : constant Boolean := Nkind (Act_Rhs) = N_Slice;
156
157       Crep : constant Boolean := Change_Of_Representation (N);
158
159       Larray  : Node_Id;
160       Rarray  : Node_Id;
161
162       Ndim : constant Pos := Number_Dimensions (L_Type);
163
164       Loop_Required : Boolean := False;
165       --  This switch is set to True if the array move must be done using
166       --  an explicit front end generated loop.
167
168       procedure Apply_Dereference (Arg : Node_Id);
169       --  If the argument is an access to an array, and the assignment is
170       --  converted into a procedure call, apply explicit dereference.
171
172       function Has_Address_Clause (Exp : Node_Id) return Boolean;
173       --  Test if Exp is a reference to an array whose declaration has
174       --  an address clause, or it is a slice of such an array.
175
176       function Is_Formal_Array (Exp : Node_Id) return Boolean;
177       --  Test if Exp is a reference to an array which is either a formal
178       --  parameter or a slice of a formal parameter. These are the cases
179       --  where hidden aliasing can occur.
180
181       function Is_Non_Local_Array (Exp : Node_Id) return Boolean;
182       --  Determine if Exp is a reference to an array variable which is other
183       --  than an object defined in the current scope, or a slice of such
184       --  an object. Such objects can be aliased to parameters (unlike local
185       --  array references).
186
187       -----------------------
188       -- Apply_Dereference --
189       -----------------------
190
191       procedure Apply_Dereference (Arg : Node_Id) is
192          Typ : constant Entity_Id := Etype (Arg);
193       begin
194          if Is_Access_Type (Typ) then
195             Rewrite (Arg, Make_Explicit_Dereference (Loc,
196               Prefix => Relocate_Node (Arg)));
197             Analyze_And_Resolve (Arg, Designated_Type (Typ));
198          end if;
199       end Apply_Dereference;
200
201       ------------------------
202       -- Has_Address_Clause --
203       ------------------------
204
205       function Has_Address_Clause (Exp : Node_Id) return Boolean is
206       begin
207          return
208            (Is_Entity_Name (Exp) and then
209                               Present (Address_Clause (Entity (Exp))))
210              or else
211            (Nkind (Exp) = N_Slice and then Has_Address_Clause (Prefix (Exp)));
212       end Has_Address_Clause;
213
214       ---------------------
215       -- Is_Formal_Array --
216       ---------------------
217
218       function Is_Formal_Array (Exp : Node_Id) return Boolean is
219       begin
220          return
221            (Is_Entity_Name (Exp) and then Is_Formal (Entity (Exp)))
222              or else
223            (Nkind (Exp) = N_Slice and then Is_Formal_Array (Prefix (Exp)));
224       end Is_Formal_Array;
225
226       ------------------------
227       -- Is_Non_Local_Array --
228       ------------------------
229
230       function Is_Non_Local_Array (Exp : Node_Id) return Boolean is
231       begin
232          return (Is_Entity_Name (Exp)
233                    and then Scope (Entity (Exp)) /= Current_Scope)
234             or else (Nkind (Exp) = N_Slice
235                        and then Is_Non_Local_Array (Prefix (Exp)));
236       end Is_Non_Local_Array;
237
238       --  Determine if Lhs, Rhs are formal arrays or nonlocal arrays
239
240       Lhs_Formal : constant Boolean := Is_Formal_Array (Act_Lhs);
241       Rhs_Formal : constant Boolean := Is_Formal_Array (Act_Rhs);
242
243       Lhs_Non_Local_Var : constant Boolean := Is_Non_Local_Array (Act_Lhs);
244       Rhs_Non_Local_Var : constant Boolean := Is_Non_Local_Array (Act_Rhs);
245
246    --  Start of processing for Expand_Assign_Array
247
248    begin
249       --  Deal with length check. Note that the length check is done with
250       --  respect to the right hand side as given, not a possible underlying
251       --  renamed object, since this would generate incorrect extra checks.
252
253       Apply_Length_Check (Rhs, L_Type);
254
255       --  We start by assuming that the move can be done in either direction,
256       --  i.e. that the two sides are completely disjoint.
257
258       Set_Forwards_OK  (N, True);
259       Set_Backwards_OK (N, True);
260
261       --  Normally it is only the slice case that can lead to overlap, and
262       --  explicit checks for slices are made below. But there is one case
263       --  where the slice can be implicit and invisible to us: when we have a
264       --  one dimensional array, and either both operands are parameters, or
265       --  one is a parameter (which can be a slice passed by reference) and the
266       --  other is a non-local variable. In this case the parameter could be a
267       --  slice that overlaps with the other operand.
268
269       --  However, if the array subtype is a constrained first subtype in the
270       --  parameter case, then we don't have to worry about overlap, since
271       --  slice assignments aren't possible (other than for a slice denoting
272       --  the whole array).
273
274       --  Note: No overlap is possible if there is a change of representation,
275       --  so we can exclude this case.
276
277       if Ndim = 1
278         and then not Crep
279         and then
280            ((Lhs_Formal and Rhs_Formal)
281               or else
282             (Lhs_Formal and Rhs_Non_Local_Var)
283               or else
284             (Rhs_Formal and Lhs_Non_Local_Var))
285         and then
286            (not Is_Constrained (Etype (Lhs))
287              or else not Is_First_Subtype (Etype (Lhs)))
288
289          --  In the case of compiling for the Java or .NET Virtual Machine,
290          --  slices are always passed by making a copy, so we don't have to
291          --  worry about overlap. We also want to prevent generation of "<"
292          --  comparisons for array addresses, since that's a meaningless
293          --  operation on the VM.
294
295         and then VM_Target = No_VM
296       then
297          Set_Forwards_OK  (N, False);
298          Set_Backwards_OK (N, False);
299
300          --  Note: the bit-packed case is not worrisome here, since if we have
301          --  a slice passed as a parameter, it is always aligned on a byte
302          --  boundary, and if there are no explicit slices, the assignment
303          --  can be performed directly.
304       end if;
305
306       --  If either operand has an address clause clear Backwards_OK and
307       --  Forwards_OK, since we cannot tell if the operands overlap. We
308       --  exclude this treatment when Rhs is an aggregate, since we know
309       --  that overlap can't occur.
310
311       if (Has_Address_Clause (Lhs) and then Nkind (Rhs) /= N_Aggregate)
312         or else Has_Address_Clause (Rhs)
313       then
314          Set_Forwards_OK  (N, False);
315          Set_Backwards_OK (N, False);
316       end if;
317
318       --  We certainly must use a loop for change of representation and also
319       --  we use the operand of the conversion on the right hand side as the
320       --  effective right hand side (the component types must match in this
321       --  situation).
322
323       if Crep then
324          Act_Rhs := Get_Referenced_Object (Rhs);
325          R_Type  := Get_Actual_Subtype (Act_Rhs);
326          Loop_Required := True;
327
328       --  We require a loop if the left side is possibly bit unaligned
329
330       elsif Possible_Bit_Aligned_Component (Lhs)
331               or else
332             Possible_Bit_Aligned_Component (Rhs)
333       then
334          Loop_Required := True;
335
336       --  Arrays with controlled components are expanded into a loop to force
337       --  calls to Adjust at the component level.
338
339       elsif Has_Controlled_Component (L_Type) then
340          Loop_Required := True;
341
342          --  If object is atomic, we cannot tolerate a loop
343
344       elsif Is_Atomic_Object (Act_Lhs)
345               or else
346             Is_Atomic_Object (Act_Rhs)
347       then
348          return;
349
350       --  Loop is required if we have atomic components since we have to
351       --  be sure to do any accesses on an element by element basis.
352
353       elsif Has_Atomic_Components (L_Type)
354         or else Has_Atomic_Components (R_Type)
355         or else Is_Atomic (Component_Type (L_Type))
356         or else Is_Atomic (Component_Type (R_Type))
357       then
358          Loop_Required := True;
359
360       --  Case where no slice is involved
361
362       elsif not L_Slice and not R_Slice then
363
364          --  The following code deals with the case of unconstrained bit packed
365          --  arrays. The problem is that the template for such arrays contains
366          --  the bounds of the actual source level array, but the copy of an
367          --  entire array requires the bounds of the underlying array. It would
368          --  be nice if the back end could take care of this, but right now it
369          --  does not know how, so if we have such a type, then we expand out
370          --  into a loop, which is inefficient but works correctly. If we don't
371          --  do this, we get the wrong length computed for the array to be
372          --  moved. The two cases we need to worry about are:
373
374          --  Explicit dereference of an unconstrained packed array type as in
375          --  the following example:
376
377          --    procedure C52 is
378          --       type BITS is array(INTEGER range <>) of BOOLEAN;
379          --       pragma PACK(BITS);
380          --       type A is access BITS;
381          --       P1,P2 : A;
382          --    begin
383          --       P1 := new BITS (1 .. 65_535);
384          --       P2 := new BITS (1 .. 65_535);
385          --       P2.ALL := P1.ALL;
386          --    end C52;
387
388          --  A formal parameter reference with an unconstrained bit array type
389          --  is the other case we need to worry about (here we assume the same
390          --  BITS type declared above):
391
392          --    procedure Write_All (File : out BITS; Contents : BITS);
393          --    begin
394          --       File.Storage := Contents;
395          --    end Write_All;
396
397          --  We expand to a loop in either of these two cases
398
399          --  Question for future thought. Another potentially more efficient
400          --  approach would be to create the actual subtype, and then do an
401          --  unchecked conversion to this actual subtype ???
402
403          Check_Unconstrained_Bit_Packed_Array : declare
404
405             function Is_UBPA_Reference (Opnd : Node_Id) return Boolean;
406             --  Function to perform required test for the first case, above
407             --  (dereference of an unconstrained bit packed array).
408
409             -----------------------
410             -- Is_UBPA_Reference --
411             -----------------------
412
413             function Is_UBPA_Reference (Opnd : Node_Id) return Boolean is
414                Typ      : constant Entity_Id := Underlying_Type (Etype (Opnd));
415                P_Type   : Entity_Id;
416                Des_Type : Entity_Id;
417
418             begin
419                if Present (Packed_Array_Type (Typ))
420                  and then Is_Array_Type (Packed_Array_Type (Typ))
421                  and then not Is_Constrained (Packed_Array_Type (Typ))
422                then
423                   return True;
424
425                elsif Nkind (Opnd) = N_Explicit_Dereference then
426                   P_Type := Underlying_Type (Etype (Prefix (Opnd)));
427
428                   if not Is_Access_Type (P_Type) then
429                      return False;
430
431                   else
432                      Des_Type := Designated_Type (P_Type);
433                      return
434                        Is_Bit_Packed_Array (Des_Type)
435                          and then not Is_Constrained (Des_Type);
436                   end if;
437
438                else
439                   return False;
440                end if;
441             end Is_UBPA_Reference;
442
443          --  Start of processing for Check_Unconstrained_Bit_Packed_Array
444
445          begin
446             if Is_UBPA_Reference (Lhs)
447                  or else
448                Is_UBPA_Reference (Rhs)
449             then
450                Loop_Required := True;
451
452             --  Here if we do not have the case of a reference to a bit packed
453             --  unconstrained array case. In this case gigi can most certainly
454             --  handle the assignment if a forwards move is allowed.
455
456             --  (could it handle the backwards case also???)
457
458             elsif Forwards_OK (N) then
459                return;
460             end if;
461          end Check_Unconstrained_Bit_Packed_Array;
462
463       --  The back end can always handle the assignment if the right side is a
464       --  string literal (note that overlap is definitely impossible in this
465       --  case). If the type is packed, a string literal is always converted
466       --  into an aggregate, except in the case of a null slice, for which no
467       --  aggregate can be written. In that case, rewrite the assignment as a
468       --  null statement, a length check has already been emitted to verify
469       --  that the range of the left-hand side is empty.
470
471       --  Note that this code is not executed if we have an assignment of a
472       --  string literal to a non-bit aligned component of a record, a case
473       --  which cannot be handled by the backend.
474
475       elsif Nkind (Rhs) = N_String_Literal then
476          if String_Length (Strval (Rhs)) = 0
477            and then Is_Bit_Packed_Array (L_Type)
478          then
479             Rewrite (N, Make_Null_Statement (Loc));
480             Analyze (N);
481          end if;
482
483          return;
484
485       --  If either operand is bit packed, then we need a loop, since we can't
486       --  be sure that the slice is byte aligned. Similarly, if either operand
487       --  is a possibly unaligned slice, then we need a loop (since the back
488       --  end cannot handle unaligned slices).
489
490       elsif Is_Bit_Packed_Array (L_Type)
491         or else Is_Bit_Packed_Array (R_Type)
492         or else Is_Possibly_Unaligned_Slice (Lhs)
493         or else Is_Possibly_Unaligned_Slice (Rhs)
494       then
495          Loop_Required := True;
496
497       --  If we are not bit-packed, and we have only one slice, then no overlap
498       --  is possible except in the parameter case, so we can let the back end
499       --  handle things.
500
501       elsif not (L_Slice and R_Slice) then
502          if Forwards_OK (N) then
503             return;
504          end if;
505       end if;
506
507       --  If the right-hand side is a string literal, introduce a temporary for
508       --  it, for use in the generated loop that will follow.
509
510       if Nkind (Rhs) = N_String_Literal then
511          declare
512             Temp : constant Entity_Id := Make_Temporary (Loc, 'T', Rhs);
513             Decl : Node_Id;
514
515          begin
516             Decl :=
517               Make_Object_Declaration (Loc,
518                  Defining_Identifier => Temp,
519                  Object_Definition => New_Occurrence_Of (L_Type, Loc),
520                  Expression => Relocate_Node (Rhs));
521
522             Insert_Action (N, Decl);
523             Rewrite (Rhs, New_Occurrence_Of (Temp, Loc));
524             R_Type := Etype (Temp);
525          end;
526       end if;
527
528       --  Come here to complete the analysis
529
530       --    Loop_Required: Set to True if we know that a loop is required
531       --                   regardless of overlap considerations.
532
533       --    Forwards_OK:   Set to False if we already know that a forwards
534       --                   move is not safe, else set to True.
535
536       --    Backwards_OK:  Set to False if we already know that a backwards
537       --                   move is not safe, else set to True
538
539       --  Our task at this stage is to complete the overlap analysis, which can
540       --  result in possibly setting Forwards_OK or Backwards_OK to False, and
541       --  then generating the final code, either by deciding that it is OK
542       --  after all to let Gigi handle it, or by generating appropriate code
543       --  in the front end.
544
545       declare
546          L_Index_Typ : constant Node_Id := Etype (First_Index (L_Type));
547          R_Index_Typ : constant Node_Id := Etype (First_Index (R_Type));
548
549          Left_Lo  : constant Node_Id := Type_Low_Bound  (L_Index_Typ);
550          Left_Hi  : constant Node_Id := Type_High_Bound (L_Index_Typ);
551          Right_Lo : constant Node_Id := Type_Low_Bound  (R_Index_Typ);
552          Right_Hi : constant Node_Id := Type_High_Bound (R_Index_Typ);
553
554          Act_L_Array : Node_Id;
555          Act_R_Array : Node_Id;
556
557          Cleft_Lo  : Node_Id;
558          Cright_Lo : Node_Id;
559          Condition : Node_Id;
560
561          Cresult : Compare_Result;
562
563       begin
564          --  Get the expressions for the arrays. If we are dealing with a
565          --  private type, then convert to the underlying type. We can do
566          --  direct assignments to an array that is a private type, but we
567          --  cannot assign to elements of the array without this extra
568          --  unchecked conversion.
569
570          --  Note: We propagate Parent to the conversion nodes to generate
571          --  a well-formed subtree.
572
573          if Nkind (Act_Lhs) = N_Slice then
574             Larray := Prefix (Act_Lhs);
575          else
576             Larray := Act_Lhs;
577
578             if Is_Private_Type (Etype (Larray)) then
579                declare
580                   Par : constant Node_Id := Parent (Larray);
581                begin
582                   Larray :=
583                     Unchecked_Convert_To
584                       (Underlying_Type (Etype (Larray)), Larray);
585                   Set_Parent (Larray, Par);
586                end;
587             end if;
588          end if;
589
590          if Nkind (Act_Rhs) = N_Slice then
591             Rarray := Prefix (Act_Rhs);
592          else
593             Rarray := Act_Rhs;
594
595             if Is_Private_Type (Etype (Rarray)) then
596                declare
597                   Par : constant Node_Id := Parent (Rarray);
598                begin
599                   Rarray :=
600                     Unchecked_Convert_To
601                       (Underlying_Type (Etype (Rarray)), Rarray);
602                   Set_Parent (Rarray, Par);
603                end;
604             end if;
605          end if;
606
607          --  If both sides are slices, we must figure out whether it is safe
608          --  to do the move in one direction or the other. It is always safe
609          --  if there is a change of representation since obviously two arrays
610          --  with different representations cannot possibly overlap.
611
612          if (not Crep) and L_Slice and R_Slice then
613             Act_L_Array := Get_Referenced_Object (Prefix (Act_Lhs));
614             Act_R_Array := Get_Referenced_Object (Prefix (Act_Rhs));
615
616             --  If both left and right hand arrays are entity names, and refer
617             --  to different entities, then we know that the move is safe (the
618             --  two storage areas are completely disjoint).
619
620             if Is_Entity_Name (Act_L_Array)
621               and then Is_Entity_Name (Act_R_Array)
622               and then Entity (Act_L_Array) /= Entity (Act_R_Array)
623             then
624                null;
625
626             --  Otherwise, we assume the worst, which is that the two arrays
627             --  are the same array. There is no need to check if we know that
628             --  is the case, because if we don't know it, we still have to
629             --  assume it!
630
631             --  Generally if the same array is involved, then we have an
632             --  overlapping case. We will have to really assume the worst (i.e.
633             --  set neither of the OK flags) unless we can determine the lower
634             --  or upper bounds at compile time and compare them.
635
636             else
637                Cresult :=
638                  Compile_Time_Compare
639                    (Left_Lo, Right_Lo, Assume_Valid => True);
640
641                if Cresult = Unknown then
642                   Cresult :=
643                     Compile_Time_Compare
644                       (Left_Hi, Right_Hi, Assume_Valid => True);
645                end if;
646
647                case Cresult is
648                   when LT | LE | EQ => Set_Backwards_OK (N, False);
649                   when GT | GE      => Set_Forwards_OK  (N, False);
650                   when NE | Unknown => Set_Backwards_OK (N, False);
651                                        Set_Forwards_OK  (N, False);
652                end case;
653             end if;
654          end if;
655
656          --  If after that analysis Loop_Required is False, meaning that we
657          --  have not discovered some non-overlap reason for requiring a loop,
658          --  then the outcome depends on the capabilities of the back end.
659
660          if not Loop_Required then
661
662             --  The GCC back end can deal with all cases of overlap by falling
663             --  back to memmove if it cannot use a more efficient approach.
664
665             if VM_Target = No_VM and not AAMP_On_Target then
666                return;
667
668             --  Assume other back ends can handle it if Forwards_OK is set
669
670             elsif Forwards_OK (N) then
671                return;
672
673             --  If Forwards_OK is not set, the back end will need something
674             --  like memmove to handle the move. For now, this processing is
675             --  activated using the .s debug flag (-gnatd.s).
676
677             elsif Debug_Flag_Dot_S then
678                return;
679             end if;
680          end if;
681
682          --  At this stage we have to generate an explicit loop, and we have
683          --  the following cases:
684
685          --  Forwards_OK = True
686
687          --    Rnn : right_index := right_index'First;
688          --    for Lnn in left-index loop
689          --       left (Lnn) := right (Rnn);
690          --       Rnn := right_index'Succ (Rnn);
691          --    end loop;
692
693          --    Note: the above code MUST be analyzed with checks off, because
694          --    otherwise the Succ could overflow. But in any case this is more
695          --    efficient!
696
697          --  Forwards_OK = False, Backwards_OK = True
698
699          --    Rnn : right_index := right_index'Last;
700          --    for Lnn in reverse left-index loop
701          --       left (Lnn) := right (Rnn);
702          --       Rnn := right_index'Pred (Rnn);
703          --    end loop;
704
705          --    Note: the above code MUST be analyzed with checks off, because
706          --    otherwise the Pred could overflow. But in any case this is more
707          --    efficient!
708
709          --  Forwards_OK = Backwards_OK = False
710
711          --    This only happens if we have the same array on each side. It is
712          --    possible to create situations using overlays that violate this,
713          --    but we simply do not promise to get this "right" in this case.
714
715          --    There are two possible subcases. If the No_Implicit_Conditionals
716          --    restriction is set, then we generate the following code:
717
718          --      declare
719          --        T : constant <operand-type> := rhs;
720          --      begin
721          --        lhs := T;
722          --      end;
723
724          --    If implicit conditionals are permitted, then we generate:
725
726          --      if Left_Lo <= Right_Lo then
727          --         <code for Forwards_OK = True above>
728          --      else
729          --         <code for Backwards_OK = True above>
730          --      end if;
731
732          --  In order to detect possible aliasing, we examine the renamed
733          --  expression when the source or target is a renaming. However,
734          --  the renaming may be intended to capture an address that may be
735          --  affected by subsequent code, and therefore we must recover
736          --  the actual entity for the expansion that follows, not the
737          --  object it renames. In particular, if source or target designate
738          --  a portion of a dynamically allocated object, the pointer to it
739          --  may be reassigned but the renaming preserves the proper location.
740
741          if Is_Entity_Name (Rhs)
742            and then
743              Nkind (Parent (Entity (Rhs))) = N_Object_Renaming_Declaration
744            and then Nkind (Act_Rhs) = N_Slice
745          then
746             Rarray := Rhs;
747          end if;
748
749          if Is_Entity_Name (Lhs)
750            and then
751              Nkind (Parent (Entity (Lhs))) = N_Object_Renaming_Declaration
752            and then Nkind (Act_Lhs) = N_Slice
753          then
754             Larray := Lhs;
755          end if;
756
757          --  Cases where either Forwards_OK or Backwards_OK is true
758
759          if Forwards_OK (N) or else Backwards_OK (N) then
760             if Needs_Finalization (Component_Type (L_Type))
761               and then Base_Type (L_Type) = Base_Type (R_Type)
762               and then Ndim = 1
763               and then not No_Ctrl_Actions (N)
764             then
765                declare
766                   Proc    : constant Entity_Id :=
767                               TSS (Base_Type (L_Type), TSS_Slice_Assign);
768                   Actuals : List_Id;
769
770                begin
771                   Apply_Dereference (Larray);
772                   Apply_Dereference (Rarray);
773                   Actuals := New_List (
774                     Duplicate_Subexpr (Larray,   Name_Req => True),
775                     Duplicate_Subexpr (Rarray,   Name_Req => True),
776                     Duplicate_Subexpr (Left_Lo,  Name_Req => True),
777                     Duplicate_Subexpr (Left_Hi,  Name_Req => True),
778                     Duplicate_Subexpr (Right_Lo, Name_Req => True),
779                     Duplicate_Subexpr (Right_Hi, Name_Req => True));
780
781                   Append_To (Actuals,
782                     New_Occurrence_Of (
783                       Boolean_Literals (not Forwards_OK (N)), Loc));
784
785                   Rewrite (N,
786                     Make_Procedure_Call_Statement (Loc,
787                       Name => New_Reference_To (Proc, Loc),
788                       Parameter_Associations => Actuals));
789                end;
790
791             else
792                Rewrite (N,
793                  Expand_Assign_Array_Loop
794                    (N, Larray, Rarray, L_Type, R_Type, Ndim,
795                     Rev => not Forwards_OK (N)));
796             end if;
797
798          --  Case of both are false with No_Implicit_Conditionals
799
800          elsif Restriction_Active (No_Implicit_Conditionals) then
801             declare
802                   T : constant Entity_Id :=
803                         Make_Defining_Identifier (Loc, Chars => Name_T);
804
805             begin
806                Rewrite (N,
807                  Make_Block_Statement (Loc,
808                   Declarations => New_List (
809                     Make_Object_Declaration (Loc,
810                       Defining_Identifier => T,
811                       Constant_Present  => True,
812                       Object_Definition =>
813                         New_Occurrence_Of (Etype (Rhs), Loc),
814                       Expression        => Relocate_Node (Rhs))),
815
816                     Handled_Statement_Sequence =>
817                       Make_Handled_Sequence_Of_Statements (Loc,
818                         Statements => New_List (
819                           Make_Assignment_Statement (Loc,
820                             Name       => Relocate_Node (Lhs),
821                             Expression => New_Occurrence_Of (T, Loc))))));
822             end;
823
824          --  Case of both are false with implicit conditionals allowed
825
826          else
827             --  Before we generate this code, we must ensure that the left and
828             --  right side array types are defined. They may be itypes, and we
829             --  cannot let them be defined inside the if, since the first use
830             --  in the then may not be executed.
831
832             Ensure_Defined (L_Type, N);
833             Ensure_Defined (R_Type, N);
834
835             --  We normally compare addresses to find out which way round to
836             --  do the loop, since this is reliable, and handles the cases of
837             --  parameters, conversions etc. But we can't do that in the bit
838             --  packed case or the VM case, because addresses don't work there.
839
840             if not Is_Bit_Packed_Array (L_Type) and then VM_Target = No_VM then
841                Condition :=
842                  Make_Op_Le (Loc,
843                    Left_Opnd =>
844                      Unchecked_Convert_To (RTE (RE_Integer_Address),
845                        Make_Attribute_Reference (Loc,
846                          Prefix =>
847                            Make_Indexed_Component (Loc,
848                              Prefix =>
849                                Duplicate_Subexpr_Move_Checks (Larray, True),
850                              Expressions => New_List (
851                                Make_Attribute_Reference (Loc,
852                                  Prefix =>
853                                    New_Reference_To
854                                      (L_Index_Typ, Loc),
855                                  Attribute_Name => Name_First))),
856                          Attribute_Name => Name_Address)),
857
858                    Right_Opnd =>
859                      Unchecked_Convert_To (RTE (RE_Integer_Address),
860                        Make_Attribute_Reference (Loc,
861                          Prefix =>
862                            Make_Indexed_Component (Loc,
863                              Prefix =>
864                                Duplicate_Subexpr_Move_Checks (Rarray, True),
865                              Expressions => New_List (
866                                Make_Attribute_Reference (Loc,
867                                  Prefix =>
868                                    New_Reference_To
869                                      (R_Index_Typ, Loc),
870                                  Attribute_Name => Name_First))),
871                          Attribute_Name => Name_Address)));
872
873             --  For the bit packed and VM cases we use the bounds. That's OK,
874             --  because we don't have to worry about parameters, since they
875             --  cannot cause overlap. Perhaps we should worry about weird slice
876             --  conversions ???
877
878             else
879                --  Copy the bounds
880
881                Cleft_Lo  := New_Copy_Tree (Left_Lo);
882                Cright_Lo := New_Copy_Tree (Right_Lo);
883
884                --  If the types do not match we add an implicit conversion
885                --  here to ensure proper match
886
887                if Etype (Left_Lo) /= Etype (Right_Lo) then
888                   Cright_Lo :=
889                     Unchecked_Convert_To (Etype (Left_Lo), Cright_Lo);
890                end if;
891
892                --  Reset the Analyzed flag, because the bounds of the index
893                --  type itself may be universal, and must must be reanalyzed
894                --  to acquire the proper type for the back end.
895
896                Set_Analyzed (Cleft_Lo, False);
897                Set_Analyzed (Cright_Lo, False);
898
899                Condition :=
900                  Make_Op_Le (Loc,
901                    Left_Opnd  => Cleft_Lo,
902                    Right_Opnd => Cright_Lo);
903             end if;
904
905             if Needs_Finalization (Component_Type (L_Type))
906               and then Base_Type (L_Type) = Base_Type (R_Type)
907               and then Ndim = 1
908               and then not No_Ctrl_Actions (N)
909             then
910
911                --  Call TSS procedure for array assignment, passing the
912                --  explicit bounds of right and left hand sides.
913
914                declare
915                   Proc    : constant Entity_Id :=
916                               TSS (Base_Type (L_Type), TSS_Slice_Assign);
917                   Actuals : List_Id;
918
919                begin
920                   Apply_Dereference (Larray);
921                   Apply_Dereference (Rarray);
922                   Actuals := New_List (
923                     Duplicate_Subexpr (Larray,   Name_Req => True),
924                     Duplicate_Subexpr (Rarray,   Name_Req => True),
925                     Duplicate_Subexpr (Left_Lo,  Name_Req => True),
926                     Duplicate_Subexpr (Left_Hi,  Name_Req => True),
927                     Duplicate_Subexpr (Right_Lo, Name_Req => True),
928                     Duplicate_Subexpr (Right_Hi, Name_Req => True));
929
930                   Append_To (Actuals,
931                      Make_Op_Not (Loc,
932                        Right_Opnd => Condition));
933
934                   Rewrite (N,
935                     Make_Procedure_Call_Statement (Loc,
936                       Name => New_Reference_To (Proc, Loc),
937                       Parameter_Associations => Actuals));
938                end;
939
940             else
941                Rewrite (N,
942                  Make_Implicit_If_Statement (N,
943                    Condition => Condition,
944
945                    Then_Statements => New_List (
946                      Expand_Assign_Array_Loop
947                       (N, Larray, Rarray, L_Type, R_Type, Ndim,
948                        Rev => False)),
949
950                    Else_Statements => New_List (
951                      Expand_Assign_Array_Loop
952                       (N, Larray, Rarray, L_Type, R_Type, Ndim,
953                        Rev => True))));
954             end if;
955          end if;
956
957          Analyze (N, Suppress => All_Checks);
958       end;
959
960    exception
961       when RE_Not_Available =>
962          return;
963    end Expand_Assign_Array;
964
965    ------------------------------
966    -- Expand_Assign_Array_Loop --
967    ------------------------------
968
969    --  The following is an example of the loop generated for the case of a
970    --  two-dimensional array:
971
972    --    declare
973    --       R2b : Tm1X1 := 1;
974    --    begin
975    --       for L1b in 1 .. 100 loop
976    --          declare
977    --             R4b : Tm1X2 := 1;
978    --          begin
979    --             for L3b in 1 .. 100 loop
980    --                vm1 (L1b, L3b) := vm2 (R2b, R4b);
981    --                R4b := Tm1X2'succ(R4b);
982    --             end loop;
983    --          end;
984    --          R2b := Tm1X1'succ(R2b);
985    --       end loop;
986    --    end;
987
988    --  Here Rev is False, and Tm1Xn are the subscript types for the right hand
989    --  side. The declarations of R2b and R4b are inserted before the original
990    --  assignment statement.
991
992    function Expand_Assign_Array_Loop
993      (N      : Node_Id;
994       Larray : Entity_Id;
995       Rarray : Entity_Id;
996       L_Type : Entity_Id;
997       R_Type : Entity_Id;
998       Ndim   : Pos;
999       Rev    : Boolean) return Node_Id
1000    is
1001       Loc  : constant Source_Ptr := Sloc (N);
1002
1003       Lnn : array (1 .. Ndim) of Entity_Id;
1004       Rnn : array (1 .. Ndim) of Entity_Id;
1005       --  Entities used as subscripts on left and right sides
1006
1007       L_Index_Type : array (1 .. Ndim) of Entity_Id;
1008       R_Index_Type : array (1 .. Ndim) of Entity_Id;
1009       --  Left and right index types
1010
1011       Assign : Node_Id;
1012
1013       F_Or_L : Name_Id;
1014       S_Or_P : Name_Id;
1015
1016       function Build_Step (J : Nat) return Node_Id;
1017       --  The increment step for the index of the right-hand side is written
1018       --  as an attribute reference (Succ or Pred). This function returns
1019       --  the corresponding node, which is placed at the end of the loop body.
1020
1021       ----------------
1022       -- Build_Step --
1023       ----------------
1024
1025       function Build_Step (J : Nat) return Node_Id is
1026          Step : Node_Id;
1027          Lim  : Name_Id;
1028
1029       begin
1030          if Rev then
1031             Lim := Name_First;
1032          else
1033             Lim := Name_Last;
1034          end if;
1035
1036          Step :=
1037             Make_Assignment_Statement (Loc,
1038                Name => New_Occurrence_Of (Rnn (J), Loc),
1039                Expression =>
1040                  Make_Attribute_Reference (Loc,
1041                    Prefix =>
1042                      New_Occurrence_Of (R_Index_Type (J), Loc),
1043                    Attribute_Name => S_Or_P,
1044                    Expressions => New_List (
1045                      New_Occurrence_Of (Rnn (J), Loc))));
1046
1047       --  Note that on the last iteration of the loop, the index is increased
1048       --  (or decreased) past the corresponding bound. This is consistent with
1049       --  the C semantics of the back-end, where such an off-by-one value on a
1050       --  dead index variable is OK. However, in CodePeer mode this leads to
1051       --  spurious warnings, and thus we place a guard around the attribute
1052       --  reference. For obvious reasons we only do this for CodePeer.
1053
1054          if CodePeer_Mode then
1055             Step :=
1056               Make_If_Statement (Loc,
1057                  Condition =>
1058                     Make_Op_Ne (Loc,
1059                        Left_Opnd  => New_Occurrence_Of (Lnn (J), Loc),
1060                        Right_Opnd =>
1061                          Make_Attribute_Reference (Loc,
1062                            Prefix => New_Occurrence_Of (L_Index_Type (J), Loc),
1063                            Attribute_Name => Lim)),
1064                  Then_Statements => New_List (Step));
1065          end if;
1066
1067          return Step;
1068       end Build_Step;
1069
1070    --  Start of processing for Expand_Assign_Array_Loop
1071
1072    begin
1073       if Rev then
1074          F_Or_L := Name_Last;
1075          S_Or_P := Name_Pred;
1076       else
1077          F_Or_L := Name_First;
1078          S_Or_P := Name_Succ;
1079       end if;
1080
1081       --  Setup index types and subscript entities
1082
1083       declare
1084          L_Index : Node_Id;
1085          R_Index : Node_Id;
1086
1087       begin
1088          L_Index := First_Index (L_Type);
1089          R_Index := First_Index (R_Type);
1090
1091          for J in 1 .. Ndim loop
1092             Lnn (J) := Make_Temporary (Loc, 'L');
1093             Rnn (J) := Make_Temporary (Loc, 'R');
1094
1095             L_Index_Type (J) := Etype (L_Index);
1096             R_Index_Type (J) := Etype (R_Index);
1097
1098             Next_Index (L_Index);
1099             Next_Index (R_Index);
1100          end loop;
1101       end;
1102
1103       --  Now construct the assignment statement
1104
1105       declare
1106          ExprL : constant List_Id := New_List;
1107          ExprR : constant List_Id := New_List;
1108
1109       begin
1110          for J in 1 .. Ndim loop
1111             Append_To (ExprL, New_Occurrence_Of (Lnn (J), Loc));
1112             Append_To (ExprR, New_Occurrence_Of (Rnn (J), Loc));
1113          end loop;
1114
1115          Assign :=
1116            Make_Assignment_Statement (Loc,
1117              Name =>
1118                Make_Indexed_Component (Loc,
1119                  Prefix      => Duplicate_Subexpr (Larray, Name_Req => True),
1120                  Expressions => ExprL),
1121              Expression =>
1122                Make_Indexed_Component (Loc,
1123                  Prefix      => Duplicate_Subexpr (Rarray, Name_Req => True),
1124                  Expressions => ExprR));
1125
1126          --  We set assignment OK, since there are some cases, e.g. in object
1127          --  declarations, where we are actually assigning into a constant.
1128          --  If there really is an illegality, it was caught long before now,
1129          --  and was flagged when the original assignment was analyzed.
1130
1131          Set_Assignment_OK (Name (Assign));
1132
1133          --  Propagate the No_Ctrl_Actions flag to individual assignments
1134
1135          Set_No_Ctrl_Actions (Assign, No_Ctrl_Actions (N));
1136       end;
1137
1138       --  Now construct the loop from the inside out, with the last subscript
1139       --  varying most rapidly. Note that Assign is first the raw assignment
1140       --  statement, and then subsequently the loop that wraps it up.
1141
1142       for J in reverse 1 .. Ndim loop
1143          Assign :=
1144            Make_Block_Statement (Loc,
1145              Declarations => New_List (
1146               Make_Object_Declaration (Loc,
1147                 Defining_Identifier => Rnn (J),
1148                 Object_Definition =>
1149                   New_Occurrence_Of (R_Index_Type (J), Loc),
1150                 Expression =>
1151                   Make_Attribute_Reference (Loc,
1152                     Prefix => New_Occurrence_Of (R_Index_Type (J), Loc),
1153                     Attribute_Name => F_Or_L))),
1154
1155            Handled_Statement_Sequence =>
1156              Make_Handled_Sequence_Of_Statements (Loc,
1157                Statements => New_List (
1158                  Make_Implicit_Loop_Statement (N,
1159                    Iteration_Scheme =>
1160                      Make_Iteration_Scheme (Loc,
1161                        Loop_Parameter_Specification =>
1162                          Make_Loop_Parameter_Specification (Loc,
1163                            Defining_Identifier => Lnn (J),
1164                            Reverse_Present => Rev,
1165                            Discrete_Subtype_Definition =>
1166                              New_Reference_To (L_Index_Type (J), Loc))),
1167
1168                    Statements => New_List (Assign, Build_Step (J))))));
1169       end loop;
1170
1171       return Assign;
1172    end Expand_Assign_Array_Loop;
1173
1174    --------------------------
1175    -- Expand_Assign_Record --
1176    --------------------------
1177
1178    procedure Expand_Assign_Record (N : Node_Id) is
1179       Lhs   : constant Node_Id    := Name (N);
1180       Rhs   : Node_Id             := Expression (N);
1181       L_Typ : constant Entity_Id  := Base_Type (Etype (Lhs));
1182
1183    begin
1184       --  If change of representation, then extract the real right hand side
1185       --  from the type conversion, and proceed with component-wise assignment,
1186       --  since the two types are not the same as far as the back end is
1187       --  concerned.
1188
1189       if Change_Of_Representation (N) then
1190          Rhs := Expression (Rhs);
1191
1192       --  If this may be a case of a large bit aligned component, then proceed
1193       --  with component-wise assignment, to avoid possible clobbering of other
1194       --  components sharing bits in the first or last byte of the component to
1195       --  be assigned.
1196
1197       elsif Possible_Bit_Aligned_Component (Lhs)
1198               or
1199             Possible_Bit_Aligned_Component (Rhs)
1200       then
1201          null;
1202
1203       --  If we have a tagged type that has a complete record representation
1204       --  clause, we must do we must do component-wise assignments, since child
1205       --  types may have used gaps for their components, and we might be
1206       --  dealing with a view conversion.
1207
1208       elsif Is_Fully_Repped_Tagged_Type (L_Typ) then
1209          null;
1210
1211       --  If neither condition met, then nothing special to do, the back end
1212       --  can handle assignment of the entire component as a single entity.
1213
1214       else
1215          return;
1216       end if;
1217
1218       --  At this stage we know that we must do a component wise assignment
1219
1220       declare
1221          Loc   : constant Source_Ptr := Sloc (N);
1222          R_Typ : constant Entity_Id  := Base_Type (Etype (Rhs));
1223          Decl  : constant Node_Id    := Declaration_Node (R_Typ);
1224          RDef  : Node_Id;
1225          F     : Entity_Id;
1226
1227          function Find_Component
1228            (Typ  : Entity_Id;
1229             Comp : Entity_Id) return Entity_Id;
1230          --  Find the component with the given name in the underlying record
1231          --  declaration for Typ. We need to use the actual entity because the
1232          --  type may be private and resolution by identifier alone would fail.
1233
1234          function Make_Component_List_Assign
1235            (CL  : Node_Id;
1236             U_U : Boolean := False) return List_Id;
1237          --  Returns a sequence of statements to assign the components that
1238          --  are referenced in the given component list. The flag U_U is
1239          --  used to force the usage of the inferred value of the variant
1240          --  part expression as the switch for the generated case statement.
1241
1242          function Make_Field_Assign
1243            (C   : Entity_Id;
1244             U_U : Boolean := False) return Node_Id;
1245          --  Given C, the entity for a discriminant or component, build an
1246          --  assignment for the corresponding field values. The flag U_U
1247          --  signals the presence of an Unchecked_Union and forces the usage
1248          --  of the inferred discriminant value of C as the right hand side
1249          --  of the assignment.
1250
1251          function Make_Field_Assigns (CI : List_Id) return List_Id;
1252          --  Given CI, a component items list, construct series of statements
1253          --  for fieldwise assignment of the corresponding components.
1254
1255          --------------------
1256          -- Find_Component --
1257          --------------------
1258
1259          function Find_Component
1260            (Typ  : Entity_Id;
1261             Comp : Entity_Id) return Entity_Id
1262          is
1263             Utyp : constant Entity_Id := Underlying_Type (Typ);
1264             C    : Entity_Id;
1265
1266          begin
1267             C := First_Entity (Utyp);
1268             while Present (C) loop
1269                if Chars (C) = Chars (Comp) then
1270                   return C;
1271                end if;
1272
1273                Next_Entity (C);
1274             end loop;
1275
1276             raise Program_Error;
1277          end Find_Component;
1278
1279          --------------------------------
1280          -- Make_Component_List_Assign --
1281          --------------------------------
1282
1283          function Make_Component_List_Assign
1284            (CL  : Node_Id;
1285             U_U : Boolean := False) return List_Id
1286          is
1287             CI : constant List_Id := Component_Items (CL);
1288             VP : constant Node_Id := Variant_Part (CL);
1289
1290             Alts   : List_Id;
1291             DC     : Node_Id;
1292             DCH    : List_Id;
1293             Expr   : Node_Id;
1294             Result : List_Id;
1295             V      : Node_Id;
1296
1297          begin
1298             Result := Make_Field_Assigns (CI);
1299
1300             if Present (VP) then
1301                V := First_Non_Pragma (Variants (VP));
1302                Alts := New_List;
1303                while Present (V) loop
1304                   DCH := New_List;
1305                   DC := First (Discrete_Choices (V));
1306                   while Present (DC) loop
1307                      Append_To (DCH, New_Copy_Tree (DC));
1308                      Next (DC);
1309                   end loop;
1310
1311                   Append_To (Alts,
1312                     Make_Case_Statement_Alternative (Loc,
1313                       Discrete_Choices => DCH,
1314                       Statements =>
1315                         Make_Component_List_Assign (Component_List (V))));
1316                   Next_Non_Pragma (V);
1317                end loop;
1318
1319                --  If we have an Unchecked_Union, use the value of the inferred
1320                --  discriminant of the variant part expression as the switch
1321                --  for the case statement. The case statement may later be
1322                --  folded.
1323
1324                if U_U then
1325                   Expr :=
1326                     New_Copy (Get_Discriminant_Value (
1327                       Entity (Name (VP)),
1328                       Etype (Rhs),
1329                       Discriminant_Constraint (Etype (Rhs))));
1330                else
1331                   Expr :=
1332                     Make_Selected_Component (Loc,
1333                       Prefix        => Duplicate_Subexpr (Rhs),
1334                       Selector_Name =>
1335                         Make_Identifier (Loc, Chars (Name (VP))));
1336                end if;
1337
1338                Append_To (Result,
1339                  Make_Case_Statement (Loc,
1340                    Expression => Expr,
1341                    Alternatives => Alts));
1342             end if;
1343
1344             return Result;
1345          end Make_Component_List_Assign;
1346
1347          -----------------------
1348          -- Make_Field_Assign --
1349          -----------------------
1350
1351          function Make_Field_Assign
1352            (C   : Entity_Id;
1353             U_U : Boolean := False) return Node_Id
1354          is
1355             A    : Node_Id;
1356             Expr : Node_Id;
1357
1358          begin
1359             --  In the case of an Unchecked_Union, use the discriminant
1360             --  constraint value as on the right hand side of the assignment.
1361
1362             if U_U then
1363                Expr :=
1364                  New_Copy (Get_Discriminant_Value (C,
1365                    Etype (Rhs),
1366                    Discriminant_Constraint (Etype (Rhs))));
1367             else
1368                Expr :=
1369                  Make_Selected_Component (Loc,
1370                    Prefix        => Duplicate_Subexpr (Rhs),
1371                    Selector_Name => New_Occurrence_Of (C, Loc));
1372             end if;
1373
1374             A :=
1375               Make_Assignment_Statement (Loc,
1376                 Name =>
1377                   Make_Selected_Component (Loc,
1378                     Prefix        => Duplicate_Subexpr (Lhs),
1379                     Selector_Name =>
1380                       New_Occurrence_Of (Find_Component (L_Typ, C), Loc)),
1381                 Expression => Expr);
1382
1383             --  Set Assignment_OK, so discriminants can be assigned
1384
1385             Set_Assignment_OK (Name (A), True);
1386
1387             if Componentwise_Assignment (N)
1388               and then Nkind (Name (A)) = N_Selected_Component
1389               and then Chars (Selector_Name (Name (A))) = Name_uParent
1390             then
1391                Set_Componentwise_Assignment (A);
1392             end if;
1393
1394             return A;
1395          end Make_Field_Assign;
1396
1397          ------------------------
1398          -- Make_Field_Assigns --
1399          ------------------------
1400
1401          function Make_Field_Assigns (CI : List_Id) return List_Id is
1402             Item   : Node_Id;
1403             Result : List_Id;
1404
1405          begin
1406             Item := First (CI);
1407             Result := New_List;
1408
1409             while Present (Item) loop
1410
1411                --  Look for components, but exclude _tag field assignment if
1412                --  the special Componentwise_Assignment flag is set.
1413
1414                if Nkind (Item) = N_Component_Declaration
1415                  and then not (Is_Tag (Defining_Identifier (Item))
1416                                  and then Componentwise_Assignment (N))
1417                then
1418                   Append_To
1419                     (Result, Make_Field_Assign (Defining_Identifier (Item)));
1420                end if;
1421
1422                Next (Item);
1423             end loop;
1424
1425             return Result;
1426          end Make_Field_Assigns;
1427
1428       --  Start of processing for Expand_Assign_Record
1429
1430       begin
1431          --  Note that we use the base types for this processing. This results
1432          --  in some extra work in the constrained case, but the change of
1433          --  representation case is so unusual that it is not worth the effort.
1434
1435          --  First copy the discriminants. This is done unconditionally. It
1436          --  is required in the unconstrained left side case, and also in the
1437          --  case where this assignment was constructed during the expansion
1438          --  of a type conversion (since initialization of discriminants is
1439          --  suppressed in this case). It is unnecessary but harmless in
1440          --  other cases.
1441
1442          if Has_Discriminants (L_Typ) then
1443             F := First_Discriminant (R_Typ);
1444             while Present (F) loop
1445
1446                --  If we are expanding the initialization of a derived record
1447                --  that constrains or renames discriminants of the parent, we
1448                --  must use the corresponding discriminant in the parent.
1449
1450                declare
1451                   CF : Entity_Id;
1452
1453                begin
1454                   if Inside_Init_Proc
1455                     and then Present (Corresponding_Discriminant (F))
1456                   then
1457                      CF := Corresponding_Discriminant (F);
1458                   else
1459                      CF := F;
1460                   end if;
1461
1462                   if Is_Unchecked_Union (Base_Type (R_Typ)) then
1463                      Insert_Action (N, Make_Field_Assign (CF, True));
1464                   else
1465                      Insert_Action (N, Make_Field_Assign (CF));
1466                   end if;
1467
1468                   Next_Discriminant (F);
1469                end;
1470             end loop;
1471          end if;
1472
1473          --  We know the underlying type is a record, but its current view
1474          --  may be private. We must retrieve the usable record declaration.
1475
1476          if Nkind_In (Decl, N_Private_Type_Declaration,
1477                             N_Private_Extension_Declaration)
1478            and then Present (Full_View (R_Typ))
1479          then
1480             RDef := Type_Definition (Declaration_Node (Full_View (R_Typ)));
1481          else
1482             RDef := Type_Definition (Decl);
1483          end if;
1484
1485          if Nkind (RDef) = N_Derived_Type_Definition then
1486             RDef := Record_Extension_Part (RDef);
1487          end if;
1488
1489          if Nkind (RDef) = N_Record_Definition
1490            and then Present (Component_List (RDef))
1491          then
1492             if Is_Unchecked_Union (R_Typ) then
1493                Insert_Actions (N,
1494                  Make_Component_List_Assign (Component_List (RDef), True));
1495             else
1496                Insert_Actions
1497                  (N, Make_Component_List_Assign (Component_List (RDef)));
1498             end if;
1499
1500             Rewrite (N, Make_Null_Statement (Loc));
1501          end if;
1502       end;
1503    end Expand_Assign_Record;
1504
1505    -----------------------------------
1506    -- Expand_N_Assignment_Statement --
1507    -----------------------------------
1508
1509    --  This procedure implements various cases where an assignment statement
1510    --  cannot just be passed on to the back end in untransformed state.
1511
1512    procedure Expand_N_Assignment_Statement (N : Node_Id) is
1513       Loc  : constant Source_Ptr := Sloc (N);
1514       Crep : constant Boolean    := Change_Of_Representation (N);
1515       Lhs  : constant Node_Id    := Name (N);
1516       Rhs  : constant Node_Id    := Expression (N);
1517       Typ  : constant Entity_Id  := Underlying_Type (Etype (Lhs));
1518       Exp  : Node_Id;
1519
1520    begin
1521       --  Special case to check right away, if the Componentwise_Assignment
1522       --  flag is set, this is a reanalysis from the expansion of the primitive
1523       --  assignment procedure for a tagged type, and all we need to do is to
1524       --  expand to assignment of components, because otherwise, we would get
1525       --  infinite recursion (since this looks like a tagged assignment which
1526       --  would normally try to *call* the primitive assignment procedure).
1527
1528       if Componentwise_Assignment (N) then
1529          Expand_Assign_Record (N);
1530          return;
1531       end if;
1532
1533       --  Defend against invalid subscripts on left side if we are in standard
1534       --  validity checking mode. No need to do this if we are checking all
1535       --  subscripts.
1536
1537       --  Note that we do this right away, because there are some early return
1538       --  paths in this procedure, and this is required on all paths.
1539
1540       if Validity_Checks_On
1541         and then Validity_Check_Default
1542         and then not Validity_Check_Subscripts
1543       then
1544          Check_Valid_Lvalue_Subscripts (Lhs);
1545       end if;
1546
1547       --  Ada 2005 (AI-327): Handle assignment to priority of protected object
1548
1549       --  Rewrite an assignment to X'Priority into a run-time call
1550
1551       --   For example:         X'Priority := New_Prio_Expr;
1552       --   ...is expanded into  Set_Ceiling (X._Object, New_Prio_Expr);
1553
1554       --  Note that although X'Priority is notionally an object, it is quite
1555       --  deliberately not defined as an aliased object in the RM. This means
1556       --  that it works fine to rewrite it as a call, without having to worry
1557       --  about complications that would other arise from X'Priority'Access,
1558       --  which is illegal, because of the lack of aliasing.
1559
1560       if Ada_Version >= Ada_2005 then
1561          declare
1562             Call           : Node_Id;
1563             Conctyp        : Entity_Id;
1564             Ent            : Entity_Id;
1565             Subprg         : Entity_Id;
1566             RT_Subprg_Name : Node_Id;
1567
1568          begin
1569             --  Handle chains of renamings
1570
1571             Ent := Name (N);
1572             while Nkind (Ent) in N_Has_Entity
1573               and then Present (Entity (Ent))
1574               and then Present (Renamed_Object (Entity (Ent)))
1575             loop
1576                Ent := Renamed_Object (Entity (Ent));
1577             end loop;
1578
1579             --  The attribute Priority applied to protected objects has been
1580             --  previously expanded into a call to the Get_Ceiling run-time
1581             --  subprogram.
1582
1583             if Nkind (Ent) = N_Function_Call
1584               and then (Entity (Name (Ent)) = RTE (RE_Get_Ceiling)
1585                           or else
1586                         Entity (Name (Ent)) = RTE (RO_PE_Get_Ceiling))
1587             then
1588                --  Look for the enclosing concurrent type
1589
1590                Conctyp := Current_Scope;
1591                while not Is_Concurrent_Type (Conctyp) loop
1592                   Conctyp := Scope (Conctyp);
1593                end loop;
1594
1595                pragma Assert (Is_Protected_Type (Conctyp));
1596
1597                --  Generate the first actual of the call
1598
1599                Subprg := Current_Scope;
1600                while not Present (Protected_Body_Subprogram (Subprg)) loop
1601                   Subprg := Scope (Subprg);
1602                end loop;
1603
1604                --  Select the appropriate run-time call
1605
1606                if Number_Entries (Conctyp) = 0 then
1607                   RT_Subprg_Name :=
1608                     New_Reference_To (RTE (RE_Set_Ceiling), Loc);
1609                else
1610                   RT_Subprg_Name :=
1611                     New_Reference_To (RTE (RO_PE_Set_Ceiling), Loc);
1612                end if;
1613
1614                Call :=
1615                  Make_Procedure_Call_Statement (Loc,
1616                    Name => RT_Subprg_Name,
1617                    Parameter_Associations => New_List (
1618                      New_Copy_Tree (First (Parameter_Associations (Ent))),
1619                      Relocate_Node (Expression (N))));
1620
1621                Rewrite (N, Call);
1622                Analyze (N);
1623                return;
1624             end if;
1625          end;
1626       end if;
1627
1628       --  Deal with assignment checks unless suppressed
1629
1630       if not Suppress_Assignment_Checks (N) then
1631
1632          --  First deal with generation of range check if required
1633
1634          if Do_Range_Check (Rhs) then
1635             Set_Do_Range_Check (Rhs, False);
1636             Generate_Range_Check (Rhs, Typ, CE_Range_Check_Failed);
1637          end if;
1638
1639          --  Then generate predicate check if required
1640
1641          Apply_Predicate_Check (Rhs, Typ);
1642       end if;
1643
1644       --  Check for a special case where a high level transformation is
1645       --  required. If we have either of:
1646
1647       --    P.field := rhs;
1648       --    P (sub) := rhs;
1649
1650       --  where P is a reference to a bit packed array, then we have to unwind
1651       --  the assignment. The exact meaning of being a reference to a bit
1652       --  packed array is as follows:
1653
1654       --    An indexed component whose prefix is a bit packed array is a
1655       --    reference to a bit packed array.
1656
1657       --    An indexed component or selected component whose prefix is a
1658       --    reference to a bit packed array is itself a reference ot a
1659       --    bit packed array.
1660
1661       --  The required transformation is
1662
1663       --     Tnn : prefix_type := P;
1664       --     Tnn.field := rhs;
1665       --     P := Tnn;
1666
1667       --  or
1668
1669       --     Tnn : prefix_type := P;
1670       --     Tnn (subscr) := rhs;
1671       --     P := Tnn;
1672
1673       --  Since P is going to be evaluated more than once, any subscripts
1674       --  in P must have their evaluation forced.
1675
1676       if Nkind_In (Lhs, N_Indexed_Component, N_Selected_Component)
1677         and then Is_Ref_To_Bit_Packed_Array (Prefix (Lhs))
1678       then
1679          declare
1680             BPAR_Expr : constant Node_Id   := Relocate_Node (Prefix (Lhs));
1681             BPAR_Typ  : constant Entity_Id := Etype (BPAR_Expr);
1682             Tnn       : constant Entity_Id :=
1683                           Make_Temporary (Loc, 'T', BPAR_Expr);
1684
1685          begin
1686             --  Insert the post assignment first, because we want to copy the
1687             --  BPAR_Expr tree before it gets analyzed in the context of the
1688             --  pre assignment. Note that we do not analyze the post assignment
1689             --  yet (we cannot till we have completed the analysis of the pre
1690             --  assignment). As usual, the analysis of this post assignment
1691             --  will happen on its own when we "run into" it after finishing
1692             --  the current assignment.
1693
1694             Insert_After (N,
1695               Make_Assignment_Statement (Loc,
1696                 Name       => New_Copy_Tree (BPAR_Expr),
1697                 Expression => New_Occurrence_Of (Tnn, Loc)));
1698
1699             --  At this stage BPAR_Expr is a reference to a bit packed array
1700             --  where the reference was not expanded in the original tree,
1701             --  since it was on the left side of an assignment. But in the
1702             --  pre-assignment statement (the object definition), BPAR_Expr
1703             --  will end up on the right hand side, and must be reexpanded. To
1704             --  achieve this, we reset the analyzed flag of all selected and
1705             --  indexed components down to the actual indexed component for
1706             --  the packed array.
1707
1708             Exp := BPAR_Expr;
1709             loop
1710                Set_Analyzed (Exp, False);
1711
1712                if Nkind_In
1713                    (Exp, N_Selected_Component, N_Indexed_Component)
1714                then
1715                   Exp := Prefix (Exp);
1716                else
1717                   exit;
1718                end if;
1719             end loop;
1720
1721             --  Now we can insert and analyze the pre-assignment
1722
1723             --  If the right-hand side requires a transient scope, it has
1724             --  already been placed on the stack. However, the declaration is
1725             --  inserted in the tree outside of this scope, and must reflect
1726             --  the proper scope for its variable. This awkward bit is forced
1727             --  by the stricter scope discipline imposed by GCC 2.97.
1728
1729             declare
1730                Uses_Transient_Scope : constant Boolean :=
1731                                         Scope_Is_Transient
1732                                           and then N = Node_To_Be_Wrapped;
1733
1734             begin
1735                if Uses_Transient_Scope then
1736                   Push_Scope (Scope (Current_Scope));
1737                end if;
1738
1739                Insert_Before_And_Analyze (N,
1740                  Make_Object_Declaration (Loc,
1741                    Defining_Identifier => Tnn,
1742                    Object_Definition   => New_Occurrence_Of (BPAR_Typ, Loc),
1743                    Expression          => BPAR_Expr));
1744
1745                if Uses_Transient_Scope then
1746                   Pop_Scope;
1747                end if;
1748             end;
1749
1750             --  Now fix up the original assignment and continue processing
1751
1752             Rewrite (Prefix (Lhs),
1753               New_Occurrence_Of (Tnn, Loc));
1754
1755             --  We do not need to reanalyze that assignment, and we do not need
1756             --  to worry about references to the temporary, but we do need to
1757             --  make sure that the temporary is not marked as a true constant
1758             --  since we now have a generated assignment to it!
1759
1760             Set_Is_True_Constant (Tnn, False);
1761          end;
1762       end if;
1763
1764       --  When we have the appropriate type of aggregate in the expression (it
1765       --  has been determined during analysis of the aggregate by setting the
1766       --  delay flag), let's perform in place assignment and thus avoid
1767       --  creating a temporary.
1768
1769       if Is_Delayed_Aggregate (Rhs) then
1770          Convert_Aggr_In_Assignment (N);
1771          Rewrite (N, Make_Null_Statement (Loc));
1772          Analyze (N);
1773          return;
1774       end if;
1775
1776       --  Apply discriminant check if required. If Lhs is an access type to a
1777       --  designated type with discriminants, we must always check.
1778
1779       if Has_Discriminants (Etype (Lhs)) then
1780
1781          --  Skip discriminant check if change of representation. Will be
1782          --  done when the change of representation is expanded out.
1783
1784          if not Crep then
1785             Apply_Discriminant_Check (Rhs, Etype (Lhs), Lhs);
1786          end if;
1787
1788       --  If the type is private without discriminants, and the full type
1789       --  has discriminants (necessarily with defaults) a check may still be
1790       --  necessary if the Lhs is aliased. The private determinants must be
1791       --  visible to build the discriminant constraints.
1792       --  What is a "determinant"???
1793
1794       --  Only an explicit dereference that comes from source indicates
1795       --  aliasing. Access to formals of protected operations and entries
1796       --  create dereferences but are not semantic aliasings.
1797
1798       elsif Is_Private_Type (Etype (Lhs))
1799         and then Has_Discriminants (Typ)
1800         and then Nkind (Lhs) = N_Explicit_Dereference
1801         and then Comes_From_Source (Lhs)
1802       then
1803          declare
1804             Lt : constant Entity_Id := Etype (Lhs);
1805          begin
1806             Set_Etype (Lhs, Typ);
1807             Rewrite (Rhs, OK_Convert_To (Base_Type (Typ), Rhs));
1808             Apply_Discriminant_Check (Rhs, Typ, Lhs);
1809             Set_Etype (Lhs, Lt);
1810          end;
1811
1812          --  If the Lhs has a private type with unknown discriminants, it
1813          --  may have a full view with discriminants, but those are nameable
1814          --  only in the underlying type, so convert the Rhs to it before
1815          --  potential checking.
1816
1817       elsif Has_Unknown_Discriminants (Base_Type (Etype (Lhs)))
1818         and then Has_Discriminants (Typ)
1819       then
1820          Rewrite (Rhs, OK_Convert_To (Base_Type (Typ), Rhs));
1821          Apply_Discriminant_Check (Rhs, Typ, Lhs);
1822
1823       --  In the access type case, we need the same discriminant check, and
1824       --  also range checks if we have an access to constrained array.
1825
1826       elsif Is_Access_Type (Etype (Lhs))
1827         and then Is_Constrained (Designated_Type (Etype (Lhs)))
1828       then
1829          if Has_Discriminants (Designated_Type (Etype (Lhs))) then
1830
1831             --  Skip discriminant check if change of representation. Will be
1832             --  done when the change of representation is expanded out.
1833
1834             if not Crep then
1835                Apply_Discriminant_Check (Rhs, Etype (Lhs));
1836             end if;
1837
1838          elsif Is_Array_Type (Designated_Type (Etype (Lhs))) then
1839             Apply_Range_Check (Rhs, Etype (Lhs));
1840
1841             if Is_Constrained (Etype (Lhs)) then
1842                Apply_Length_Check (Rhs, Etype (Lhs));
1843             end if;
1844
1845             if Nkind (Rhs) = N_Allocator then
1846                declare
1847                   Target_Typ : constant Entity_Id := Etype (Expression (Rhs));
1848                   C_Es       : Check_Result;
1849
1850                begin
1851                   C_Es :=
1852                     Get_Range_Checks
1853                       (Lhs,
1854                        Target_Typ,
1855                        Etype (Designated_Type (Etype (Lhs))));
1856
1857                   Insert_Range_Checks
1858                     (C_Es,
1859                      N,
1860                      Target_Typ,
1861                      Sloc (Lhs),
1862                      Lhs);
1863                end;
1864             end if;
1865          end if;
1866
1867       --  Apply range check for access type case
1868
1869       elsif Is_Access_Type (Etype (Lhs))
1870         and then Nkind (Rhs) = N_Allocator
1871         and then Nkind (Expression (Rhs)) = N_Qualified_Expression
1872       then
1873          Analyze_And_Resolve (Expression (Rhs));
1874          Apply_Range_Check
1875            (Expression (Rhs), Designated_Type (Etype (Lhs)));
1876       end if;
1877
1878       --  Ada 2005 (AI-231): Generate the run-time check
1879
1880       if Is_Access_Type (Typ)
1881         and then Can_Never_Be_Null (Etype (Lhs))
1882         and then not Can_Never_Be_Null (Etype (Rhs))
1883       then
1884          Apply_Constraint_Check (Rhs, Etype (Lhs));
1885       end if;
1886
1887       --  Case of assignment to a bit packed array element. If there is a
1888       --  change of representation this must be expanded into components,
1889       --  otherwise this is a bit-field assignment.
1890
1891       if Nkind (Lhs) = N_Indexed_Component
1892         and then Is_Bit_Packed_Array (Etype (Prefix (Lhs)))
1893       then
1894          --  Normal case, no change of representation
1895
1896          if not Crep then
1897             Expand_Bit_Packed_Element_Set (N);
1898             return;
1899
1900          --  Change of representation case
1901
1902          else
1903             --  Generate the following, to force component-by-component
1904             --  assignments in an efficient way. Otherwise each component
1905             --  will require a temporary and two bit-field manipulations.
1906
1907             --  T1 : Elmt_Type;
1908             --  T1 := RhS;
1909             --  Lhs := T1;
1910
1911             declare
1912                Tnn : constant Entity_Id := Make_Temporary (Loc, 'T');
1913                Stats : List_Id;
1914
1915             begin
1916                Stats :=
1917                  New_List (
1918                    Make_Object_Declaration (Loc,
1919                      Defining_Identifier => Tnn,
1920                      Object_Definition   =>
1921                        New_Occurrence_Of (Etype (Lhs), Loc)),
1922                    Make_Assignment_Statement (Loc,
1923                      Name       => New_Occurrence_Of (Tnn, Loc),
1924                      Expression => Relocate_Node (Rhs)),
1925                    Make_Assignment_Statement (Loc,
1926                      Name       => Relocate_Node (Lhs),
1927                      Expression => New_Occurrence_Of (Tnn, Loc)));
1928
1929                Insert_Actions (N, Stats);
1930                Rewrite (N, Make_Null_Statement (Loc));
1931                Analyze (N);
1932             end;
1933          end if;
1934
1935       --  Build-in-place function call case. Note that we're not yet doing
1936       --  build-in-place for user-written assignment statements (the assignment
1937       --  here came from an aggregate.)
1938
1939       elsif Ada_Version >= Ada_2005
1940         and then Is_Build_In_Place_Function_Call (Rhs)
1941       then
1942          Make_Build_In_Place_Call_In_Assignment (N, Rhs);
1943
1944       elsif Is_Tagged_Type (Typ) and then Is_Value_Type (Etype (Lhs)) then
1945
1946          --  Nothing to do for valuetypes
1947          --  ??? Set_Scope_Is_Transient (False);
1948
1949          return;
1950
1951       elsif Is_Tagged_Type (Typ)
1952         or else (Needs_Finalization (Typ) and then not Is_Array_Type (Typ))
1953       then
1954          Tagged_Case : declare
1955             L                   : List_Id := No_List;
1956             Expand_Ctrl_Actions : constant Boolean := not No_Ctrl_Actions (N);
1957
1958          begin
1959             --  In the controlled case, we ensure that function calls are
1960             --  evaluated before finalizing the target. In all cases, it makes
1961             --  the expansion easier if the side-effects are removed first.
1962
1963             Remove_Side_Effects (Lhs);
1964             Remove_Side_Effects (Rhs);
1965
1966             --  Avoid recursion in the mechanism
1967
1968             Set_Analyzed (N);
1969
1970             --  If dispatching assignment, we need to dispatch to _assign
1971
1972             if Is_Class_Wide_Type (Typ)
1973
1974                --  If the type is tagged, we may as well use the predefined
1975                --  primitive assignment. This avoids inlining a lot of code
1976                --  and in the class-wide case, the assignment is replaced
1977                --  by a dispatching call to _assign. It is suppressed in the
1978                --  case of assignments created by the expander that correspond
1979                --  to initializations, where we do want to copy the tag
1980                --  (Expand_Ctrl_Actions flag is set True in this case). It is
1981                --  also suppressed if restriction No_Dispatching_Calls is in
1982                --  force because in that case predefined primitives are not
1983                --  generated.
1984
1985                or else (Is_Tagged_Type (Typ)
1986                          and then not Is_Value_Type (Etype (Lhs))
1987                          and then Chars (Current_Scope) /= Name_uAssign
1988                          and then Expand_Ctrl_Actions
1989                          and then
1990                            not Restriction_Active (No_Dispatching_Calls))
1991             then
1992                --  Fetch the primitive op _assign and proper type to call it.
1993                --  Because of possible conflicts between private and full view,
1994                --  fetch the proper type directly from the operation profile.
1995
1996                declare
1997                   Op    : constant Entity_Id :=
1998                             Find_Prim_Op (Typ, Name_uAssign);
1999                   F_Typ : Entity_Id := Etype (First_Formal (Op));
2000
2001                begin
2002                   --  If the assignment is dispatching, make sure to use the
2003                   --  proper type.
2004
2005                   if Is_Class_Wide_Type (Typ) then
2006                      F_Typ := Class_Wide_Type (F_Typ);
2007                   end if;
2008
2009                   L := New_List;
2010
2011                   --  In case of assignment to a class-wide tagged type, before
2012                   --  the assignment we generate run-time check to ensure that
2013                   --  the tags of source and target match.
2014
2015                   if Is_Class_Wide_Type (Typ)
2016                     and then Is_Tagged_Type (Typ)
2017                     and then Is_Tagged_Type (Underlying_Type (Etype (Rhs)))
2018                   then
2019                      Append_To (L,
2020                        Make_Raise_Constraint_Error (Loc,
2021                          Condition =>
2022                            Make_Op_Ne (Loc,
2023                              Left_Opnd =>
2024                                Make_Selected_Component (Loc,
2025                                  Prefix        => Duplicate_Subexpr (Lhs),
2026                                  Selector_Name =>
2027                                    Make_Identifier (Loc, Name_uTag)),
2028                              Right_Opnd =>
2029                                Make_Selected_Component (Loc,
2030                                  Prefix        => Duplicate_Subexpr (Rhs),
2031                                  Selector_Name =>
2032                                    Make_Identifier (Loc, Name_uTag))),
2033                          Reason => CE_Tag_Check_Failed));
2034                   end if;
2035
2036                   declare
2037                      Left_N  : Node_Id := Duplicate_Subexpr (Lhs);
2038                      Right_N : Node_Id := Duplicate_Subexpr (Rhs);
2039
2040                   begin
2041                      --  In order to dispatch the call to _assign the type of
2042                      --  the actuals must match. Add conversion (if required).
2043
2044                      if Etype (Lhs) /= F_Typ then
2045                         Left_N := Unchecked_Convert_To (F_Typ, Left_N);
2046                      end if;
2047
2048                      if Etype (Rhs) /= F_Typ then
2049                         Right_N := Unchecked_Convert_To (F_Typ, Right_N);
2050                      end if;
2051
2052                      Append_To (L,
2053                        Make_Procedure_Call_Statement (Loc,
2054                          Name => New_Reference_To (Op, Loc),
2055                          Parameter_Associations => New_List (
2056                            Node1 => Left_N,
2057                            Node2 => Right_N)));
2058                   end;
2059                end;
2060
2061             else
2062                L := Make_Tag_Ctrl_Assignment (N);
2063
2064                --  We can't afford to have destructive Finalization Actions in
2065                --  the Self assignment case, so if the target and the source
2066                --  are not obviously different, code is generated to avoid the
2067                --  self assignment case:
2068
2069                --    if lhs'address /= rhs'address then
2070                --       <code for controlled and/or tagged assignment>
2071                --    end if;
2072
2073                --  Skip this if Restriction (No_Finalization) is active
2074
2075                if not Statically_Different (Lhs, Rhs)
2076                  and then Expand_Ctrl_Actions
2077                  and then not Restriction_Active (No_Finalization)
2078                then
2079                   L := New_List (
2080                     Make_Implicit_If_Statement (N,
2081                       Condition =>
2082                         Make_Op_Ne (Loc,
2083                           Left_Opnd =>
2084                             Make_Attribute_Reference (Loc,
2085                               Prefix         => Duplicate_Subexpr (Lhs),
2086                               Attribute_Name => Name_Address),
2087
2088                            Right_Opnd =>
2089                             Make_Attribute_Reference (Loc,
2090                               Prefix         => Duplicate_Subexpr (Rhs),
2091                               Attribute_Name => Name_Address)),
2092
2093                       Then_Statements => L));
2094                end if;
2095
2096                --  We need to set up an exception handler for implementing
2097                --  7.6.1(18). The remaining adjustments are tackled by the
2098                --  implementation of adjust for record_controllers (see
2099                --  s-finimp.adb).
2100
2101                --  This is skipped if we have no finalization
2102
2103                if Expand_Ctrl_Actions
2104                  and then not Restriction_Active (No_Finalization)
2105                then
2106                   L := New_List (
2107                     Make_Block_Statement (Loc,
2108                       Handled_Statement_Sequence =>
2109                         Make_Handled_Sequence_Of_Statements (Loc,
2110                           Statements => L,
2111                           Exception_Handlers => New_List (
2112                             Make_Handler_For_Ctrl_Operation (Loc)))));
2113                end if;
2114             end if;
2115
2116             Rewrite (N,
2117               Make_Block_Statement (Loc,
2118                 Handled_Statement_Sequence =>
2119                   Make_Handled_Sequence_Of_Statements (Loc, Statements => L)));
2120
2121             --  If no restrictions on aborts, protect the whole assignment
2122             --  for controlled objects as per 9.8(11).
2123
2124             if Needs_Finalization (Typ)
2125               and then Expand_Ctrl_Actions
2126               and then Abort_Allowed
2127             then
2128                declare
2129                   Blk : constant Entity_Id :=
2130                           New_Internal_Entity
2131                             (E_Block, Current_Scope, Sloc (N), 'B');
2132
2133                begin
2134                   Set_Scope (Blk, Current_Scope);
2135                   Set_Etype (Blk, Standard_Void_Type);
2136                   Set_Identifier (N, New_Occurrence_Of (Blk, Sloc (N)));
2137
2138                   Prepend_To (L, Build_Runtime_Call (Loc, RE_Abort_Defer));
2139                   Set_At_End_Proc (Handled_Statement_Sequence (N),
2140                     New_Occurrence_Of (RTE (RE_Abort_Undefer_Direct), Loc));
2141                   Expand_At_End_Handler
2142                     (Handled_Statement_Sequence (N), Blk);
2143                end;
2144             end if;
2145
2146             --  N has been rewritten to a block statement for which it is
2147             --  known by construction that no checks are necessary: analyze
2148             --  it with all checks suppressed.
2149
2150             Analyze (N, Suppress => All_Checks);
2151             return;
2152          end Tagged_Case;
2153
2154       --  Array types
2155
2156       elsif Is_Array_Type (Typ) then
2157          declare
2158             Actual_Rhs : Node_Id := Rhs;
2159
2160          begin
2161             while Nkind_In (Actual_Rhs, N_Type_Conversion,
2162                                         N_Qualified_Expression)
2163             loop
2164                Actual_Rhs := Expression (Actual_Rhs);
2165             end loop;
2166
2167             Expand_Assign_Array (N, Actual_Rhs);
2168             return;
2169          end;
2170
2171       --  Record types
2172
2173       elsif Is_Record_Type (Typ) then
2174          Expand_Assign_Record (N);
2175          return;
2176
2177       --  Scalar types. This is where we perform the processing related to the
2178       --  requirements of (RM 13.9.1(9-11)) concerning the handling of invalid
2179       --  scalar values.
2180
2181       elsif Is_Scalar_Type (Typ) then
2182
2183          --  Case where right side is known valid
2184
2185          if Expr_Known_Valid (Rhs) then
2186
2187             --  Here the right side is valid, so it is fine. The case to deal
2188             --  with is when the left side is a local variable reference whose
2189             --  value is not currently known to be valid. If this is the case,
2190             --  and the assignment appears in an unconditional context, then
2191             --  we can mark the left side as now being valid if one of these
2192             --  conditions holds:
2193
2194             --    The expression of the right side has Do_Range_Check set so
2195             --    that we know a range check will be performed. Note that it
2196             --    can be the case that a range check is omitted because we
2197             --    make the assumption that we can assume validity for operands
2198             --    appearing in the right side in determining whether a range
2199             --    check is required
2200
2201             --    The subtype of the right side matches the subtype of the
2202             --    left side. In this case, even though we have not checked
2203             --    the range of the right side, we know it is in range of its
2204             --    subtype if the expression is valid.
2205
2206             if Is_Local_Variable_Reference (Lhs)
2207               and then not Is_Known_Valid (Entity (Lhs))
2208               and then In_Unconditional_Context (N)
2209             then
2210                if Do_Range_Check (Rhs)
2211                  or else Etype (Lhs) = Etype (Rhs)
2212                then
2213                   Set_Is_Known_Valid (Entity (Lhs), True);
2214                end if;
2215             end if;
2216
2217          --  Case where right side may be invalid in the sense of the RM
2218          --  reference above. The RM does not require that we check for the
2219          --  validity on an assignment, but it does require that the assignment
2220          --  of an invalid value not cause erroneous behavior.
2221
2222          --  The general approach in GNAT is to use the Is_Known_Valid flag
2223          --  to avoid the need for validity checking on assignments. However
2224          --  in some cases, we have to do validity checking in order to make
2225          --  sure that the setting of this flag is correct.
2226
2227          else
2228             --  Validate right side if we are validating copies
2229
2230             if Validity_Checks_On
2231               and then Validity_Check_Copies
2232             then
2233                --  Skip this if left hand side is an array or record component
2234                --  and elementary component validity checks are suppressed.
2235
2236                if Nkind_In (Lhs, N_Selected_Component, N_Indexed_Component)
2237                  and then not Validity_Check_Components
2238                then
2239                   null;
2240                else
2241                   Ensure_Valid (Rhs);
2242                end if;
2243
2244                --  We can propagate this to the left side where appropriate
2245
2246                if Is_Local_Variable_Reference (Lhs)
2247                  and then not Is_Known_Valid (Entity (Lhs))
2248                  and then In_Unconditional_Context (N)
2249                then
2250                   Set_Is_Known_Valid (Entity (Lhs), True);
2251                end if;
2252
2253             --  Otherwise check to see what should be done
2254
2255             --  If left side is a local variable, then we just set its flag to
2256             --  indicate that its value may no longer be valid, since we are
2257             --  copying a potentially invalid value.
2258
2259             elsif Is_Local_Variable_Reference (Lhs) then
2260                Set_Is_Known_Valid (Entity (Lhs), False);
2261
2262             --  Check for case of a nonlocal variable on the left side which
2263             --  is currently known to be valid. In this case, we simply ensure
2264             --  that the right side is valid. We only play the game of copying
2265             --  validity status for local variables, since we are doing this
2266             --  statically, not by tracing the full flow graph.
2267
2268             elsif Is_Entity_Name (Lhs)
2269               and then Is_Known_Valid (Entity (Lhs))
2270             then
2271                --  Note: If Validity_Checking mode is set to none, we ignore
2272                --  the Ensure_Valid call so don't worry about that case here.
2273
2274                Ensure_Valid (Rhs);
2275
2276             --  In all other cases, we can safely copy an invalid value without
2277             --  worrying about the status of the left side. Since it is not a
2278             --  variable reference it will not be considered
2279             --  as being known to be valid in any case.
2280
2281             else
2282                null;
2283             end if;
2284          end if;
2285       end if;
2286
2287    exception
2288       when RE_Not_Available =>
2289          return;
2290    end Expand_N_Assignment_Statement;
2291
2292    ------------------------------
2293    -- Expand_N_Block_Statement --
2294    ------------------------------
2295
2296    --  Encode entity names defined in block statement
2297
2298    procedure Expand_N_Block_Statement (N : Node_Id) is
2299    begin
2300       Qualify_Entity_Names (N);
2301    end Expand_N_Block_Statement;
2302
2303    -----------------------------
2304    -- Expand_N_Case_Statement --
2305    -----------------------------
2306
2307    procedure Expand_N_Case_Statement (N : Node_Id) is
2308       Loc    : constant Source_Ptr := Sloc (N);
2309       Expr   : constant Node_Id    := Expression (N);
2310       Alt    : Node_Id;
2311       Len    : Nat;
2312       Cond   : Node_Id;
2313       Choice : Node_Id;
2314       Chlist : List_Id;
2315
2316    begin
2317       --  Check for the situation where we know at compile time which branch
2318       --  will be taken
2319
2320       if Compile_Time_Known_Value (Expr) then
2321          Alt := Find_Static_Alternative (N);
2322
2323          Process_Statements_For_Controlled_Objects (Alt);
2324
2325          --  Move statements from this alternative after the case statement.
2326          --  They are already analyzed, so will be skipped by the analyzer.
2327
2328          Insert_List_After (N, Statements (Alt));
2329
2330          --  That leaves the case statement as a shell. So now we can kill all
2331          --  other alternatives in the case statement.
2332
2333          Kill_Dead_Code (Expression (N));
2334
2335          declare
2336             Dead_Alt : Node_Id;
2337
2338          begin
2339             --  Loop through case alternatives, skipping pragmas, and skipping
2340             --  the one alternative that we select (and therefore retain).
2341
2342             Dead_Alt := First (Alternatives (N));
2343             while Present (Dead_Alt) loop
2344                if Dead_Alt /= Alt
2345                  and then Nkind (Dead_Alt) = N_Case_Statement_Alternative
2346                then
2347                   Kill_Dead_Code (Statements (Dead_Alt), Warn_On_Deleted_Code);
2348                end if;
2349
2350                Next (Dead_Alt);
2351             end loop;
2352          end;
2353
2354          Rewrite (N, Make_Null_Statement (Loc));
2355          return;
2356       end if;
2357
2358       --  Here if the choice is not determined at compile time
2359
2360       declare
2361          Last_Alt : constant Node_Id := Last (Alternatives (N));
2362
2363          Others_Present : Boolean;
2364          Others_Node    : Node_Id;
2365
2366          Then_Stms : List_Id;
2367          Else_Stms : List_Id;
2368
2369       begin
2370          if Nkind (First (Discrete_Choices (Last_Alt))) = N_Others_Choice then
2371             Others_Present := True;
2372             Others_Node    := Last_Alt;
2373          else
2374             Others_Present := False;
2375          end if;
2376
2377          --  First step is to worry about possible invalid argument. The RM
2378          --  requires (RM 5.4(13)) that if the result is invalid (e.g. it is
2379          --  outside the base range), then Constraint_Error must be raised.
2380
2381          --  Case of validity check required (validity checks are on, the
2382          --  expression is not known to be valid, and the case statement
2383          --  comes from source -- no need to validity check internally
2384          --  generated case statements).
2385
2386          if Validity_Check_Default then
2387             Ensure_Valid (Expr);
2388          end if;
2389
2390          --  If there is only a single alternative, just replace it with the
2391          --  sequence of statements since obviously that is what is going to
2392          --  be executed in all cases.
2393
2394          Len := List_Length (Alternatives (N));
2395
2396          if Len = 1 then
2397
2398             --  We still need to evaluate the expression if it has any side
2399             --  effects.
2400
2401             Remove_Side_Effects (Expression (N));
2402
2403             Alt := First (Alternatives (N));
2404
2405             Process_Statements_For_Controlled_Objects (Alt);
2406             Insert_List_After (N, Statements (Alt));
2407
2408             --  That leaves the case statement as a shell. The alternative that
2409             --  will be executed is reset to a null list. So now we can kill
2410             --  the entire case statement.
2411
2412             Kill_Dead_Code (Expression (N));
2413             Rewrite (N, Make_Null_Statement (Loc));
2414             return;
2415
2416          --  An optimization. If there are only two alternatives, and only
2417          --  a single choice, then rewrite the whole case statement as an
2418          --  if statement, since this can result in subsequent optimizations.
2419          --  This helps not only with case statements in the source of a
2420          --  simple form, but also with generated code (discriminant check
2421          --  functions in particular)
2422
2423          elsif Len = 2 then
2424             Chlist := Discrete_Choices (First (Alternatives (N)));
2425
2426             if List_Length (Chlist) = 1 then
2427                Choice := First (Chlist);
2428
2429                Then_Stms := Statements (First (Alternatives (N)));
2430                Else_Stms := Statements (Last  (Alternatives (N)));
2431
2432                --  For TRUE, generate "expression", not expression = true
2433
2434                if Nkind (Choice) = N_Identifier
2435                  and then Entity (Choice) = Standard_True
2436                then
2437                   Cond := Expression (N);
2438
2439                --  For FALSE, generate "expression" and switch then/else
2440
2441                elsif Nkind (Choice) = N_Identifier
2442                  and then Entity (Choice) = Standard_False
2443                then
2444                   Cond := Expression (N);
2445                   Else_Stms := Statements (First (Alternatives (N)));
2446                   Then_Stms := Statements (Last  (Alternatives (N)));
2447
2448                --  For a range, generate "expression in range"
2449
2450                elsif Nkind (Choice) = N_Range
2451                  or else (Nkind (Choice) = N_Attribute_Reference
2452                            and then Attribute_Name (Choice) = Name_Range)
2453                  or else (Is_Entity_Name (Choice)
2454                            and then Is_Type (Entity (Choice)))
2455                  or else Nkind (Choice) = N_Subtype_Indication
2456                then
2457                   Cond :=
2458                     Make_In (Loc,
2459                       Left_Opnd  => Expression (N),
2460                       Right_Opnd => Relocate_Node (Choice));
2461
2462                --  For any other subexpression "expression = value"
2463
2464                else
2465                   Cond :=
2466                     Make_Op_Eq (Loc,
2467                       Left_Opnd  => Expression (N),
2468                       Right_Opnd => Relocate_Node (Choice));
2469                end if;
2470
2471                --  Now rewrite the case as an IF
2472
2473                Rewrite (N,
2474                  Make_If_Statement (Loc,
2475                    Condition => Cond,
2476                    Then_Statements => Then_Stms,
2477                    Else_Statements => Else_Stms));
2478                Analyze (N);
2479                return;
2480             end if;
2481          end if;
2482
2483          --  If the last alternative is not an Others choice, replace it with
2484          --  an N_Others_Choice. Note that we do not bother to call Analyze on
2485          --  the modified case statement, since it's only effect would be to
2486          --  compute the contents of the Others_Discrete_Choices which is not
2487          --  needed by the back end anyway.
2488
2489          --  The reason we do this is that the back end always needs some
2490          --  default for a switch, so if we have not supplied one in the
2491          --  processing above for validity checking, then we need to supply
2492          --  one here.
2493
2494          if not Others_Present then
2495             Others_Node := Make_Others_Choice (Sloc (Last_Alt));
2496             Set_Others_Discrete_Choices
2497               (Others_Node, Discrete_Choices (Last_Alt));
2498             Set_Discrete_Choices (Last_Alt, New_List (Others_Node));
2499          end if;
2500
2501          Alt := First (Alternatives (N));
2502          while Present (Alt)
2503            and then Nkind (Alt) = N_Case_Statement_Alternative
2504          loop
2505             Process_Statements_For_Controlled_Objects (Alt);
2506             Next (Alt);
2507          end loop;
2508       end;
2509    end Expand_N_Case_Statement;
2510
2511    -----------------------------
2512    -- Expand_N_Exit_Statement --
2513    -----------------------------
2514
2515    --  The only processing required is to deal with a possible C/Fortran
2516    --  boolean value used as the condition for the exit statement.
2517
2518    procedure Expand_N_Exit_Statement (N : Node_Id) is
2519    begin
2520       Adjust_Condition (Condition (N));
2521    end Expand_N_Exit_Statement;
2522
2523    -----------------------------
2524    -- Expand_N_Goto_Statement --
2525    -----------------------------
2526
2527    --  Add poll before goto if polling active
2528
2529    procedure Expand_N_Goto_Statement (N : Node_Id) is
2530    begin
2531       Generate_Poll_Call (N);
2532    end Expand_N_Goto_Statement;
2533
2534    ---------------------------
2535    -- Expand_N_If_Statement --
2536    ---------------------------
2537
2538    --  First we deal with the case of C and Fortran convention boolean values,
2539    --  with zero/non-zero semantics.
2540
2541    --  Second, we deal with the obvious rewriting for the cases where the
2542    --  condition of the IF is known at compile time to be True or False.
2543
2544    --  Third, we remove elsif parts which have non-empty Condition_Actions and
2545    --  rewrite as independent if statements. For example:
2546
2547    --     if x then xs
2548    --     elsif y then ys
2549    --     ...
2550    --     end if;
2551
2552    --  becomes
2553    --
2554    --     if x then xs
2555    --     else
2556    --        <<condition actions of y>>
2557    --        if y then ys
2558    --        ...
2559    --        end if;
2560    --     end if;
2561
2562    --  This rewriting is needed if at least one elsif part has a non-empty
2563    --  Condition_Actions list. We also do the same processing if there is a
2564    --  constant condition in an elsif part (in conjunction with the first
2565    --  processing step mentioned above, for the recursive call made to deal
2566    --  with the created inner if, this deals with properly optimizing the
2567    --  cases of constant elsif conditions).
2568
2569    procedure Expand_N_If_Statement (N : Node_Id) is
2570       Loc    : constant Source_Ptr := Sloc (N);
2571       Hed    : Node_Id;
2572       E      : Node_Id;
2573       New_If : Node_Id;
2574
2575       Warn_If_Deleted : constant Boolean :=
2576                           Warn_On_Deleted_Code and then Comes_From_Source (N);
2577       --  Indicates whether we want warnings when we delete branches of the
2578       --  if statement based on constant condition analysis. We never want
2579       --  these warnings for expander generated code.
2580
2581    begin
2582       Process_Statements_For_Controlled_Objects (N);
2583
2584       Adjust_Condition (Condition (N));
2585
2586       --  The following loop deals with constant conditions for the IF. We
2587       --  need a loop because as we eliminate False conditions, we grab the
2588       --  first elsif condition and use it as the primary condition.
2589
2590       while Compile_Time_Known_Value (Condition (N)) loop
2591
2592          --  If condition is True, we can simply rewrite the if statement now
2593          --  by replacing it by the series of then statements.
2594
2595          if Is_True (Expr_Value (Condition (N))) then
2596
2597             --  All the else parts can be killed
2598
2599             Kill_Dead_Code (Elsif_Parts (N), Warn_If_Deleted);
2600             Kill_Dead_Code (Else_Statements (N), Warn_If_Deleted);
2601
2602             Hed := Remove_Head (Then_Statements (N));
2603             Insert_List_After (N, Then_Statements (N));
2604             Rewrite (N, Hed);
2605             return;
2606
2607          --  If condition is False, then we can delete the condition and
2608          --  the Then statements
2609
2610          else
2611             --  We do not delete the condition if constant condition warnings
2612             --  are enabled, since otherwise we end up deleting the desired
2613             --  warning. Of course the backend will get rid of this True/False
2614             --  test anyway, so nothing is lost here.
2615
2616             if not Constant_Condition_Warnings then
2617                Kill_Dead_Code (Condition (N));
2618             end if;
2619
2620             Kill_Dead_Code (Then_Statements (N), Warn_If_Deleted);
2621
2622             --  If there are no elsif statements, then we simply replace the
2623             --  entire if statement by the sequence of else statements.
2624
2625             if No (Elsif_Parts (N)) then
2626                if No (Else_Statements (N))
2627                  or else Is_Empty_List (Else_Statements (N))
2628                then
2629                   Rewrite (N,
2630                     Make_Null_Statement (Sloc (N)));
2631                else
2632                   Hed := Remove_Head (Else_Statements (N));
2633                   Insert_List_After (N, Else_Statements (N));
2634                   Rewrite (N, Hed);
2635                end if;
2636
2637                return;
2638
2639             --  If there are elsif statements, the first of them becomes the
2640             --  if/then section of the rebuilt if statement This is the case
2641             --  where we loop to reprocess this copied condition.
2642
2643             else
2644                Hed := Remove_Head (Elsif_Parts (N));
2645                Insert_Actions      (N, Condition_Actions (Hed));
2646                Set_Condition       (N, Condition (Hed));
2647                Set_Then_Statements (N, Then_Statements (Hed));
2648
2649                --  Hed might have been captured as the condition determining
2650                --  the current value for an entity. Now it is detached from
2651                --  the tree, so a Current_Value pointer in the condition might
2652                --  need to be updated.
2653
2654                Set_Current_Value_Condition (N);
2655
2656                if Is_Empty_List (Elsif_Parts (N)) then
2657                   Set_Elsif_Parts (N, No_List);
2658                end if;
2659             end if;
2660          end if;
2661       end loop;
2662
2663       --  Loop through elsif parts, dealing with constant conditions and
2664       --  possible expression actions that are present.
2665
2666       if Present (Elsif_Parts (N)) then
2667          E := First (Elsif_Parts (N));
2668          while Present (E) loop
2669             Process_Statements_For_Controlled_Objects (E);
2670
2671             Adjust_Condition (Condition (E));
2672
2673             --  If there are condition actions, then rewrite the if statement
2674             --  as indicated above. We also do the same rewrite for a True or
2675             --  False condition. The further processing of this constant
2676             --  condition is then done by the recursive call to expand the
2677             --  newly created if statement
2678
2679             if Present (Condition_Actions (E))
2680               or else Compile_Time_Known_Value (Condition (E))
2681             then
2682                --  Note this is not an implicit if statement, since it is part
2683                --  of an explicit if statement in the source (or of an implicit
2684                --  if statement that has already been tested).
2685
2686                New_If :=
2687                  Make_If_Statement (Sloc (E),
2688                    Condition       => Condition (E),
2689                    Then_Statements => Then_Statements (E),
2690                    Elsif_Parts     => No_List,
2691                    Else_Statements => Else_Statements (N));
2692
2693                --  Elsif parts for new if come from remaining elsif's of parent
2694
2695                while Present (Next (E)) loop
2696                   if No (Elsif_Parts (New_If)) then
2697                      Set_Elsif_Parts (New_If, New_List);
2698                   end if;
2699
2700                   Append (Remove_Next (E), Elsif_Parts (New_If));
2701                end loop;
2702
2703                Set_Else_Statements (N, New_List (New_If));
2704
2705                if Present (Condition_Actions (E)) then
2706                   Insert_List_Before (New_If, Condition_Actions (E));
2707                end if;
2708
2709                Remove (E);
2710
2711                if Is_Empty_List (Elsif_Parts (N)) then
2712                   Set_Elsif_Parts (N, No_List);
2713                end if;
2714
2715                Analyze (New_If);
2716                return;
2717
2718             --  No special processing for that elsif part, move to next
2719
2720             else
2721                Next (E);
2722             end if;
2723          end loop;
2724       end if;
2725
2726       --  Some more optimizations applicable if we still have an IF statement
2727
2728       if Nkind (N) /= N_If_Statement then
2729          return;
2730       end if;
2731
2732       --  Another optimization, special cases that can be simplified
2733
2734       --     if expression then
2735       --        return true;
2736       --     else
2737       --        return false;
2738       --     end if;
2739
2740       --  can be changed to:
2741
2742       --     return expression;
2743
2744       --  and
2745
2746       --     if expression then
2747       --        return false;
2748       --     else
2749       --        return true;
2750       --     end if;
2751
2752       --  can be changed to:
2753
2754       --     return not (expression);
2755
2756       --  Only do these optimizations if we are at least at -O1 level and
2757       --  do not do them if control flow optimizations are suppressed.
2758
2759       if Optimization_Level > 0
2760         and then not Opt.Suppress_Control_Flow_Optimizations
2761       then
2762          if Nkind (N) = N_If_Statement
2763            and then No (Elsif_Parts (N))
2764            and then Present (Else_Statements (N))
2765            and then List_Length (Then_Statements (N)) = 1
2766            and then List_Length (Else_Statements (N)) = 1
2767          then
2768             declare
2769                Then_Stm : constant Node_Id := First (Then_Statements (N));
2770                Else_Stm : constant Node_Id := First (Else_Statements (N));
2771
2772             begin
2773                if Nkind (Then_Stm) = N_Simple_Return_Statement
2774                     and then
2775                   Nkind (Else_Stm) = N_Simple_Return_Statement
2776                then
2777                   declare
2778                      Then_Expr : constant Node_Id := Expression (Then_Stm);
2779                      Else_Expr : constant Node_Id := Expression (Else_Stm);
2780
2781                   begin
2782                      if Nkind (Then_Expr) = N_Identifier
2783                           and then
2784                         Nkind (Else_Expr) = N_Identifier
2785                      then
2786                         if Entity (Then_Expr) = Standard_True
2787                           and then Entity (Else_Expr) = Standard_False
2788                         then
2789                            Rewrite (N,
2790                              Make_Simple_Return_Statement (Loc,
2791                                Expression => Relocate_Node (Condition (N))));
2792                            Analyze (N);
2793                            return;
2794
2795                         elsif Entity (Then_Expr) = Standard_False
2796                           and then Entity (Else_Expr) = Standard_True
2797                         then
2798                            Rewrite (N,
2799                              Make_Simple_Return_Statement (Loc,
2800                                Expression =>
2801                                  Make_Op_Not (Loc,
2802                                    Right_Opnd =>
2803                                      Relocate_Node (Condition (N)))));
2804                            Analyze (N);
2805                            return;
2806                         end if;
2807                      end if;
2808                   end;
2809                end if;
2810             end;
2811          end if;
2812       end if;
2813    end Expand_N_If_Statement;
2814
2815    --------------------------
2816    -- Expand_Iterator_Loop --
2817    --------------------------
2818
2819    procedure Expand_Iterator_Loop (N : Node_Id) is
2820       Isc    : constant Node_Id    := Iteration_Scheme (N);
2821       I_Spec : constant Node_Id    := Iterator_Specification (Isc);
2822       Id     : constant Entity_Id  := Defining_Identifier (I_Spec);
2823       Loc    : constant Source_Ptr := Sloc (N);
2824
2825       Container     : constant Node_Id   := Name (I_Spec);
2826       Container_Typ : constant Entity_Id := Etype (Container);
2827       Cursor        : Entity_Id;
2828       New_Loop      : Node_Id;
2829       Stats         : List_Id := Statements (N);
2830
2831    begin
2832       --  Processing for arrays
2833
2834       if Is_Array_Type (Container_Typ) then
2835
2836          --  for Element of Array loop
2837          --
2838          --  This case requires an internally generated cursor to iterate over
2839          --  the array.
2840
2841          if Of_Present (I_Spec) then
2842             Cursor := Make_Temporary (Loc, 'C');
2843
2844             --  Generate:
2845             --    Element : Component_Type renames Container (Cursor);
2846
2847             Prepend_To (Stats,
2848               Make_Object_Renaming_Declaration (Loc,
2849                 Defining_Identifier => Id,
2850                 Subtype_Mark =>
2851                   New_Reference_To (Component_Type (Container_Typ), Loc),
2852                 Name =>
2853                   Make_Indexed_Component (Loc,
2854                     Prefix => Relocate_Node (Container),
2855                     Expressions => New_List (
2856                       New_Reference_To (Cursor, Loc)))));
2857
2858          --  for Index in Array loop
2859          --
2860          --  This case utilizes the already given cursor name
2861
2862          else
2863             Cursor := Id;
2864          end if;
2865
2866          --  Generate:
2867          --    for Cursor in [reverse] Container'Range loop
2868          --       Element : Component_Type renames Container (Cursor);
2869          --       --  for the "of" form
2870          --
2871          --       <original loop statements>
2872          --    end loop;
2873
2874          New_Loop :=
2875            Make_Loop_Statement (Loc,
2876              Iteration_Scheme =>
2877                Make_Iteration_Scheme (Loc,
2878                  Loop_Parameter_Specification =>
2879                    Make_Loop_Parameter_Specification (Loc,
2880                      Defining_Identifier => Cursor,
2881                        Discrete_Subtype_Definition =>
2882                          Make_Attribute_Reference (Loc,
2883                            Prefix => Relocate_Node (Container),
2884                            Attribute_Name => Name_Range),
2885                       Reverse_Present => Reverse_Present (I_Spec))),
2886               Statements => Stats,
2887               End_Label  => Empty);
2888
2889       --  Processing for containers
2890
2891       else
2892          --  The for loop is expanded into a while loop which uses a container
2893          --  specific cursor to examine each element.
2894
2895          --    Cursor : Pack.Cursor := Container.First;
2896          --    while Cursor /= Pack.No_Element loop
2897          --       declare
2898          --       --  the block is added when Element_Type is controlled
2899
2900          --          Obj : Pack.Element_Type := Element (Cursor);
2901          --          --  for the "of" loop form
2902          --       begin
2903          --          <original loop statements>
2904          --       end;
2905
2906          --       Pack.Next (Cursor);
2907          --    end loop;
2908
2909          --  If "reverse" is present, then the initialization of the cursor
2910          --  uses Last and the step becomes Prev. Pack is the name of the
2911          --  package which instantiates the container.
2912
2913          declare
2914             Element_Type : constant Entity_Id := Etype (Id);
2915             Pack         : constant Entity_Id :=
2916                              Scope (Base_Type (Container_Typ));
2917             Decl         : Node_Id;
2918             Cntr         : Node_Id;
2919             Name_Init    : Name_Id;
2920             Name_Step    : Name_Id;
2921
2922          begin
2923             --  The "of" case uses an internally generated cursor
2924
2925             if Of_Present (I_Spec) then
2926                Cursor := Make_Temporary (Loc, 'C');
2927             else
2928                Cursor := Id;
2929             end if;
2930
2931             --  The code below only handles containers where Element is not a
2932             --  primitive operation of the container. This excludes for now the
2933             --  Hi-Lite formal containers.
2934
2935             if Of_Present (I_Spec) then
2936
2937                --  Generate:
2938                --    Id : Element_Type := Pack.Element (Cursor);
2939
2940                Decl :=
2941                  Make_Object_Renaming_Declaration (Loc,
2942                    Defining_Identifier => Id,
2943                    Subtype_Mark =>
2944                      New_Reference_To (Element_Type, Loc),
2945                    Name =>
2946                      Make_Indexed_Component (Loc,
2947                        Prefix =>
2948                          Make_Selected_Component (Loc,
2949                            Prefix =>
2950                              New_Reference_To (Pack, Loc),
2951                            Selector_Name =>
2952                              Make_Identifier (Loc, Chars => Name_Element)),
2953                        Expressions => New_List (
2954                          New_Reference_To (Cursor, Loc))));
2955
2956                --  When the container holds controlled objects, wrap the loop
2957                --  statements and element renaming declaration with a block.
2958                --  This ensures that the transient result of Element (Cursor)
2959                --  is cleaned up after each iteration of the loop.
2960
2961                if Needs_Finalization (Element_Type) then
2962
2963                   --  Generate:
2964                   --    declare
2965                   --       Id : Element_Type := Pack.Element (Cursor);
2966                   --    begin
2967                   --       <original loop statements>
2968                   --    end;
2969
2970                   Stats := New_List (
2971                     Make_Block_Statement (Loc,
2972                       Declarations => New_List (Decl),
2973                       Handled_Statement_Sequence =>
2974                         Make_Handled_Sequence_Of_Statements (Loc,
2975                           Statements => Stats)));
2976                else
2977                   Prepend_To (Stats, Decl);
2978                end if;
2979             end if;
2980
2981             --  Determine the advancement and initialization steps for the
2982             --  cursor.
2983
2984             --  Must verify that the container has a reverse iterator ???
2985
2986             if Reverse_Present (I_Spec) then
2987                Name_Init := Name_Last;
2988                Name_Step := Name_Previous;
2989             else
2990                Name_Init := Name_First;
2991                Name_Step := Name_Next;
2992             end if;
2993
2994             --  For both iterator forms, add a call to the step operation to
2995             --  advance the cursor. Generate:
2996             --
2997             --    Pack.[Next | Prev] (Cursor);
2998
2999             Append_To (Stats,
3000               Make_Procedure_Call_Statement (Loc,
3001                 Name =>
3002                   Make_Selected_Component (Loc,
3003                     Prefix =>
3004                       New_Reference_To (Pack, Loc),
3005                     Selector_Name =>
3006                       Make_Identifier (Loc, Name_Step)),
3007
3008                 Parameter_Associations => New_List (
3009                   New_Reference_To (Cursor, Loc))));
3010
3011             --  Generate:
3012             --    while Cursor /= Pack.No_Element loop
3013             --       <Stats>
3014             --    end loop;
3015
3016             New_Loop :=
3017               Make_Loop_Statement (Loc,
3018                 Iteration_Scheme =>
3019                   Make_Iteration_Scheme (Loc,
3020                     Condition =>
3021                       Make_Op_Ne (Loc,
3022                         Left_Opnd =>
3023                           New_Reference_To (Cursor, Loc),
3024                         Right_Opnd =>
3025                           Make_Selected_Component (Loc,
3026                             Prefix =>
3027                               New_Reference_To (Pack, Loc),
3028                             Selector_Name =>
3029                               Make_Identifier (Loc, Name_No_Element)))),
3030                 Statements => Stats,
3031                 End_Label  => Empty);
3032
3033             Cntr := Relocate_Node (Container);
3034
3035             --  When the container is provided by a function call, create an
3036             --  explicit renaming of the function result. Generate:
3037             --
3038             --    Cnn : Container_Typ renames Func_Call (...);
3039             --
3040             --  The renaming avoids the generation of a transient scope when
3041             --  initializing the cursor and the premature finalization of the
3042             --  container.
3043
3044             if Nkind (Cntr) = N_Function_Call then
3045                declare
3046                   Ren_Id : constant Entity_Id := Make_Temporary (Loc, 'C');
3047
3048                begin
3049                   Insert_Action (N,
3050                     Make_Object_Renaming_Declaration (Loc,
3051                       Defining_Identifier => Ren_Id,
3052                       Subtype_Mark =>
3053                         New_Reference_To (Container_Typ, Loc),
3054                       Name => Cntr));
3055
3056                   Cntr := New_Reference_To (Ren_Id, Loc);
3057                end;
3058             end if;
3059
3060             --  Create the declaration of the cursor and insert it before the
3061             --  source loop. Generate:
3062             --
3063             --    C : Pack.Cursor_Type := Container.[First | Last];
3064
3065             Insert_Action (N,
3066               Make_Object_Declaration (Loc,
3067                 Defining_Identifier => Cursor,
3068                 Object_Definition =>
3069                   Make_Selected_Component (Loc,
3070                     Prefix =>
3071                       New_Reference_To (Pack, Loc),
3072                     Selector_Name =>
3073                       Make_Identifier (Loc, Name_Cursor)),
3074
3075                 Expression =>
3076                   Make_Selected_Component (Loc,
3077                     Prefix => Cntr,
3078                     Selector_Name =>
3079                       Make_Identifier (Loc, Name_Init))));
3080
3081             --  The cursor is not modified in the source, but of course will
3082             --  be updated in the generated code. Indicate that it is actually
3083             --  set to prevent spurious warnings.
3084
3085             Set_Never_Set_In_Source (Cursor, False);
3086
3087             --  If the range of iteration is given by a function call that
3088             --  returns a container, the finalization actions have been saved
3089             --  in the Condition_Actions of the iterator. Insert them now at
3090             --  the head of the loop.
3091
3092             if Present (Condition_Actions (Isc)) then
3093                Insert_List_Before (N, Condition_Actions (Isc));
3094             end if;
3095          end;
3096       end if;
3097
3098       Rewrite (N, New_Loop);
3099       Analyze (N);
3100    end Expand_Iterator_Loop;
3101
3102    -----------------------------
3103    -- Expand_N_Loop_Statement --
3104    -----------------------------
3105
3106    --  1. Remove null loop entirely
3107    --  2. Deal with while condition for C/Fortran boolean
3108    --  3. Deal with loops with a non-standard enumeration type range
3109    --  4. Deal with while loops where Condition_Actions is set
3110    --  5. Deal with loops over predicated subtypes
3111    --  6. Deal with loops with iterators over arrays and containers
3112    --  7. Insert polling call if required
3113
3114    procedure Expand_N_Loop_Statement (N : Node_Id) is
3115       Loc  : constant Source_Ptr := Sloc (N);
3116       Isc  : constant Node_Id    := Iteration_Scheme (N);
3117
3118    begin
3119       --  Delete null loop
3120
3121       if Is_Null_Loop (N) then
3122          Rewrite (N, Make_Null_Statement (Loc));
3123          return;
3124       end if;
3125
3126       Process_Statements_For_Controlled_Objects (N);
3127
3128       --  Deal with condition for C/Fortran Boolean
3129
3130       if Present (Isc) then
3131          Adjust_Condition (Condition (Isc));
3132       end if;
3133
3134       --  Generate polling call
3135
3136       if Is_Non_Empty_List (Statements (N)) then
3137          Generate_Poll_Call (First (Statements (N)));
3138       end if;
3139
3140       --  Nothing more to do for plain loop with no iteration scheme
3141
3142       if No (Isc) then
3143          null;
3144
3145       --  Case of for loop (Loop_Parameter_Specification present)
3146
3147       --  Note: we do not have to worry about validity checking of the for loop
3148       --  range bounds here, since they were frozen with constant declarations
3149       --  and it is during that process that the validity checking is done.
3150
3151       elsif Present (Loop_Parameter_Specification (Isc)) then
3152          declare
3153             LPS     : constant Node_Id   := Loop_Parameter_Specification (Isc);
3154             Loop_Id : constant Entity_Id := Defining_Identifier (LPS);
3155             Ltype   : constant Entity_Id := Etype (Loop_Id);
3156             Btype   : constant Entity_Id := Base_Type (Ltype);
3157             Expr    : Node_Id;
3158             New_Id  : Entity_Id;
3159
3160          begin
3161             --  Deal with loop over predicates
3162
3163             if Is_Discrete_Type (Ltype)
3164               and then Present (Predicate_Function (Ltype))
3165             then
3166                Expand_Predicated_Loop (N);
3167
3168             --  Handle the case where we have a for loop with the range type
3169             --  being an enumeration type with non-standard representation.
3170             --  In this case we expand:
3171
3172             --    for x in [reverse] a .. b loop
3173             --       ...
3174             --    end loop;
3175
3176             --  to
3177
3178             --    for xP in [reverse] integer
3179             --      range etype'Pos (a) .. etype'Pos (b)
3180             --    loop
3181             --       declare
3182             --          x : constant etype := Pos_To_Rep (xP);
3183             --       begin
3184             --          ...
3185             --       end;
3186             --    end loop;
3187
3188             elsif Is_Enumeration_Type (Btype)
3189               and then Present (Enum_Pos_To_Rep (Btype))
3190             then
3191                New_Id :=
3192                  Make_Defining_Identifier (Loc,
3193                    Chars => New_External_Name (Chars (Loop_Id), 'P'));
3194
3195                --  If the type has a contiguous representation, successive
3196                --  values can be generated as offsets from the first literal.
3197
3198                if Has_Contiguous_Rep (Btype) then
3199                   Expr :=
3200                      Unchecked_Convert_To (Btype,
3201                        Make_Op_Add (Loc,
3202                          Left_Opnd =>
3203                             Make_Integer_Literal (Loc,
3204                               Enumeration_Rep (First_Literal (Btype))),
3205                          Right_Opnd => New_Reference_To (New_Id, Loc)));
3206                else
3207                   --  Use the constructed array Enum_Pos_To_Rep
3208
3209                   Expr :=
3210                     Make_Indexed_Component (Loc,
3211                       Prefix      =>
3212                         New_Reference_To (Enum_Pos_To_Rep (Btype), Loc),
3213                       Expressions =>
3214                         New_List (New_Reference_To (New_Id, Loc)));
3215                end if;
3216
3217                Rewrite (N,
3218                  Make_Loop_Statement (Loc,
3219                    Identifier => Identifier (N),
3220
3221                    Iteration_Scheme =>
3222                      Make_Iteration_Scheme (Loc,
3223                        Loop_Parameter_Specification =>
3224                          Make_Loop_Parameter_Specification (Loc,
3225                            Defining_Identifier => New_Id,
3226                            Reverse_Present => Reverse_Present (LPS),
3227
3228                            Discrete_Subtype_Definition =>
3229                              Make_Subtype_Indication (Loc,
3230
3231                                Subtype_Mark =>
3232                                  New_Reference_To (Standard_Natural, Loc),
3233
3234                                Constraint =>
3235                                  Make_Range_Constraint (Loc,
3236                                    Range_Expression =>
3237                                      Make_Range (Loc,
3238
3239                                        Low_Bound =>
3240                                          Make_Attribute_Reference (Loc,
3241                                            Prefix =>
3242                                              New_Reference_To (Btype, Loc),
3243
3244                                            Attribute_Name => Name_Pos,
3245
3246                                            Expressions => New_List (
3247                                              Relocate_Node
3248                                                (Type_Low_Bound (Ltype)))),
3249
3250                                        High_Bound =>
3251                                          Make_Attribute_Reference (Loc,
3252                                            Prefix =>
3253                                              New_Reference_To (Btype, Loc),
3254
3255                                            Attribute_Name => Name_Pos,
3256
3257                                            Expressions => New_List (
3258                                              Relocate_Node
3259                                                (Type_High_Bound
3260                                                   (Ltype))))))))),
3261
3262                    Statements => New_List (
3263                      Make_Block_Statement (Loc,
3264                        Declarations => New_List (
3265                          Make_Object_Declaration (Loc,
3266                            Defining_Identifier => Loop_Id,
3267                            Constant_Present    => True,
3268                            Object_Definition   =>
3269                              New_Reference_To (Ltype, Loc),
3270                            Expression          => Expr)),
3271
3272                        Handled_Statement_Sequence =>
3273                          Make_Handled_Sequence_Of_Statements (Loc,
3274                            Statements => Statements (N)))),
3275
3276                    End_Label => End_Label (N)));
3277                Analyze (N);
3278
3279             --  Nothing to do with other cases of for loops
3280
3281             else
3282                null;
3283             end if;
3284          end;
3285
3286       --  Second case, if we have a while loop with Condition_Actions set, then
3287       --  we change it into a plain loop:
3288
3289       --    while C loop
3290       --       ...
3291       --    end loop;
3292
3293       --  changed to:
3294
3295       --    loop
3296       --       <<condition actions>>
3297       --       exit when not C;
3298       --       ...
3299       --    end loop
3300
3301       elsif Present (Isc)
3302         and then Present (Condition_Actions (Isc))
3303         and then Present (Condition (Isc))
3304       then
3305          declare
3306             ES : Node_Id;
3307
3308          begin
3309             ES :=
3310               Make_Exit_Statement (Sloc (Condition (Isc)),
3311                 Condition =>
3312                   Make_Op_Not (Sloc (Condition (Isc)),
3313                     Right_Opnd => Condition (Isc)));
3314
3315             Prepend (ES, Statements (N));
3316             Insert_List_Before (ES, Condition_Actions (Isc));
3317
3318             --  This is not an implicit loop, since it is generated in response
3319             --  to the loop statement being processed. If this is itself
3320             --  implicit, the restriction has already been checked. If not,
3321             --  it is an explicit loop.
3322
3323             Rewrite (N,
3324               Make_Loop_Statement (Sloc (N),
3325                 Identifier => Identifier (N),
3326                 Statements => Statements (N),
3327                 End_Label  => End_Label  (N)));
3328
3329             Analyze (N);
3330          end;
3331
3332       --  Here to deal with iterator case
3333
3334       elsif Present (Isc)
3335         and then Present (Iterator_Specification (Isc))
3336       then
3337          Expand_Iterator_Loop (N);
3338       end if;
3339    end Expand_N_Loop_Statement;
3340
3341    ----------------------------
3342    -- Expand_Predicated_Loop --
3343    ----------------------------
3344
3345    --  Note: the expander can handle generation of loops over predicated
3346    --  subtypes for both the dynamic and static cases. Depending on what
3347    --  we decide is allowed in Ada 2012 mode and/or extensions allowed
3348    --  mode, the semantic analyzer may disallow one or both forms.
3349
3350    procedure Expand_Predicated_Loop (N : Node_Id) is
3351       Loc     : constant Source_Ptr := Sloc (N);
3352       Isc     : constant Node_Id    := Iteration_Scheme (N);
3353       LPS     : constant Node_Id    := Loop_Parameter_Specification (Isc);
3354       Loop_Id : constant Entity_Id  := Defining_Identifier (LPS);
3355       Ltype   : constant Entity_Id  := Etype (Loop_Id);
3356       Stat    : constant List_Id    := Static_Predicate (Ltype);
3357       Stmts   : constant List_Id    := Statements (N);
3358
3359    begin
3360       --  Case of iteration over non-static predicate, should not be possible
3361       --  since this is not allowed by the semantics and should have been
3362       --  caught during analysis of the loop statement.
3363
3364       if No (Stat) then
3365          raise Program_Error;
3366
3367       --  If the predicate list is empty, that corresponds to a predicate of
3368       --  False, in which case the loop won't run at all, and we rewrite the
3369       --  entire loop as a null statement.
3370
3371       elsif Is_Empty_List (Stat) then
3372          Rewrite (N, Make_Null_Statement (Loc));
3373          Analyze (N);
3374
3375       --  For expansion over a static predicate we generate the following
3376
3377       --     declare
3378       --        J : Ltype := min-val;
3379       --     begin
3380       --        loop
3381       --           body
3382       --           case J is
3383       --              when endpoint => J := startpoint;
3384       --              when endpoint => J := startpoint;
3385       --              ...
3386       --              when max-val  => exit;
3387       --              when others   => J := Lval'Succ (J);
3388       --           end case;
3389       --        end loop;
3390       --     end;
3391
3392       --  To make this a little clearer, let's take a specific example:
3393
3394       --        type Int is range 1 .. 10;
3395       --        subtype L is Int with
3396       --          predicate => L in 3 | 10 | 5 .. 7;
3397       --          ...
3398       --        for L in StaticP loop
3399       --           Put_Line ("static:" & J'Img);
3400       --        end loop;
3401
3402       --  In this case, the loop is transformed into
3403
3404       --     begin
3405       --        J : L := 3;
3406       --        loop
3407       --           body
3408       --           case J is
3409       --              when 3  => J := 5;
3410       --              when 7  => J := 10;
3411       --              when 10 => exit;
3412       --              when others  => J := L'Succ (J);
3413       --           end case;
3414       --        end loop;
3415       --     end;
3416
3417       else
3418          Static_Predicate : declare
3419             S    : Node_Id;
3420             D    : Node_Id;
3421             P    : Node_Id;
3422             Alts : List_Id;
3423             Cstm : Node_Id;
3424
3425             function Lo_Val (N : Node_Id) return Node_Id;
3426             --  Given static expression or static range, returns an identifier
3427             --  whose value is the low bound of the expression value or range.
3428
3429             function Hi_Val (N : Node_Id) return Node_Id;
3430             --  Given static expression or static range, returns an identifier
3431             --  whose value is the high bound of the expression value or range.
3432
3433             ------------
3434             -- Hi_Val --
3435             ------------
3436
3437             function Hi_Val (N : Node_Id) return Node_Id is
3438             begin
3439                if Is_Static_Expression (N) then
3440                   return New_Copy (N);
3441                else
3442                   pragma Assert (Nkind (N) = N_Range);
3443                   return New_Copy (High_Bound (N));
3444                end if;
3445             end Hi_Val;
3446
3447             ------------
3448             -- Lo_Val --
3449             ------------
3450
3451             function Lo_Val (N : Node_Id) return Node_Id is
3452             begin
3453                if Is_Static_Expression (N) then
3454                   return New_Copy (N);
3455                else
3456                   pragma Assert (Nkind (N) = N_Range);
3457                   return New_Copy (Low_Bound (N));
3458                end if;
3459             end Lo_Val;
3460
3461          --  Start of processing for Static_Predicate
3462
3463          begin
3464             --  Convert loop identifier to normal variable and reanalyze it so
3465             --  that this conversion works. We have to use the same defining
3466             --  identifier, since there may be references in the loop body.
3467
3468             Set_Analyzed (Loop_Id, False);
3469             Set_Ekind    (Loop_Id, E_Variable);
3470
3471             --  Loop to create branches of case statement
3472
3473             Alts := New_List;
3474             P := First (Stat);
3475             while Present (P) loop
3476                if No (Next (P)) then
3477                   S := Make_Exit_Statement (Loc);
3478                else
3479                   S :=
3480                     Make_Assignment_Statement (Loc,
3481                       Name       => New_Occurrence_Of (Loop_Id, Loc),
3482                       Expression => Lo_Val (Next (P)));
3483                   Set_Suppress_Assignment_Checks (S);
3484                end if;
3485
3486                Append_To (Alts,
3487                  Make_Case_Statement_Alternative (Loc,
3488                    Statements       => New_List (S),
3489                    Discrete_Choices => New_List (Hi_Val (P))));
3490
3491                Next (P);
3492             end loop;
3493
3494             --  Add others choice
3495
3496             S :=
3497                Make_Assignment_Statement (Loc,
3498                  Name       => New_Occurrence_Of (Loop_Id, Loc),
3499                  Expression =>
3500                    Make_Attribute_Reference (Loc,
3501                      Prefix => New_Occurrence_Of (Ltype, Loc),
3502                      Attribute_Name => Name_Succ,
3503                      Expressions    => New_List (
3504                        New_Occurrence_Of (Loop_Id, Loc))));
3505             Set_Suppress_Assignment_Checks (S);
3506
3507             Append_To (Alts,
3508               Make_Case_Statement_Alternative (Loc,
3509                 Discrete_Choices => New_List (Make_Others_Choice (Loc)),
3510                 Statements       => New_List (S)));
3511
3512             --  Construct case statement and append to body statements
3513
3514             Cstm :=
3515               Make_Case_Statement (Loc,
3516                 Expression   => New_Occurrence_Of (Loop_Id, Loc),
3517                 Alternatives => Alts);
3518             Append_To (Stmts, Cstm);
3519
3520             --  Rewrite the loop
3521
3522             D :=
3523                Make_Object_Declaration (Loc,
3524                  Defining_Identifier => Loop_Id,
3525                  Object_Definition   => New_Occurrence_Of (Ltype, Loc),
3526                  Expression          => Lo_Val (First (Stat)));
3527             Set_Suppress_Assignment_Checks (D);
3528
3529             Rewrite (N,
3530               Make_Block_Statement (Loc,
3531                 Declarations               => New_List (D),
3532                 Handled_Statement_Sequence =>
3533                   Make_Handled_Sequence_Of_Statements (Loc,
3534                     Statements => New_List (
3535                       Make_Loop_Statement (Loc,
3536                         Statements => Stmts,
3537                         End_Label  => Empty)))));
3538
3539             Analyze (N);
3540          end Static_Predicate;
3541       end if;
3542    end Expand_Predicated_Loop;
3543
3544    ------------------------------
3545    -- Make_Tag_Ctrl_Assignment --
3546    ------------------------------
3547
3548    function Make_Tag_Ctrl_Assignment (N : Node_Id) return List_Id is
3549       Asn : constant Node_Id    := Relocate_Node (N);
3550       L   : constant Node_Id    := Name (N);
3551       Loc : constant Source_Ptr := Sloc (N);
3552       Res : constant List_Id    := New_List;
3553       T   : constant Entity_Id  := Underlying_Type (Etype (L));
3554
3555       Comp_Asn : constant Boolean := Is_Fully_Repped_Tagged_Type (T);
3556       Ctrl_Act : constant Boolean := Needs_Finalization (T)
3557                                        and then not No_Ctrl_Actions (N);
3558       Save_Tag : constant Boolean := Is_Tagged_Type (T)
3559                                        and then not Comp_Asn
3560                                        and then not No_Ctrl_Actions (N)
3561                                        and then Tagged_Type_Expansion;
3562       --  Tags are not saved and restored when VM_Target because VM tags are
3563       --  represented implicitly in objects.
3564
3565       Next_Id : Entity_Id;
3566       Prev_Id : Entity_Id;
3567       Tag_Id  : Entity_Id;
3568
3569    begin
3570       --  Finalize the target of the assignment when controlled
3571
3572       --  We have two exceptions here:
3573
3574       --   1. If we are in an init proc since it is an initialization more
3575       --      than an assignment.
3576
3577       --   2. If the left-hand side is a temporary that was not initialized
3578       --      (or the parent part of a temporary since it is the case in
3579       --      extension aggregates). Such a temporary does not come from
3580       --      source. We must examine the original node for the prefix, because
3581       --      it may be a component of an entry formal, in which case it has
3582       --      been rewritten and does not appear to come from source either.
3583
3584       --  Case of init proc
3585
3586       if not Ctrl_Act then
3587          null;
3588
3589       --  The left hand side is an uninitialized temporary object
3590
3591       elsif Nkind (L) = N_Type_Conversion
3592         and then Is_Entity_Name (Expression (L))
3593         and then Nkind (Parent (Entity (Expression (L)))) =
3594                                               N_Object_Declaration
3595         and then No_Initialization (Parent (Entity (Expression (L))))
3596       then
3597          null;
3598
3599       else
3600          Append_To (Res,
3601            Make_Final_Call
3602              (Obj_Ref => Duplicate_Subexpr_No_Checks (L),
3603               Typ     => Etype (L)));
3604       end if;
3605
3606       --  Save the Tag in a local variable Tag_Id
3607
3608       if Save_Tag then
3609          Tag_Id := Make_Temporary (Loc, 'A');
3610
3611          Append_To (Res,
3612            Make_Object_Declaration (Loc,
3613              Defining_Identifier => Tag_Id,
3614              Object_Definition   => New_Reference_To (RTE (RE_Tag), Loc),
3615              Expression          =>
3616                Make_Selected_Component (Loc,
3617                  Prefix        => Duplicate_Subexpr_No_Checks (L),
3618                  Selector_Name =>
3619                    New_Reference_To (First_Tag_Component (T), Loc))));
3620
3621       --  Otherwise Tag_Id is not used
3622
3623       else
3624          Tag_Id := Empty;
3625       end if;
3626
3627       --  Save the Prev and Next fields on .NET/JVM. This is not needed on non
3628       --  VM targets since the fields are not part of the object.
3629
3630       if VM_Target /= No_VM
3631         and then Is_Controlled (T)
3632       then
3633          Prev_Id := Make_Temporary (Loc, 'P');
3634          Next_Id := Make_Temporary (Loc, 'N');
3635
3636          --  Generate:
3637          --    Pnn : Root_Controlled_Ptr := Root_Controlled (L).Prev;
3638
3639          Append_To (Res,
3640            Make_Object_Declaration (Loc,
3641              Defining_Identifier => Prev_Id,
3642              Object_Definition   =>
3643                New_Reference_To (RTE (RE_Root_Controlled_Ptr), Loc),
3644              Expression          =>
3645                Make_Selected_Component (Loc,
3646                  Prefix        =>
3647                    Unchecked_Convert_To
3648                      (RTE (RE_Root_Controlled), New_Copy_Tree (L)),
3649                  Selector_Name =>
3650                    Make_Identifier (Loc, Name_Prev))));
3651
3652          --  Generate:
3653          --    Nnn : Root_Controlled_Ptr := Root_Controlled (L).Next;
3654
3655          Append_To (Res,
3656            Make_Object_Declaration (Loc,
3657              Defining_Identifier => Next_Id,
3658              Object_Definition   =>
3659                New_Reference_To (RTE (RE_Root_Controlled_Ptr), Loc),
3660              Expression          =>
3661                Make_Selected_Component (Loc,
3662                  Prefix        =>
3663                    Unchecked_Convert_To
3664                      (RTE (RE_Root_Controlled), New_Copy_Tree (L)),
3665                  Selector_Name =>
3666                    Make_Identifier (Loc, Name_Next))));
3667       end if;
3668
3669       --  If the tagged type has a full rep clause, expand the assignment into
3670       --  component-wise assignments. Mark the node as unanalyzed in order to
3671       --  generate the proper code and propagate this scenario by setting a
3672       --  flag to avoid infinite recursion.
3673
3674       if Comp_Asn then
3675          Set_Analyzed (Asn, False);
3676          Set_Componentwise_Assignment (Asn, True);
3677       end if;
3678
3679       Append_To (Res, Asn);
3680
3681       --  Restore the tag
3682
3683       if Save_Tag then
3684          Append_To (Res,
3685            Make_Assignment_Statement (Loc,
3686              Name       =>
3687                Make_Selected_Component (Loc,
3688                  Prefix        => Duplicate_Subexpr_No_Checks (L),
3689                  Selector_Name =>
3690                    New_Reference_To (First_Tag_Component (T), Loc)),
3691              Expression => New_Reference_To (Tag_Id, Loc)));
3692       end if;
3693
3694       --  Restore the Prev and Next fields on .NET/JVM
3695
3696       if VM_Target /= No_VM
3697         and then Is_Controlled (T)
3698       then
3699          --  Generate:
3700          --    Root_Controlled (L).Prev := Prev_Id;
3701
3702          Append_To (Res,
3703            Make_Assignment_Statement (Loc,
3704              Name       =>
3705                Make_Selected_Component (Loc,
3706                  Prefix        =>
3707                    Unchecked_Convert_To
3708                      (RTE (RE_Root_Controlled), New_Copy_Tree (L)),
3709                  Selector_Name =>
3710                    Make_Identifier (Loc, Name_Prev)),
3711              Expression => New_Reference_To (Prev_Id, Loc)));
3712
3713          --  Generate:
3714          --    Root_Controlled (L).Next := Next_Id;
3715
3716          Append_To (Res,
3717            Make_Assignment_Statement (Loc,
3718              Name       =>
3719                Make_Selected_Component (Loc,
3720                  Prefix        =>
3721                    Unchecked_Convert_To
3722                      (RTE (RE_Root_Controlled), New_Copy_Tree (L)),
3723                  Selector_Name => Make_Identifier (Loc, Name_Next)),
3724              Expression => New_Reference_To (Next_Id, Loc)));
3725       end if;
3726
3727       --  Adjust the target after the assignment when controlled (not in the
3728       --  init proc since it is an initialization more than an assignment).
3729
3730       if Ctrl_Act then
3731          Append_To (Res,
3732            Make_Adjust_Call
3733              (Obj_Ref => Duplicate_Subexpr_Move_Checks (L),
3734               Typ     => Etype (L)));
3735       end if;
3736
3737       return Res;
3738
3739    exception
3740
3741       --  Could use comment here ???
3742
3743       when RE_Not_Available =>
3744          return Empty_List;
3745    end Make_Tag_Ctrl_Assignment;
3746
3747 end Exp_Ch5;