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