ada: Remove extra parentheses
[official-gcc.git] / gcc / ada / exp_ch4.adb
blobf197c2ef570e94949461f4bbff11478f94f8d3fe
1 ------------------------------------------------------------------------------
2 -- --
3 -- GNAT COMPILER COMPONENTS --
4 -- --
5 -- E X P _ C H 4 --
6 -- --
7 -- B o d y --
8 -- --
9 -- Copyright (C) 1992-2023, 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 Accessibility; use Accessibility;
27 with Aspects; use Aspects;
28 with Atree; use Atree;
29 with Checks; use Checks;
30 with Debug; use Debug;
31 with Einfo; use Einfo;
32 with Einfo.Entities; use Einfo.Entities;
33 with Einfo.Utils; use Einfo.Utils;
34 with Elists; use Elists;
35 with Errout; use Errout;
36 with Exp_Aggr; use Exp_Aggr;
37 with Exp_Ch3; use Exp_Ch3;
38 with Exp_Ch6; use Exp_Ch6;
39 with Exp_Ch7; use Exp_Ch7;
40 with Exp_Ch9; use Exp_Ch9;
41 with Exp_Disp; use Exp_Disp;
42 with Exp_Fixd; use Exp_Fixd;
43 with Exp_Intr; use Exp_Intr;
44 with Exp_Pakd; use Exp_Pakd;
45 with Exp_Tss; use Exp_Tss;
46 with Exp_Util; use Exp_Util;
47 with Freeze; use Freeze;
48 with Inline; use Inline;
49 with Lib; use Lib;
50 with Namet; use Namet;
51 with Nlists; use Nlists;
52 with Nmake; use Nmake;
53 with Opt; use Opt;
54 with Par_SCO; use Par_SCO;
55 with Restrict; use Restrict;
56 with Rident; use Rident;
57 with Rtsfind; use Rtsfind;
58 with Sem; use Sem;
59 with Sem_Aux; use Sem_Aux;
60 with Sem_Cat; use Sem_Cat;
61 with Sem_Ch3; use Sem_Ch3;
62 with Sem_Ch13; use Sem_Ch13;
63 with Sem_Eval; use Sem_Eval;
64 with Sem_Res; use Sem_Res;
65 with Sem_Type; use Sem_Type;
66 with Sem_Util; use Sem_Util;
67 with Sem_Warn; use Sem_Warn;
68 with Sinfo; use Sinfo;
69 with Sinfo.Nodes; use Sinfo.Nodes;
70 with Sinfo.Utils; use Sinfo.Utils;
71 with Snames; use Snames;
72 with Stand; use Stand;
73 with SCIL_LL; use SCIL_LL;
74 with Targparm; use Targparm;
75 with Tbuild; use Tbuild;
76 with Ttypes; use Ttypes;
77 with Uintp; use Uintp;
78 with Urealp; use Urealp;
79 with Validsw; use Validsw;
80 with Warnsw; use Warnsw;
82 package body Exp_Ch4 is
84 Too_Large_Length_For_Array : constant Unat := Uint_256;
85 -- Threshold from which we do not try to create static array temporaries in
86 -- order to eliminate dynamic stack allocations.
88 -----------------------
89 -- Local Subprograms --
90 -----------------------
92 procedure Binary_Op_Validity_Checks (N : Node_Id);
93 pragma Inline (Binary_Op_Validity_Checks);
94 -- Performs validity checks for a binary operator
96 procedure Build_Boolean_Array_Proc_Call
97 (N : Node_Id;
98 Op1 : Node_Id;
99 Op2 : Node_Id);
100 -- If a boolean array assignment can be done in place, build call to
101 -- corresponding library procedure.
103 procedure Displace_Allocator_Pointer (N : Node_Id);
104 -- Ada 2005 (AI-251): Subsidiary procedure to Expand_N_Allocator and
105 -- Expand_Allocator_Expression. Allocating class-wide interface objects
106 -- this routine displaces the pointer to the allocated object to reference
107 -- the component referencing the corresponding secondary dispatch table.
109 procedure Expand_Allocator_Expression (N : Node_Id);
110 -- Subsidiary to Expand_N_Allocator, for the case when the expression
111 -- is a qualified expression.
113 procedure Expand_Array_Comparison (N : Node_Id);
114 -- This routine handles expansion of the comparison operators (N_Op_Lt,
115 -- N_Op_Le, N_Op_Gt, N_Op_Ge) when operating on an array type. The basic
116 -- code for these operators is similar, differing only in the details of
117 -- the actual comparison call that is made. Special processing (call a
118 -- run-time routine)
120 function Expand_Array_Equality
121 (Nod : Node_Id;
122 Lhs : Node_Id;
123 Rhs : Node_Id;
124 Bodies : List_Id;
125 Typ : Entity_Id) return Node_Id;
126 -- Expand an array equality into a call to a function implementing this
127 -- equality, and a call to it. Loc is the location for the generated nodes.
128 -- Lhs and Rhs are the array expressions to be compared. Bodies is a list
129 -- on which to attach bodies of local functions that are created in the
130 -- process. It is the responsibility of the caller to insert those bodies
131 -- at the right place. Nod provides the Sloc value for the generated code.
132 -- Normally the types used for the generated equality routine are taken
133 -- from Lhs and Rhs. However, in some situations of generated code, the
134 -- Etype fields of Lhs and Rhs are not set yet. In such cases, Typ supplies
135 -- the type to be used for the formal parameters.
137 procedure Expand_Boolean_Operator (N : Node_Id);
138 -- Common expansion processing for Boolean operators (And, Or, Xor) for the
139 -- case of array type arguments.
141 procedure Expand_Nonbinary_Modular_Op (N : Node_Id);
142 -- When generating C code, convert nonbinary modular arithmetic operations
143 -- into code that relies on the front-end expansion of operator Mod. No
144 -- expansion is performed if N is not a nonbinary modular operand.
146 procedure Expand_Short_Circuit_Operator (N : Node_Id);
147 -- Common expansion processing for short-circuit boolean operators
149 procedure Expand_Compare_Minimize_Eliminate_Overflow (N : Node_Id);
150 -- Deal with comparison in MINIMIZED/ELIMINATED overflow mode. This is
151 -- where we allow comparison of "out of range" values.
153 function Expand_Composite_Equality
154 (Outer_Type : Entity_Id;
155 Nod : Node_Id;
156 Comp_Type : Entity_Id;
157 Lhs : Node_Id;
158 Rhs : Node_Id) return Node_Id;
159 -- Local recursive function used to expand equality for nested composite
160 -- types. Used by Expand_Record/Array_Equality. Nod provides the Sloc value
161 -- for generated code. Lhs and Rhs are the left and right sides for the
162 -- comparison, and Comp_Typ is the type of the objects to compare.
163 -- Outer_Type is the composite type containing a component of type
164 -- Comp_Type -- used for printing messages.
166 procedure Expand_Concatenate (Cnode : Node_Id; Opnds : List_Id);
167 -- Routine to expand concatenation of a sequence of two or more operands
168 -- (in the list Operands) and replace node Cnode with the result of the
169 -- concatenation. The operands can be of any appropriate type, and can
170 -- include both arrays and singleton elements.
172 procedure Expand_Membership_Minimize_Eliminate_Overflow (N : Node_Id);
173 -- N is an N_In membership test mode, with the overflow check mode set to
174 -- MINIMIZED or ELIMINATED, and the type of the left operand is a signed
175 -- integer type. This is a case where top level processing is required to
176 -- handle overflow checks in subtrees.
178 procedure Fixup_Universal_Fixed_Operation (N : Node_Id);
179 -- N is a N_Op_Divide or N_Op_Multiply node whose result is universal
180 -- fixed. We do not have such a type at runtime, so the purpose of this
181 -- routine is to find the real type by looking up the tree. We also
182 -- determine if the operation must be rounded.
184 procedure Get_First_Index_Bounds (T : Entity_Id; Lo, Hi : out Uint);
185 -- T is an array whose index bounds are all known at compile time. Return
186 -- the value of the low and high bounds of the first index of T.
188 function Get_Size_For_Range (Lo, Hi : Uint) return Uint;
189 -- Return the size of a small signed integer type covering Lo .. Hi, the
190 -- main goal being to return a size lower than that of standard types.
192 procedure Insert_Dereference_Action (N : Node_Id);
193 -- N is an expression whose type is an access. When the type of the
194 -- associated storage pool is derived from Checked_Pool, generate a
195 -- call to the 'Dereference' primitive operation.
197 function Make_Array_Comparison_Op
198 (Typ : Entity_Id;
199 Nod : Node_Id) return Node_Id;
200 -- Comparisons between arrays are expanded in line. This function produces
201 -- the body of the implementation of (a > b), where a and b are one-
202 -- dimensional arrays of some discrete type. The original node is then
203 -- expanded into the appropriate call to this function. Nod provides the
204 -- Sloc value for the generated code.
206 function Make_Boolean_Array_Op
207 (Typ : Entity_Id;
208 N : Node_Id) return Node_Id;
209 -- Boolean operations on boolean arrays are expanded in line. This function
210 -- produce the body for the node N, which is (a and b), (a or b), or (a xor
211 -- b). It is used only the normal case and not the packed case. The type
212 -- involved, Typ, is the Boolean array type, and the logical operations in
213 -- the body are simple boolean operations. Note that Typ is always a
214 -- constrained type (the caller has ensured this by using
215 -- Convert_To_Actual_Subtype if necessary).
217 function Minimized_Eliminated_Overflow_Check (N : Node_Id) return Boolean;
218 -- For signed arithmetic operations when the current overflow mode is
219 -- MINIMIZED or ELIMINATED, we must call Apply_Arithmetic_Overflow_Checks
220 -- as the first thing we do. We then return. We count on the recursive
221 -- apparatus for overflow checks to call us back with an equivalent
222 -- operation that is in CHECKED mode, avoiding a recursive entry into this
223 -- routine, and that is when we will proceed with the expansion of the
224 -- operator (e.g. converting X+0 to X, or X**2 to X*X). We cannot do
225 -- these optimizations without first making this check, since there may be
226 -- operands further down the tree that are relying on the recursive calls
227 -- triggered by the top level nodes to properly process overflow checking
228 -- and remaining expansion on these nodes. Note that this call back may be
229 -- skipped if the operation is done in Bignum mode but that's fine, since
230 -- the Bignum call takes care of everything.
232 procedure Narrow_Large_Operation (N : Node_Id);
233 -- Try to compute the result of a large operation in a narrower type than
234 -- its nominal type. This is mainly aimed at getting rid of operations done
235 -- in Universal_Integer that can be generated for attributes.
237 procedure Optimize_Length_Comparison (N : Node_Id);
238 -- Given an expression, if it is of the form X'Length op N (or the other
239 -- way round), where N is known at compile time to be 0 or 1, or something
240 -- else where the value is known to be nonnegative and in the 32-bit range,
241 -- and X is a simple entity, and op is a comparison operator, optimizes it
242 -- into a comparison of X'First and X'Last.
244 procedure Process_If_Case_Statements (N : Node_Id; Stmts : List_Id);
245 -- Inspect and process statement list Stmt of if or case expression N for
246 -- transient objects. If such objects are found, the routine generates code
247 -- to clean them up when the context of the expression is evaluated.
249 procedure Process_Transient_In_Expression
250 (Obj_Decl : Node_Id;
251 Expr : Node_Id;
252 Stmts : List_Id);
253 -- Subsidiary routine to the expansion of expression_with_actions, if and
254 -- case expressions. Generate all necessary code to finalize a transient
255 -- object when the enclosing context is elaborated or evaluated. Obj_Decl
256 -- denotes the declaration of the transient object, which is usually the
257 -- result of a controlled function call. Expr denotes the expression with
258 -- actions, if expression, or case expression node. Stmts denotes the
259 -- statement list which contains Decl, either at the top level or within a
260 -- nested construct.
262 procedure Rewrite_Comparison (N : Node_Id);
263 -- If N is the node for a comparison whose outcome can be determined at
264 -- compile time, then the node N can be rewritten with True or False. If
265 -- the outcome cannot be determined at compile time, the call has no
266 -- effect. If N is a type conversion, then this processing is applied to
267 -- its expression. If N is neither comparison nor a type conversion, the
268 -- call has no effect.
270 procedure Tagged_Membership
271 (N : Node_Id;
272 SCIL_Node : out Node_Id;
273 Result : out Node_Id);
274 -- Construct the expression corresponding to the tagged membership test.
275 -- Deals with a second operand being (or not) a class-wide type.
277 function Safe_In_Place_Array_Op
278 (Lhs : Node_Id;
279 Op1 : Node_Id;
280 Op2 : Node_Id) return Boolean;
281 -- In the context of an assignment, where the right-hand side is a boolean
282 -- operation on arrays, check whether operation can be performed in place.
284 procedure Unary_Op_Validity_Checks (N : Node_Id);
285 pragma Inline (Unary_Op_Validity_Checks);
286 -- Performs validity checks for a unary operator
288 -------------------------------
289 -- Binary_Op_Validity_Checks --
290 -------------------------------
292 procedure Binary_Op_Validity_Checks (N : Node_Id) is
293 begin
294 if Validity_Checks_On and Validity_Check_Operands then
295 Ensure_Valid (Left_Opnd (N));
296 Ensure_Valid (Right_Opnd (N));
297 end if;
298 end Binary_Op_Validity_Checks;
300 ------------------------------------
301 -- Build_Boolean_Array_Proc_Call --
302 ------------------------------------
304 procedure Build_Boolean_Array_Proc_Call
305 (N : Node_Id;
306 Op1 : Node_Id;
307 Op2 : Node_Id)
309 Loc : constant Source_Ptr := Sloc (N);
310 Kind : constant Node_Kind := Nkind (Expression (N));
311 Target : constant Node_Id :=
312 Make_Attribute_Reference (Loc,
313 Prefix => Name (N),
314 Attribute_Name => Name_Address);
316 Arg1 : Node_Id := Op1;
317 Arg2 : Node_Id := Op2;
318 Call_Node : Node_Id;
319 Proc_Name : Entity_Id;
321 begin
322 if Kind = N_Op_Not then
323 if Nkind (Op1) in N_Binary_Op then
325 -- Use negated version of the binary operators
327 if Nkind (Op1) = N_Op_And then
328 Proc_Name := RTE (RE_Vector_Nand);
330 elsif Nkind (Op1) = N_Op_Or then
331 Proc_Name := RTE (RE_Vector_Nor);
333 else pragma Assert (Nkind (Op1) = N_Op_Xor);
334 Proc_Name := RTE (RE_Vector_Xor);
335 end if;
337 Call_Node :=
338 Make_Procedure_Call_Statement (Loc,
339 Name => New_Occurrence_Of (Proc_Name, Loc),
341 Parameter_Associations => New_List (
342 Target,
343 Make_Attribute_Reference (Loc,
344 Prefix => Left_Opnd (Op1),
345 Attribute_Name => Name_Address),
347 Make_Attribute_Reference (Loc,
348 Prefix => Right_Opnd (Op1),
349 Attribute_Name => Name_Address),
351 Make_Attribute_Reference (Loc,
352 Prefix => Left_Opnd (Op1),
353 Attribute_Name => Name_Length)));
355 else
356 Proc_Name := RTE (RE_Vector_Not);
358 Call_Node :=
359 Make_Procedure_Call_Statement (Loc,
360 Name => New_Occurrence_Of (Proc_Name, Loc),
361 Parameter_Associations => New_List (
362 Target,
364 Make_Attribute_Reference (Loc,
365 Prefix => Op1,
366 Attribute_Name => Name_Address),
368 Make_Attribute_Reference (Loc,
369 Prefix => Op1,
370 Attribute_Name => Name_Length)));
371 end if;
373 else
374 -- We use the following equivalences:
376 -- (not X) or (not Y) = not (X and Y) = Nand (X, Y)
377 -- (not X) and (not Y) = not (X or Y) = Nor (X, Y)
378 -- (not X) xor (not Y) = X xor Y
379 -- X xor (not Y) = not (X xor Y) = Nxor (X, Y)
381 if Nkind (Op1) = N_Op_Not then
382 Arg1 := Right_Opnd (Op1);
383 Arg2 := Right_Opnd (Op2);
385 if Kind = N_Op_And then
386 Proc_Name := RTE (RE_Vector_Nor);
387 elsif Kind = N_Op_Or then
388 Proc_Name := RTE (RE_Vector_Nand);
389 else
390 Proc_Name := RTE (RE_Vector_Xor);
391 end if;
393 else
394 if Kind = N_Op_And then
395 Proc_Name := RTE (RE_Vector_And);
396 elsif Kind = N_Op_Or then
397 Proc_Name := RTE (RE_Vector_Or);
398 elsif Nkind (Op2) = N_Op_Not then
399 Proc_Name := RTE (RE_Vector_Nxor);
400 Arg2 := Right_Opnd (Op2);
401 else
402 Proc_Name := RTE (RE_Vector_Xor);
403 end if;
404 end if;
406 Call_Node :=
407 Make_Procedure_Call_Statement (Loc,
408 Name => New_Occurrence_Of (Proc_Name, Loc),
409 Parameter_Associations => New_List (
410 Target,
411 Make_Attribute_Reference (Loc,
412 Prefix => Arg1,
413 Attribute_Name => Name_Address),
414 Make_Attribute_Reference (Loc,
415 Prefix => Arg2,
416 Attribute_Name => Name_Address),
417 Make_Attribute_Reference (Loc,
418 Prefix => Arg1,
419 Attribute_Name => Name_Length)));
420 end if;
422 Rewrite (N, Call_Node);
423 Analyze (N);
425 exception
426 when RE_Not_Available =>
427 return;
428 end Build_Boolean_Array_Proc_Call;
430 -----------------------
431 -- Build_Eq_Call --
432 -----------------------
434 function Build_Eq_Call
435 (Typ : Entity_Id;
436 Loc : Source_Ptr;
437 Lhs : Node_Id;
438 Rhs : Node_Id) return Node_Id
440 Eq : constant Entity_Id := Get_User_Defined_Equality (Typ);
442 begin
443 if Present (Eq) then
444 if Is_Abstract_Subprogram (Eq) then
445 return Make_Raise_Program_Error (Loc,
446 Reason => PE_Explicit_Raise);
448 else
449 return
450 Make_Function_Call (Loc,
451 Name => New_Occurrence_Of (Eq, Loc),
452 Parameter_Associations => New_List (Lhs, Rhs));
453 end if;
454 end if;
456 -- If not found, predefined operation will be used
458 return Empty;
459 end Build_Eq_Call;
461 --------------------------------
462 -- Displace_Allocator_Pointer --
463 --------------------------------
465 procedure Displace_Allocator_Pointer (N : Node_Id) is
466 Loc : constant Source_Ptr := Sloc (N);
467 Orig_Node : constant Node_Id := Original_Node (N);
468 Dtyp : Entity_Id;
469 Etyp : Entity_Id;
470 PtrT : Entity_Id;
472 begin
473 -- Do nothing in case of VM targets: the virtual machine will handle
474 -- interfaces directly.
476 if not Tagged_Type_Expansion then
477 return;
478 end if;
480 pragma Assert (Nkind (N) = N_Identifier
481 and then Nkind (Orig_Node) = N_Allocator);
483 PtrT := Etype (Orig_Node);
484 Dtyp := Available_View (Designated_Type (PtrT));
485 Etyp := Etype (Expression (Orig_Node));
487 if Is_Class_Wide_Type (Dtyp) and then Is_Interface (Dtyp) then
489 -- If the type of the allocator expression is not an interface type
490 -- we can generate code to reference the record component containing
491 -- the pointer to the secondary dispatch table.
493 if not Is_Interface (Etyp) then
494 declare
495 Saved_Typ : constant Entity_Id := Etype (Orig_Node);
497 begin
498 -- 1) Get access to the allocated object
500 Rewrite (N,
501 Make_Explicit_Dereference (Loc, Relocate_Node (N)));
502 Set_Etype (N, Etyp);
503 Set_Analyzed (N);
505 -- 2) Add the conversion to displace the pointer to reference
506 -- the secondary dispatch table.
508 Rewrite (N, Convert_To (Dtyp, Relocate_Node (N)));
509 Analyze_And_Resolve (N, Dtyp);
511 -- 3) The 'access to the secondary dispatch table will be used
512 -- as the value returned by the allocator.
514 Rewrite (N,
515 Make_Attribute_Reference (Loc,
516 Prefix => Relocate_Node (N),
517 Attribute_Name => Name_Access));
518 Set_Etype (N, Saved_Typ);
519 Set_Analyzed (N);
520 end;
522 -- If the type of the allocator expression is an interface type we
523 -- generate a run-time call to displace "this" to reference the
524 -- component containing the pointer to the secondary dispatch table
525 -- or else raise Constraint_Error if the actual object does not
526 -- implement the target interface. This case corresponds to the
527 -- following example:
529 -- function Op (Obj : Iface_1'Class) return access Iface_2'Class is
530 -- begin
531 -- return new Iface_2'Class'(Obj);
532 -- end Op;
534 else
535 Rewrite (N,
536 Unchecked_Convert_To (PtrT,
537 Make_Function_Call (Loc,
538 Name => New_Occurrence_Of (RTE (RE_Displace), Loc),
539 Parameter_Associations => New_List (
540 Unchecked_Convert_To (RTE (RE_Address),
541 Relocate_Node (N)),
543 New_Occurrence_Of
544 (Elists.Node
545 (First_Elmt
546 (Access_Disp_Table (Etype (Base_Type (Dtyp))))),
547 Loc)))));
548 Analyze_And_Resolve (N, PtrT);
549 end if;
550 end if;
551 end Displace_Allocator_Pointer;
553 ---------------------------------
554 -- Expand_Allocator_Expression --
555 ---------------------------------
557 procedure Expand_Allocator_Expression (N : Node_Id) is
558 Loc : constant Source_Ptr := Sloc (N);
559 Exp : constant Node_Id := Expression (Expression (N));
560 PtrT : constant Entity_Id := Etype (N);
561 DesigT : constant Entity_Id := Designated_Type (PtrT);
563 -- Local variables
565 Indic : constant Node_Id := Subtype_Mark (Expression (N));
566 T : constant Entity_Id := Entity (Indic);
567 Adj_Call : Node_Id;
568 Aggr_In_Place : Boolean;
569 Node : Node_Id;
570 Tag_Assign : Node_Id;
571 Temp : Entity_Id;
572 Temp_Decl : Node_Id;
574 TagT : Entity_Id := Empty;
575 -- Type used as source for tag assignment
577 TagR : Node_Id := Empty;
578 -- Target reference for tag assignment
580 -- Start of processing for Expand_Allocator_Expression
582 begin
583 -- Handle call to C++ constructor
585 if Is_CPP_Constructor_Call (Exp) then
586 Make_CPP_Constructor_Call_In_Allocator
587 (Allocator => N,
588 Function_Call => Exp);
589 return;
590 end if;
592 -- If we have:
593 -- type A is access T1;
594 -- X : A := new T2'(...);
595 -- T1 and T2 can be different subtypes, and we might need to check
596 -- both constraints. First check against the type of the qualified
597 -- expression.
599 Apply_Constraint_Check (Exp, T, No_Sliding => True);
601 Apply_Predicate_Check (Exp, T);
603 -- Check that any anonymous access discriminants are suitable
604 -- for use in an allocator.
606 -- Note: This check is performed here instead of during analysis so that
607 -- we can check against the fully resolved etype of Exp.
609 if Is_Entity_Name (Exp)
610 and then Has_Anonymous_Access_Discriminant (Etype (Exp))
611 and then Static_Accessibility_Level (Exp, Object_Decl_Level)
612 > Static_Accessibility_Level (N, Object_Decl_Level)
613 then
614 -- A dynamic check and a warning are generated when we are within
615 -- an instance.
617 if In_Instance then
618 Insert_Action (N,
619 Make_Raise_Program_Error (Loc,
620 Reason => PE_Accessibility_Check_Failed));
622 Error_Msg_Warn := SPARK_Mode /= On;
623 Error_Msg_N ("anonymous access discriminant is too deep for use"
624 & " in allocator<<", N);
625 Error_Msg_N ("\Program_Error [<<", N);
627 -- Otherwise, make the error static
629 else
630 Error_Msg_N ("anonymous access discriminant is too deep for use"
631 & " in allocator", N);
632 end if;
633 end if;
635 if Do_Range_Check (Exp) then
636 Generate_Range_Check (Exp, T, CE_Range_Check_Failed);
637 end if;
639 -- A check is also needed in cases where the designated subtype is
640 -- constrained and differs from the subtype given in the qualified
641 -- expression. Note that the check on the qualified expression does
642 -- not allow sliding, but this check does (a relaxation from Ada 83).
644 if Is_Constrained (DesigT)
645 and then not Subtypes_Statically_Match (T, DesigT)
646 then
647 Apply_Constraint_Check (Exp, DesigT, No_Sliding => False);
649 Apply_Predicate_Check (Exp, DesigT);
651 if Do_Range_Check (Exp) then
652 Generate_Range_Check (Exp, DesigT, CE_Range_Check_Failed);
653 end if;
654 end if;
656 if Nkind (Exp) = N_Raise_Constraint_Error then
657 Rewrite (N, New_Copy (Exp));
658 Set_Etype (N, PtrT);
659 return;
660 end if;
662 Aggr_In_Place := Is_Delayed_Aggregate (Exp);
664 -- Case of tagged type or type requiring finalization
666 if Is_Tagged_Type (T) or else Needs_Finalization (T) then
668 -- Ada 2005 (AI-318-02): If the initialization expression is a call
669 -- to a build-in-place function, then access to the allocated object
670 -- must be passed to the function.
672 if Is_Build_In_Place_Function_Call (Exp) then
673 Make_Build_In_Place_Call_In_Allocator (N, Exp);
674 Apply_Accessibility_Check_For_Allocator
675 (N, Exp, N, Built_In_Place => True);
676 return;
678 -- Ada 2005 (AI-318-02): Specialization of the previous case for
679 -- expressions containing a build-in-place function call whose
680 -- returned object covers interface types, and Expr has calls to
681 -- Ada.Tags.Displace to displace the pointer to the returned build-
682 -- in-place object to reference the secondary dispatch table of a
683 -- covered interface type.
685 elsif Present (Unqual_BIP_Iface_Function_Call (Exp)) then
686 Make_Build_In_Place_Iface_Call_In_Allocator (N, Exp);
687 Apply_Accessibility_Check_For_Allocator
688 (N, Exp, N, Built_In_Place => True);
689 return;
690 end if;
692 -- Actions inserted before:
693 -- Temp : constant ptr_T := new T'(Expression);
694 -- Temp._tag = T'tag; -- when not class-wide
695 -- [Deep_]Adjust (Temp.all);
697 -- We analyze by hand the new internal allocator to avoid any
698 -- recursion and inappropriate call to Initialize.
700 -- We don't want to remove side effects when the expression must be
701 -- built in place and we don't need it when there is no storage pool
702 -- or this is a return/secondary stack allocation.
704 if not Aggr_In_Place
705 and then Present (Storage_Pool (N))
706 and then not Is_RTE (Storage_Pool (N), RE_RS_Pool)
707 and then not Is_RTE (Storage_Pool (N), RE_SS_Pool)
708 then
709 Remove_Side_Effects (Exp);
710 end if;
712 Temp := Make_Temporary (Loc, 'P', N);
714 -- For a class wide allocation generate the following code:
716 -- type Equiv_Record is record ... end record;
717 -- implicit subtype CW is <Class_Wide_Subytpe>;
718 -- temp : PtrT := new CW'(CW!(expr));
720 if Is_Class_Wide_Type (T) then
721 Expand_Subtype_From_Expr (Empty, T, Indic, Exp);
723 -- Ada 2005 (AI-251): If the expression is a class-wide interface
724 -- object we generate code to move up "this" to reference the
725 -- base of the object before allocating the new object.
727 -- Note that Exp'Address is recursively expanded into a call
728 -- to Base_Address (Exp.Tag)
730 if Is_Class_Wide_Type (Etype (Exp))
731 and then Is_Interface (Etype (Exp))
732 and then Tagged_Type_Expansion
733 then
734 Set_Expression
735 (Expression (N),
736 Unchecked_Convert_To (Entity (Indic),
737 Make_Explicit_Dereference (Loc,
738 Unchecked_Convert_To (RTE (RE_Tag_Ptr),
739 Make_Attribute_Reference (Loc,
740 Prefix => Exp,
741 Attribute_Name => Name_Address)))));
742 else
743 Set_Expression
744 (Expression (N),
745 Unchecked_Convert_To (Entity (Indic), Exp));
746 end if;
748 Analyze_And_Resolve (Expression (N), Entity (Indic));
749 end if;
751 -- Processing for allocators returning non-interface types
753 if not Is_Interface (DesigT) then
754 if Aggr_In_Place then
755 Temp_Decl :=
756 Make_Object_Declaration (Loc,
757 Defining_Identifier => Temp,
758 Object_Definition => New_Occurrence_Of (PtrT, Loc),
759 Expression =>
760 Make_Allocator (Loc,
761 Expression =>
762 New_Occurrence_Of (Etype (Exp), Loc)));
764 -- Copy the Comes_From_Source flag for the allocator we just
765 -- built, since logically this allocator is a replacement of
766 -- the original allocator node. This is for proper handling of
767 -- restriction No_Implicit_Heap_Allocations.
769 Preserve_Comes_From_Source
770 (Expression (Temp_Decl), N);
772 Set_No_Initialization (Expression (Temp_Decl));
773 Insert_Action (N, Temp_Decl);
775 Build_Allocate_Deallocate_Proc (Temp_Decl, True);
776 Convert_Aggr_In_Allocator (N, Temp_Decl, Exp);
778 else
779 Node := Relocate_Node (N);
780 Set_Analyzed (Node);
782 Temp_Decl :=
783 Make_Object_Declaration (Loc,
784 Defining_Identifier => Temp,
785 Constant_Present => True,
786 Object_Definition => New_Occurrence_Of (PtrT, Loc),
787 Expression => Node);
789 Insert_Action (N, Temp_Decl);
790 Build_Allocate_Deallocate_Proc (Temp_Decl, True);
791 end if;
793 -- Ada 2005 (AI-251): Handle allocators whose designated type is an
794 -- interface type. In this case we use the type of the qualified
795 -- expression to allocate the object.
797 else
798 declare
799 Def_Id : constant Entity_Id := Make_Temporary (Loc, 'T');
800 New_Decl : Node_Id;
802 begin
803 New_Decl :=
804 Make_Full_Type_Declaration (Loc,
805 Defining_Identifier => Def_Id,
806 Type_Definition =>
807 Make_Access_To_Object_Definition (Loc,
808 All_Present => True,
809 Null_Exclusion_Present => False,
810 Constant_Present =>
811 Is_Access_Constant (Etype (N)),
812 Subtype_Indication =>
813 New_Occurrence_Of (Etype (Exp), Loc)));
815 Insert_Action (N, New_Decl);
817 -- Inherit the allocation-related attributes from the original
818 -- access type.
820 Set_Finalization_Master
821 (Def_Id, Finalization_Master (PtrT));
823 Set_Associated_Storage_Pool
824 (Def_Id, Associated_Storage_Pool (PtrT));
826 -- Declare the object using the previous type declaration
828 if Aggr_In_Place then
829 Temp_Decl :=
830 Make_Object_Declaration (Loc,
831 Defining_Identifier => Temp,
832 Object_Definition => New_Occurrence_Of (Def_Id, Loc),
833 Expression =>
834 Make_Allocator (Loc,
835 New_Occurrence_Of (Etype (Exp), Loc)));
837 -- Copy the Comes_From_Source flag for the allocator we just
838 -- built, since logically this allocator is a replacement of
839 -- the original allocator node. This is for proper handling
840 -- of restriction No_Implicit_Heap_Allocations.
842 Set_Comes_From_Source
843 (Expression (Temp_Decl), Comes_From_Source (N));
845 Set_No_Initialization (Expression (Temp_Decl));
846 Insert_Action (N, Temp_Decl);
848 Build_Allocate_Deallocate_Proc (Temp_Decl, True);
849 Convert_Aggr_In_Allocator (N, Temp_Decl, Exp);
851 else
852 Node := Relocate_Node (N);
853 Set_Analyzed (Node);
855 Temp_Decl :=
856 Make_Object_Declaration (Loc,
857 Defining_Identifier => Temp,
858 Constant_Present => True,
859 Object_Definition => New_Occurrence_Of (Def_Id, Loc),
860 Expression => Node);
862 Insert_Action (N, Temp_Decl);
863 Build_Allocate_Deallocate_Proc (Temp_Decl, True);
864 end if;
866 -- Generate an additional object containing the address of the
867 -- returned object. The type of this second object declaration
868 -- is the correct type required for the common processing that
869 -- is still performed by this subprogram. The displacement of
870 -- this pointer to reference the component associated with the
871 -- interface type will be done at the end of common processing.
873 New_Decl :=
874 Make_Object_Declaration (Loc,
875 Defining_Identifier => Make_Temporary (Loc, 'P'),
876 Object_Definition => New_Occurrence_Of (PtrT, Loc),
877 Expression =>
878 Unchecked_Convert_To (PtrT,
879 New_Occurrence_Of (Temp, Loc)));
881 Insert_Action (N, New_Decl);
883 Temp_Decl := New_Decl;
884 Temp := Defining_Identifier (New_Decl);
885 end;
886 end if;
888 -- Generate the tag assignment
890 -- Suppress the tag assignment for VM targets because VM tags are
891 -- represented implicitly in objects.
893 if not Tagged_Type_Expansion then
894 null;
896 -- Ada 2005 (AI-251): Suppress the tag assignment with class-wide
897 -- interface objects because in this case the tag does not change.
899 elsif Is_Interface (Directly_Designated_Type (Etype (N))) then
900 pragma Assert (Is_Class_Wide_Type
901 (Directly_Designated_Type (Etype (N))));
902 null;
904 -- Likewise if the allocator is made for a special return object
906 elsif For_Special_Return_Object (N) then
907 null;
909 elsif Is_Tagged_Type (T) and then not Is_Class_Wide_Type (T) then
910 TagT := T;
911 TagR :=
912 Make_Explicit_Dereference (Loc,
913 Prefix => New_Occurrence_Of (Temp, Loc));
915 elsif Is_Private_Type (T)
916 and then Is_Tagged_Type (Underlying_Type (T))
917 then
918 TagT := Underlying_Type (T);
919 TagR :=
920 Unchecked_Convert_To (Underlying_Type (T),
921 Make_Explicit_Dereference (Loc,
922 Prefix => New_Occurrence_Of (Temp, Loc)));
923 end if;
925 if Present (TagT) then
926 declare
927 Full_T : constant Entity_Id := Underlying_Type (TagT);
929 begin
930 Tag_Assign :=
931 Make_Assignment_Statement (Loc,
932 Name =>
933 Make_Selected_Component (Loc,
934 Prefix => TagR,
935 Selector_Name =>
936 New_Occurrence_Of
937 (First_Tag_Component (Full_T), Loc)),
939 Expression =>
940 Unchecked_Convert_To (RTE (RE_Tag),
941 New_Occurrence_Of
942 (Elists.Node
943 (First_Elmt (Access_Disp_Table (Full_T))), Loc)));
944 end;
946 -- The previous assignment has to be done in any case
948 Set_Assignment_OK (Name (Tag_Assign));
949 Insert_Action (N, Tag_Assign);
950 end if;
952 -- Generate an Adjust call if the object will be moved. In Ada 2005,
953 -- the object may be inherently limited, in which case there is no
954 -- Adjust procedure, and the object is built in place. In Ada 95, the
955 -- object can be limited but not inherently limited if this allocator
956 -- came from a return statement (we're allocating the result on the
957 -- secondary stack); in that case, the object will be moved, so we do
958 -- want to Adjust. But the call is always skipped if the allocator is
959 -- made for a special return object because it's generated elsewhere.
961 -- Needs_Finalization (DesigT) may differ from Needs_Finalization (T)
962 -- if one of the two types is class-wide, and the other is not.
964 if Needs_Finalization (DesigT)
965 and then Needs_Finalization (T)
966 and then not Is_Limited_View (T)
967 and then not Aggr_In_Place
968 and then Nkind (Exp) /= N_Function_Call
969 and then not For_Special_Return_Object (N)
970 then
971 -- An unchecked conversion is needed in the classwide case because
972 -- the designated type can be an ancestor of the subtype mark of
973 -- the allocator.
975 Adj_Call :=
976 Make_Adjust_Call
977 (Obj_Ref =>
978 Unchecked_Convert_To (T,
979 Make_Explicit_Dereference (Loc,
980 Prefix => New_Occurrence_Of (Temp, Loc))),
981 Typ => T);
983 if Present (Adj_Call) then
984 Insert_Action (N, Adj_Call);
985 end if;
986 end if;
988 -- Note: the accessibility check must be inserted after the call to
989 -- [Deep_]Adjust to ensure proper completion of the assignment.
991 Apply_Accessibility_Check_For_Allocator (N, Exp, Temp);
993 Rewrite (N, New_Occurrence_Of (Temp, Loc));
994 Analyze_And_Resolve (N, PtrT);
996 -- Ada 2005 (AI-251): Displace the pointer to reference the record
997 -- component containing the secondary dispatch table of the interface
998 -- type.
1000 if Is_Interface (DesigT) then
1001 Displace_Allocator_Pointer (N);
1002 end if;
1004 -- Always force the generation of a temporary for aggregates when
1005 -- generating C code, to simplify the work in the code generator.
1007 elsif Aggr_In_Place
1008 or else (Modify_Tree_For_C and then Nkind (Exp) = N_Aggregate)
1009 then
1010 Temp := Make_Temporary (Loc, 'P', N);
1011 Temp_Decl :=
1012 Make_Object_Declaration (Loc,
1013 Defining_Identifier => Temp,
1014 Object_Definition => New_Occurrence_Of (PtrT, Loc),
1015 Expression =>
1016 Make_Allocator (Loc,
1017 Expression => New_Occurrence_Of (Etype (Exp), Loc)));
1019 -- Copy the Comes_From_Source flag for the allocator we just built,
1020 -- since logically this allocator is a replacement of the original
1021 -- allocator node. This is for proper handling of restriction
1022 -- No_Implicit_Heap_Allocations.
1024 Set_Comes_From_Source
1025 (Expression (Temp_Decl), Comes_From_Source (N));
1027 Set_No_Initialization (Expression (Temp_Decl));
1028 Insert_Action (N, Temp_Decl);
1030 Build_Allocate_Deallocate_Proc (Temp_Decl, True);
1031 Convert_Aggr_In_Allocator (N, Temp_Decl, Exp);
1033 Rewrite (N, New_Occurrence_Of (Temp, Loc));
1034 Analyze_And_Resolve (N, PtrT);
1036 elsif Is_Access_Type (T) and then Can_Never_Be_Null (T) then
1037 Install_Null_Excluding_Check (Exp);
1039 elsif Is_Access_Type (DesigT)
1040 and then Nkind (Exp) = N_Allocator
1041 and then Nkind (Expression (Exp)) /= N_Qualified_Expression
1042 then
1043 -- Apply constraint to designated subtype indication
1045 Apply_Constraint_Check
1046 (Expression (Exp), Designated_Type (DesigT), No_Sliding => True);
1048 if Nkind (Expression (Exp)) = N_Raise_Constraint_Error then
1050 -- Propagate constraint_error to enclosing allocator
1052 Rewrite (Exp, New_Copy (Expression (Exp)));
1053 end if;
1055 else
1056 Build_Allocate_Deallocate_Proc (N, True);
1058 -- For an access to unconstrained packed array, GIGI needs to see an
1059 -- expression with a constrained subtype in order to compute the
1060 -- proper size for the allocator.
1062 if Is_Packed_Array (T)
1063 and then not Is_Constrained (T)
1064 then
1065 declare
1066 ConstrT : constant Entity_Id := Make_Temporary (Loc, 'A');
1067 Internal_Exp : constant Node_Id := Relocate_Node (Exp);
1068 begin
1069 Insert_Action (Exp,
1070 Make_Subtype_Declaration (Loc,
1071 Defining_Identifier => ConstrT,
1072 Subtype_Indication =>
1073 Make_Subtype_From_Expr (Internal_Exp, T)));
1074 Freeze_Itype (ConstrT, Exp);
1075 Rewrite (Exp, OK_Convert_To (ConstrT, Internal_Exp));
1076 end;
1077 end if;
1079 -- Ada 2005 (AI-318-02): If the initialization expression is a call
1080 -- to a build-in-place function, then access to the allocated object
1081 -- must be passed to the function.
1083 if Is_Build_In_Place_Function_Call (Exp) then
1084 Make_Build_In_Place_Call_In_Allocator (N, Exp);
1085 end if;
1086 end if;
1088 exception
1089 when RE_Not_Available =>
1090 return;
1091 end Expand_Allocator_Expression;
1093 -----------------------------
1094 -- Expand_Array_Comparison --
1095 -----------------------------
1097 -- Expansion is only required in the case of array types. For the unpacked
1098 -- case, an appropriate runtime routine is called. For packed cases, and
1099 -- also in some other cases where a runtime routine cannot be called, the
1100 -- form of the expansion is:
1102 -- [body for greater_nn; boolean_expression]
1104 -- The body is built by Make_Array_Comparison_Op, and the form of the
1105 -- Boolean expression depends on the operator involved.
1107 procedure Expand_Array_Comparison (N : Node_Id) is
1108 Loc : constant Source_Ptr := Sloc (N);
1109 Op1 : Node_Id := Left_Opnd (N);
1110 Op2 : Node_Id := Right_Opnd (N);
1111 Typ1 : constant Entity_Id := Base_Type (Etype (Op1));
1112 Ctyp : constant Entity_Id := Component_Type (Typ1);
1114 Expr : Node_Id;
1115 Func_Body : Node_Id;
1116 Func_Name : Entity_Id;
1118 Comp : RE_Id;
1120 Byte_Addressable : constant Boolean := System_Storage_Unit = Byte'Size;
1121 -- True for byte addressable target
1123 function Length_Less_Than_4 (Opnd : Node_Id) return Boolean;
1124 -- Returns True if the length of the given operand is known to be less
1125 -- than 4. Returns False if this length is known to be four or greater
1126 -- or is not known at compile time.
1128 ------------------------
1129 -- Length_Less_Than_4 --
1130 ------------------------
1132 function Length_Less_Than_4 (Opnd : Node_Id) return Boolean is
1133 Otyp : constant Entity_Id := Etype (Opnd);
1135 begin
1136 if Ekind (Otyp) = E_String_Literal_Subtype then
1137 return String_Literal_Length (Otyp) < 4;
1139 elsif Compile_Time_Known_Bounds (Otyp) then
1140 declare
1141 Lo, Hi : Uint;
1143 begin
1144 Get_First_Index_Bounds (Otyp, Lo, Hi);
1145 return Hi < Lo + 3;
1146 end;
1148 else
1149 return False;
1150 end if;
1151 end Length_Less_Than_4;
1153 -- Start of processing for Expand_Array_Comparison
1155 begin
1156 -- Deal first with unpacked case, where we can call a runtime routine
1157 -- except that we avoid this for targets for which are not addressable
1158 -- by bytes.
1160 if not Is_Bit_Packed_Array (Typ1) and then Byte_Addressable then
1161 -- The call we generate is:
1163 -- Compare_Array_xn[_Unaligned]
1164 -- (left'address, right'address, left'length, right'length) <op> 0
1166 -- x = U for unsigned, S for signed
1167 -- n = 8,16,32,64,128 for component size
1168 -- Add _Unaligned if length < 4 and component size is 8.
1169 -- <op> is the standard comparison operator
1171 if Component_Size (Typ1) = 8 then
1172 if Length_Less_Than_4 (Op1)
1173 or else
1174 Length_Less_Than_4 (Op2)
1175 then
1176 if Is_Unsigned_Type (Ctyp) then
1177 Comp := RE_Compare_Array_U8_Unaligned;
1178 else
1179 Comp := RE_Compare_Array_S8_Unaligned;
1180 end if;
1182 else
1183 if Is_Unsigned_Type (Ctyp) then
1184 Comp := RE_Compare_Array_U8;
1185 else
1186 Comp := RE_Compare_Array_S8;
1187 end if;
1188 end if;
1190 elsif Component_Size (Typ1) = 16 then
1191 if Is_Unsigned_Type (Ctyp) then
1192 Comp := RE_Compare_Array_U16;
1193 else
1194 Comp := RE_Compare_Array_S16;
1195 end if;
1197 elsif Component_Size (Typ1) = 32 then
1198 if Is_Unsigned_Type (Ctyp) then
1199 Comp := RE_Compare_Array_U32;
1200 else
1201 Comp := RE_Compare_Array_S32;
1202 end if;
1204 elsif Component_Size (Typ1) = 64 then
1205 if Is_Unsigned_Type (Ctyp) then
1206 Comp := RE_Compare_Array_U64;
1207 else
1208 Comp := RE_Compare_Array_S64;
1209 end if;
1211 else pragma Assert (Component_Size (Typ1) = 128);
1212 if Is_Unsigned_Type (Ctyp) then
1213 Comp := RE_Compare_Array_U128;
1214 else
1215 Comp := RE_Compare_Array_S128;
1216 end if;
1217 end if;
1219 if RTE_Available (Comp) then
1221 -- Expand to a call only if the runtime function is available,
1222 -- otherwise fall back to inline code.
1224 Remove_Side_Effects (Op1, Name_Req => True);
1225 Remove_Side_Effects (Op2, Name_Req => True);
1227 declare
1228 Comp_Call : constant Node_Id :=
1229 Make_Function_Call (Loc,
1230 Name => New_Occurrence_Of (RTE (Comp), Loc),
1232 Parameter_Associations => New_List (
1233 Make_Attribute_Reference (Loc,
1234 Prefix => Relocate_Node (Op1),
1235 Attribute_Name => Name_Address),
1237 Make_Attribute_Reference (Loc,
1238 Prefix => Relocate_Node (Op2),
1239 Attribute_Name => Name_Address),
1241 Make_Attribute_Reference (Loc,
1242 Prefix => Relocate_Node (Op1),
1243 Attribute_Name => Name_Length),
1245 Make_Attribute_Reference (Loc,
1246 Prefix => Relocate_Node (Op2),
1247 Attribute_Name => Name_Length)));
1249 Zero : constant Node_Id :=
1250 Make_Integer_Literal (Loc,
1251 Intval => Uint_0);
1253 Comp_Op : Node_Id;
1255 begin
1256 case Nkind (N) is
1257 when N_Op_Lt =>
1258 Comp_Op := Make_Op_Lt (Loc, Comp_Call, Zero);
1259 when N_Op_Le =>
1260 Comp_Op := Make_Op_Le (Loc, Comp_Call, Zero);
1261 when N_Op_Gt =>
1262 Comp_Op := Make_Op_Gt (Loc, Comp_Call, Zero);
1263 when N_Op_Ge =>
1264 Comp_Op := Make_Op_Ge (Loc, Comp_Call, Zero);
1265 when others =>
1266 raise Program_Error;
1267 end case;
1269 Rewrite (N, Comp_Op);
1270 end;
1272 Analyze_And_Resolve (N, Standard_Boolean);
1273 return;
1274 end if;
1275 end if;
1277 -- Cases where we cannot make runtime call
1279 -- For (a <= b) we convert to not (a > b)
1281 if Chars (N) = Name_Op_Le then
1282 Rewrite (N,
1283 Make_Op_Not (Loc,
1284 Right_Opnd =>
1285 Make_Op_Gt (Loc,
1286 Left_Opnd => Op1,
1287 Right_Opnd => Op2)));
1288 Analyze_And_Resolve (N, Standard_Boolean);
1289 return;
1291 -- For < the Boolean expression is
1292 -- greater__nn (op2, op1)
1294 elsif Chars (N) = Name_Op_Lt then
1295 Func_Body := Make_Array_Comparison_Op (Typ1, N);
1297 -- Switch operands
1299 Op1 := Right_Opnd (N);
1300 Op2 := Left_Opnd (N);
1302 -- For (a >= b) we convert to not (a < b)
1304 elsif Chars (N) = Name_Op_Ge then
1305 Rewrite (N,
1306 Make_Op_Not (Loc,
1307 Right_Opnd =>
1308 Make_Op_Lt (Loc,
1309 Left_Opnd => Op1,
1310 Right_Opnd => Op2)));
1311 Analyze_And_Resolve (N, Standard_Boolean);
1312 return;
1314 -- For > the Boolean expression is
1315 -- greater__nn (op1, op2)
1317 else
1318 pragma Assert (Chars (N) = Name_Op_Gt);
1319 Func_Body := Make_Array_Comparison_Op (Typ1, N);
1320 end if;
1322 Func_Name := Defining_Unit_Name (Specification (Func_Body));
1323 Expr :=
1324 Make_Function_Call (Loc,
1325 Name => New_Occurrence_Of (Func_Name, Loc),
1326 Parameter_Associations => New_List (Op1, Op2));
1328 Insert_Action (N, Func_Body);
1329 Rewrite (N, Expr);
1330 Analyze_And_Resolve (N, Standard_Boolean);
1331 end Expand_Array_Comparison;
1333 ---------------------------
1334 -- Expand_Array_Equality --
1335 ---------------------------
1337 -- Expand an equality function for multi-dimensional arrays. Here is an
1338 -- example of such a function for Nb_Dimension = 2
1340 -- function Enn (A : atyp; B : btyp) return boolean is
1341 -- begin
1342 -- if (A'length (1) = 0 or else A'length (2) = 0)
1343 -- and then
1344 -- (B'length (1) = 0 or else B'length (2) = 0)
1345 -- then
1346 -- return true; -- RM 4.5.2(22)
1347 -- end if;
1349 -- if A'length (1) /= B'length (1)
1350 -- or else
1351 -- A'length (2) /= B'length (2)
1352 -- then
1353 -- return false; -- RM 4.5.2(23)
1354 -- end if;
1356 -- declare
1357 -- A1 : Index_T1 := A'first (1);
1358 -- B1 : Index_T1 := B'first (1);
1359 -- begin
1360 -- loop
1361 -- declare
1362 -- A2 : Index_T2 := A'first (2);
1363 -- B2 : Index_T2 := B'first (2);
1364 -- begin
1365 -- loop
1366 -- if A (A1, A2) /= B (B1, B2) then
1367 -- return False;
1368 -- end if;
1370 -- exit when A2 = A'last (2);
1371 -- A2 := Index_T2'succ (A2);
1372 -- B2 := Index_T2'succ (B2);
1373 -- end loop;
1374 -- end;
1376 -- exit when A1 = A'last (1);
1377 -- A1 := Index_T1'succ (A1);
1378 -- B1 := Index_T1'succ (B1);
1379 -- end loop;
1380 -- end;
1382 -- return true;
1383 -- end Enn;
1385 -- Note on the formal types used (atyp and btyp). If either of the arrays
1386 -- is of a private type, we use the underlying type, and do an unchecked
1387 -- conversion of the actual. If either of the arrays has a bound depending
1388 -- on a discriminant, then we use the base type since otherwise we have an
1389 -- escaped discriminant in the function.
1391 -- If both arrays are constrained and have the same bounds, we can generate
1392 -- a loop with an explicit iteration scheme using a 'Range attribute over
1393 -- the first array.
1395 function Expand_Array_Equality
1396 (Nod : Node_Id;
1397 Lhs : Node_Id;
1398 Rhs : Node_Id;
1399 Bodies : List_Id;
1400 Typ : Entity_Id) return Node_Id
1402 Loc : constant Source_Ptr := Sloc (Nod);
1403 Decls : constant List_Id := New_List;
1404 Index_List1 : constant List_Id := New_List;
1405 Index_List2 : constant List_Id := New_List;
1407 First_Idx : Node_Id;
1408 Formals : List_Id;
1409 Func_Name : Entity_Id;
1410 Func_Body : Node_Id;
1412 A : constant Entity_Id := Make_Defining_Identifier (Loc, Name_uA);
1413 B : constant Entity_Id := Make_Defining_Identifier (Loc, Name_uB);
1415 Ltyp : Entity_Id;
1416 Rtyp : Entity_Id;
1417 -- The parameter types to be used for the formals
1419 New_Lhs : Node_Id;
1420 New_Rhs : Node_Id;
1421 -- The LHS and RHS converted to the parameter types
1423 function Arr_Attr
1424 (Arr : Entity_Id;
1425 Nam : Name_Id;
1426 Dim : Pos) return Node_Id;
1427 -- This builds the attribute reference Arr'Nam (Dim)
1429 function Component_Equality (Typ : Entity_Id) return Node_Id;
1430 -- Create one statement to compare corresponding components, designated
1431 -- by a full set of indexes.
1433 function Get_Arg_Type (N : Node_Id) return Entity_Id;
1434 -- Given one of the arguments, computes the appropriate type to be used
1435 -- for that argument in the corresponding function formal
1437 function Handle_One_Dimension
1438 (N : Pos;
1439 Index : Node_Id) return Node_Id;
1440 -- This procedure returns the following code
1442 -- declare
1443 -- An : Index_T := A'First (N);
1444 -- Bn : Index_T := B'First (N);
1445 -- begin
1446 -- loop
1447 -- xxx
1448 -- exit when An = A'Last (N);
1449 -- An := Index_T'Succ (An)
1450 -- Bn := Index_T'Succ (Bn)
1451 -- end loop;
1452 -- end;
1454 -- If both indexes are constrained and identical, the procedure
1455 -- returns a simpler loop:
1457 -- for An in A'Range (N) loop
1458 -- xxx
1459 -- end loop
1461 -- N is the dimension for which we are generating a loop. Index is the
1462 -- N'th index node, whose Etype is Index_Type_n in the above code. The
1463 -- xxx statement is either the loop or declare for the next dimension
1464 -- or if this is the last dimension the comparison of corresponding
1465 -- components of the arrays.
1467 -- The actual way the code works is to return the comparison of
1468 -- corresponding components for the N+1 call. That's neater.
1470 function Test_Empty_Arrays return Node_Id;
1471 -- This function constructs the test for both arrays being empty
1472 -- (A'length (1) = 0 or else A'length (2) = 0 or else ...)
1473 -- and then
1474 -- (B'length (1) = 0 or else B'length (2) = 0 or else ...)
1476 function Test_Lengths_Correspond return Node_Id;
1477 -- This function constructs the test for arrays having different lengths
1478 -- in at least one index position, in which case the resulting code is:
1480 -- A'length (1) /= B'length (1)
1481 -- or else
1482 -- A'length (2) /= B'length (2)
1483 -- or else
1484 -- ...
1486 --------------
1487 -- Arr_Attr --
1488 --------------
1490 function Arr_Attr
1491 (Arr : Entity_Id;
1492 Nam : Name_Id;
1493 Dim : Pos) return Node_Id
1495 begin
1496 return
1497 Make_Attribute_Reference (Loc,
1498 Attribute_Name => Nam,
1499 Prefix => New_Occurrence_Of (Arr, Loc),
1500 Expressions => New_List (Make_Integer_Literal (Loc, Dim)));
1501 end Arr_Attr;
1503 ------------------------
1504 -- Component_Equality --
1505 ------------------------
1507 function Component_Equality (Typ : Entity_Id) return Node_Id is
1508 Test : Node_Id;
1509 L, R : Node_Id;
1511 begin
1512 -- if a(i1...) /= b(j1...) then return false; end if;
1514 L :=
1515 Make_Indexed_Component (Loc,
1516 Prefix => Make_Identifier (Loc, Chars (A)),
1517 Expressions => Index_List1);
1519 R :=
1520 Make_Indexed_Component (Loc,
1521 Prefix => Make_Identifier (Loc, Chars (B)),
1522 Expressions => Index_List2);
1524 Test := Expand_Composite_Equality
1525 (Outer_Type => Typ, Nod => Nod, Comp_Type => Component_Type (Typ),
1526 Lhs => L, Rhs => R);
1528 -- If some (sub)component is an unchecked_union, the whole operation
1529 -- will raise program error.
1531 if Nkind (Test) = N_Raise_Program_Error then
1533 -- This node is going to be inserted at a location where a
1534 -- statement is expected: clear its Etype so analysis will set
1535 -- it to the expected Standard_Void_Type.
1537 Set_Etype (Test, Empty);
1538 return Test;
1540 else
1541 return
1542 Make_Implicit_If_Statement (Nod,
1543 Condition => Make_Op_Not (Loc, Right_Opnd => Test),
1544 Then_Statements => New_List (
1545 Make_Simple_Return_Statement (Loc,
1546 Expression => New_Occurrence_Of (Standard_False, Loc))));
1547 end if;
1548 end Component_Equality;
1550 ------------------
1551 -- Get_Arg_Type --
1552 ------------------
1554 function Get_Arg_Type (N : Node_Id) return Entity_Id is
1555 T : Entity_Id;
1556 X : Node_Id;
1558 begin
1559 T := Etype (N);
1561 if No (T) then
1562 return Typ;
1564 else
1565 T := Underlying_Type (T);
1567 X := First_Index (T);
1568 while Present (X) loop
1569 if Denotes_Discriminant (Type_Low_Bound (Etype (X)))
1570 or else
1571 Denotes_Discriminant (Type_High_Bound (Etype (X)))
1572 then
1573 T := Base_Type (T);
1574 exit;
1575 end if;
1577 Next_Index (X);
1578 end loop;
1580 return T;
1581 end if;
1582 end Get_Arg_Type;
1584 --------------------------
1585 -- Handle_One_Dimension --
1586 ---------------------------
1588 function Handle_One_Dimension
1589 (N : Pos;
1590 Index : Node_Id) return Node_Id
1592 Need_Separate_Indexes : constant Boolean :=
1593 Ltyp /= Rtyp or else not Is_Constrained (Ltyp);
1594 -- If the index types are identical, and we are working with
1595 -- constrained types, then we can use the same index for both
1596 -- of the arrays.
1598 An : constant Entity_Id := Make_Temporary (Loc, 'A');
1600 Bn : Entity_Id;
1601 Index_T : Entity_Id;
1602 Stm_List : List_Id;
1603 Loop_Stm : Node_Id;
1605 begin
1606 if N > Number_Dimensions (Ltyp) then
1607 return Component_Equality (Ltyp);
1608 end if;
1610 -- Case where we generate a loop
1612 Index_T := Base_Type (Etype (Index));
1614 if Need_Separate_Indexes then
1615 Bn := Make_Temporary (Loc, 'B');
1616 else
1617 Bn := An;
1618 end if;
1620 Append (New_Occurrence_Of (An, Loc), Index_List1);
1621 Append (New_Occurrence_Of (Bn, Loc), Index_List2);
1623 Stm_List := New_List (
1624 Handle_One_Dimension (N + 1, Next_Index (Index)));
1626 if Need_Separate_Indexes then
1628 -- Generate guard for loop, followed by increments of indexes
1630 Append_To (Stm_List,
1631 Make_Exit_Statement (Loc,
1632 Condition =>
1633 Make_Op_Eq (Loc,
1634 Left_Opnd => New_Occurrence_Of (An, Loc),
1635 Right_Opnd => Arr_Attr (A, Name_Last, N))));
1637 Append_To (Stm_List,
1638 Make_Assignment_Statement (Loc,
1639 Name => New_Occurrence_Of (An, Loc),
1640 Expression =>
1641 Make_Attribute_Reference (Loc,
1642 Prefix => New_Occurrence_Of (Index_T, Loc),
1643 Attribute_Name => Name_Succ,
1644 Expressions => New_List (
1645 New_Occurrence_Of (An, Loc)))));
1647 Append_To (Stm_List,
1648 Make_Assignment_Statement (Loc,
1649 Name => New_Occurrence_Of (Bn, Loc),
1650 Expression =>
1651 Make_Attribute_Reference (Loc,
1652 Prefix => New_Occurrence_Of (Index_T, Loc),
1653 Attribute_Name => Name_Succ,
1654 Expressions => New_List (
1655 New_Occurrence_Of (Bn, Loc)))));
1656 end if;
1658 -- If separate indexes, we need a declare block for An and Bn, and a
1659 -- loop without an iteration scheme.
1661 if Need_Separate_Indexes then
1662 Loop_Stm :=
1663 Make_Implicit_Loop_Statement (Nod, Statements => Stm_List);
1665 return
1666 Make_Block_Statement (Loc,
1667 Declarations => New_List (
1668 Make_Object_Declaration (Loc,
1669 Defining_Identifier => An,
1670 Object_Definition => New_Occurrence_Of (Index_T, Loc),
1671 Expression => Arr_Attr (A, Name_First, N)),
1673 Make_Object_Declaration (Loc,
1674 Defining_Identifier => Bn,
1675 Object_Definition => New_Occurrence_Of (Index_T, Loc),
1676 Expression => Arr_Attr (B, Name_First, N))),
1678 Handled_Statement_Sequence =>
1679 Make_Handled_Sequence_Of_Statements (Loc,
1680 Statements => New_List (Loop_Stm)));
1682 -- If no separate indexes, return loop statement with explicit
1683 -- iteration scheme on its own.
1685 else
1686 Loop_Stm :=
1687 Make_Implicit_Loop_Statement (Nod,
1688 Statements => Stm_List,
1689 Iteration_Scheme =>
1690 Make_Iteration_Scheme (Loc,
1691 Loop_Parameter_Specification =>
1692 Make_Loop_Parameter_Specification (Loc,
1693 Defining_Identifier => An,
1694 Discrete_Subtype_Definition =>
1695 Arr_Attr (A, Name_Range, N))));
1696 return Loop_Stm;
1697 end if;
1698 end Handle_One_Dimension;
1700 -----------------------
1701 -- Test_Empty_Arrays --
1702 -----------------------
1704 function Test_Empty_Arrays return Node_Id is
1705 Alist : Node_Id := Empty;
1706 Blist : Node_Id := Empty;
1708 begin
1709 for J in 1 .. Number_Dimensions (Ltyp) loop
1710 Evolve_Or_Else (Alist,
1711 Make_Op_Eq (Loc,
1712 Left_Opnd => Arr_Attr (A, Name_Length, J),
1713 Right_Opnd => Make_Integer_Literal (Loc, Uint_0)));
1715 Evolve_Or_Else (Blist,
1716 Make_Op_Eq (Loc,
1717 Left_Opnd => Arr_Attr (B, Name_Length, J),
1718 Right_Opnd => Make_Integer_Literal (Loc, Uint_0)));
1719 end loop;
1721 return
1722 Make_And_Then (Loc,
1723 Left_Opnd => Alist,
1724 Right_Opnd => Blist);
1725 end Test_Empty_Arrays;
1727 -----------------------------
1728 -- Test_Lengths_Correspond --
1729 -----------------------------
1731 function Test_Lengths_Correspond return Node_Id is
1732 Result : Node_Id := Empty;
1734 begin
1735 for J in 1 .. Number_Dimensions (Ltyp) loop
1736 Evolve_Or_Else (Result,
1737 Make_Op_Ne (Loc,
1738 Left_Opnd => Arr_Attr (A, Name_Length, J),
1739 Right_Opnd => Arr_Attr (B, Name_Length, J)));
1740 end loop;
1742 return Result;
1743 end Test_Lengths_Correspond;
1745 -- Start of processing for Expand_Array_Equality
1747 begin
1748 Ltyp := Get_Arg_Type (Lhs);
1749 Rtyp := Get_Arg_Type (Rhs);
1751 -- For now, if the argument types are not the same, go to the base type,
1752 -- since the code assumes that the formals have the same type. This is
1753 -- fixable in future ???
1755 if Ltyp /= Rtyp then
1756 Ltyp := Base_Type (Ltyp);
1757 Rtyp := Base_Type (Rtyp);
1758 end if;
1760 -- If the array type is distinct from the type of the arguments, it
1761 -- is the full view of a private type. Apply an unchecked conversion
1762 -- to ensure that analysis of the code below succeeds.
1764 if No (Etype (Lhs))
1765 or else Base_Type (Etype (Lhs)) /= Base_Type (Ltyp)
1766 then
1767 New_Lhs := OK_Convert_To (Ltyp, Lhs);
1768 else
1769 New_Lhs := Lhs;
1770 end if;
1772 if No (Etype (Rhs))
1773 or else Base_Type (Etype (Rhs)) /= Base_Type (Rtyp)
1774 then
1775 New_Rhs := OK_Convert_To (Rtyp, Rhs);
1776 else
1777 New_Rhs := Rhs;
1778 end if;
1780 pragma Assert (Ltyp = Rtyp);
1781 First_Idx := First_Index (Ltyp);
1783 -- If optimization is enabled and the array boils down to a couple of
1784 -- consecutive elements, generate a simple conjunction of comparisons
1785 -- which should be easier to optimize by the code generator.
1787 if Optimization_Level > 0
1788 and then Is_Constrained (Ltyp)
1789 and then Number_Dimensions (Ltyp) = 1
1790 and then Compile_Time_Known_Bounds (Ltyp)
1791 and then Expr_Value (Type_High_Bound (Etype (First_Idx))) =
1792 Expr_Value (Type_Low_Bound (Etype (First_Idx))) + 1
1793 then
1794 declare
1795 Ctyp : constant Entity_Id := Component_Type (Ltyp);
1796 Low_B : constant Node_Id :=
1797 Type_Low_Bound (Etype (First_Idx));
1798 High_B : constant Node_Id :=
1799 Type_High_Bound (Etype (First_Idx));
1800 L, R : Node_Id;
1801 TestL, TestH : Node_Id;
1803 begin
1804 L :=
1805 Make_Indexed_Component (Loc,
1806 Prefix => New_Copy_Tree (New_Lhs),
1807 Expressions => New_List (New_Copy_Tree (Low_B)));
1809 R :=
1810 Make_Indexed_Component (Loc,
1811 Prefix => New_Copy_Tree (New_Rhs),
1812 Expressions => New_List (New_Copy_Tree (Low_B)));
1814 TestL := Expand_Composite_Equality
1815 (Outer_Type => Ltyp, Nod => Nod, Comp_Type => Ctyp,
1816 Lhs => L, Rhs => R);
1818 L :=
1819 Make_Indexed_Component (Loc,
1820 Prefix => New_Lhs,
1821 Expressions => New_List (New_Copy_Tree (High_B)));
1823 R :=
1824 Make_Indexed_Component (Loc,
1825 Prefix => New_Rhs,
1826 Expressions => New_List (New_Copy_Tree (High_B)));
1828 TestH := Expand_Composite_Equality
1829 (Outer_Type => Ltyp, Nod => Nod, Comp_Type => Ctyp,
1830 Lhs => L, Rhs => R);
1832 return
1833 Make_And_Then (Loc, Left_Opnd => TestL, Right_Opnd => TestH);
1834 end;
1835 end if;
1837 -- Build list of formals for function
1839 Formals := New_List (
1840 Make_Parameter_Specification (Loc,
1841 Defining_Identifier => A,
1842 Parameter_Type => New_Occurrence_Of (Ltyp, Loc)),
1844 Make_Parameter_Specification (Loc,
1845 Defining_Identifier => B,
1846 Parameter_Type => New_Occurrence_Of (Rtyp, Loc)));
1848 Func_Name := Make_Temporary (Loc, 'E');
1850 -- Build statement sequence for function
1852 Func_Body :=
1853 Make_Subprogram_Body (Loc,
1854 Specification =>
1855 Make_Function_Specification (Loc,
1856 Defining_Unit_Name => Func_Name,
1857 Parameter_Specifications => Formals,
1858 Result_Definition => New_Occurrence_Of (Standard_Boolean, Loc)),
1860 Declarations => Decls,
1862 Handled_Statement_Sequence =>
1863 Make_Handled_Sequence_Of_Statements (Loc,
1864 Statements => New_List (
1866 Make_Implicit_If_Statement (Nod,
1867 Condition => Test_Empty_Arrays,
1868 Then_Statements => New_List (
1869 Make_Simple_Return_Statement (Loc,
1870 Expression =>
1871 New_Occurrence_Of (Standard_True, Loc)))),
1873 Make_Implicit_If_Statement (Nod,
1874 Condition => Test_Lengths_Correspond,
1875 Then_Statements => New_List (
1876 Make_Simple_Return_Statement (Loc,
1877 Expression => New_Occurrence_Of (Standard_False, Loc)))),
1879 Handle_One_Dimension (1, First_Idx),
1881 Make_Simple_Return_Statement (Loc,
1882 Expression => New_Occurrence_Of (Standard_True, Loc)))));
1884 Set_Has_Completion (Func_Name, True);
1885 Set_Is_Inlined (Func_Name);
1887 Append_To (Bodies, Func_Body);
1889 return
1890 Make_Function_Call (Loc,
1891 Name => New_Occurrence_Of (Func_Name, Loc),
1892 Parameter_Associations => New_List (New_Lhs, New_Rhs));
1893 end Expand_Array_Equality;
1895 -----------------------------
1896 -- Expand_Boolean_Operator --
1897 -----------------------------
1899 -- Note that we first get the actual subtypes of the operands, since we
1900 -- always want to deal with types that have bounds.
1902 procedure Expand_Boolean_Operator (N : Node_Id) is
1903 Typ : constant Entity_Id := Etype (N);
1905 begin
1906 -- Special case of bit packed array where both operands are known to be
1907 -- properly aligned. In this case we use an efficient run time routine
1908 -- to carry out the operation (see System.Bit_Ops).
1910 if Is_Bit_Packed_Array (Typ)
1911 and then not Is_Possibly_Unaligned_Object (Left_Opnd (N))
1912 and then not Is_Possibly_Unaligned_Object (Right_Opnd (N))
1913 then
1914 Expand_Packed_Boolean_Operator (N);
1915 return;
1916 end if;
1918 -- For the normal non-packed case, the general expansion is to build
1919 -- function for carrying out the comparison (use Make_Boolean_Array_Op)
1920 -- and then inserting it into the tree. The original operator node is
1921 -- then rewritten as a call to this function. We also use this in the
1922 -- packed case if either operand is a possibly unaligned object.
1924 declare
1925 Loc : constant Source_Ptr := Sloc (N);
1926 L : constant Node_Id := Relocate_Node (Left_Opnd (N));
1927 R : Node_Id := Relocate_Node (Right_Opnd (N));
1928 Func_Body : Node_Id;
1929 Func_Name : Entity_Id;
1931 begin
1932 Convert_To_Actual_Subtype (L);
1933 Convert_To_Actual_Subtype (R);
1934 Ensure_Defined (Etype (L), N);
1935 Ensure_Defined (Etype (R), N);
1936 Apply_Length_Check (R, Etype (L));
1938 if Nkind (N) = N_Op_Xor then
1939 R := Duplicate_Subexpr (R);
1940 Silly_Boolean_Array_Xor_Test (N, R, Etype (L));
1941 end if;
1943 if Nkind (Parent (N)) = N_Assignment_Statement
1944 and then Safe_In_Place_Array_Op (Name (Parent (N)), L, R)
1945 then
1946 Build_Boolean_Array_Proc_Call (Parent (N), L, R);
1948 elsif Nkind (Parent (N)) = N_Op_Not
1949 and then Nkind (N) = N_Op_And
1950 and then Nkind (Parent (Parent (N))) = N_Assignment_Statement
1951 and then Safe_In_Place_Array_Op (Name (Parent (Parent (N))), L, R)
1952 then
1953 return;
1954 else
1955 Func_Body := Make_Boolean_Array_Op (Etype (L), N);
1956 Func_Name := Defining_Unit_Name (Specification (Func_Body));
1957 Insert_Action (N, Func_Body);
1959 -- Now rewrite the expression with a call
1961 if Transform_Function_Array then
1962 declare
1963 Temp_Id : constant Entity_Id := Make_Temporary (Loc, 'T');
1964 Call : Node_Id;
1965 Decl : Node_Id;
1967 begin
1968 -- Generate:
1969 -- Temp : ...;
1971 Decl :=
1972 Make_Object_Declaration (Loc,
1973 Defining_Identifier => Temp_Id,
1974 Object_Definition =>
1975 New_Occurrence_Of (Etype (L), Loc));
1977 -- Generate:
1978 -- Proc_Call (L, R, Temp);
1980 Call :=
1981 Make_Procedure_Call_Statement (Loc,
1982 Name => New_Occurrence_Of (Func_Name, Loc),
1983 Parameter_Associations =>
1984 New_List (
1986 Make_Type_Conversion
1987 (Loc, New_Occurrence_Of (Etype (L), Loc), R),
1988 New_Occurrence_Of (Temp_Id, Loc)));
1990 Insert_Actions (Parent (N), New_List (Decl, Call));
1991 Rewrite (N, New_Occurrence_Of (Temp_Id, Loc));
1992 end;
1993 else
1994 Rewrite (N,
1995 Make_Function_Call (Loc,
1996 Name => New_Occurrence_Of (Func_Name, Loc),
1997 Parameter_Associations =>
1998 New_List (
2000 Make_Type_Conversion
2001 (Loc, New_Occurrence_Of (Etype (L), Loc), R))));
2002 end if;
2004 Analyze_And_Resolve (N, Typ);
2005 end if;
2006 end;
2007 end Expand_Boolean_Operator;
2009 ------------------------------------------------
2010 -- Expand_Compare_Minimize_Eliminate_Overflow --
2011 ------------------------------------------------
2013 procedure Expand_Compare_Minimize_Eliminate_Overflow (N : Node_Id) is
2014 Loc : constant Source_Ptr := Sloc (N);
2016 Result_Type : constant Entity_Id := Etype (N);
2017 -- Capture result type (could be a derived boolean type)
2019 Llo, Lhi : Uint;
2020 Rlo, Rhi : Uint;
2022 LLIB : constant Entity_Id := Base_Type (Standard_Long_Long_Integer);
2023 -- Entity for Long_Long_Integer'Base
2025 procedure Set_True;
2026 procedure Set_False;
2027 -- These procedures rewrite N with an occurrence of Standard_True or
2028 -- Standard_False, and then makes a call to Warn_On_Known_Condition.
2030 ---------------
2031 -- Set_False --
2032 ---------------
2034 procedure Set_False is
2035 begin
2036 Rewrite (N, New_Occurrence_Of (Standard_False, Loc));
2037 Warn_On_Known_Condition (N);
2038 end Set_False;
2040 --------------
2041 -- Set_True --
2042 --------------
2044 procedure Set_True is
2045 begin
2046 Rewrite (N, New_Occurrence_Of (Standard_True, Loc));
2047 Warn_On_Known_Condition (N);
2048 end Set_True;
2050 -- Start of processing for Expand_Compare_Minimize_Eliminate_Overflow
2052 begin
2053 -- OK, this is the case we are interested in. First step is to process
2054 -- our operands using the Minimize_Eliminate circuitry which applies
2055 -- this processing to the two operand subtrees.
2057 Minimize_Eliminate_Overflows
2058 (Left_Opnd (N), Llo, Lhi, Top_Level => False);
2059 Minimize_Eliminate_Overflows
2060 (Right_Opnd (N), Rlo, Rhi, Top_Level => False);
2062 -- See if the range information decides the result of the comparison.
2063 -- We can only do this if we in fact have full range information (which
2064 -- won't be the case if either operand is bignum at this stage).
2066 if Present (Llo) and then Present (Rlo) then
2067 case N_Op_Compare (Nkind (N)) is
2068 when N_Op_Eq =>
2069 if Llo = Lhi and then Rlo = Rhi and then Llo = Rlo then
2070 Set_True;
2071 elsif Llo > Rhi or else Lhi < Rlo then
2072 Set_False;
2073 end if;
2075 when N_Op_Ge =>
2076 if Llo >= Rhi then
2077 Set_True;
2078 elsif Lhi < Rlo then
2079 Set_False;
2080 end if;
2082 when N_Op_Gt =>
2083 if Llo > Rhi then
2084 Set_True;
2085 elsif Lhi <= Rlo then
2086 Set_False;
2087 end if;
2089 when N_Op_Le =>
2090 if Llo > Rhi then
2091 Set_False;
2092 elsif Lhi <= Rlo then
2093 Set_True;
2094 end if;
2096 when N_Op_Lt =>
2097 if Llo >= Rhi then
2098 Set_False;
2099 elsif Lhi < Rlo then
2100 Set_True;
2101 end if;
2103 when N_Op_Ne =>
2104 if Llo = Lhi and then Rlo = Rhi and then Llo = Rlo then
2105 Set_False;
2106 elsif Llo > Rhi or else Lhi < Rlo then
2107 Set_True;
2108 end if;
2109 end case;
2111 -- All done if we did the rewrite
2113 if Nkind (N) not in N_Op_Compare then
2114 return;
2115 end if;
2116 end if;
2118 -- Otherwise, time to do the comparison
2120 declare
2121 Ltype : constant Entity_Id := Etype (Left_Opnd (N));
2122 Rtype : constant Entity_Id := Etype (Right_Opnd (N));
2124 begin
2125 -- If the two operands have the same signed integer type we are
2126 -- all set, nothing more to do. This is the case where either
2127 -- both operands were unchanged, or we rewrote both of them to
2128 -- be Long_Long_Integer.
2130 -- Note: Entity for the comparison may be wrong, but it's not worth
2131 -- the effort to change it, since the back end does not use it.
2133 if Is_Signed_Integer_Type (Ltype)
2134 and then Base_Type (Ltype) = Base_Type (Rtype)
2135 then
2136 return;
2138 -- Here if bignums are involved (can only happen in ELIMINATED mode)
2140 elsif Is_RTE (Ltype, RE_Bignum) or else Is_RTE (Rtype, RE_Bignum) then
2141 declare
2142 Left : Node_Id := Left_Opnd (N);
2143 Right : Node_Id := Right_Opnd (N);
2144 -- Bignum references for left and right operands
2146 begin
2147 if not Is_RTE (Ltype, RE_Bignum) then
2148 Left := Convert_To_Bignum (Left);
2149 elsif not Is_RTE (Rtype, RE_Bignum) then
2150 Right := Convert_To_Bignum (Right);
2151 end if;
2153 -- We rewrite our node with:
2155 -- do
2156 -- Bnn : Result_Type;
2157 -- declare
2158 -- M : Mark_Id := SS_Mark;
2159 -- begin
2160 -- Bnn := Big_xx (Left, Right); (xx = EQ, NT etc)
2161 -- SS_Release (M);
2162 -- end;
2163 -- in
2164 -- Bnn
2165 -- end
2167 declare
2168 Blk : constant Node_Id := Make_Bignum_Block (Loc);
2169 Bnn : constant Entity_Id := Make_Temporary (Loc, 'B', N);
2170 Ent : RE_Id;
2172 begin
2173 case N_Op_Compare (Nkind (N)) is
2174 when N_Op_Eq => Ent := RE_Big_EQ;
2175 when N_Op_Ge => Ent := RE_Big_GE;
2176 when N_Op_Gt => Ent := RE_Big_GT;
2177 when N_Op_Le => Ent := RE_Big_LE;
2178 when N_Op_Lt => Ent := RE_Big_LT;
2179 when N_Op_Ne => Ent := RE_Big_NE;
2180 end case;
2182 -- Insert assignment to Bnn into the bignum block
2184 Insert_Before
2185 (First (Statements (Handled_Statement_Sequence (Blk))),
2186 Make_Assignment_Statement (Loc,
2187 Name => New_Occurrence_Of (Bnn, Loc),
2188 Expression =>
2189 Make_Function_Call (Loc,
2190 Name =>
2191 New_Occurrence_Of (RTE (Ent), Loc),
2192 Parameter_Associations => New_List (Left, Right))));
2194 -- Now do the rewrite with expression actions
2196 Rewrite (N,
2197 Make_Expression_With_Actions (Loc,
2198 Actions => New_List (
2199 Make_Object_Declaration (Loc,
2200 Defining_Identifier => Bnn,
2201 Object_Definition =>
2202 New_Occurrence_Of (Result_Type, Loc)),
2203 Blk),
2204 Expression => New_Occurrence_Of (Bnn, Loc)));
2205 Analyze_And_Resolve (N, Result_Type);
2206 end;
2207 end;
2209 -- No bignums involved, but types are different, so we must have
2210 -- rewritten one of the operands as a Long_Long_Integer but not
2211 -- the other one.
2213 -- If left operand is Long_Long_Integer, convert right operand
2214 -- and we are done (with a comparison of two Long_Long_Integers).
2216 elsif Ltype = LLIB then
2217 Convert_To_And_Rewrite (LLIB, Right_Opnd (N));
2218 Analyze_And_Resolve (Right_Opnd (N), LLIB, Suppress => All_Checks);
2219 return;
2221 -- If right operand is Long_Long_Integer, convert left operand
2222 -- and we are done (with a comparison of two Long_Long_Integers).
2224 -- This is the only remaining possibility
2226 else pragma Assert (Rtype = LLIB);
2227 Convert_To_And_Rewrite (LLIB, Left_Opnd (N));
2228 Analyze_And_Resolve (Left_Opnd (N), LLIB, Suppress => All_Checks);
2229 return;
2230 end if;
2231 end;
2232 end Expand_Compare_Minimize_Eliminate_Overflow;
2234 -------------------------------
2235 -- Expand_Composite_Equality --
2236 -------------------------------
2238 -- This function is only called for comparing internal fields of composite
2239 -- types when these fields are themselves composites. This is a special
2240 -- case because it is not possible to respect normal Ada visibility rules.
2242 function Expand_Composite_Equality
2243 (Outer_Type : Entity_Id;
2244 Nod : Node_Id;
2245 Comp_Type : Entity_Id;
2246 Lhs : Node_Id;
2247 Rhs : Node_Id) return Node_Id
2249 Loc : constant Source_Ptr := Sloc (Nod);
2250 Full_Type : Entity_Id;
2251 Eq_Op : Entity_Id;
2253 begin
2254 if Is_Private_Type (Comp_Type) then
2255 Full_Type := Underlying_Type (Comp_Type);
2256 else
2257 Full_Type := Comp_Type;
2258 end if;
2260 -- If the private type has no completion the context may be the
2261 -- expansion of a composite equality for a composite type with some
2262 -- still incomplete components. The expression will not be analyzed
2263 -- until the enclosing type is completed, at which point this will be
2264 -- properly expanded, unless there is a bona fide completion error.
2266 if No (Full_Type) then
2267 return Make_Op_Eq (Loc, Left_Opnd => Lhs, Right_Opnd => Rhs);
2268 end if;
2270 Full_Type := Base_Type (Full_Type);
2272 -- When the base type itself is private, use the full view to expand
2273 -- the composite equality.
2275 if Is_Private_Type (Full_Type) then
2276 Full_Type := Underlying_Type (Full_Type);
2277 end if;
2279 -- Case of tagged record types
2281 if Is_Tagged_Type (Full_Type) then
2282 Eq_Op := Find_Primitive_Eq (Comp_Type);
2283 pragma Assert (Present (Eq_Op));
2285 return
2286 Make_Function_Call (Loc,
2287 Name => New_Occurrence_Of (Eq_Op, Loc),
2288 Parameter_Associations =>
2289 New_List
2290 (Unchecked_Convert_To (Etype (First_Formal (Eq_Op)), Lhs),
2291 Unchecked_Convert_To (Etype (First_Formal (Eq_Op)), Rhs)));
2293 -- Case of untagged record types
2295 elsif Is_Record_Type (Full_Type) then
2296 Eq_Op := TSS (Full_Type, TSS_Composite_Equality);
2298 if Present (Eq_Op) then
2299 if Etype (First_Formal (Eq_Op)) /= Full_Type then
2301 -- Inherited equality from parent type. Convert the actuals to
2302 -- match signature of operation.
2304 declare
2305 T : constant Entity_Id := Etype (First_Formal (Eq_Op));
2307 begin
2308 return
2309 Make_Function_Call (Loc,
2310 Name => New_Occurrence_Of (Eq_Op, Loc),
2311 Parameter_Associations => New_List (
2312 OK_Convert_To (T, Lhs),
2313 OK_Convert_To (T, Rhs)));
2314 end;
2316 else
2317 -- Comparison between Unchecked_Union components
2319 if Is_Unchecked_Union (Full_Type) then
2320 declare
2321 Lhs_Type : Node_Id := Full_Type;
2322 Rhs_Type : Node_Id := Full_Type;
2323 Lhs_Discr_Val : Node_Id;
2324 Rhs_Discr_Val : Node_Id;
2326 begin
2327 -- Lhs subtype
2329 if Nkind (Lhs) = N_Selected_Component then
2330 Lhs_Type := Etype (Entity (Selector_Name (Lhs)));
2331 end if;
2333 -- Rhs subtype
2335 if Nkind (Rhs) = N_Selected_Component then
2336 Rhs_Type := Etype (Entity (Selector_Name (Rhs)));
2337 end if;
2339 -- Lhs of the composite equality
2341 if Is_Constrained (Lhs_Type) then
2343 -- Since the enclosing record type can never be an
2344 -- Unchecked_Union (this code is executed for records
2345 -- that do not have variants), we may reference its
2346 -- discriminant(s).
2348 if Nkind (Lhs) = N_Selected_Component
2349 and then Has_Per_Object_Constraint
2350 (Entity (Selector_Name (Lhs)))
2351 then
2352 Lhs_Discr_Val :=
2353 Make_Selected_Component (Loc,
2354 Prefix => Prefix (Lhs),
2355 Selector_Name =>
2356 New_Copy
2357 (Get_Discriminant_Value
2358 (First_Discriminant (Lhs_Type),
2359 Lhs_Type,
2360 Stored_Constraint (Lhs_Type))));
2362 else
2363 Lhs_Discr_Val :=
2364 New_Copy
2365 (Get_Discriminant_Value
2366 (First_Discriminant (Lhs_Type),
2367 Lhs_Type,
2368 Stored_Constraint (Lhs_Type)));
2370 end if;
2371 else
2372 -- It is not possible to infer the discriminant since
2373 -- the subtype is not constrained.
2375 return
2376 Make_Raise_Program_Error (Loc,
2377 Reason => PE_Unchecked_Union_Restriction);
2378 end if;
2380 -- Rhs of the composite equality
2382 if Is_Constrained (Rhs_Type) then
2383 if Nkind (Rhs) = N_Selected_Component
2384 and then Has_Per_Object_Constraint
2385 (Entity (Selector_Name (Rhs)))
2386 then
2387 Rhs_Discr_Val :=
2388 Make_Selected_Component (Loc,
2389 Prefix => Prefix (Rhs),
2390 Selector_Name =>
2391 New_Copy
2392 (Get_Discriminant_Value
2393 (First_Discriminant (Rhs_Type),
2394 Rhs_Type,
2395 Stored_Constraint (Rhs_Type))));
2397 else
2398 Rhs_Discr_Val :=
2399 New_Copy
2400 (Get_Discriminant_Value
2401 (First_Discriminant (Rhs_Type),
2402 Rhs_Type,
2403 Stored_Constraint (Rhs_Type)));
2405 end if;
2406 else
2407 return
2408 Make_Raise_Program_Error (Loc,
2409 Reason => PE_Unchecked_Union_Restriction);
2410 end if;
2412 -- Call the TSS equality function with the inferred
2413 -- discriminant values.
2415 return
2416 Make_Function_Call (Loc,
2417 Name => New_Occurrence_Of (Eq_Op, Loc),
2418 Parameter_Associations => New_List (
2419 Lhs,
2420 Rhs,
2421 Lhs_Discr_Val,
2422 Rhs_Discr_Val));
2423 end;
2425 -- All cases other than comparing Unchecked_Union types
2427 else
2428 declare
2429 T : constant Entity_Id := Etype (First_Formal (Eq_Op));
2430 begin
2431 return
2432 Make_Function_Call (Loc,
2433 Name =>
2434 New_Occurrence_Of (Eq_Op, Loc),
2435 Parameter_Associations => New_List (
2436 OK_Convert_To (T, Lhs),
2437 OK_Convert_To (T, Rhs)));
2438 end;
2439 end if;
2440 end if;
2442 -- Equality composes in Ada 2012 for untagged record types. It also
2443 -- composes for bounded strings, because they are part of the
2444 -- predefined environment (see 4.5.2(32.1/1)). We could make it
2445 -- compose for bounded strings by making them tagged, or by making
2446 -- sure all subcomponents are set to the same value, even when not
2447 -- used. Instead, we have this special case in the compiler, because
2448 -- it's more efficient.
2450 elsif Ada_Version >= Ada_2012 or else Is_Bounded_String (Comp_Type)
2451 then
2452 -- If no TSS has been created for the type, check whether there is
2453 -- a primitive equality declared for it.
2455 declare
2456 Op : constant Node_Id :=
2457 Build_Eq_Call (Comp_Type, Loc, Lhs, Rhs);
2459 begin
2460 -- Use user-defined primitive if it exists, otherwise use
2461 -- predefined equality.
2463 if Present (Op) then
2464 return Op;
2465 else
2466 return Make_Op_Eq (Loc, Lhs, Rhs);
2467 end if;
2468 end;
2470 else
2471 return Expand_Record_Equality (Nod, Full_Type, Lhs, Rhs);
2472 end if;
2474 -- Case of non-record types (always use predefined equality)
2476 else
2477 -- Print a warning if there is a user-defined "=", because it can be
2478 -- surprising that the predefined "=" takes precedence over it.
2480 -- Suppress the warning if the "user-defined" one is in the
2481 -- predefined library, because those are defined to compose
2482 -- properly by RM-4.5.2(32.1/1). Intrinsics also compose.
2484 declare
2485 Op : constant Entity_Id := Find_Primitive_Eq (Comp_Type);
2486 begin
2487 if Warn_On_Ignored_Equality
2488 and then Present (Op)
2489 and then not In_Predefined_Unit (Base_Type (Comp_Type))
2490 and then not Is_Intrinsic_Subprogram (Op)
2491 then
2492 pragma Assert
2493 (Is_First_Subtype (Outer_Type)
2494 or else Is_Generic_Actual_Type (Outer_Type));
2495 Error_Msg_Node_1 := Outer_Type;
2496 Error_Msg_Node_2 := Comp_Type;
2497 Error_Msg
2498 ("?_q?""="" for type & uses predefined ""="" for }", Loc);
2499 Error_Msg_Sloc := Sloc (Op);
2500 Error_Msg ("\?_q?""="" # is ignored here", Loc);
2501 end if;
2502 end;
2504 return Make_Op_Eq (Loc, Left_Opnd => Lhs, Right_Opnd => Rhs);
2505 end if;
2506 end Expand_Composite_Equality;
2508 ------------------------
2509 -- Expand_Concatenate --
2510 ------------------------
2512 procedure Expand_Concatenate (Cnode : Node_Id; Opnds : List_Id) is
2513 Loc : constant Source_Ptr := Sloc (Cnode);
2515 Atyp : constant Entity_Id := Base_Type (Etype (Cnode));
2516 -- Result type of concatenation
2518 Ctyp : constant Entity_Id := Base_Type (Component_Type (Etype (Cnode)));
2519 -- Component type. Elements of this component type can appear as one
2520 -- of the operands of concatenation as well as arrays.
2522 Istyp : constant Entity_Id := Etype (First_Index (Atyp));
2523 -- Index subtype
2525 Ityp : constant Entity_Id := Base_Type (Istyp);
2526 -- Index type. This is the base type of the index subtype, and is used
2527 -- for all computed bounds (which may be out of range of Istyp in the
2528 -- case of null ranges).
2530 Artyp : Entity_Id;
2531 -- This is the type we use to do arithmetic to compute the bounds and
2532 -- lengths of operands. The choice of this type is a little subtle and
2533 -- is discussed in a separate section at the start of the body code.
2535 Result_May_Be_Null : Boolean := True;
2536 -- Reset to False if at least one operand is encountered which is known
2537 -- at compile time to be non-null. Used for handling the special case
2538 -- of setting the high bound to the last operand high bound for a null
2539 -- result, thus ensuring a proper high bound in the superflat case.
2541 N : constant Nat := List_Length (Opnds);
2542 -- Number of concatenation operands including possibly null operands
2544 NN : Nat := 0;
2545 -- Number of operands excluding any known to be null, except that the
2546 -- last operand is always retained, in case it provides the bounds for
2547 -- a null result.
2549 Opnd : Node_Id := Empty;
2550 -- Current operand being processed in the loop through operands. After
2551 -- this loop is complete, always contains the last operand (which is not
2552 -- the same as Operands (NN), since null operands are skipped).
2554 -- Arrays describing the operands, only the first NN entries of each
2555 -- array are set (NN < N when we exclude known null operands).
2557 Is_Fixed_Length : array (1 .. N) of Boolean;
2558 -- True if length of corresponding operand known at compile time
2560 Operands : array (1 .. N) of Node_Id;
2561 -- Set to the corresponding entry in the Opnds list (but note that null
2562 -- operands are excluded, so not all entries in the list are stored).
2564 Fixed_Length : array (1 .. N) of Unat;
2565 -- Set to length of operand. Entries in this array are set only if the
2566 -- corresponding entry in Is_Fixed_Length is True.
2568 Max_Length : array (1 .. N) of Unat;
2569 -- Set to the maximum length of operand, or Too_Large_Length_For_Array
2570 -- if it is not known. Entries in this array are set only if the
2571 -- corresponding entry in Is_Fixed_Length is False;
2573 Opnd_Low_Bound : array (1 .. N) of Node_Id;
2574 -- Set to lower bound of operand. Either an integer literal in the case
2575 -- where the bound is known at compile time, else actual lower bound.
2576 -- The operand low bound is of type Ityp.
2578 Var_Length : array (1 .. N) of Entity_Id;
2579 -- Set to an entity of type Natural that contains the length of an
2580 -- operand whose length is not known at compile time. Entries in this
2581 -- array are set only if the corresponding entry in Is_Fixed_Length
2582 -- is False. The entity is of type Artyp.
2584 Aggr_Length : array (0 .. N) of Node_Id;
2585 -- The J'th entry is an expression node that represents the total length
2586 -- of operands 1 through J. It is either an integer literal node, or a
2587 -- reference to a constant entity with the right value, so it is fine
2588 -- to just do a Copy_Node to get an appropriate copy. The extra zeroth
2589 -- entry always is set to zero. The length is of type Artyp.
2591 Max_Aggr_Length : Unat := Too_Large_Length_For_Array;
2592 -- Set to the maximum total length, or Too_Large_Length_For_Array at
2593 -- least if it is not known.
2595 Low_Bound : Node_Id := Empty;
2596 -- A tree node representing the low bound of the result (of type Ityp).
2597 -- This is either an integer literal node, or an identifier reference to
2598 -- a constant entity initialized to the appropriate value.
2600 High_Bound : Node_Id := Empty;
2601 -- A tree node representing the high bound of the result (of type Ityp)
2603 Last_Opnd_Low_Bound : Node_Id := Empty;
2604 -- A tree node representing the low bound of the last operand. This
2605 -- need only be set if the result could be null. It is used for the
2606 -- special case of setting the right low bound for a null result.
2607 -- This is of type Ityp.
2609 Last_Opnd_High_Bound : Node_Id := Empty;
2610 -- A tree node representing the high bound of the last operand. This
2611 -- need only be set if the result could be null. It is used for the
2612 -- special case of setting the right high bound for a null result.
2613 -- This is of type Ityp.
2615 Result : Node_Id := Empty;
2616 -- Result of the concatenation (of type Ityp)
2618 Actions : constant List_Id := New_List;
2619 -- Collect actions to be inserted
2621 Known_Non_Null_Operand_Seen : Boolean;
2622 -- Set True during generation of the assignments of operands into
2623 -- result once an operand known to be non-null has been seen.
2625 function Library_Level_Target return Boolean;
2626 -- Return True if the concatenation is within the expression of the
2627 -- declaration of a library-level object.
2629 function Make_Artyp_Literal (Val : Uint) return Node_Id;
2630 -- This function makes an N_Integer_Literal node that is returned in
2631 -- analyzed form with the type set to Artyp. Importantly this literal
2632 -- is not flagged as static, so that if we do computations with it that
2633 -- result in statically detected out of range conditions, we will not
2634 -- generate error messages but instead warning messages.
2636 function To_Artyp (X : Node_Id) return Node_Id;
2637 -- Given a node of type Ityp, returns the corresponding value of type
2638 -- Artyp. For non-enumeration types, this is a plain integer conversion.
2639 -- For enum types, the Pos of the value is returned.
2641 function To_Ityp (X : Node_Id) return Node_Id;
2642 -- The inverse function (uses Val in the case of enumeration types)
2644 --------------------------
2645 -- Library_Level_Target --
2646 --------------------------
2648 function Library_Level_Target return Boolean is
2649 P : Node_Id := Parent (Cnode);
2651 begin
2652 while Present (P) loop
2653 if Nkind (P) = N_Object_Declaration then
2654 return Is_Library_Level_Entity (Defining_Identifier (P));
2656 -- Prevent the search from going too far
2658 elsif Is_Body_Or_Package_Declaration (P) then
2659 return False;
2660 end if;
2662 P := Parent (P);
2663 end loop;
2665 return False;
2666 end Library_Level_Target;
2668 ------------------------
2669 -- Make_Artyp_Literal --
2670 ------------------------
2672 function Make_Artyp_Literal (Val : Uint) return Node_Id is
2673 Result : constant Node_Id := Make_Integer_Literal (Loc, Val);
2674 begin
2675 Set_Etype (Result, Artyp);
2676 Set_Analyzed (Result, True);
2677 Set_Is_Static_Expression (Result, False);
2678 return Result;
2679 end Make_Artyp_Literal;
2681 --------------
2682 -- To_Artyp --
2683 --------------
2685 function To_Artyp (X : Node_Id) return Node_Id is
2686 begin
2687 if Ityp = Base_Type (Artyp) then
2688 return X;
2690 elsif Is_Enumeration_Type (Ityp) then
2691 return
2692 Make_Attribute_Reference (Loc,
2693 Prefix => New_Occurrence_Of (Ityp, Loc),
2694 Attribute_Name => Name_Pos,
2695 Expressions => New_List (X));
2697 else
2698 return Convert_To (Artyp, X);
2699 end if;
2700 end To_Artyp;
2702 -------------
2703 -- To_Ityp --
2704 -------------
2706 function To_Ityp (X : Node_Id) return Node_Id is
2707 begin
2708 if Is_Enumeration_Type (Ityp) then
2709 return
2710 Make_Attribute_Reference (Loc,
2711 Prefix => New_Occurrence_Of (Ityp, Loc),
2712 Attribute_Name => Name_Val,
2713 Expressions => New_List (X));
2715 -- Case where we will do a type conversion
2717 else
2718 if Ityp = Base_Type (Artyp) then
2719 return X;
2720 else
2721 return Convert_To (Ityp, X);
2722 end if;
2723 end if;
2724 end To_Ityp;
2726 -- Local Declarations
2728 Opnd_Typ : Entity_Id;
2729 Slice_Rng : Node_Id;
2730 Subtyp_Ind : Node_Id;
2731 Subtyp_Rng : Node_Id;
2732 Ent : Entity_Id;
2733 Len : Unat;
2734 J : Nat;
2735 Clen : Node_Id;
2736 Set : Boolean;
2738 -- Start of processing for Expand_Concatenate
2740 begin
2741 -- Choose an appropriate computational type
2743 -- We will be doing calculations of lengths and bounds in this routine
2744 -- and computing one from the other in some cases, e.g. getting the high
2745 -- bound by adding the length-1 to the low bound.
2747 -- We can't just use the index type, or even its base type for this
2748 -- purpose for two reasons. First it might be an enumeration type which
2749 -- is not suitable for computations of any kind, and second it may
2750 -- simply not have enough range. For example if the index type is
2751 -- -128..+127 then lengths can be up to 256, which is out of range of
2752 -- the type.
2754 -- For enumeration types, we can simply use Standard_Integer, this is
2755 -- sufficient since the actual number of enumeration literals cannot
2756 -- possibly exceed the range of integer (remember we will be doing the
2757 -- arithmetic with POS values, not representation values).
2759 if Is_Enumeration_Type (Ityp) then
2760 Artyp := Standard_Integer;
2762 -- For modular types, we use a 32-bit modular type for types whose size
2763 -- is in the range 1-31 bits. For 32-bit unsigned types, we use the
2764 -- identity type, and for larger unsigned types we use a 64-bit type.
2766 elsif Is_Modular_Integer_Type (Ityp) then
2767 if RM_Size (Ityp) < Standard_Integer_Size then
2768 Artyp := Standard_Unsigned;
2769 elsif RM_Size (Ityp) = Standard_Integer_Size then
2770 Artyp := Ityp;
2771 else
2772 Artyp := Standard_Long_Long_Unsigned;
2773 end if;
2775 -- Similar treatment for signed types
2777 else
2778 if RM_Size (Ityp) < Standard_Integer_Size then
2779 Artyp := Standard_Integer;
2780 elsif RM_Size (Ityp) = Standard_Integer_Size then
2781 Artyp := Ityp;
2782 else
2783 Artyp := Standard_Long_Long_Integer;
2784 end if;
2785 end if;
2787 -- Supply dummy entry at start of length array
2789 Aggr_Length (0) := Make_Artyp_Literal (Uint_0);
2791 -- Go through operands setting up the above arrays
2793 J := 1;
2794 while J <= N loop
2795 Opnd := Remove_Head (Opnds);
2796 Opnd_Typ := Etype (Opnd);
2798 -- The parent got messed up when we put the operands in a list,
2799 -- so now put back the proper parent for the saved operand, that
2800 -- is to say the concatenation node, to make sure that each operand
2801 -- is seen as a subexpression, e.g. if actions must be inserted.
2803 Set_Parent (Opnd, Cnode);
2805 -- Set will be True when we have setup one entry in the array
2807 Set := False;
2809 -- Singleton element (or character literal) case
2811 if Base_Type (Opnd_Typ) = Ctyp then
2812 NN := NN + 1;
2813 Operands (NN) := Opnd;
2814 Is_Fixed_Length (NN) := True;
2815 Fixed_Length (NN) := Uint_1;
2816 Result_May_Be_Null := False;
2818 -- Set low bound of operand (no need to set Last_Opnd_High_Bound
2819 -- since we know that the result cannot be null).
2821 Opnd_Low_Bound (NN) :=
2822 Make_Attribute_Reference (Loc,
2823 Prefix => New_Occurrence_Of (Istyp, Loc),
2824 Attribute_Name => Name_First);
2826 Set := True;
2828 -- String literal case (can only occur for strings of course)
2830 elsif Nkind (Opnd) = N_String_Literal then
2831 Len := String_Literal_Length (Opnd_Typ);
2833 if Len > 0 then
2834 Result_May_Be_Null := False;
2835 end if;
2837 -- Capture last operand low and high bound if result could be null
2839 if J = N and then Result_May_Be_Null then
2840 Last_Opnd_Low_Bound :=
2841 New_Copy_Tree (String_Literal_Low_Bound (Opnd_Typ));
2843 Last_Opnd_High_Bound :=
2844 Make_Op_Subtract (Loc,
2845 Left_Opnd =>
2846 New_Copy_Tree (String_Literal_Low_Bound (Opnd_Typ)),
2847 Right_Opnd => Make_Integer_Literal (Loc, 1));
2848 end if;
2850 -- Skip null string literal
2852 if J < N and then Len = 0 then
2853 goto Continue;
2854 end if;
2856 NN := NN + 1;
2857 Operands (NN) := Opnd;
2858 Is_Fixed_Length (NN) := True;
2860 -- Set length and bounds
2862 Fixed_Length (NN) := Len;
2864 Opnd_Low_Bound (NN) :=
2865 New_Copy_Tree (String_Literal_Low_Bound (Opnd_Typ));
2867 Set := True;
2869 -- All other cases
2871 else
2872 -- Check constrained case with known bounds
2874 if Is_Constrained (Opnd_Typ)
2875 and then Compile_Time_Known_Bounds (Opnd_Typ)
2876 then
2877 declare
2878 Lo, Hi : Uint;
2880 begin
2881 -- Fixed length constrained array type with known at compile
2882 -- time bounds is last case of fixed length operand.
2884 Get_First_Index_Bounds (Opnd_Typ, Lo, Hi);
2885 Len := UI_Max (Hi - Lo + 1, Uint_0);
2887 if Len > 0 then
2888 Result_May_Be_Null := False;
2889 end if;
2891 -- Capture last operand bounds if result could be null
2893 if J = N and then Result_May_Be_Null then
2894 Last_Opnd_Low_Bound :=
2895 To_Ityp (Make_Integer_Literal (Loc, Lo));
2897 Last_Opnd_High_Bound :=
2898 To_Ityp (Make_Integer_Literal (Loc, Hi));
2899 end if;
2901 -- Exclude null length case unless last operand
2903 if J < N and then Len = 0 then
2904 goto Continue;
2905 end if;
2907 NN := NN + 1;
2908 Operands (NN) := Opnd;
2909 Is_Fixed_Length (NN) := True;
2910 Fixed_Length (NN) := Len;
2912 Opnd_Low_Bound (NN) :=
2913 To_Ityp (Make_Integer_Literal (Loc, Lo));
2914 Set := True;
2915 end;
2916 end if;
2918 -- All cases where the length is not known at compile time, or the
2919 -- special case of an operand which is known to be null but has a
2920 -- lower bound other than 1 or is other than a string type.
2922 if not Set then
2923 NN := NN + 1;
2925 -- Capture operand bounds
2927 Opnd_Low_Bound (NN) :=
2928 Make_Attribute_Reference (Loc,
2929 Prefix =>
2930 Duplicate_Subexpr (Opnd, Name_Req => True),
2931 Attribute_Name => Name_First);
2933 -- Capture last operand bounds if result could be null
2935 if J = N and Result_May_Be_Null then
2936 Last_Opnd_Low_Bound :=
2937 Convert_To (Ityp,
2938 Make_Attribute_Reference (Loc,
2939 Prefix =>
2940 Duplicate_Subexpr (Opnd, Name_Req => True),
2941 Attribute_Name => Name_First));
2943 Last_Opnd_High_Bound :=
2944 Convert_To (Ityp,
2945 Make_Attribute_Reference (Loc,
2946 Prefix =>
2947 Duplicate_Subexpr (Opnd, Name_Req => True),
2948 Attribute_Name => Name_Last));
2949 end if;
2951 -- Capture length of operand in entity
2953 Operands (NN) := Opnd;
2954 Is_Fixed_Length (NN) := False;
2956 Var_Length (NN) := Make_Temporary (Loc, 'L');
2958 -- If the operand is a slice, try to compute an upper bound for
2959 -- its length.
2961 if Nkind (Opnd) = N_Slice
2962 and then Is_Constrained (Etype (Prefix (Opnd)))
2963 and then Compile_Time_Known_Bounds (Etype (Prefix (Opnd)))
2964 then
2965 declare
2966 Lo, Hi : Uint;
2968 begin
2969 Get_First_Index_Bounds (Etype (Prefix (Opnd)), Lo, Hi);
2970 Max_Length (NN) := UI_Max (Hi - Lo + 1, Uint_0);
2971 end;
2973 else
2974 Max_Length (NN) := Too_Large_Length_For_Array;
2975 end if;
2977 Append_To (Actions,
2978 Make_Object_Declaration (Loc,
2979 Defining_Identifier => Var_Length (NN),
2980 Constant_Present => True,
2981 Object_Definition => New_Occurrence_Of (Artyp, Loc),
2982 Expression =>
2983 Make_Attribute_Reference (Loc,
2984 Prefix =>
2985 Duplicate_Subexpr (Opnd, Name_Req => True),
2986 Attribute_Name => Name_Length)));
2987 end if;
2988 end if;
2990 -- Set next entry in aggregate length array
2992 -- For first entry, make either integer literal for fixed length
2993 -- or a reference to the saved length for variable length.
2995 if NN = 1 then
2996 if Is_Fixed_Length (1) then
2997 Aggr_Length (1) := Make_Integer_Literal (Loc, Fixed_Length (1));
2998 Max_Aggr_Length := Fixed_Length (1);
2999 else
3000 Aggr_Length (1) := New_Occurrence_Of (Var_Length (1), Loc);
3001 Max_Aggr_Length := Max_Length (1);
3002 end if;
3004 -- If entry is fixed length and only fixed lengths so far, make
3005 -- appropriate new integer literal adding new length.
3007 elsif Is_Fixed_Length (NN)
3008 and then Nkind (Aggr_Length (NN - 1)) = N_Integer_Literal
3009 then
3010 Aggr_Length (NN) :=
3011 Make_Integer_Literal (Loc,
3012 Intval => Fixed_Length (NN) + Intval (Aggr_Length (NN - 1)));
3013 Max_Aggr_Length := Intval (Aggr_Length (NN));
3015 -- All other cases, construct an addition node for the length and
3016 -- create an entity initialized to this length.
3018 else
3019 Ent := Make_Temporary (Loc, 'L');
3021 if Is_Fixed_Length (NN) then
3022 Clen := Make_Integer_Literal (Loc, Fixed_Length (NN));
3023 Max_Aggr_Length := Max_Aggr_Length + Fixed_Length (NN);
3025 else
3026 Clen := New_Occurrence_Of (Var_Length (NN), Loc);
3027 Max_Aggr_Length := Max_Aggr_Length + Max_Length (NN);
3028 end if;
3030 Append_To (Actions,
3031 Make_Object_Declaration (Loc,
3032 Defining_Identifier => Ent,
3033 Constant_Present => True,
3034 Object_Definition => New_Occurrence_Of (Artyp, Loc),
3035 Expression =>
3036 Make_Op_Add (Loc,
3037 Left_Opnd => New_Copy_Tree (Aggr_Length (NN - 1)),
3038 Right_Opnd => Clen)));
3040 Aggr_Length (NN) := Make_Identifier (Loc, Chars => Chars (Ent));
3041 end if;
3043 <<Continue>>
3044 J := J + 1;
3045 end loop;
3047 -- If we have only skipped null operands, return the last operand
3049 if NN = 0 then
3050 Result := Opnd;
3051 goto Done;
3052 end if;
3054 -- If we have only one non-null operand, return it and we are done.
3055 -- There is one case in which this cannot be done, and that is when
3056 -- the sole operand is of the element type, in which case it must be
3057 -- converted to an array, and the easiest way of doing that is to go
3058 -- through the normal general circuit.
3060 if NN = 1 and then Base_Type (Etype (Operands (1))) /= Ctyp then
3061 Result := Operands (1);
3062 goto Done;
3063 end if;
3065 -- Cases where we have a real concatenation
3067 -- Next step is to find the low bound for the result array that we
3068 -- will allocate. The rules for this are in (RM 4.5.6(5-7)).
3070 -- If the ultimate ancestor of the index subtype is a constrained array
3071 -- definition, then the lower bound is that of the index subtype as
3072 -- specified by (RM 4.5.3(6)).
3074 -- The right test here is to go to the root type, and then the ultimate
3075 -- ancestor is the first subtype of this root type.
3077 if Is_Constrained (First_Subtype (Root_Type (Atyp))) then
3078 Low_Bound :=
3079 Make_Attribute_Reference (Loc,
3080 Prefix =>
3081 New_Occurrence_Of (First_Subtype (Root_Type (Atyp)), Loc),
3082 Attribute_Name => Name_First);
3084 -- If the first operand in the list has known length we know that
3085 -- the lower bound of the result is the lower bound of this operand.
3087 elsif Is_Fixed_Length (1) then
3088 Low_Bound := Opnd_Low_Bound (1);
3090 -- OK, we don't know the lower bound, we have to build a horrible
3091 -- if expression node of the form
3093 -- if Cond1'Length /= 0 then
3094 -- Opnd1 low bound
3095 -- else
3096 -- if Opnd2'Length /= 0 then
3097 -- Opnd2 low bound
3098 -- else
3099 -- ...
3101 -- The nesting ends either when we hit an operand whose length is known
3102 -- at compile time, or on reaching the last operand, whose low bound we
3103 -- take unconditionally whether or not it is null. It's easiest to do
3104 -- this with a recursive procedure:
3106 else
3107 declare
3108 function Get_Known_Bound (J : Nat) return Node_Id;
3109 -- Returns the lower bound determined by operands J .. NN
3111 ---------------------
3112 -- Get_Known_Bound --
3113 ---------------------
3115 function Get_Known_Bound (J : Nat) return Node_Id is
3116 begin
3117 if Is_Fixed_Length (J) or else J = NN then
3118 return New_Copy_Tree (Opnd_Low_Bound (J));
3120 else
3121 return
3122 Make_If_Expression (Loc,
3123 Expressions => New_List (
3125 Make_Op_Ne (Loc,
3126 Left_Opnd =>
3127 New_Occurrence_Of (Var_Length (J), Loc),
3128 Right_Opnd =>
3129 Make_Integer_Literal (Loc, 0)),
3131 New_Copy_Tree (Opnd_Low_Bound (J)),
3132 Get_Known_Bound (J + 1)));
3133 end if;
3134 end Get_Known_Bound;
3136 begin
3137 Ent := Make_Temporary (Loc, 'L');
3139 Append_To (Actions,
3140 Make_Object_Declaration (Loc,
3141 Defining_Identifier => Ent,
3142 Constant_Present => True,
3143 Object_Definition => New_Occurrence_Of (Ityp, Loc),
3144 Expression => Get_Known_Bound (1)));
3146 Low_Bound := New_Occurrence_Of (Ent, Loc);
3147 end;
3148 end if;
3150 pragma Assert (Present (Low_Bound));
3152 -- Now we can compute the high bound as Low_Bound + Length - 1
3154 if Compile_Time_Known_Value (Low_Bound)
3155 and then Nkind (Aggr_Length (NN)) = N_Integer_Literal
3156 then
3157 High_Bound :=
3158 To_Ityp
3159 (Make_Artyp_Literal
3160 (Expr_Value (Low_Bound) + Intval (Aggr_Length (NN)) - 1));
3162 else
3163 High_Bound :=
3164 To_Ityp
3165 (Make_Op_Add (Loc,
3166 Left_Opnd => To_Artyp (New_Copy_Tree (Low_Bound)),
3167 Right_Opnd =>
3168 Make_Op_Subtract (Loc,
3169 Left_Opnd => New_Copy_Tree (Aggr_Length (NN)),
3170 Right_Opnd => Make_Artyp_Literal (Uint_1))));
3172 -- Note that calculation of the high bound may cause overflow in some
3173 -- very weird cases, so in the general case we need an overflow check
3174 -- on the high bound. We can avoid this for the common case of string
3175 -- types and other types whose index is Positive, since we chose a
3176 -- wider range for the arithmetic type. If checks are suppressed, we
3177 -- do not set the flag so superfluous warnings may be omitted.
3179 if Istyp /= Standard_Positive
3180 and then not Overflow_Checks_Suppressed (Istyp)
3181 then
3182 Activate_Overflow_Check (High_Bound);
3183 end if;
3184 end if;
3186 -- Handle the exceptional case where the result is null, in which case
3187 -- case the bounds come from the last operand (so that we get the proper
3188 -- bounds if the last operand is superflat).
3190 if Result_May_Be_Null then
3191 Low_Bound :=
3192 Make_If_Expression (Loc,
3193 Expressions => New_List (
3194 Make_Op_Eq (Loc,
3195 Left_Opnd => New_Copy_Tree (Aggr_Length (NN)),
3196 Right_Opnd => Make_Artyp_Literal (Uint_0)),
3197 Last_Opnd_Low_Bound,
3198 Low_Bound));
3200 High_Bound :=
3201 Make_If_Expression (Loc,
3202 Expressions => New_List (
3203 Make_Op_Eq (Loc,
3204 Left_Opnd => New_Copy_Tree (Aggr_Length (NN)),
3205 Right_Opnd => Make_Artyp_Literal (Uint_0)),
3206 Last_Opnd_High_Bound,
3207 High_Bound));
3208 end if;
3210 -- Here is where we insert the saved up actions
3212 Insert_Actions (Cnode, Actions, Suppress => All_Checks);
3214 -- If the low bound is known at compile time and not the high bound, but
3215 -- we have computed a sensible upper bound for the length, then adjust
3216 -- the high bound for the subtype of the array. This will change it into
3217 -- a static subtype and thus help the code generator.
3219 if Compile_Time_Known_Value (Low_Bound)
3220 and then not Compile_Time_Known_Value (High_Bound)
3221 and then Max_Aggr_Length < Too_Large_Length_For_Array
3222 then
3223 declare
3224 Known_High_Bound : constant Node_Id :=
3225 To_Ityp
3226 (Make_Artyp_Literal
3227 (Expr_Value (Low_Bound) + Max_Aggr_Length - 1));
3229 begin
3230 if not Is_Out_Of_Range (Known_High_Bound, Ityp) then
3231 Slice_Rng := Make_Range (Loc, Low_Bound, High_Bound);
3232 High_Bound := Known_High_Bound;
3234 else
3235 Slice_Rng := Empty;
3236 end if;
3237 end;
3239 else
3240 Slice_Rng := Empty;
3241 end if;
3243 Subtyp_Rng := Make_Range (Loc, Low_Bound, High_Bound);
3245 -- If the result cannot be null then the range cannot be superflat
3247 Set_Cannot_Be_Superflat (Subtyp_Rng, not Result_May_Be_Null);
3249 -- Now we construct an array object with appropriate bounds. We mark
3250 -- the target as internal to prevent useless initialization when
3251 -- Initialize_Scalars is enabled. Also since this is the actual result
3252 -- entity, we make sure we have debug information for the result.
3254 Subtyp_Ind :=
3255 Make_Subtype_Indication (Loc,
3256 Subtype_Mark => New_Occurrence_Of (Atyp, Loc),
3257 Constraint =>
3258 Make_Index_Or_Discriminant_Constraint (Loc,
3259 Constraints => New_List (Subtyp_Rng)));
3261 Ent := Make_Temporary (Loc, 'S');
3262 Set_Is_Internal (Ent);
3263 Set_Debug_Info_Needed (Ent);
3265 -- If we are concatenating strings and the current scope already uses
3266 -- the secondary stack, allocate the result also on the secondary stack
3267 -- to avoid putting too much pressure on the primary stack.
3269 -- Don't do this if -gnatd.h is set, as this will break the wrapping of
3270 -- Cnode in an Expression_With_Actions, see Expand_N_Op_Concat.
3272 if Atyp = Standard_String
3273 and then Uses_Sec_Stack (Current_Scope)
3274 and then RTE_Available (RE_SS_Pool)
3275 and then not Debug_Flag_Dot_H
3276 then
3277 -- Generate:
3278 -- subtype Axx is String (<low-bound> .. <high-bound>)
3279 -- type Ayy is access Axx;
3280 -- Rxx : Ayy := new <Axx> [storage_pool = ss_pool];
3281 -- Sxx : Axx renames Rxx.all;
3283 declare
3284 ConstrT : constant Entity_Id := Make_Temporary (Loc, 'A');
3285 Acc_Typ : constant Entity_Id := Make_Temporary (Loc, 'A');
3287 Alloc : Node_Id;
3288 Temp : Entity_Id;
3290 begin
3291 Insert_Action (Cnode,
3292 Make_Subtype_Declaration (Loc,
3293 Defining_Identifier => ConstrT,
3294 Subtype_Indication => Subtyp_Ind),
3295 Suppress => All_Checks);
3297 Freeze_Itype (ConstrT, Cnode);
3299 Insert_Action (Cnode,
3300 Make_Full_Type_Declaration (Loc,
3301 Defining_Identifier => Acc_Typ,
3302 Type_Definition =>
3303 Make_Access_To_Object_Definition (Loc,
3304 Subtype_Indication => New_Occurrence_Of (ConstrT, Loc))),
3305 Suppress => All_Checks);
3307 Mutate_Ekind (Acc_Typ, E_Access_Type);
3308 Set_Associated_Storage_Pool (Acc_Typ, RTE (RE_SS_Pool));
3310 Alloc :=
3311 Make_Allocator (Loc,
3312 Expression => New_Occurrence_Of (ConstrT, Loc));
3314 -- This is currently done only for type String, which normally
3315 -- doesn't have default initialization, but we need to set the
3316 -- No_Initialization flag in case of either Initialize_Scalars
3317 -- or Normalize_Scalars.
3319 Set_No_Initialization (Alloc);
3321 Temp := Make_Temporary (Loc, 'R', Alloc);
3322 Insert_Action (Cnode,
3323 Make_Object_Declaration (Loc,
3324 Defining_Identifier => Temp,
3325 Object_Definition => New_Occurrence_Of (Acc_Typ, Loc),
3326 Expression => Alloc),
3327 Suppress => All_Checks);
3329 Insert_Action (Cnode,
3330 Make_Object_Renaming_Declaration (Loc,
3331 Defining_Identifier => Ent,
3332 Subtype_Mark => New_Occurrence_Of (ConstrT, Loc),
3333 Name =>
3334 Make_Explicit_Dereference (Loc,
3335 Prefix => New_Occurrence_Of (Temp, Loc))),
3336 Suppress => All_Checks);
3337 end;
3339 else
3340 -- If the bound is statically known to be out of range, we do not
3341 -- want to abort, we want a warning and a runtime constraint error.
3342 -- Note that we have arranged that the result will not be treated
3343 -- as a static constant, so we won't get an illegality during this
3344 -- insertion. We also enable checks (in particular range checks) in
3345 -- case the bounds of Subtyp_Ind are out of range.
3347 Insert_Action (Cnode,
3348 Make_Object_Declaration (Loc,
3349 Defining_Identifier => Ent,
3350 Object_Definition => Subtyp_Ind));
3351 end if;
3353 -- If the result of the concatenation appears as the initializing
3354 -- expression of an object declaration, we can just rename the
3355 -- result, rather than copying it.
3357 Set_OK_To_Rename (Ent);
3359 -- Catch the static out of range case now
3361 if Raises_Constraint_Error (High_Bound)
3362 or else Is_Out_Of_Range (High_Bound, Ityp)
3363 then
3364 -- Kill warning generated for the declaration of the static out of
3365 -- range high bound, and instead generate a Constraint_Error with
3366 -- an appropriate specific message.
3368 if Nkind (High_Bound) = N_Integer_Literal then
3369 Kill_Dead_Code (High_Bound);
3370 Rewrite (High_Bound, New_Copy_Tree (Low_Bound));
3372 else
3373 Kill_Dead_Code (Declaration_Node (Entity (High_Bound)));
3374 end if;
3376 Apply_Compile_Time_Constraint_Error
3377 (N => Cnode,
3378 Msg => "concatenation result upper bound out of range??",
3379 Reason => CE_Range_Check_Failed);
3381 return;
3382 end if;
3384 -- Now we will generate the assignments to do the actual concatenation
3386 -- There is one case in which we will not do this, namely when all the
3387 -- following conditions are met:
3389 -- The result type is Standard.String
3391 -- There are nine or fewer retained (non-null) operands
3393 -- The optimization level is -O0 or the debug flag gnatd.C is set,
3394 -- and the debug flag gnatd.c is not set.
3396 -- The corresponding System.Concat_n.Str_Concat_n routine is
3397 -- available in the run time.
3399 -- If all these conditions are met then we generate a call to the
3400 -- relevant concatenation routine. The purpose of this is to avoid
3401 -- undesirable code bloat at -O0.
3403 -- If the concatenation is within the declaration of a library-level
3404 -- object, we call the built-in concatenation routines to prevent code
3405 -- bloat, regardless of the optimization level. This is space efficient
3406 -- and prevents linking problems when units are compiled with different
3407 -- optimization levels.
3409 if Atyp = Standard_String
3410 and then NN in 2 .. 9
3411 and then (((Optimization_Level = 0 or else Debug_Flag_Dot_CC)
3412 and then not Debug_Flag_Dot_C)
3413 or else Library_Level_Target)
3414 then
3415 declare
3416 RR : constant array (Nat range 2 .. 9) of RE_Id :=
3417 (RE_Str_Concat_2,
3418 RE_Str_Concat_3,
3419 RE_Str_Concat_4,
3420 RE_Str_Concat_5,
3421 RE_Str_Concat_6,
3422 RE_Str_Concat_7,
3423 RE_Str_Concat_8,
3424 RE_Str_Concat_9);
3426 begin
3427 if RTE_Available (RR (NN)) then
3428 declare
3429 Opnds : constant List_Id :=
3430 New_List (New_Occurrence_Of (Ent, Loc));
3432 begin
3433 for J in 1 .. NN loop
3434 if Is_List_Member (Operands (J)) then
3435 Remove (Operands (J));
3436 end if;
3438 if Base_Type (Etype (Operands (J))) = Ctyp then
3439 Append_To (Opnds,
3440 Make_Aggregate (Loc,
3441 Component_Associations => New_List (
3442 Make_Component_Association (Loc,
3443 Choices => New_List (
3444 Make_Integer_Literal (Loc, 1)),
3445 Expression => Operands (J)))));
3447 else
3448 Append_To (Opnds, Operands (J));
3449 end if;
3450 end loop;
3452 Insert_Action (Cnode,
3453 Make_Procedure_Call_Statement (Loc,
3454 Name => New_Occurrence_Of (RTE (RR (NN)), Loc),
3455 Parameter_Associations => Opnds));
3457 -- No assignments left to do below
3459 NN := 0;
3460 end;
3461 end if;
3462 end;
3463 end if;
3465 -- Not special case so generate the assignments
3467 Known_Non_Null_Operand_Seen := False;
3469 for J in 1 .. NN loop
3470 declare
3471 Lo : constant Node_Id :=
3472 Make_Op_Add (Loc,
3473 Left_Opnd => To_Artyp (New_Copy_Tree (Low_Bound)),
3474 Right_Opnd => Aggr_Length (J - 1));
3476 Hi : constant Node_Id :=
3477 Make_Op_Add (Loc,
3478 Left_Opnd => To_Artyp (New_Copy_Tree (Low_Bound)),
3479 Right_Opnd =>
3480 Make_Op_Subtract (Loc,
3481 Left_Opnd => Aggr_Length (J),
3482 Right_Opnd => Make_Artyp_Literal (Uint_1)));
3484 begin
3485 -- Singleton case, simple assignment
3487 if Base_Type (Etype (Operands (J))) = Ctyp then
3488 Known_Non_Null_Operand_Seen := True;
3489 Insert_Action (Cnode,
3490 Make_Assignment_Statement (Loc,
3491 Name =>
3492 Make_Indexed_Component (Loc,
3493 Prefix => New_Occurrence_Of (Ent, Loc),
3494 Expressions => New_List (To_Ityp (Lo))),
3495 Expression => Operands (J)),
3496 Suppress => All_Checks);
3498 -- Array case, slice assignment, skipped when argument is fixed
3499 -- length and known to be null.
3501 elsif not Is_Fixed_Length (J) or else Fixed_Length (J) > 0 then
3502 declare
3503 Assign : Node_Id :=
3504 Make_Assignment_Statement (Loc,
3505 Name =>
3506 Make_Slice (Loc,
3507 Prefix =>
3508 New_Occurrence_Of (Ent, Loc),
3509 Discrete_Range =>
3510 Make_Range (Loc,
3511 Low_Bound => To_Ityp (Lo),
3512 High_Bound => To_Ityp (Hi))),
3513 Expression => Operands (J));
3514 begin
3515 if Is_Fixed_Length (J) then
3516 Known_Non_Null_Operand_Seen := True;
3518 elsif not Known_Non_Null_Operand_Seen then
3520 -- Here if operand length is not statically known and no
3521 -- operand known to be non-null has been processed yet.
3522 -- If operand length is 0, we do not need to perform the
3523 -- assignment, and we must avoid the evaluation of the
3524 -- high bound of the slice, since it may underflow if the
3525 -- low bound is Ityp'First.
3527 Assign :=
3528 Make_Implicit_If_Statement (Cnode,
3529 Condition =>
3530 Make_Op_Ne (Loc,
3531 Left_Opnd =>
3532 New_Occurrence_Of (Var_Length (J), Loc),
3533 Right_Opnd => Make_Integer_Literal (Loc, 0)),
3534 Then_Statements => New_List (Assign));
3535 end if;
3537 Insert_Action (Cnode, Assign, Suppress => All_Checks);
3538 end;
3539 end if;
3540 end;
3541 end loop;
3543 -- Finally we build the result, which is either a direct reference to
3544 -- the array object or a slice of it.
3546 Result := New_Occurrence_Of (Ent, Loc);
3548 if Present (Slice_Rng) then
3549 Result := Make_Slice (Loc, Result, Slice_Rng);
3550 end if;
3552 <<Done>>
3553 pragma Assert (Present (Result));
3554 Rewrite (Cnode, Result);
3555 Analyze_And_Resolve (Cnode, Atyp);
3556 end Expand_Concatenate;
3558 ---------------------------------------------------
3559 -- Expand_Membership_Minimize_Eliminate_Overflow --
3560 ---------------------------------------------------
3562 procedure Expand_Membership_Minimize_Eliminate_Overflow (N : Node_Id) is
3563 pragma Assert (Nkind (N) = N_In);
3564 -- Despite the name, this routine applies only to N_In, not to
3565 -- N_Not_In. The latter is always rewritten as not (X in Y).
3567 Result_Type : constant Entity_Id := Etype (N);
3568 -- Capture result type, may be a derived boolean type
3570 Loc : constant Source_Ptr := Sloc (N);
3571 Lop : constant Node_Id := Left_Opnd (N);
3572 Rop : constant Node_Id := Right_Opnd (N);
3574 -- Note: there are many referencs to Etype (Lop) and Etype (Rop). It
3575 -- is thus tempting to capture these values, but due to the rewrites
3576 -- that occur as a result of overflow checking, these values change
3577 -- as we go along, and it is safe just to always use Etype explicitly.
3579 Restype : constant Entity_Id := Etype (N);
3580 -- Save result type
3582 Lo, Hi : Uint;
3583 -- Bounds in Minimize calls, not used currently
3585 LLIB : constant Entity_Id := Base_Type (Standard_Long_Long_Integer);
3586 -- Entity for Long_Long_Integer'Base
3588 begin
3589 Minimize_Eliminate_Overflows (Lop, Lo, Hi, Top_Level => False);
3591 -- If right operand is a subtype name, and the subtype name has no
3592 -- predicate, then we can just replace the right operand with an
3593 -- explicit range T'First .. T'Last, and use the explicit range code.
3595 if Nkind (Rop) /= N_Range
3596 and then No (Predicate_Function (Etype (Rop)))
3597 then
3598 declare
3599 Rtyp : constant Entity_Id := Etype (Rop);
3600 begin
3601 Rewrite (Rop,
3602 Make_Range (Loc,
3603 Low_Bound =>
3604 Make_Attribute_Reference (Loc,
3605 Attribute_Name => Name_First,
3606 Prefix => New_Occurrence_Of (Rtyp, Loc)),
3607 High_Bound =>
3608 Make_Attribute_Reference (Loc,
3609 Attribute_Name => Name_Last,
3610 Prefix => New_Occurrence_Of (Rtyp, Loc))));
3611 Analyze_And_Resolve (Rop, Rtyp, Suppress => All_Checks);
3612 end;
3613 end if;
3615 -- Here for the explicit range case. Note that the bounds of the range
3616 -- have not been processed for minimized or eliminated checks.
3618 if Nkind (Rop) = N_Range then
3619 Minimize_Eliminate_Overflows
3620 (Low_Bound (Rop), Lo, Hi, Top_Level => False);
3621 Minimize_Eliminate_Overflows
3622 (High_Bound (Rop), Lo, Hi, Top_Level => False);
3624 -- We have A in B .. C, treated as A >= B and then A <= C
3626 -- Bignum case
3628 if Is_RTE (Etype (Lop), RE_Bignum)
3629 or else Is_RTE (Etype (Low_Bound (Rop)), RE_Bignum)
3630 or else Is_RTE (Etype (High_Bound (Rop)), RE_Bignum)
3631 then
3632 declare
3633 Blk : constant Node_Id := Make_Bignum_Block (Loc);
3634 Bnn : constant Entity_Id := Make_Temporary (Loc, 'B', N);
3635 L : constant Entity_Id :=
3636 Make_Defining_Identifier (Loc, Name_uL);
3637 Lopnd : constant Node_Id := Convert_To_Bignum (Lop);
3638 Lbound : constant Node_Id :=
3639 Convert_To_Bignum (Low_Bound (Rop));
3640 Hbound : constant Node_Id :=
3641 Convert_To_Bignum (High_Bound (Rop));
3643 -- Now we rewrite the membership test node to look like
3645 -- do
3646 -- Bnn : Result_Type;
3647 -- declare
3648 -- M : Mark_Id := SS_Mark;
3649 -- L : Bignum := Lopnd;
3650 -- begin
3651 -- Bnn := Big_GE (L, Lbound) and then Big_LE (L, Hbound)
3652 -- SS_Release (M);
3653 -- end;
3654 -- in
3655 -- Bnn
3656 -- end
3658 begin
3659 -- Insert declaration of L into declarations of bignum block
3661 Insert_After
3662 (Last (Declarations (Blk)),
3663 Make_Object_Declaration (Loc,
3664 Defining_Identifier => L,
3665 Object_Definition =>
3666 New_Occurrence_Of (RTE (RE_Bignum), Loc),
3667 Expression => Lopnd));
3669 -- Insert assignment to Bnn into expressions of bignum block
3671 Insert_Before
3672 (First (Statements (Handled_Statement_Sequence (Blk))),
3673 Make_Assignment_Statement (Loc,
3674 Name => New_Occurrence_Of (Bnn, Loc),
3675 Expression =>
3676 Make_And_Then (Loc,
3677 Left_Opnd =>
3678 Make_Function_Call (Loc,
3679 Name =>
3680 New_Occurrence_Of (RTE (RE_Big_GE), Loc),
3681 Parameter_Associations => New_List (
3682 New_Occurrence_Of (L, Loc),
3683 Lbound)),
3685 Right_Opnd =>
3686 Make_Function_Call (Loc,
3687 Name =>
3688 New_Occurrence_Of (RTE (RE_Big_LE), Loc),
3689 Parameter_Associations => New_List (
3690 New_Occurrence_Of (L, Loc),
3691 Hbound)))));
3693 -- Now rewrite the node
3695 Rewrite (N,
3696 Make_Expression_With_Actions (Loc,
3697 Actions => New_List (
3698 Make_Object_Declaration (Loc,
3699 Defining_Identifier => Bnn,
3700 Object_Definition =>
3701 New_Occurrence_Of (Result_Type, Loc)),
3702 Blk),
3703 Expression => New_Occurrence_Of (Bnn, Loc)));
3704 Analyze_And_Resolve (N, Result_Type);
3705 return;
3706 end;
3708 -- Here if no bignums around
3710 else
3711 -- Case where types are all the same
3713 if Base_Type (Etype (Lop)) = Base_Type (Etype (Low_Bound (Rop)))
3714 and then
3715 Base_Type (Etype (Lop)) = Base_Type (Etype (High_Bound (Rop)))
3716 then
3717 null;
3719 -- If types are not all the same, it means that we have rewritten
3720 -- at least one of them to be of type Long_Long_Integer, and we
3721 -- will convert the other operands to Long_Long_Integer.
3723 else
3724 Convert_To_And_Rewrite (LLIB, Lop);
3725 Set_Analyzed (Lop, False);
3726 Analyze_And_Resolve (Lop, LLIB);
3728 -- For the right operand, avoid unnecessary recursion into
3729 -- this routine, we know that overflow is not possible.
3731 Convert_To_And_Rewrite (LLIB, Low_Bound (Rop));
3732 Convert_To_And_Rewrite (LLIB, High_Bound (Rop));
3733 Set_Analyzed (Rop, False);
3734 Analyze_And_Resolve (Rop, LLIB, Suppress => Overflow_Check);
3735 end if;
3737 -- Now the three operands are of the same signed integer type,
3738 -- so we can use the normal expansion routine for membership,
3739 -- setting the flag to prevent recursion into this procedure.
3741 Set_No_Minimize_Eliminate (N);
3742 Expand_N_In (N);
3743 end if;
3745 -- Right operand is a subtype name and the subtype has a predicate. We
3746 -- have to make sure the predicate is checked, and for that we need to
3747 -- use the standard N_In circuitry with appropriate types.
3749 else
3750 pragma Assert (Present (Predicate_Function (Etype (Rop))));
3752 -- If types are "right", just call Expand_N_In preventing recursion
3754 if Base_Type (Etype (Lop)) = Base_Type (Etype (Rop)) then
3755 Set_No_Minimize_Eliminate (N);
3756 Expand_N_In (N);
3758 -- Bignum case
3760 elsif Is_RTE (Etype (Lop), RE_Bignum) then
3762 -- For X in T, we want to rewrite our node as
3764 -- do
3765 -- Bnn : Result_Type;
3767 -- declare
3768 -- M : Mark_Id := SS_Mark;
3769 -- Lnn : Long_Long_Integer'Base
3770 -- Nnn : Bignum;
3772 -- begin
3773 -- Nnn := X;
3775 -- if not Bignum_In_LLI_Range (Nnn) then
3776 -- Bnn := False;
3777 -- else
3778 -- Lnn := From_Bignum (Nnn);
3779 -- Bnn :=
3780 -- Lnn in LLIB (T'Base'First) .. LLIB (T'Base'Last)
3781 -- and then T'Base (Lnn) in T;
3782 -- end if;
3784 -- SS_Release (M);
3785 -- end
3786 -- in
3787 -- Bnn
3788 -- end
3790 -- A bit gruesome, but there doesn't seem to be a simpler way
3792 declare
3793 Blk : constant Node_Id := Make_Bignum_Block (Loc);
3794 Bnn : constant Entity_Id := Make_Temporary (Loc, 'B', N);
3795 Lnn : constant Entity_Id := Make_Temporary (Loc, 'L', N);
3796 Nnn : constant Entity_Id := Make_Temporary (Loc, 'N', N);
3797 T : constant Entity_Id := Etype (Rop);
3798 TB : constant Entity_Id := Base_Type (T);
3799 Nin : Node_Id;
3801 begin
3802 -- Mark the last membership operation to prevent recursion
3804 Nin :=
3805 Make_In (Loc,
3806 Left_Opnd => Convert_To (TB, New_Occurrence_Of (Lnn, Loc)),
3807 Right_Opnd => New_Occurrence_Of (T, Loc));
3808 Set_No_Minimize_Eliminate (Nin);
3810 -- Now decorate the block
3812 Insert_After
3813 (Last (Declarations (Blk)),
3814 Make_Object_Declaration (Loc,
3815 Defining_Identifier => Lnn,
3816 Object_Definition => New_Occurrence_Of (LLIB, Loc)));
3818 Insert_After
3819 (Last (Declarations (Blk)),
3820 Make_Object_Declaration (Loc,
3821 Defining_Identifier => Nnn,
3822 Object_Definition =>
3823 New_Occurrence_Of (RTE (RE_Bignum), Loc)));
3825 Insert_List_Before
3826 (First (Statements (Handled_Statement_Sequence (Blk))),
3827 New_List (
3828 Make_Assignment_Statement (Loc,
3829 Name => New_Occurrence_Of (Nnn, Loc),
3830 Expression => Relocate_Node (Lop)),
3832 Make_Implicit_If_Statement (N,
3833 Condition =>
3834 Make_Op_Not (Loc,
3835 Right_Opnd =>
3836 Make_Function_Call (Loc,
3837 Name =>
3838 New_Occurrence_Of
3839 (RTE (RE_Bignum_In_LLI_Range), Loc),
3840 Parameter_Associations => New_List (
3841 New_Occurrence_Of (Nnn, Loc)))),
3843 Then_Statements => New_List (
3844 Make_Assignment_Statement (Loc,
3845 Name => New_Occurrence_Of (Bnn, Loc),
3846 Expression =>
3847 New_Occurrence_Of (Standard_False, Loc))),
3849 Else_Statements => New_List (
3850 Make_Assignment_Statement (Loc,
3851 Name => New_Occurrence_Of (Lnn, Loc),
3852 Expression =>
3853 Make_Function_Call (Loc,
3854 Name =>
3855 New_Occurrence_Of (RTE (RE_From_Bignum), Loc),
3856 Parameter_Associations => New_List (
3857 New_Occurrence_Of (Nnn, Loc)))),
3859 Make_Assignment_Statement (Loc,
3860 Name => New_Occurrence_Of (Bnn, Loc),
3861 Expression =>
3862 Make_And_Then (Loc,
3863 Left_Opnd =>
3864 Make_In (Loc,
3865 Left_Opnd => New_Occurrence_Of (Lnn, Loc),
3866 Right_Opnd =>
3867 Make_Range (Loc,
3868 Low_Bound =>
3869 Convert_To (LLIB,
3870 Make_Attribute_Reference (Loc,
3871 Attribute_Name => Name_First,
3872 Prefix =>
3873 New_Occurrence_Of (TB, Loc))),
3875 High_Bound =>
3876 Convert_To (LLIB,
3877 Make_Attribute_Reference (Loc,
3878 Attribute_Name => Name_Last,
3879 Prefix =>
3880 New_Occurrence_Of (TB, Loc))))),
3882 Right_Opnd => Nin))))));
3884 -- Now we can do the rewrite
3886 Rewrite (N,
3887 Make_Expression_With_Actions (Loc,
3888 Actions => New_List (
3889 Make_Object_Declaration (Loc,
3890 Defining_Identifier => Bnn,
3891 Object_Definition =>
3892 New_Occurrence_Of (Result_Type, Loc)),
3893 Blk),
3894 Expression => New_Occurrence_Of (Bnn, Loc)));
3895 Analyze_And_Resolve (N, Result_Type);
3896 return;
3897 end;
3899 -- Not bignum case, but types don't match (this means we rewrote the
3900 -- left operand to be Long_Long_Integer).
3902 else
3903 pragma Assert (Base_Type (Etype (Lop)) = LLIB);
3905 -- We rewrite the membership test as (where T is the type with
3906 -- the predicate, i.e. the type of the right operand)
3908 -- Lop in LLIB (T'Base'First) .. LLIB (T'Base'Last)
3909 -- and then T'Base (Lop) in T
3911 declare
3912 T : constant Entity_Id := Etype (Rop);
3913 TB : constant Entity_Id := Base_Type (T);
3914 Nin : Node_Id;
3916 begin
3917 -- The last membership test is marked to prevent recursion
3919 Nin :=
3920 Make_In (Loc,
3921 Left_Opnd => Convert_To (TB, Duplicate_Subexpr (Lop)),
3922 Right_Opnd => New_Occurrence_Of (T, Loc));
3923 Set_No_Minimize_Eliminate (Nin);
3925 -- Now do the rewrite
3927 Rewrite (N,
3928 Make_And_Then (Loc,
3929 Left_Opnd =>
3930 Make_In (Loc,
3931 Left_Opnd => Lop,
3932 Right_Opnd =>
3933 Make_Range (Loc,
3934 Low_Bound =>
3935 Convert_To (LLIB,
3936 Make_Attribute_Reference (Loc,
3937 Attribute_Name => Name_First,
3938 Prefix =>
3939 New_Occurrence_Of (TB, Loc))),
3940 High_Bound =>
3941 Convert_To (LLIB,
3942 Make_Attribute_Reference (Loc,
3943 Attribute_Name => Name_Last,
3944 Prefix =>
3945 New_Occurrence_Of (TB, Loc))))),
3946 Right_Opnd => Nin));
3947 Set_Analyzed (N, False);
3948 Analyze_And_Resolve (N, Restype);
3949 end;
3950 end if;
3951 end if;
3952 end Expand_Membership_Minimize_Eliminate_Overflow;
3954 ---------------------------------
3955 -- Expand_Nonbinary_Modular_Op --
3956 ---------------------------------
3958 procedure Expand_Nonbinary_Modular_Op (N : Node_Id) is
3959 Loc : constant Source_Ptr := Sloc (N);
3960 Typ : constant Entity_Id := Etype (N);
3962 procedure Expand_Modular_Addition;
3963 -- Expand the modular addition, handling the special case of adding a
3964 -- constant.
3966 procedure Expand_Modular_Op;
3967 -- Compute the general rule: (lhs OP rhs) mod Modulus
3969 procedure Expand_Modular_Subtraction;
3970 -- Expand the modular addition, handling the special case of subtracting
3971 -- a constant.
3973 -----------------------------
3974 -- Expand_Modular_Addition --
3975 -----------------------------
3977 procedure Expand_Modular_Addition is
3978 begin
3979 -- If this is not the addition of a constant then compute it using
3980 -- the general rule: (lhs + rhs) mod Modulus
3982 if Nkind (Right_Opnd (N)) /= N_Integer_Literal then
3983 Expand_Modular_Op;
3985 -- If this is an addition of a constant, convert it to a subtraction
3986 -- plus a conditional expression since we can compute it faster than
3987 -- computing the modulus.
3989 -- modMinusRhs = Modulus - rhs
3990 -- if lhs < modMinusRhs then lhs + rhs
3991 -- else lhs - modMinusRhs
3993 else
3994 declare
3995 Mod_Minus_Right : constant Uint :=
3996 Modulus (Typ) - Intval (Right_Opnd (N));
3998 Cond_Expr : Node_Id;
3999 Then_Expr : Node_Id;
4000 Else_Expr : Node_Id;
4001 begin
4002 -- To prevent spurious visibility issues, convert all
4003 -- operands to Standard.Unsigned.
4005 Cond_Expr :=
4006 Make_Op_Lt (Loc,
4007 Left_Opnd =>
4008 Unchecked_Convert_To (Standard_Unsigned,
4009 New_Copy_Tree (Left_Opnd (N))),
4010 Right_Opnd =>
4011 Make_Integer_Literal (Loc, Mod_Minus_Right));
4013 Then_Expr :=
4014 Make_Op_Add (Loc,
4015 Left_Opnd =>
4016 Unchecked_Convert_To (Standard_Unsigned,
4017 New_Copy_Tree (Left_Opnd (N))),
4018 Right_Opnd =>
4019 Make_Integer_Literal (Loc, Intval (Right_Opnd (N))));
4021 Else_Expr :=
4022 Make_Op_Subtract (Loc,
4023 Left_Opnd =>
4024 Unchecked_Convert_To (Standard_Unsigned,
4025 New_Copy_Tree (Left_Opnd (N))),
4026 Right_Opnd =>
4027 Make_Integer_Literal (Loc, Mod_Minus_Right));
4029 Rewrite (N,
4030 Unchecked_Convert_To (Typ,
4031 Make_If_Expression (Loc,
4032 Expressions =>
4033 New_List (Cond_Expr, Then_Expr, Else_Expr))));
4034 end;
4035 end if;
4036 end Expand_Modular_Addition;
4038 -----------------------
4039 -- Expand_Modular_Op --
4040 -----------------------
4042 procedure Expand_Modular_Op is
4043 -- We will convert to another type (not a nonbinary-modulus modular
4044 -- type), evaluate the op in that representation, reduce the result,
4045 -- and convert back to the original type. This means that the
4046 -- backend does not have to deal with nonbinary-modulus ops.
4048 Op_Expr : constant Node_Id := New_Op_Node (Nkind (N), Loc);
4049 Mod_Expr : Node_Id;
4051 Target_Type : Entity_Id;
4052 begin
4053 -- Select a target type that is large enough to avoid spurious
4054 -- intermediate overflow on pre-reduction computation (for
4055 -- correctness) but is no larger than is needed (for performance).
4057 declare
4058 Required_Size : Uint := RM_Size (Etype (N));
4059 Use_Unsigned : Boolean := True;
4060 begin
4061 case Nkind (N) is
4062 when N_Op_Add =>
4063 -- For example, if modulus is 255 then RM_Size will be 8
4064 -- and the range of possible values (before reduction) will
4065 -- be 0 .. 508; that range requires 9 bits.
4066 Required_Size := Required_Size + 1;
4068 when N_Op_Subtract =>
4069 -- For example, if modulus is 255 then RM_Size will be 8
4070 -- and the range of possible values (before reduction) will
4071 -- be -254 .. 254; that range requires 9 bits, signed.
4072 Use_Unsigned := False;
4073 Required_Size := Required_Size + 1;
4075 when N_Op_Multiply =>
4076 -- For example, if modulus is 255 then RM_Size will be 8
4077 -- and the range of possible values (before reduction) will
4078 -- be 0 .. 64,516; that range requires 16 bits.
4079 Required_Size := Required_Size * 2;
4081 when others =>
4082 null;
4083 end case;
4085 if Use_Unsigned then
4086 if Required_Size <= Standard_Short_Short_Integer_Size then
4087 Target_Type := Standard_Short_Short_Unsigned;
4088 elsif Required_Size <= Standard_Short_Integer_Size then
4089 Target_Type := Standard_Short_Unsigned;
4090 elsif Required_Size <= Standard_Integer_Size then
4091 Target_Type := Standard_Unsigned;
4092 else
4093 pragma Assert (Required_Size <= 64);
4094 Target_Type := Standard_Unsigned_64;
4095 end if;
4096 elsif Required_Size <= 8 then
4097 Target_Type := Standard_Integer_8;
4098 elsif Required_Size <= 16 then
4099 Target_Type := Standard_Integer_16;
4100 elsif Required_Size <= 32 then
4101 Target_Type := Standard_Integer_32;
4102 else
4103 pragma Assert (Required_Size <= 64);
4104 Target_Type := Standard_Integer_64;
4105 end if;
4107 pragma Assert (Present (Target_Type));
4108 end;
4110 Set_Left_Opnd (Op_Expr,
4111 Unchecked_Convert_To (Target_Type,
4112 New_Copy_Tree (Left_Opnd (N))));
4113 Set_Right_Opnd (Op_Expr,
4114 Unchecked_Convert_To (Target_Type,
4115 New_Copy_Tree (Right_Opnd (N))));
4117 -- ??? Why do this stuff for some ops and not others?
4118 if Nkind (N) not in N_Op_And | N_Op_Or | N_Op_Xor then
4120 -- Link this node to the tree to analyze it
4122 -- If the parent node is an expression with actions we link it to
4123 -- N since otherwise Force_Evaluation cannot identify if this node
4124 -- comes from the Expression and rejects generating the temporary.
4126 if Nkind (Parent (N)) = N_Expression_With_Actions then
4127 Set_Parent (Op_Expr, N);
4129 -- Common case
4131 else
4132 Set_Parent (Op_Expr, Parent (N));
4133 end if;
4135 Analyze (Op_Expr);
4137 -- Force generating a temporary because in the expansion of this
4138 -- expression we may generate code that performs this computation
4139 -- several times.
4141 Force_Evaluation (Op_Expr, Mode => Strict);
4142 end if;
4144 Mod_Expr :=
4145 Make_Op_Mod (Loc,
4146 Left_Opnd => Op_Expr,
4147 Right_Opnd => Make_Integer_Literal (Loc, Modulus (Typ)));
4149 Rewrite (N,
4150 Unchecked_Convert_To (Typ, Mod_Expr));
4151 end Expand_Modular_Op;
4153 --------------------------------
4154 -- Expand_Modular_Subtraction --
4155 --------------------------------
4157 procedure Expand_Modular_Subtraction is
4158 begin
4159 -- If this is not the addition of a constant then compute it using
4160 -- the general rule: (lhs + rhs) mod Modulus
4162 if Nkind (Right_Opnd (N)) /= N_Integer_Literal then
4163 Expand_Modular_Op;
4165 -- If this is an addition of a constant, convert it to a subtraction
4166 -- plus a conditional expression since we can compute it faster than
4167 -- computing the modulus.
4169 -- modMinusRhs = Modulus - rhs
4170 -- if lhs < rhs then lhs + modMinusRhs
4171 -- else lhs - rhs
4173 else
4174 declare
4175 Mod_Minus_Right : constant Uint :=
4176 Modulus (Typ) - Intval (Right_Opnd (N));
4178 Cond_Expr : Node_Id;
4179 Then_Expr : Node_Id;
4180 Else_Expr : Node_Id;
4181 begin
4182 Cond_Expr :=
4183 Make_Op_Lt (Loc,
4184 Left_Opnd =>
4185 Unchecked_Convert_To (Standard_Unsigned,
4186 New_Copy_Tree (Left_Opnd (N))),
4187 Right_Opnd =>
4188 Make_Integer_Literal (Loc, Intval (Right_Opnd (N))));
4190 Then_Expr :=
4191 Make_Op_Add (Loc,
4192 Left_Opnd =>
4193 Unchecked_Convert_To (Standard_Unsigned,
4194 New_Copy_Tree (Left_Opnd (N))),
4195 Right_Opnd =>
4196 Make_Integer_Literal (Loc, Mod_Minus_Right));
4198 Else_Expr :=
4199 Make_Op_Subtract (Loc,
4200 Left_Opnd =>
4201 Unchecked_Convert_To (Standard_Unsigned,
4202 New_Copy_Tree (Left_Opnd (N))),
4203 Right_Opnd =>
4204 Unchecked_Convert_To (Standard_Unsigned,
4205 New_Copy_Tree (Right_Opnd (N))));
4207 Rewrite (N,
4208 Unchecked_Convert_To (Typ,
4209 Make_If_Expression (Loc,
4210 Expressions =>
4211 New_List (Cond_Expr, Then_Expr, Else_Expr))));
4212 end;
4213 end if;
4214 end Expand_Modular_Subtraction;
4216 -- Start of processing for Expand_Nonbinary_Modular_Op
4218 begin
4219 -- No action needed if front-end expansion is not required or if we
4220 -- have a binary modular operand.
4222 if not Expand_Nonbinary_Modular_Ops
4223 or else not Non_Binary_Modulus (Typ)
4224 then
4225 return;
4226 end if;
4228 case Nkind (N) is
4229 when N_Op_Add =>
4230 Expand_Modular_Addition;
4232 when N_Op_Subtract =>
4233 Expand_Modular_Subtraction;
4235 when N_Op_Minus =>
4237 -- Expand -expr into (0 - expr)
4239 Rewrite (N,
4240 Make_Op_Subtract (Loc,
4241 Left_Opnd => Make_Integer_Literal (Loc, 0),
4242 Right_Opnd => Right_Opnd (N)));
4243 Analyze_And_Resolve (N, Typ);
4245 when others =>
4246 Expand_Modular_Op;
4247 end case;
4249 Analyze_And_Resolve (N, Typ);
4250 end Expand_Nonbinary_Modular_Op;
4252 ------------------------
4253 -- Expand_N_Allocator --
4254 ------------------------
4256 procedure Expand_N_Allocator (N : Node_Id) is
4257 Etyp : constant Entity_Id := Etype (Expression (N));
4258 Loc : constant Source_Ptr := Sloc (N);
4259 PtrT : constant Entity_Id := Etype (N);
4261 procedure Rewrite_Coextension (N : Node_Id);
4262 -- Static coextensions have the same lifetime as the entity they
4263 -- constrain. Such occurrences can be rewritten as aliased objects
4264 -- and their unrestricted access used instead of the coextension.
4266 function Size_In_Storage_Elements (E : Entity_Id) return Node_Id;
4267 -- Given a constrained array type E, returns a node representing the
4268 -- code to compute a close approximation of the size in storage elements
4269 -- for the given type; for indexes that are modular types we compute
4270 -- 'Last - First (instead of 'Length) because for large arrays computing
4271 -- 'Last -'First + 1 causes overflow. This is done without using the
4272 -- attribute 'Size_In_Storage_Elements (which malfunctions for large
4273 -- sizes ???).
4275 -------------------------
4276 -- Rewrite_Coextension --
4277 -------------------------
4279 procedure Rewrite_Coextension (N : Node_Id) is
4280 Temp_Id : constant Node_Id := Make_Temporary (Loc, 'C');
4281 Temp_Decl : Node_Id;
4283 begin
4284 -- Generate:
4285 -- Cnn : aliased Etyp;
4287 Temp_Decl :=
4288 Make_Object_Declaration (Loc,
4289 Defining_Identifier => Temp_Id,
4290 Aliased_Present => True,
4291 Object_Definition => New_Occurrence_Of (Etyp, Loc));
4293 if Nkind (Expression (N)) = N_Qualified_Expression then
4294 Set_Expression (Temp_Decl, Expression (Expression (N)));
4295 end if;
4297 Insert_Action (N, Temp_Decl);
4298 Rewrite (N,
4299 Make_Attribute_Reference (Loc,
4300 Prefix => New_Occurrence_Of (Temp_Id, Loc),
4301 Attribute_Name => Name_Unrestricted_Access));
4303 Analyze_And_Resolve (N, PtrT);
4304 end Rewrite_Coextension;
4306 ------------------------------
4307 -- Size_In_Storage_Elements --
4308 ------------------------------
4310 function Size_In_Storage_Elements (E : Entity_Id) return Node_Id is
4311 Idx : Node_Id := First_Index (E);
4312 Len : Node_Id;
4313 Res : Node_Id := Empty;
4315 begin
4316 -- Logically this just returns E'Max_Size_In_Storage_Elements.
4317 -- However, the reason for the existence of this function is to
4318 -- construct a test for sizes too large, which means near the 32-bit
4319 -- limit on a 32-bit machine, and precisely the trouble is that we
4320 -- get overflows when sizes are greater than 2**31.
4322 -- So what we end up doing for array types is to use the expression:
4324 -- number-of-elements * component_type'Max_Size_In_Storage_Elements
4326 -- which avoids this problem. All this is a bit bogus, but it does
4327 -- mean we catch common cases of trying to allocate arrays that are
4328 -- too large, and which in the absence of a check results in
4329 -- undetected chaos ???
4331 for J in 1 .. Number_Dimensions (E) loop
4333 if not Is_Modular_Integer_Type (Etype (Idx)) then
4334 Len :=
4335 Make_Attribute_Reference (Loc,
4336 Prefix => New_Occurrence_Of (E, Loc),
4337 Attribute_Name => Name_Length,
4338 Expressions => New_List (Make_Integer_Literal (Loc, J)));
4340 -- For indexes that are modular types we cannot generate code to
4341 -- compute 'Length since for large arrays 'Last -'First + 1 causes
4342 -- overflow; therefore we compute 'Last - 'First (which is not the
4343 -- exact number of components but it is valid for the purpose of
4344 -- this runtime check on 32-bit targets).
4346 else
4347 declare
4348 Len_Minus_1_Expr : Node_Id;
4349 Test_Gt : Node_Id;
4351 begin
4352 Test_Gt :=
4353 Make_Op_Gt (Loc,
4354 Make_Attribute_Reference (Loc,
4355 Prefix => New_Occurrence_Of (E, Loc),
4356 Attribute_Name => Name_Last,
4357 Expressions =>
4358 New_List (Make_Integer_Literal (Loc, J))),
4359 Make_Attribute_Reference (Loc,
4360 Prefix => New_Occurrence_Of (E, Loc),
4361 Attribute_Name => Name_First,
4362 Expressions =>
4363 New_List (Make_Integer_Literal (Loc, J))));
4365 Len_Minus_1_Expr :=
4366 Convert_To (Standard_Unsigned,
4367 Make_Op_Subtract (Loc,
4368 Make_Attribute_Reference (Loc,
4369 Prefix => New_Occurrence_Of (E, Loc),
4370 Attribute_Name => Name_Last,
4371 Expressions =>
4372 New_List (Make_Integer_Literal (Loc, J))),
4373 Make_Attribute_Reference (Loc,
4374 Prefix => New_Occurrence_Of (E, Loc),
4375 Attribute_Name => Name_First,
4376 Expressions =>
4377 New_List (Make_Integer_Literal (Loc, J)))));
4379 -- Handle superflat arrays, i.e. arrays with such bounds as
4380 -- 4 .. 2, to ensure that the result is correct.
4382 -- Generate:
4383 -- (if X'Last > X'First then X'Last - X'First else 0)
4385 Len :=
4386 Make_If_Expression (Loc,
4387 Expressions => New_List (
4388 Test_Gt,
4389 Len_Minus_1_Expr,
4390 Make_Integer_Literal (Loc, Uint_0)));
4391 end;
4392 end if;
4394 if J = 1 then
4395 Res := Len;
4397 else
4398 pragma Assert (Present (Res));
4399 Res :=
4400 Make_Op_Multiply (Loc,
4401 Left_Opnd => Res,
4402 Right_Opnd => Len);
4403 end if;
4405 Next_Index (Idx);
4406 end loop;
4408 return
4409 Make_Op_Multiply (Loc,
4410 Left_Opnd => Len,
4411 Right_Opnd =>
4412 Make_Attribute_Reference (Loc,
4413 Prefix => New_Occurrence_Of (Component_Type (E), Loc),
4414 Attribute_Name => Name_Max_Size_In_Storage_Elements));
4415 end Size_In_Storage_Elements;
4417 -- Local variables
4419 Dtyp : constant Entity_Id := Available_View (Designated_Type (PtrT));
4420 Desig : Entity_Id;
4421 Nod : Node_Id;
4422 Pool : Entity_Id;
4423 Rel_Typ : Entity_Id;
4424 Temp : Entity_Id;
4426 -- Start of processing for Expand_N_Allocator
4428 begin
4429 -- Warn on the presence of an allocator of an anonymous access type when
4430 -- enabled, except when it's an object declaration at library level.
4432 if Warn_On_Anonymous_Allocators
4433 and then Ekind (PtrT) = E_Anonymous_Access_Type
4434 and then not (Is_Library_Level_Entity (PtrT)
4435 and then Nkind (Associated_Node_For_Itype (PtrT)) =
4436 N_Object_Declaration)
4437 then
4438 Error_Msg_N ("?_a?use of an anonymous access type allocator", N);
4439 end if;
4441 -- RM E.2.2(17). We enforce that the expected type of an allocator
4442 -- shall not be a remote access-to-class-wide-limited-private type.
4443 -- We probably shouldn't be doing this legality check during expansion,
4444 -- but this is only an issue for Annex E users, and is unlikely to be a
4445 -- problem in practice.
4447 Validate_Remote_Access_To_Class_Wide_Type (N);
4449 -- Processing for anonymous access-to-controlled types. These access
4450 -- types receive a special finalization master which appears in the
4451 -- declarations of the enclosing semantic unit. This expansion is done
4452 -- now to ensure that any additional types generated by this routine or
4453 -- Expand_Allocator_Expression inherit the proper type attributes.
4455 if (Ekind (PtrT) = E_Anonymous_Access_Type
4456 or else (Is_Itype (PtrT) and then No (Finalization_Master (PtrT))))
4457 and then Needs_Finalization (Dtyp)
4458 then
4459 -- Detect the allocation of an anonymous controlled object where the
4460 -- type of the context is named. For example:
4462 -- procedure Proc (Ptr : Named_Access_Typ);
4463 -- Proc (new Designated_Typ);
4465 -- Regardless of the anonymous-to-named access type conversion, the
4466 -- lifetime of the object must be associated with the named access
4467 -- type. Use the finalization-related attributes of this type.
4469 if Nkind (Parent (N)) in N_Type_Conversion
4470 | N_Unchecked_Type_Conversion
4471 and then Ekind (Etype (Parent (N))) in E_Access_Subtype
4472 | E_Access_Type
4473 | E_General_Access_Type
4474 then
4475 Rel_Typ := Etype (Parent (N));
4476 else
4477 Rel_Typ := Empty;
4478 end if;
4480 -- Anonymous access-to-controlled types allocate on the global pool.
4481 -- Note that this is a "root type only" attribute.
4483 if No (Associated_Storage_Pool (PtrT)) then
4484 if Present (Rel_Typ) then
4485 Set_Associated_Storage_Pool
4486 (Root_Type (PtrT), Associated_Storage_Pool (Rel_Typ));
4487 else
4488 Set_Associated_Storage_Pool
4489 (Root_Type (PtrT), RTE (RE_Global_Pool_Object));
4490 end if;
4491 end if;
4493 -- The finalization master must be inserted and analyzed as part of
4494 -- the current semantic unit. Note that the master is updated when
4495 -- analysis changes current units. Note that this is a "root type
4496 -- only" attribute.
4498 if Present (Rel_Typ) then
4499 Set_Finalization_Master
4500 (Root_Type (PtrT), Finalization_Master (Rel_Typ));
4501 else
4502 Build_Anonymous_Master (Root_Type (PtrT));
4503 end if;
4504 end if;
4506 -- Set the storage pool and find the appropriate version of Allocate to
4507 -- call. Do not overwrite the storage pool if it is already set, which
4508 -- can happen for build-in-place function returns (see
4509 -- Exp_Ch4.Expand_N_Extended_Return_Statement).
4511 if No (Storage_Pool (N)) then
4512 Pool := Associated_Storage_Pool (Root_Type (PtrT));
4514 if Present (Pool) then
4515 Set_Storage_Pool (N, Pool);
4517 if Is_RTE (Pool, RE_RS_Pool) then
4518 Set_Procedure_To_Call (N, RTE (RE_RS_Allocate));
4520 elsif Is_RTE (Pool, RE_SS_Pool) then
4521 Check_Restriction (No_Secondary_Stack, N);
4522 Set_Procedure_To_Call (N, RTE (RE_SS_Allocate));
4524 -- In the case of an allocator for a simple storage pool, locate
4525 -- and save a reference to the pool type's Allocate routine.
4527 elsif Present (Get_Rep_Pragma
4528 (Etype (Pool), Name_Simple_Storage_Pool_Type))
4529 then
4530 declare
4531 Pool_Type : constant Entity_Id := Base_Type (Etype (Pool));
4532 Alloc_Op : Entity_Id;
4533 begin
4534 Alloc_Op := Get_Name_Entity_Id (Name_Allocate);
4535 while Present (Alloc_Op) loop
4536 if Scope (Alloc_Op) = Scope (Pool_Type)
4537 and then Present (First_Formal (Alloc_Op))
4538 and then Etype (First_Formal (Alloc_Op)) = Pool_Type
4539 then
4540 Set_Procedure_To_Call (N, Alloc_Op);
4541 exit;
4542 else
4543 Alloc_Op := Homonym (Alloc_Op);
4544 end if;
4545 end loop;
4546 end;
4548 elsif Is_Class_Wide_Type (Etype (Pool)) then
4549 Set_Procedure_To_Call (N, RTE (RE_Allocate_Any));
4551 else
4552 Set_Procedure_To_Call (N,
4553 Find_Storage_Op (Etype (Pool), Name_Allocate));
4554 end if;
4555 end if;
4556 end if;
4558 -- Under certain circumstances we can replace an allocator by an access
4559 -- to statically allocated storage. The conditions, as noted in AARM
4560 -- 3.10 (10c) are as follows:
4562 -- Size and initial value is known at compile time
4563 -- Access type is access-to-constant
4565 -- The allocator is not part of a constraint on a record component,
4566 -- because in that case the inserted actions are delayed until the
4567 -- record declaration is fully analyzed, which is too late for the
4568 -- analysis of the rewritten allocator.
4570 if Is_Access_Constant (PtrT)
4571 and then Nkind (Expression (N)) = N_Qualified_Expression
4572 and then Compile_Time_Known_Value (Expression (Expression (N)))
4573 and then Size_Known_At_Compile_Time
4574 (Etype (Expression (Expression (N))))
4575 and then not Is_Record_Type (Current_Scope)
4576 then
4577 -- Here we can do the optimization. For the allocator
4579 -- new x'(y)
4581 -- We insert an object declaration
4583 -- Tnn : aliased x := y;
4585 -- and replace the allocator by Tnn'Unrestricted_Access. Tnn is
4586 -- marked as requiring static allocation.
4588 Temp := Make_Temporary (Loc, 'T', Expression (Expression (N)));
4589 Desig := Subtype_Mark (Expression (N));
4591 -- If context is constrained, use constrained subtype directly,
4592 -- so that the constant is not labelled as having a nominally
4593 -- unconstrained subtype.
4595 if Entity (Desig) = Base_Type (Dtyp) then
4596 Desig := New_Occurrence_Of (Dtyp, Loc);
4597 end if;
4599 Insert_Action (N,
4600 Make_Object_Declaration (Loc,
4601 Defining_Identifier => Temp,
4602 Aliased_Present => True,
4603 Constant_Present => Is_Access_Constant (PtrT),
4604 Object_Definition => Desig,
4605 Expression => Expression (Expression (N))));
4607 Rewrite (N,
4608 Make_Attribute_Reference (Loc,
4609 Prefix => New_Occurrence_Of (Temp, Loc),
4610 Attribute_Name => Name_Unrestricted_Access));
4612 Analyze_And_Resolve (N, PtrT);
4614 -- We set the variable as statically allocated, since we don't want
4615 -- it going on the stack of the current procedure.
4617 Set_Is_Statically_Allocated (Temp);
4618 return;
4619 end if;
4621 -- Same if the allocator is an access discriminant for a local object:
4622 -- instead of an allocator we create a local value and constrain the
4623 -- enclosing object with the corresponding access attribute.
4625 if Is_Static_Coextension (N) then
4626 Rewrite_Coextension (N);
4627 return;
4628 end if;
4630 -- Check for size too large, we do this because the back end misses
4631 -- proper checks here and can generate rubbish allocation calls when
4632 -- we are near the limit. We only do this for the 32-bit address case
4633 -- since that is from a practical point of view where we see a problem.
4635 if System_Address_Size = 32
4636 and then not Storage_Checks_Suppressed (PtrT)
4637 and then not Storage_Checks_Suppressed (Dtyp)
4638 and then not Storage_Checks_Suppressed (Etyp)
4639 then
4640 -- The check we want to generate should look like
4642 -- if Etyp'Max_Size_In_Storage_Elements > 3.5 gigabytes then
4643 -- raise Storage_Error;
4644 -- end if;
4646 -- where 3.5 gigabytes is a constant large enough to accommodate any
4647 -- reasonable request for. But we can't do it this way because at
4648 -- least at the moment we don't compute this attribute right, and
4649 -- can silently give wrong results when the result gets large. Since
4650 -- this is all about large results, that's bad, so instead we only
4651 -- apply the check for constrained arrays, and manually compute the
4652 -- value of the attribute ???
4654 -- The check on No_Initialization is used here to prevent generating
4655 -- this runtime check twice when the allocator is locally replaced by
4656 -- the expander with another one.
4658 if Is_Array_Type (Etyp) and then not No_Initialization (N) then
4659 declare
4660 Cond : Node_Id;
4661 Ins_Nod : Node_Id := N;
4662 Siz_Typ : Entity_Id := Etyp;
4663 Expr : Node_Id;
4665 begin
4666 -- For unconstrained array types initialized with a qualified
4667 -- expression we use its type to perform this check
4669 if not Is_Constrained (Etyp)
4670 and then not No_Initialization (N)
4671 and then Nkind (Expression (N)) = N_Qualified_Expression
4672 then
4673 Expr := Expression (Expression (N));
4674 Siz_Typ := Etype (Expression (Expression (N)));
4676 -- If the qualified expression has been moved to an internal
4677 -- temporary (to remove side effects) then we must insert
4678 -- the runtime check before its declaration to ensure that
4679 -- the check is performed before the execution of the code
4680 -- computing the qualified expression.
4682 if Nkind (Expr) = N_Identifier
4683 and then Is_Internal_Name (Chars (Expr))
4684 and then
4685 Nkind (Parent (Entity (Expr))) = N_Object_Declaration
4686 then
4687 Ins_Nod := Parent (Entity (Expr));
4688 else
4689 Ins_Nod := Expr;
4690 end if;
4691 end if;
4693 if Is_Constrained (Siz_Typ)
4694 and then Ekind (Siz_Typ) /= E_String_Literal_Subtype
4695 then
4696 -- For CCG targets, the largest array may have up to 2**31-1
4697 -- components (i.e. 2 gigabytes if each array component is
4698 -- one byte). This ensures that fat pointer fields do not
4699 -- overflow, since they are 32-bit integer types, and also
4700 -- ensures that 'Length can be computed at run time.
4702 if Modify_Tree_For_C then
4703 Cond :=
4704 Make_Op_Gt (Loc,
4705 Left_Opnd => Size_In_Storage_Elements (Siz_Typ),
4706 Right_Opnd => Make_Integer_Literal (Loc,
4707 Uint_2 ** 31 - Uint_1));
4709 -- For native targets the largest object is 3.5 gigabytes
4711 else
4712 Cond :=
4713 Make_Op_Gt (Loc,
4714 Left_Opnd => Size_In_Storage_Elements (Siz_Typ),
4715 Right_Opnd => Make_Integer_Literal (Loc,
4716 Uint_7 * (Uint_2 ** 29)));
4717 end if;
4719 Insert_Action (Ins_Nod,
4720 Make_Raise_Storage_Error (Loc,
4721 Condition => Cond,
4722 Reason => SE_Object_Too_Large));
4724 if Entity (Cond) = Standard_True then
4725 Error_Msg_N
4726 ("object too large: Storage_Error will be raised at "
4727 & "run time??", N);
4728 end if;
4729 end if;
4730 end;
4731 end if;
4732 end if;
4734 -- If no storage pool has been specified, or the storage pool
4735 -- is System.Pool_Global.Global_Pool_Object, and the restriction
4736 -- No_Standard_Allocators_After_Elaboration is present, then generate
4737 -- a call to Elaboration_Allocators.Check_Standard_Allocator.
4739 if Nkind (N) = N_Allocator
4740 and then (No (Storage_Pool (N))
4741 or else Is_RTE (Storage_Pool (N), RE_Global_Pool_Object))
4742 and then Restriction_Active (No_Standard_Allocators_After_Elaboration)
4743 then
4744 Insert_Action (N,
4745 Make_Procedure_Call_Statement (Loc,
4746 Name =>
4747 New_Occurrence_Of (RTE (RE_Check_Standard_Allocator), Loc)));
4748 end if;
4750 -- Handle case of qualified expression (other than optimization above)
4752 if Nkind (Expression (N)) = N_Qualified_Expression then
4753 Expand_Allocator_Expression (N);
4754 return;
4755 end if;
4757 -- If the allocator is for a type which requires initialization, and
4758 -- there is no initial value (i.e. operand is a subtype indication
4759 -- rather than a qualified expression), then we must generate a call to
4760 -- the initialization routine using an expressions action node:
4762 -- [Pnnn : constant ptr_T := new (T); Init (Pnnn.all,...); Pnnn]
4764 -- Here ptr_T is the pointer type for the allocator, and T is the
4765 -- subtype of the allocator. A special case arises if the designated
4766 -- type of the access type is a task or contains tasks. In this case
4767 -- the call to Init (Temp.all ...) is replaced by code that ensures
4768 -- that tasks get activated (see Exp_Ch9.Build_Task_Allocate_Block
4769 -- for details). In addition, if the type T is a task type, then the
4770 -- first argument to Init must be converted to the task record type.
4772 declare
4773 T : constant Entity_Id := Etype (Expression (N));
4774 Args : List_Id;
4775 Decls : List_Id;
4776 Decl : Node_Id;
4777 Discr : Elmt_Id;
4778 Init : Entity_Id;
4779 Init_Arg1 : Node_Id;
4780 Init_Call : Node_Id;
4781 Temp_Decl : Node_Id;
4782 Temp_Type : Entity_Id;
4784 begin
4785 -- Apply constraint checks against designated subtype (RM 4.8(10/2))
4786 -- but ignore the expression if the No_Initialization flag is set.
4787 -- Discriminant checks will be generated by the expansion below.
4789 if Is_Array_Type (Dtyp) and then not No_Initialization (N) then
4790 Apply_Constraint_Check (Expression (N), Dtyp, No_Sliding => True);
4792 Apply_Predicate_Check (Expression (N), Dtyp);
4794 if Nkind (Expression (N)) = N_Raise_Constraint_Error then
4795 Rewrite (N, New_Copy (Expression (N)));
4796 Set_Etype (N, PtrT);
4797 return;
4798 end if;
4799 end if;
4801 if No_Initialization (N) then
4803 -- Even though this might be a simple allocation, create a custom
4804 -- Allocate if the context requires it.
4806 if Present (Finalization_Master (PtrT)) then
4807 Build_Allocate_Deallocate_Proc
4808 (N => N,
4809 Is_Allocate => True);
4810 end if;
4812 -- Optimize the default allocation of an array object when pragma
4813 -- Initialize_Scalars or Normalize_Scalars is in effect. Construct an
4814 -- in-place initialization aggregate which may be convert into a fast
4815 -- memset by the backend.
4817 elsif Init_Or_Norm_Scalars
4818 and then Is_Array_Type (T)
4820 -- The array must lack atomic components because they are treated
4821 -- as non-static, and as a result the backend will not initialize
4822 -- the memory in one go.
4824 and then not Has_Atomic_Components (T)
4826 -- The array must not be packed because the invalid values in
4827 -- System.Scalar_Values are multiples of Storage_Unit.
4829 and then not Is_Packed (T)
4831 -- The array must have static non-empty ranges, otherwise the
4832 -- backend cannot initialize the memory in one go.
4834 and then Has_Static_Non_Empty_Array_Bounds (T)
4836 -- The optimization is only relevant for arrays of scalar types
4838 and then Is_Scalar_Type (Component_Type (T))
4840 -- Similar to regular array initialization using a type init proc,
4841 -- predicate checks are not performed because the initialization
4842 -- values are intentionally invalid, and may violate the predicate.
4844 and then not Has_Predicates (Component_Type (T))
4846 -- The component type must have a single initialization value
4848 and then Needs_Simple_Initialization
4849 (Typ => Component_Type (T),
4850 Consider_IS => True)
4851 then
4852 Set_Analyzed (N);
4853 Temp := Make_Temporary (Loc, 'P');
4855 -- Generate:
4856 -- Temp : Ptr_Typ := new ...;
4858 Insert_Action
4859 (Assoc_Node => N,
4860 Ins_Action =>
4861 Make_Object_Declaration (Loc,
4862 Defining_Identifier => Temp,
4863 Object_Definition => New_Occurrence_Of (PtrT, Loc),
4864 Expression => Relocate_Node (N)),
4865 Suppress => All_Checks);
4867 -- Generate:
4868 -- Temp.all := (others => ...);
4870 Insert_Action
4871 (Assoc_Node => N,
4872 Ins_Action =>
4873 Make_Assignment_Statement (Loc,
4874 Name =>
4875 Make_Explicit_Dereference (Loc,
4876 Prefix => New_Occurrence_Of (Temp, Loc)),
4877 Expression =>
4878 Get_Simple_Init_Val
4879 (Typ => T,
4880 N => N,
4881 Size => Esize (Component_Type (T)))),
4882 Suppress => All_Checks);
4884 Rewrite (N, New_Occurrence_Of (Temp, Loc));
4885 Analyze_And_Resolve (N, PtrT);
4887 -- Case of no initialization procedure present
4889 elsif not Has_Non_Null_Base_Init_Proc (T) then
4891 -- Case of simple initialization required
4893 if Needs_Simple_Initialization (T) then
4894 Check_Restriction (No_Default_Initialization, N);
4895 Rewrite (Expression (N),
4896 Make_Qualified_Expression (Loc,
4897 Subtype_Mark => New_Occurrence_Of (T, Loc),
4898 Expression => Get_Simple_Init_Val (T, N)));
4900 Analyze_And_Resolve (Expression (Expression (N)), T);
4901 Analyze_And_Resolve (Expression (N), T);
4902 Set_Paren_Count (Expression (Expression (N)), 1);
4903 Expand_N_Allocator (N);
4905 -- No initialization required
4907 else
4908 Build_Allocate_Deallocate_Proc
4909 (N => N,
4910 Is_Allocate => True);
4911 end if;
4913 -- Case of initialization procedure present, must be called
4915 -- NOTE: There is a *huge* amount of code duplication here from
4916 -- Build_Initialization_Call. We should probably refactor???
4918 else
4919 Check_Restriction (No_Default_Initialization, N);
4921 if not Restriction_Active (No_Default_Initialization) then
4922 Init := Base_Init_Proc (T);
4923 Nod := N;
4924 Temp := Make_Temporary (Loc, 'P');
4926 -- Construct argument list for the initialization routine call
4928 Init_Arg1 :=
4929 Make_Explicit_Dereference (Loc,
4930 Prefix =>
4931 New_Occurrence_Of (Temp, Loc));
4933 Set_Assignment_OK (Init_Arg1);
4934 Temp_Type := PtrT;
4936 -- The initialization procedure expects a specific type. if the
4937 -- context is access to class wide, indicate that the object
4938 -- being allocated has the right specific type.
4940 if Is_Class_Wide_Type (Dtyp) then
4941 Init_Arg1 := Unchecked_Convert_To (T, Init_Arg1);
4942 end if;
4944 -- If designated type is a concurrent type or if it is private
4945 -- type whose definition is a concurrent type, the first
4946 -- argument in the Init routine has to be unchecked conversion
4947 -- to the corresponding record type. If the designated type is
4948 -- a derived type, also convert the argument to its root type.
4950 if Is_Concurrent_Type (T) then
4951 Init_Arg1 :=
4952 Unchecked_Convert_To (
4953 Corresponding_Record_Type (T), Init_Arg1);
4955 elsif Is_Private_Type (T)
4956 and then Present (Full_View (T))
4957 and then Is_Concurrent_Type (Full_View (T))
4958 then
4959 Init_Arg1 :=
4960 Unchecked_Convert_To
4961 (Corresponding_Record_Type (Full_View (T)), Init_Arg1);
4963 elsif Etype (First_Formal (Init)) /= Base_Type (T) then
4964 declare
4965 Ftyp : constant Entity_Id := Etype (First_Formal (Init));
4967 begin
4968 Init_Arg1 := OK_Convert_To (Etype (Ftyp), Init_Arg1);
4969 Set_Etype (Init_Arg1, Ftyp);
4970 end;
4971 end if;
4973 Args := New_List (Init_Arg1);
4975 -- For the task case, pass the Master_Id of the access type as
4976 -- the value of the _Master parameter, and _Chain as the value
4977 -- of the _Chain parameter (_Chain will be defined as part of
4978 -- the generated code for the allocator).
4980 -- In Ada 2005, the context may be a function that returns an
4981 -- anonymous access type. In that case the Master_Id has been
4982 -- created when expanding the function declaration.
4984 if Has_Task (T) then
4985 if No (Master_Id (Base_Type (PtrT))) then
4987 -- The designated type was an incomplete type, and the
4988 -- access type did not get expanded. Salvage it now.
4990 if Present (Parent (Base_Type (PtrT))) then
4991 Expand_N_Full_Type_Declaration
4992 (Parent (Base_Type (PtrT)));
4994 -- The only other possibility is an itype. For this
4995 -- case, the master must exist in the context. This is
4996 -- the case when the allocator initializes an access
4997 -- component in an init-proc.
4999 else
5000 pragma Assert (Is_Itype (PtrT));
5001 Build_Master_Renaming (PtrT, N);
5002 end if;
5003 end if;
5005 -- If the context of the allocator is a declaration or an
5006 -- assignment, we can generate a meaningful image for it,
5007 -- even though subsequent assignments might remove the
5008 -- connection between task and entity. We build this image
5009 -- when the left-hand side is a simple variable, a simple
5010 -- indexed assignment or a simple selected component.
5012 if Nkind (Parent (N)) = N_Assignment_Statement then
5013 declare
5014 Nam : constant Node_Id := Name (Parent (N));
5016 begin
5017 if Is_Entity_Name (Nam) then
5018 Decls :=
5019 Build_Task_Image_Decls
5020 (Loc,
5021 New_Occurrence_Of
5022 (Entity (Nam), Sloc (Nam)), T);
5024 elsif Nkind (Nam) in N_Indexed_Component
5025 | N_Selected_Component
5026 and then Is_Entity_Name (Prefix (Nam))
5027 then
5028 Decls :=
5029 Build_Task_Image_Decls
5030 (Loc, Nam, Etype (Prefix (Nam)));
5031 else
5032 Decls := Build_Task_Image_Decls (Loc, T, T);
5033 end if;
5034 end;
5036 elsif Nkind (Parent (N)) = N_Object_Declaration then
5037 Decls :=
5038 Build_Task_Image_Decls
5039 (Loc, Defining_Identifier (Parent (N)), T);
5041 else
5042 Decls := Build_Task_Image_Decls (Loc, T, T);
5043 end if;
5045 if Restriction_Active (No_Task_Hierarchy) then
5046 Append_To
5047 (Args, Make_Integer_Literal (Loc, Library_Task_Level));
5048 else
5049 Append_To (Args,
5050 New_Occurrence_Of
5051 (Master_Id (Base_Type (Root_Type (PtrT))), Loc));
5052 end if;
5054 Append_To (Args, Make_Identifier (Loc, Name_uChain));
5056 Decl := Last (Decls);
5057 Append_To (Args,
5058 New_Occurrence_Of (Defining_Identifier (Decl), Loc));
5060 -- Has_Task is false, Decls not used
5062 else
5063 Decls := No_List;
5064 end if;
5066 -- Add discriminants if discriminated type
5068 declare
5069 Dis : Boolean := False;
5070 Typ : Entity_Id := T;
5072 begin
5073 if Has_Discriminants (T) then
5074 Dis := True;
5076 -- Type may be a private type with no visible discriminants
5077 -- in which case check full view if in scope, or the
5078 -- underlying_full_view if dealing with a type whose full
5079 -- view may be derived from a private type whose own full
5080 -- view has discriminants.
5082 elsif Is_Private_Type (T) then
5083 if Present (Full_View (T))
5084 and then Has_Discriminants (Full_View (T))
5085 then
5086 Dis := True;
5087 Typ := Full_View (T);
5089 elsif Present (Underlying_Full_View (T))
5090 and then Has_Discriminants (Underlying_Full_View (T))
5091 then
5092 Dis := True;
5093 Typ := Underlying_Full_View (T);
5094 end if;
5095 end if;
5097 if Dis then
5099 -- If the allocated object will be constrained by the
5100 -- default values for discriminants, then build a subtype
5101 -- with those defaults, and change the allocated subtype
5102 -- to that. Note that this happens in fewer cases in Ada
5103 -- 2005 (AI-363).
5105 if not Is_Constrained (Typ)
5106 and then Present (Discriminant_Default_Value
5107 (First_Discriminant (Typ)))
5108 and then (Ada_Version < Ada_2005
5109 or else not
5110 Object_Type_Has_Constrained_Partial_View
5111 (Typ, Current_Scope))
5112 then
5113 Typ := Build_Default_Subtype (Typ, N);
5114 Set_Expression (N, New_Occurrence_Of (Typ, Loc));
5115 end if;
5117 Discr := First_Elmt (Discriminant_Constraint (Typ));
5118 while Present (Discr) loop
5119 Nod := Node (Discr);
5120 Append (New_Copy_Tree (Node (Discr)), Args);
5122 -- AI-416: when the discriminant constraint is an
5123 -- anonymous access type make sure an accessibility
5124 -- check is inserted if necessary (3.10.2(22.q/2))
5126 if Ada_Version >= Ada_2005
5127 and then
5128 Ekind (Etype (Nod)) = E_Anonymous_Access_Type
5129 and then not
5130 No_Dynamic_Accessibility_Checks_Enabled (Nod)
5131 then
5132 Apply_Accessibility_Check
5133 (Nod, Typ, Insert_Node => Nod);
5134 end if;
5136 Next_Elmt (Discr);
5137 end loop;
5138 end if;
5140 -- When the designated subtype is unconstrained and
5141 -- the allocator specifies a constrained subtype (or
5142 -- such a subtype has been created, such as above by
5143 -- Build_Default_Subtype), associate that subtype with
5144 -- the dereference of the allocator's access value.
5145 -- This is needed by the expander for cases where the
5146 -- access type has a Designated_Storage_Model in order
5147 -- to support allocation of a host object of the right
5148 -- size for passing to the initialization procedure.
5150 if not Is_Constrained (Dtyp)
5151 and then Is_Constrained (Typ)
5152 then
5153 declare
5154 Deref : constant Node_Id := Unqual_Conv (Init_Arg1);
5156 begin
5157 pragma Assert (Nkind (Deref) = N_Explicit_Dereference);
5159 Set_Actual_Designated_Subtype (Deref, Typ);
5160 end;
5161 end if;
5162 end;
5164 -- We set the allocator as analyzed so that when we analyze
5165 -- the if expression node, we do not get an unwanted recursive
5166 -- expansion of the allocator expression.
5168 Set_Analyzed (N, True);
5169 Nod := Relocate_Node (N);
5171 -- Here is the transformation:
5172 -- input: new Ctrl_Typ
5173 -- output: Temp : constant Ctrl_Typ_Ptr := new Ctrl_Typ;
5174 -- Ctrl_TypIP (Temp.all, ...);
5175 -- [Deep_]Initialize (Temp.all);
5177 -- Here Ctrl_Typ_Ptr is the pointer type for the allocator, and
5178 -- is the subtype of the allocator.
5180 Temp_Decl :=
5181 Make_Object_Declaration (Loc,
5182 Defining_Identifier => Temp,
5183 Constant_Present => True,
5184 Object_Definition => New_Occurrence_Of (Temp_Type, Loc),
5185 Expression => Nod);
5187 Set_Assignment_OK (Temp_Decl);
5188 Insert_Action (N, Temp_Decl, Suppress => All_Checks);
5190 Build_Allocate_Deallocate_Proc (Temp_Decl, True);
5192 -- If the designated type is a task type or contains tasks,
5193 -- create block to activate created tasks, and insert
5194 -- declaration for Task_Image variable ahead of call.
5196 if Has_Task (T) then
5197 declare
5198 L : constant List_Id := New_List;
5199 Blk : Node_Id;
5200 begin
5201 Build_Task_Allocate_Block (L, Nod, Args);
5202 Blk := Last (L);
5203 Insert_List_Before (First (Declarations (Blk)), Decls);
5204 Insert_Actions (N, L);
5205 end;
5207 else
5208 Insert_Action (N,
5209 Make_Procedure_Call_Statement (Loc,
5210 Name => New_Occurrence_Of (Init, Loc),
5211 Parameter_Associations => Args));
5212 end if;
5214 if Needs_Finalization (T) then
5216 -- Generate:
5217 -- [Deep_]Initialize (Init_Arg1);
5219 Init_Call :=
5220 Make_Init_Call
5221 (Obj_Ref => New_Copy_Tree (Init_Arg1),
5222 Typ => T);
5224 -- Guard against a missing [Deep_]Initialize when the
5225 -- designated type was not properly frozen.
5227 if Present (Init_Call) then
5228 Insert_Action (N, Init_Call);
5229 end if;
5230 end if;
5232 Rewrite (N, New_Occurrence_Of (Temp, Loc));
5233 Analyze_And_Resolve (N, PtrT);
5235 -- When designated type has Default_Initial_Condition aspects,
5236 -- make a call to the type's DIC procedure to perform the
5237 -- checks. Theoretically this might also be needed for cases
5238 -- where the type doesn't have an init proc, but those should
5239 -- be very uncommon, and for now we only support the init proc
5240 -- case. ???
5242 if Has_DIC (Dtyp)
5243 and then Present (DIC_Procedure (Dtyp))
5244 and then not Has_Null_Body (DIC_Procedure (Dtyp))
5245 then
5246 Insert_Action (N,
5247 Build_DIC_Call (Loc,
5248 Make_Explicit_Dereference (Loc,
5249 Prefix => New_Occurrence_Of (Temp, Loc)),
5250 Dtyp));
5251 end if;
5252 end if;
5253 end if;
5254 end;
5256 -- Ada 2005 (AI-251): If the allocator is for a class-wide interface
5257 -- object that has been rewritten as a reference, we displace "this"
5258 -- to reference properly its secondary dispatch table.
5260 if Nkind (N) = N_Identifier and then Is_Interface (Dtyp) then
5261 Displace_Allocator_Pointer (N);
5262 end if;
5264 exception
5265 when RE_Not_Available =>
5266 return;
5267 end Expand_N_Allocator;
5269 -----------------------
5270 -- Expand_N_And_Then --
5271 -----------------------
5273 procedure Expand_N_And_Then (N : Node_Id)
5274 renames Expand_Short_Circuit_Operator;
5276 ------------------------------
5277 -- Expand_N_Case_Expression --
5278 ------------------------------
5280 procedure Expand_N_Case_Expression (N : Node_Id) is
5281 function Is_Copy_Type (Typ : Entity_Id) return Boolean;
5282 -- Return True if we can copy objects of this type when expanding a case
5283 -- expression.
5285 ------------------
5286 -- Is_Copy_Type --
5287 ------------------
5289 function Is_Copy_Type (Typ : Entity_Id) return Boolean is
5290 begin
5291 -- If Minimize_Expression_With_Actions is True, we can afford to copy
5292 -- large objects, as long as they are constrained and not limited.
5294 return
5295 Is_Elementary_Type (Underlying_Type (Typ))
5296 or else
5297 (Minimize_Expression_With_Actions
5298 and then Is_Constrained (Underlying_Type (Typ))
5299 and then not Is_Limited_Type (Underlying_Type (Typ)));
5300 end Is_Copy_Type;
5302 -- Local variables
5304 Loc : constant Source_Ptr := Sloc (N);
5305 Par : constant Node_Id := Parent (N);
5306 Typ : constant Entity_Id := Etype (N);
5308 Acts : List_Id;
5309 Alt : Node_Id;
5310 Case_Stmt : Node_Id;
5311 Decl : Node_Id;
5312 Expr : Node_Id;
5313 Target : Entity_Id := Empty;
5314 Target_Typ : Entity_Id;
5316 In_Predicate : Boolean := False;
5317 -- Flag set when the case expression appears within a predicate
5319 Optimize_Return_Stmt : Boolean := False;
5320 -- Flag set when the case expression can be optimized in the context of
5321 -- a simple return statement.
5323 -- Start of processing for Expand_N_Case_Expression
5325 begin
5326 -- Check for MINIMIZED/ELIMINATED overflow mode
5328 if Minimized_Eliminated_Overflow_Check (N) then
5329 Apply_Arithmetic_Overflow_Check (N);
5330 return;
5331 end if;
5333 -- If the case expression is a predicate specification, and the type
5334 -- to which it applies has a static predicate aspect, do not expand,
5335 -- because it will be converted to the proper predicate form later.
5337 if Ekind (Current_Scope) in E_Function | E_Procedure
5338 and then Is_Predicate_Function (Current_Scope)
5339 then
5340 In_Predicate := True;
5342 if Has_Static_Predicate_Aspect (Etype (First_Entity (Current_Scope)))
5343 then
5344 return;
5345 end if;
5346 end if;
5348 -- When the type of the case expression is elementary, expand
5350 -- (case X is when A => AX, when B => BX ...)
5352 -- into
5354 -- do
5355 -- Target : Typ;
5356 -- case X is
5357 -- when A =>
5358 -- Target := AX;
5359 -- when B =>
5360 -- Target := BX;
5361 -- ...
5362 -- end case;
5363 -- in Target end;
5365 -- In all other cases expand into
5367 -- do
5368 -- type Ptr_Typ is access all Typ;
5369 -- Target : Ptr_Typ;
5370 -- case X is
5371 -- when A =>
5372 -- Target := AX'Unrestricted_Access;
5373 -- when B =>
5374 -- Target := BX'Unrestricted_Access;
5375 -- ...
5376 -- end case;
5377 -- in Target.all end;
5379 -- This approach avoids extra copies of potentially large objects. It
5380 -- also allows handling of values of limited or unconstrained types.
5381 -- Note that we do the copy also for constrained, nonlimited types
5382 -- when minimizing expressions with actions (e.g. when generating C
5383 -- code) since it allows us to do the optimization below in more cases.
5385 -- Small optimization: when the case expression appears in the context
5386 -- of a simple return statement, expand into
5388 -- case X is
5389 -- when A =>
5390 -- return AX;
5391 -- when B =>
5392 -- return BX;
5393 -- ...
5394 -- end case;
5396 Case_Stmt :=
5397 Make_Case_Statement (Loc,
5398 Expression => Expression (N),
5399 Alternatives => New_List);
5401 -- Preserve the original context for which the case statement is being
5402 -- generated. This is needed by the finalization machinery to prevent
5403 -- the premature finalization of controlled objects found within the
5404 -- case statement.
5406 Set_From_Conditional_Expression (Case_Stmt);
5407 Acts := New_List;
5409 -- Scalar/Copy case
5411 if Is_Copy_Type (Typ) then
5412 Target_Typ := Typ;
5414 -- Do not perform the optimization when the return statement is
5415 -- within a predicate function, as this causes spurious errors.
5417 Optimize_Return_Stmt :=
5418 Nkind (Par) = N_Simple_Return_Statement and then not In_Predicate;
5420 -- Otherwise create an access type to handle the general case using
5421 -- 'Unrestricted_Access.
5423 -- Generate:
5424 -- type Ptr_Typ is access all Typ;
5426 else
5427 if Generate_C_Code then
5429 -- We cannot ensure that correct C code will be generated if any
5430 -- temporary is created down the line (to e.g. handle checks or
5431 -- capture values) since we might end up with dangling references
5432 -- to local variables, so better be safe and reject the construct.
5434 Error_Msg_N
5435 ("case expression too complex, use case statement instead", N);
5436 end if;
5438 Target_Typ := Make_Temporary (Loc, 'P');
5440 Append_To (Acts,
5441 Make_Full_Type_Declaration (Loc,
5442 Defining_Identifier => Target_Typ,
5443 Type_Definition =>
5444 Make_Access_To_Object_Definition (Loc,
5445 All_Present => True,
5446 Subtype_Indication => New_Occurrence_Of (Typ, Loc))));
5447 end if;
5449 -- Create the declaration of the target which captures the value of the
5450 -- expression.
5452 -- Generate:
5453 -- Target : [Ptr_]Typ;
5455 if not Optimize_Return_Stmt then
5456 Target := Make_Temporary (Loc, 'T');
5458 Decl :=
5459 Make_Object_Declaration (Loc,
5460 Defining_Identifier => Target,
5461 Object_Definition => New_Occurrence_Of (Target_Typ, Loc));
5462 Set_No_Initialization (Decl);
5464 Append_To (Acts, Decl);
5465 end if;
5467 -- Process the alternatives
5469 Alt := First (Alternatives (N));
5470 while Present (Alt) loop
5471 declare
5472 Alt_Expr : Node_Id := Expression (Alt);
5473 Alt_Loc : constant Source_Ptr := Sloc (Alt_Expr);
5474 LHS : Node_Id;
5475 Stmts : List_Id;
5477 begin
5478 -- Take the unrestricted access of the expression value for non-
5479 -- scalar types. This approach avoids big copies and covers the
5480 -- limited and unconstrained cases.
5482 -- Generate:
5483 -- AX'Unrestricted_Access
5485 if not Is_Copy_Type (Typ) then
5486 Alt_Expr :=
5487 Make_Attribute_Reference (Alt_Loc,
5488 Prefix => Relocate_Node (Alt_Expr),
5489 Attribute_Name => Name_Unrestricted_Access);
5490 end if;
5492 -- Generate:
5493 -- return AX['Unrestricted_Access];
5495 if Optimize_Return_Stmt then
5496 Stmts := New_List (
5497 Make_Simple_Return_Statement (Alt_Loc,
5498 Expression => Alt_Expr));
5500 -- Generate:
5501 -- Target := AX['Unrestricted_Access];
5503 else
5504 LHS := New_Occurrence_Of (Target, Loc);
5505 Set_Assignment_OK (LHS);
5507 Stmts := New_List (
5508 Make_Assignment_Statement (Alt_Loc,
5509 Name => LHS,
5510 Expression => Alt_Expr));
5511 end if;
5513 -- Propagate declarations inserted in the node by Insert_Actions
5514 -- (for example, temporaries generated to remove side effects).
5515 -- These actions must remain attached to the alternative, given
5516 -- that they are generated by the corresponding expression.
5518 if Present (Actions (Alt)) then
5519 Prepend_List (Actions (Alt), Stmts);
5520 end if;
5522 -- Finalize any transient objects on exit from the alternative.
5523 -- This is done only in the return optimization case because
5524 -- otherwise the case expression is converted into an expression
5525 -- with actions which already contains this form of processing.
5527 if Optimize_Return_Stmt then
5528 Process_If_Case_Statements (N, Stmts);
5529 end if;
5531 Append_To
5532 (Alternatives (Case_Stmt),
5533 Make_Case_Statement_Alternative (Sloc (Alt),
5534 Discrete_Choices => Discrete_Choices (Alt),
5535 Statements => Stmts));
5536 end;
5538 Next (Alt);
5539 end loop;
5541 -- Rewrite the parent return statement as a case statement
5543 if Optimize_Return_Stmt then
5544 Rewrite (Par, Case_Stmt);
5545 Analyze (Par);
5547 -- Otherwise convert the case expression into an expression with actions
5549 else
5550 Append_To (Acts, Case_Stmt);
5552 if Is_Copy_Type (Typ) then
5553 Expr := New_Occurrence_Of (Target, Loc);
5555 else
5556 Expr :=
5557 Make_Explicit_Dereference (Loc,
5558 Prefix => New_Occurrence_Of (Target, Loc));
5559 end if;
5561 -- Generate:
5562 -- do
5563 -- ...
5564 -- in Target[.all] end;
5566 Rewrite (N,
5567 Make_Expression_With_Actions (Loc,
5568 Expression => Expr,
5569 Actions => Acts));
5571 Analyze_And_Resolve (N, Typ);
5572 end if;
5573 end Expand_N_Case_Expression;
5575 -----------------------------------
5576 -- Expand_N_Explicit_Dereference --
5577 -----------------------------------
5579 procedure Expand_N_Explicit_Dereference (N : Node_Id) is
5580 begin
5581 -- Insert explicit dereference call for the checked storage pool case
5583 Insert_Dereference_Action (Prefix (N));
5585 -- If the type is an Atomic type for which Atomic_Sync is enabled, then
5586 -- we set the atomic sync flag.
5588 if Is_Atomic (Etype (N))
5589 and then not Atomic_Synchronization_Disabled (Etype (N))
5590 then
5591 Activate_Atomic_Synchronization (N);
5592 end if;
5593 end Expand_N_Explicit_Dereference;
5595 --------------------------------------
5596 -- Expand_N_Expression_With_Actions --
5597 --------------------------------------
5599 procedure Expand_N_Expression_With_Actions (N : Node_Id) is
5600 Acts : constant List_Id := Actions (N);
5602 procedure Force_Boolean_Evaluation (Expr : Node_Id);
5603 -- Force the evaluation of Boolean expression Expr
5605 function Process_Action (Act : Node_Id) return Traverse_Result;
5606 -- Inspect and process a single action of an expression_with_actions for
5607 -- transient objects. If such objects are found, the routine generates
5608 -- code to clean them up when the context of the expression is evaluated
5609 -- or elaborated.
5611 ------------------------------
5612 -- Force_Boolean_Evaluation --
5613 ------------------------------
5615 procedure Force_Boolean_Evaluation (Expr : Node_Id) is
5616 Loc : constant Source_Ptr := Sloc (N);
5617 Flag_Decl : Node_Id;
5618 Flag_Id : Entity_Id;
5620 begin
5621 -- Relocate the expression to the actions list by capturing its value
5622 -- in a Boolean flag. Generate:
5623 -- Flag : constant Boolean := Expr;
5625 Flag_Id := Make_Temporary (Loc, 'F');
5627 Flag_Decl :=
5628 Make_Object_Declaration (Loc,
5629 Defining_Identifier => Flag_Id,
5630 Constant_Present => True,
5631 Object_Definition => New_Occurrence_Of (Standard_Boolean, Loc),
5632 Expression => Relocate_Node (Expr));
5634 Append (Flag_Decl, Acts);
5635 Analyze (Flag_Decl);
5637 -- Replace the expression with a reference to the flag
5639 Rewrite (Expression (N), New_Occurrence_Of (Flag_Id, Loc));
5640 Analyze (Expression (N));
5641 end Force_Boolean_Evaluation;
5643 --------------------
5644 -- Process_Action --
5645 --------------------
5647 function Process_Action (Act : Node_Id) return Traverse_Result is
5648 begin
5649 if Nkind (Act) = N_Object_Declaration
5650 and then Is_Finalizable_Transient (Act, N)
5651 then
5652 Process_Transient_In_Expression (Act, N, Acts);
5653 return Skip;
5655 -- Avoid processing temporary function results multiple times when
5656 -- dealing with nested expression_with_actions or nested blocks.
5657 -- Similarly, do not process temporary function results in loops.
5658 -- This is done by Expand_N_Loop_Statement and Build_Finalizer.
5659 -- Note that we used to wrongly return Abandon instead of Skip here:
5660 -- this is wrong since it means that we were ignoring lots of
5661 -- relevant subsequent statements.
5663 elsif Nkind (Act) in N_Expression_With_Actions
5664 | N_Block_Statement
5665 | N_Loop_Statement
5666 then
5667 return Skip;
5668 end if;
5670 return OK;
5671 end Process_Action;
5673 procedure Process_Single_Action is new Traverse_Proc (Process_Action);
5675 -- Local variables
5677 Act : Node_Id;
5679 -- Start of processing for Expand_N_Expression_With_Actions
5681 begin
5682 -- Do not evaluate the expression when it denotes an entity because the
5683 -- expression_with_actions node will be replaced by the reference.
5685 if Is_Entity_Name (Expression (N)) then
5686 null;
5688 -- Do not evaluate the expression when there are no actions because the
5689 -- expression_with_actions node will be replaced by the expression.
5691 elsif Is_Empty_List (Acts) then
5692 null;
5694 -- Force the evaluation of the expression by capturing its value in a
5695 -- temporary. This ensures that aliases of transient objects do not leak
5696 -- to the expression of the expression_with_actions node:
5698 -- do
5699 -- Trans_Id : Ctrl_Typ := ...;
5700 -- Alias : ... := Trans_Id;
5701 -- in ... Alias ... end;
5703 -- In the example above, Trans_Id cannot be finalized at the end of the
5704 -- actions list because this may affect the alias and the final value of
5705 -- the expression_with_actions. Forcing the evaluation encapsulates the
5706 -- reference to the Alias within the actions list:
5708 -- do
5709 -- Trans_Id : Ctrl_Typ := ...;
5710 -- Alias : ... := Trans_Id;
5711 -- Val : constant Boolean := ... Alias ...;
5712 -- <finalize Trans_Id>
5713 -- in Val end;
5715 -- Once this transformation is performed, it is safe to finalize the
5716 -- transient object at the end of the actions list.
5718 -- Note that Force_Evaluation does not remove side effects in operators
5719 -- because it assumes that all operands are evaluated and side effect
5720 -- free. This is not the case when an operand depends implicitly on the
5721 -- transient object through the use of access types.
5723 elsif Is_Boolean_Type (Etype (Expression (N))) then
5724 Force_Boolean_Evaluation (Expression (N));
5726 -- The expression of an expression_with_actions node may not necessarily
5727 -- be Boolean when the node appears in an if expression. In this case do
5728 -- the usual forced evaluation to encapsulate potential aliasing.
5730 else
5731 Force_Evaluation (Expression (N));
5732 end if;
5734 -- Process all transient objects found within the actions of the EWA
5735 -- node.
5737 Act := First (Acts);
5738 while Present (Act) loop
5739 Process_Single_Action (Act);
5740 Next (Act);
5741 end loop;
5743 -- Deal with case where there are no actions. In this case we simply
5744 -- rewrite the node with its expression since we don't need the actions
5745 -- and the specification of this node does not allow a null action list.
5747 -- Note: we use Rewrite instead of Replace, because Codepeer is using
5748 -- the expanded tree and relying on being able to retrieve the original
5749 -- tree in cases like this. This raises a whole lot of issues of whether
5750 -- we have problems elsewhere, which will be addressed in the future???
5752 if Is_Empty_List (Acts) then
5753 Rewrite (N, Relocate_Node (Expression (N)));
5754 end if;
5755 end Expand_N_Expression_With_Actions;
5757 ----------------------------
5758 -- Expand_N_If_Expression --
5759 ----------------------------
5761 -- Deal with limited types and condition actions
5763 procedure Expand_N_If_Expression (N : Node_Id) is
5764 Cond : constant Node_Id := First (Expressions (N));
5765 Loc : constant Source_Ptr := Sloc (N);
5766 Thenx : constant Node_Id := Next (Cond);
5767 Elsex : constant Node_Id := Next (Thenx);
5768 Typ : constant Entity_Id := Etype (N);
5770 Force_Expand : constant Boolean := Is_Anonymous_Access_Actual (N);
5771 -- Determine if we are dealing with a special case of a conditional
5772 -- expression used as an actual for an anonymous access type which
5773 -- forces us to transform the if expression into an expression with
5774 -- actions in order to create a temporary to capture the level of the
5775 -- expression in each branch.
5777 function OK_For_Single_Subtype (T1, T2 : Entity_Id) return Boolean;
5778 -- Return true if it is acceptable to use a single subtype for two
5779 -- dependent expressions of subtype T1 and T2 respectively, which are
5780 -- unidimensional arrays whose index bounds are known at compile time.
5782 ---------------------------
5783 -- OK_For_Single_Subtype --
5784 ---------------------------
5786 function OK_For_Single_Subtype (T1, T2 : Entity_Id) return Boolean is
5787 Lo1, Hi1 : Uint;
5788 Lo2, Hi2 : Uint;
5790 begin
5791 Get_First_Index_Bounds (T1, Lo1, Hi1);
5792 Get_First_Index_Bounds (T2, Lo2, Hi2);
5794 -- Return true if the length of the covering subtype is not too large
5796 return
5797 UI_Max (Hi1, Hi2) - UI_Min (Lo1, Lo2) < Too_Large_Length_For_Array;
5798 end OK_For_Single_Subtype;
5800 -- Local variables
5802 Actions : List_Id;
5803 Decl : Node_Id;
5804 Expr : Node_Id;
5805 New_If : Node_Id;
5806 New_N : Node_Id;
5808 -- Start of processing for Expand_N_If_Expression
5810 begin
5811 -- Deal with non-standard booleans
5813 Adjust_Condition (Cond);
5815 -- Check for MINIMIZED/ELIMINATED overflow mode.
5816 -- Apply_Arithmetic_Overflow_Check will not deal with Then/Else_Actions
5817 -- so skip this step if any actions are present.
5819 if Minimized_Eliminated_Overflow_Check (N)
5820 and then No (Then_Actions (N))
5821 and then No (Else_Actions (N))
5822 then
5823 Apply_Arithmetic_Overflow_Check (N);
5824 return;
5825 end if;
5827 -- Fold at compile time if condition known. We have already folded
5828 -- static if expressions, but it is possible to fold any case in which
5829 -- the condition is known at compile time, even though the result is
5830 -- non-static.
5832 -- Note that we don't do the fold of such cases in Sem_Elab because
5833 -- it can cause infinite loops with the expander adding a conditional
5834 -- expression, and Sem_Elab circuitry removing it repeatedly.
5836 if Compile_Time_Known_Value (Cond) then
5837 declare
5838 function Fold_Known_Value (Cond : Node_Id) return Boolean;
5839 -- Fold at compile time. Assumes condition known. Return True if
5840 -- folding occurred, meaning we're done.
5842 ----------------------
5843 -- Fold_Known_Value --
5844 ----------------------
5846 function Fold_Known_Value (Cond : Node_Id) return Boolean is
5847 begin
5848 if Is_True (Expr_Value (Cond)) then
5849 Expr := Thenx;
5850 Actions := Then_Actions (N);
5851 else
5852 Expr := Elsex;
5853 Actions := Else_Actions (N);
5854 end if;
5856 Remove (Expr);
5858 if Present (Actions) then
5860 -- To minimize the use of Expression_With_Actions, just skip
5861 -- the optimization as it is not critical for correctness.
5863 if Minimize_Expression_With_Actions then
5864 return False;
5865 end if;
5867 Rewrite (N,
5868 Make_Expression_With_Actions (Loc,
5869 Expression => Relocate_Node (Expr),
5870 Actions => Actions));
5871 Analyze_And_Resolve (N, Typ);
5873 else
5874 Rewrite (N, Relocate_Node (Expr));
5875 end if;
5877 -- Note that the result is never static (legitimate cases of
5878 -- static if expressions were folded in Sem_Eval).
5880 Set_Is_Static_Expression (N, False);
5881 return True;
5882 end Fold_Known_Value;
5884 begin
5885 if Fold_Known_Value (Cond) then
5886 return;
5887 end if;
5888 end;
5889 end if;
5891 -- If the type is limited, and the back end does not handle limited
5892 -- types, then we expand as follows to avoid the possibility of
5893 -- improper copying.
5895 -- type Ptr is access all Typ;
5896 -- Cnn : Ptr;
5897 -- if cond then
5898 -- <<then actions>>
5899 -- Cnn := then-expr'Unrestricted_Access;
5900 -- else
5901 -- <<else actions>>
5902 -- Cnn := else-expr'Unrestricted_Access;
5903 -- end if;
5905 -- and replace the if expression by a reference to Cnn.all.
5907 -- This special case can be skipped if the back end handles limited
5908 -- types properly and ensures that no incorrect copies are made.
5910 if Is_By_Reference_Type (Typ)
5911 and then not Back_End_Handles_Limited_Types
5912 then
5913 -- When the "then" or "else" expressions involve controlled function
5914 -- calls, generated temporaries are chained on the corresponding list
5915 -- of actions. These temporaries need to be finalized after the if
5916 -- expression is evaluated.
5918 Process_If_Case_Statements (N, Then_Actions (N));
5919 Process_If_Case_Statements (N, Else_Actions (N));
5921 declare
5922 Cnn : constant Entity_Id := Make_Temporary (Loc, 'C', N);
5923 Ptr_Typ : constant Entity_Id := Make_Temporary (Loc, 'A');
5925 begin
5926 -- Generate:
5927 -- type Ann is access all Typ;
5929 Insert_Action (N,
5930 Make_Full_Type_Declaration (Loc,
5931 Defining_Identifier => Ptr_Typ,
5932 Type_Definition =>
5933 Make_Access_To_Object_Definition (Loc,
5934 All_Present => True,
5935 Subtype_Indication => New_Occurrence_Of (Typ, Loc))));
5937 -- Generate:
5938 -- Cnn : Ann;
5940 Decl :=
5941 Make_Object_Declaration (Loc,
5942 Defining_Identifier => Cnn,
5943 Object_Definition => New_Occurrence_Of (Ptr_Typ, Loc));
5945 -- Generate:
5946 -- if Cond then
5947 -- Cnn := <Thenx>'Unrestricted_Access;
5948 -- else
5949 -- Cnn := <Elsex>'Unrestricted_Access;
5950 -- end if;
5952 New_If :=
5953 Make_Implicit_If_Statement (N,
5954 Condition => Relocate_Node (Cond),
5955 Then_Statements => New_List (
5956 Make_Assignment_Statement (Sloc (Thenx),
5957 Name => New_Occurrence_Of (Cnn, Sloc (Thenx)),
5958 Expression =>
5959 Make_Attribute_Reference (Loc,
5960 Prefix => Relocate_Node (Thenx),
5961 Attribute_Name => Name_Unrestricted_Access))),
5963 Else_Statements => New_List (
5964 Make_Assignment_Statement (Sloc (Elsex),
5965 Name => New_Occurrence_Of (Cnn, Sloc (Elsex)),
5966 Expression =>
5967 Make_Attribute_Reference (Loc,
5968 Prefix => Relocate_Node (Elsex),
5969 Attribute_Name => Name_Unrestricted_Access))));
5971 -- Preserve the original context for which the if statement is
5972 -- being generated. This is needed by the finalization machinery
5973 -- to prevent the premature finalization of controlled objects
5974 -- found within the if statement.
5976 Set_From_Conditional_Expression (New_If);
5978 New_N :=
5979 Make_Explicit_Dereference (Loc,
5980 Prefix => New_Occurrence_Of (Cnn, Loc));
5981 end;
5983 -- If the result is a unidimensional unconstrained array but the two
5984 -- dependent expressions have constrained subtypes with known bounds,
5985 -- then we expand as follows:
5987 -- subtype Txx is Typ (<static low-bound> .. <static high-bound>);
5988 -- Cnn : Txx;
5989 -- if cond then
5990 -- <<then actions>>
5991 -- Cnn (<then low-bound .. then high-bound>) := then-expr;
5992 -- else
5993 -- <<else actions>>
5994 -- Cnn (<else low bound .. else high-bound>) := else-expr;
5995 -- end if;
5997 -- and replace the if expression by a slice of Cnn, provided that Txx
5998 -- is not too large. This will create a static temporary instead of the
5999 -- dynamic one of the next case and thus help the code generator.
6001 -- Note that we need to deal with the case where the else expression is
6002 -- itself such a slice, in order to catch if expressions with more than
6003 -- two dependent expressions in the source code.
6005 -- Also note that this creates variables on branches without an explicit
6006 -- scope, causing troubles with e.g. the LLVM IR, so disable this
6007 -- optimization when Unnest_Subprogram_Mode (enabled for LLVM).
6009 elsif Is_Array_Type (Typ)
6010 and then Number_Dimensions (Typ) = 1
6011 and then not Is_Constrained (Typ)
6012 and then Is_Constrained (Etype (Thenx))
6013 and then Compile_Time_Known_Bounds (Etype (Thenx))
6014 and then
6015 ((Is_Constrained (Etype (Elsex))
6016 and then Compile_Time_Known_Bounds (Etype (Elsex))
6017 and then OK_For_Single_Subtype (Etype (Thenx), Etype (Elsex)))
6018 or else
6019 (Nkind (Elsex) = N_Slice
6020 and then Is_Constrained (Etype (Prefix (Elsex)))
6021 and then Compile_Time_Known_Bounds (Etype (Prefix (Elsex)))
6022 and then
6023 OK_For_Single_Subtype (Etype (Thenx), Etype (Prefix (Elsex)))))
6024 and then not Generate_C_Code
6025 and then not Unnest_Subprogram_Mode
6026 then
6027 declare
6028 Ityp : constant Entity_Id := Base_Type (Etype (First_Index (Typ)));
6030 function Build_New_Bound
6031 (Then_Bnd : Uint;
6032 Else_Bnd : Uint;
6033 Slice_Bnd : Node_Id) return Node_Id;
6034 -- Build a new bound from the bounds of the if expression
6036 function To_Ityp (V : Uint) return Node_Id;
6037 -- Convert V to an index value in Ityp
6039 ---------------------
6040 -- Build_New_Bound --
6041 ---------------------
6043 function Build_New_Bound
6044 (Then_Bnd : Uint;
6045 Else_Bnd : Uint;
6046 Slice_Bnd : Node_Id) return Node_Id is
6048 begin
6049 -- We need to use the special processing for slices only if
6050 -- they do not have compile-time known bounds; if they do, they
6051 -- can be treated like any other expressions.
6053 if Nkind (Elsex) = N_Slice
6054 and then not Compile_Time_Known_Bounds (Etype (Elsex))
6055 then
6056 if Compile_Time_Known_Value (Slice_Bnd)
6057 and then Expr_Value (Slice_Bnd) = Then_Bnd
6058 then
6059 return To_Ityp (Then_Bnd);
6061 else
6062 return Make_If_Expression (Loc,
6063 Expressions => New_List (
6064 Duplicate_Subexpr (Cond),
6065 To_Ityp (Then_Bnd),
6066 New_Copy_Tree (Slice_Bnd)));
6067 end if;
6069 elsif Then_Bnd = Else_Bnd then
6070 return To_Ityp (Then_Bnd);
6072 else
6073 return Make_If_Expression (Loc,
6074 Expressions => New_List (
6075 Duplicate_Subexpr (Cond),
6076 To_Ityp (Then_Bnd),
6077 To_Ityp (Else_Bnd)));
6078 end if;
6079 end Build_New_Bound;
6081 -------------
6082 -- To_Ityp --
6083 -------------
6085 function To_Ityp (V : Uint) return Node_Id is
6086 Result : constant Node_Id := Make_Integer_Literal (Loc, V);
6088 begin
6089 if Is_Enumeration_Type (Ityp) then
6090 return
6091 Make_Attribute_Reference (Loc,
6092 Prefix => New_Occurrence_Of (Ityp, Loc),
6093 Attribute_Name => Name_Val,
6094 Expressions => New_List (Result));
6095 else
6096 return Result;
6097 end if;
6098 end To_Ityp;
6100 Ent : Node_Id;
6101 Slice_Lo, Slice_Hi : Node_Id;
6102 Subtyp_Ind : Node_Id;
6103 Else_Lo, Else_Hi : Uint;
6104 Min_Lo, Max_Hi : Uint;
6105 Then_Lo, Then_Hi : Uint;
6106 Then_List, Else_List : List_Id;
6108 begin
6109 Get_First_Index_Bounds (Etype (Thenx), Then_Lo, Then_Hi);
6111 -- See the rationale in Build_New_Bound
6113 if Nkind (Elsex) = N_Slice
6114 and then not Compile_Time_Known_Bounds (Etype (Elsex))
6115 then
6116 Slice_Lo := Low_Bound (Discrete_Range (Elsex));
6117 Slice_Hi := High_Bound (Discrete_Range (Elsex));
6118 Get_First_Index_Bounds
6119 (Etype (Prefix (Elsex)), Else_Lo, Else_Hi);
6121 else
6122 Slice_Lo := Empty;
6123 Slice_Hi := Empty;
6124 Get_First_Index_Bounds (Etype (Elsex), Else_Lo, Else_Hi);
6125 end if;
6127 Min_Lo := UI_Min (Then_Lo, Else_Lo);
6128 Max_Hi := UI_Max (Then_Hi, Else_Hi);
6130 -- Now we construct an array object with appropriate bounds and
6131 -- mark it as internal to prevent useless initialization when
6132 -- Initialize_Scalars is enabled. Also since this is the actual
6133 -- result entity, we make sure we have debug information for it.
6135 Subtyp_Ind :=
6136 Make_Subtype_Indication (Loc,
6137 Subtype_Mark => New_Occurrence_Of (Typ, Loc),
6138 Constraint =>
6139 Make_Index_Or_Discriminant_Constraint (Loc,
6140 Constraints => New_List (
6141 Make_Range (Loc,
6142 Low_Bound => To_Ityp (Min_Lo),
6143 High_Bound => To_Ityp (Max_Hi)))));
6145 Ent := Make_Temporary (Loc, 'C');
6146 Set_Is_Internal (Ent);
6147 Set_Debug_Info_Needed (Ent);
6149 Decl :=
6150 Make_Object_Declaration (Loc,
6151 Defining_Identifier => Ent,
6152 Object_Definition => Subtyp_Ind);
6154 -- If the result of the expression appears as the initializing
6155 -- expression of an object declaration, we can just rename the
6156 -- result, rather than copying it.
6158 Mutate_Ekind (Ent, E_Variable);
6159 Set_OK_To_Rename (Ent);
6161 Then_List := New_List (
6162 Make_Assignment_Statement (Loc,
6163 Name =>
6164 Make_Slice (Loc,
6165 Prefix => New_Occurrence_Of (Ent, Loc),
6166 Discrete_Range =>
6167 Make_Range (Loc,
6168 Low_Bound => To_Ityp (Then_Lo),
6169 High_Bound => To_Ityp (Then_Hi))),
6170 Expression => Relocate_Node (Thenx)));
6172 Set_Suppress_Assignment_Checks (Last (Then_List));
6174 -- See the rationale in Build_New_Bound
6176 if Nkind (Elsex) = N_Slice
6177 and then not Compile_Time_Known_Bounds (Etype (Elsex))
6178 then
6179 Else_List := New_List (
6180 Make_Assignment_Statement (Loc,
6181 Name =>
6182 Make_Slice (Loc,
6183 Prefix => New_Occurrence_Of (Ent, Loc),
6184 Discrete_Range =>
6185 Make_Range (Loc,
6186 Low_Bound => New_Copy_Tree (Slice_Lo),
6187 High_Bound => New_Copy_Tree (Slice_Hi))),
6188 Expression => Relocate_Node (Elsex)));
6190 else
6191 Else_List := New_List (
6192 Make_Assignment_Statement (Loc,
6193 Name =>
6194 Make_Slice (Loc,
6195 Prefix => New_Occurrence_Of (Ent, Loc),
6196 Discrete_Range =>
6197 Make_Range (Loc,
6198 Low_Bound => To_Ityp (Else_Lo),
6199 High_Bound => To_Ityp (Else_Hi))),
6200 Expression => Relocate_Node (Elsex)));
6201 end if;
6203 Set_Suppress_Assignment_Checks (Last (Else_List));
6205 New_If :=
6206 Make_Implicit_If_Statement (N,
6207 Condition => Duplicate_Subexpr (Cond),
6208 Then_Statements => Then_List,
6209 Else_Statements => Else_List);
6211 New_N :=
6212 Make_Slice (Loc,
6213 Prefix => New_Occurrence_Of (Ent, Loc),
6214 Discrete_Range => Make_Range (Loc,
6215 Low_Bound => Build_New_Bound (Then_Lo, Else_Lo, Slice_Lo),
6216 High_Bound => Build_New_Bound (Then_Hi, Else_Hi, Slice_Hi)));
6217 end;
6219 -- If the result is an unconstrained array and the if expression is in a
6220 -- context other than the initializing expression of the declaration of
6221 -- an object, then we pull out the if expression as follows:
6223 -- Cnn : constant typ := if-expression
6225 -- and then replace the if expression with an occurrence of Cnn. This
6226 -- avoids the need in the back end to create on-the-fly variable length
6227 -- temporaries (which it cannot do!)
6229 -- Note that the test for being in an object declaration avoids doing an
6230 -- unnecessary expansion, and also avoids infinite recursion.
6232 elsif Is_Array_Type (Typ) and then not Is_Constrained (Typ)
6233 and then (Nkind (Parent (N)) /= N_Object_Declaration
6234 or else Expression (Parent (N)) /= N)
6235 then
6236 declare
6237 Cnn : constant Node_Id := Make_Temporary (Loc, 'C', N);
6239 begin
6240 Insert_Action (N,
6241 Make_Object_Declaration (Loc,
6242 Defining_Identifier => Cnn,
6243 Constant_Present => True,
6244 Object_Definition => New_Occurrence_Of (Typ, Loc),
6245 Expression => Relocate_Node (N),
6246 Has_Init_Expression => True));
6248 Rewrite (N, New_Occurrence_Of (Cnn, Loc));
6249 return;
6250 end;
6252 -- For other types, we only need to expand if there are other actions
6253 -- associated with either branch or we need to force expansion to deal
6254 -- with if expressions used as an actual of an anonymous access type.
6256 elsif Present (Then_Actions (N))
6257 or else Present (Else_Actions (N))
6258 or else Force_Expand
6259 then
6261 -- We now wrap the actions into the appropriate expression
6263 if Minimize_Expression_With_Actions
6264 and then (Is_Elementary_Type (Underlying_Type (Typ))
6265 or else Is_Constrained (Underlying_Type (Typ)))
6266 then
6267 -- If we can't use N_Expression_With_Actions nodes, then we insert
6268 -- the following sequence of actions (using Insert_Actions):
6270 -- Cnn : typ;
6271 -- if cond then
6272 -- <<then actions>>
6273 -- Cnn := then-expr;
6274 -- else
6275 -- <<else actions>>
6276 -- Cnn := else-expr
6277 -- end if;
6279 -- and replace the if expression by a reference to Cnn
6281 declare
6282 Cnn : constant Node_Id := Make_Temporary (Loc, 'C', N);
6284 begin
6285 Decl :=
6286 Make_Object_Declaration (Loc,
6287 Defining_Identifier => Cnn,
6288 Object_Definition => New_Occurrence_Of (Typ, Loc));
6290 New_If :=
6291 Make_Implicit_If_Statement (N,
6292 Condition => Relocate_Node (Cond),
6294 Then_Statements => New_List (
6295 Make_Assignment_Statement (Sloc (Thenx),
6296 Name => New_Occurrence_Of (Cnn, Sloc (Thenx)),
6297 Expression => Relocate_Node (Thenx))),
6299 Else_Statements => New_List (
6300 Make_Assignment_Statement (Sloc (Elsex),
6301 Name => New_Occurrence_Of (Cnn, Sloc (Elsex)),
6302 Expression => Relocate_Node (Elsex))));
6304 Set_Assignment_OK (Name (First (Then_Statements (New_If))));
6305 Set_Assignment_OK (Name (First (Else_Statements (New_If))));
6307 New_N := New_Occurrence_Of (Cnn, Loc);
6308 end;
6310 -- Regular path using Expression_With_Actions
6312 else
6313 if Present (Then_Actions (N)) then
6314 Rewrite (Thenx,
6315 Make_Expression_With_Actions (Sloc (Thenx),
6316 Actions => Then_Actions (N),
6317 Expression => Relocate_Node (Thenx)));
6319 Set_Then_Actions (N, No_List);
6320 Analyze_And_Resolve (Thenx, Typ);
6321 end if;
6323 if Present (Else_Actions (N)) then
6324 Rewrite (Elsex,
6325 Make_Expression_With_Actions (Sloc (Elsex),
6326 Actions => Else_Actions (N),
6327 Expression => Relocate_Node (Elsex)));
6329 Set_Else_Actions (N, No_List);
6330 Analyze_And_Resolve (Elsex, Typ);
6331 end if;
6333 -- We must force expansion into an expression with actions when
6334 -- an if expression gets used directly as an actual for an
6335 -- anonymous access type.
6337 if Force_Expand then
6338 declare
6339 Cnn : constant Entity_Id := Make_Temporary (Loc, 'C');
6340 Acts : List_Id;
6341 begin
6342 Acts := New_List;
6344 -- Generate:
6345 -- Cnn : Ann;
6347 Decl :=
6348 Make_Object_Declaration (Loc,
6349 Defining_Identifier => Cnn,
6350 Object_Definition => New_Occurrence_Of (Typ, Loc));
6351 Append_To (Acts, Decl);
6353 Set_No_Initialization (Decl);
6355 -- Generate:
6356 -- if Cond then
6357 -- Cnn := <Thenx>;
6358 -- else
6359 -- Cnn := <Elsex>;
6360 -- end if;
6362 New_If :=
6363 Make_Implicit_If_Statement (N,
6364 Condition => Relocate_Node (Cond),
6365 Then_Statements => New_List (
6366 Make_Assignment_Statement (Sloc (Thenx),
6367 Name => New_Occurrence_Of (Cnn, Sloc (Thenx)),
6368 Expression => Relocate_Node (Thenx))),
6370 Else_Statements => New_List (
6371 Make_Assignment_Statement (Sloc (Elsex),
6372 Name => New_Occurrence_Of (Cnn, Sloc (Elsex)),
6373 Expression => Relocate_Node (Elsex))));
6374 Append_To (Acts, New_If);
6376 -- Generate:
6377 -- do
6378 -- ...
6379 -- in Cnn end;
6381 Rewrite (N,
6382 Make_Expression_With_Actions (Loc,
6383 Expression => New_Occurrence_Of (Cnn, Loc),
6384 Actions => Acts));
6385 Analyze_And_Resolve (N, Typ);
6386 end;
6387 end if;
6389 return;
6390 end if;
6392 -- For the sake of GNATcoverage, generate an intermediate temporary in
6393 -- the case where the if expression is a condition in an outer decision,
6394 -- in order to make sure that no branch is shared between the decisions.
6396 elsif Opt.Suppress_Control_Flow_Optimizations
6397 and then Nkind (Original_Node (Parent (N))) in N_Case_Expression
6398 | N_Case_Statement
6399 | N_If_Expression
6400 | N_If_Statement
6401 | N_Goto_When_Statement
6402 | N_Loop_Statement
6403 | N_Return_When_Statement
6404 | N_Short_Circuit
6405 then
6406 declare
6407 Cnn : constant Entity_Id := Make_Temporary (Loc, 'C');
6408 Acts : List_Id;
6410 begin
6411 -- Generate:
6412 -- do
6413 -- Cnn : constant Typ := N;
6414 -- in Cnn end
6416 Acts := New_List (
6417 Make_Object_Declaration (Loc,
6418 Defining_Identifier => Cnn,
6419 Constant_Present => True,
6420 Object_Definition => New_Occurrence_Of (Typ, Loc),
6421 Expression => Relocate_Node (N)));
6423 Rewrite (N,
6424 Make_Expression_With_Actions (Loc,
6425 Expression => New_Occurrence_Of (Cnn, Loc),
6426 Actions => Acts));
6428 Analyze_And_Resolve (N, Typ);
6429 return;
6430 end;
6432 -- If no actions then no expansion needed, gigi will handle it using the
6433 -- same approach as a C conditional expression.
6435 else
6436 return;
6437 end if;
6439 -- Fall through here for either the limited expansion, or the case of
6440 -- inserting actions for nonlimited types. In both these cases, we must
6441 -- move the SLOC of the parent If statement to the newly created one and
6442 -- change it to the SLOC of the expression which, after expansion, will
6443 -- correspond to what is being evaluated.
6445 if Present (Parent (N)) and then Nkind (Parent (N)) = N_If_Statement then
6446 Set_Sloc (New_If, Sloc (Parent (N)));
6447 Set_Sloc (Parent (N), Loc);
6448 end if;
6450 -- Move Then_Actions and Else_Actions, if any, to the new if statement
6452 Insert_List_Before (First (Then_Statements (New_If)), Then_Actions (N));
6453 Insert_List_Before (First (Else_Statements (New_If)), Else_Actions (N));
6455 Insert_Action (N, Decl);
6456 Insert_Action (N, New_If);
6457 Rewrite (N, New_N);
6458 Analyze_And_Resolve (N, Typ);
6459 end Expand_N_If_Expression;
6461 -----------------
6462 -- Expand_N_In --
6463 -----------------
6465 procedure Expand_N_In (N : Node_Id) is
6466 Loc : constant Source_Ptr := Sloc (N);
6467 Restyp : constant Entity_Id := Etype (N);
6468 Lop : constant Node_Id := Left_Opnd (N);
6469 Rop : constant Node_Id := Right_Opnd (N);
6470 Static : constant Boolean := Is_OK_Static_Expression (N);
6472 procedure Substitute_Valid_Test;
6473 -- Replaces node N by Lop'Valid. This is done when we have an explicit
6474 -- test for the left operand being in range of its subtype.
6476 ---------------------------
6477 -- Substitute_Valid_Test --
6478 ---------------------------
6480 procedure Substitute_Valid_Test is
6481 function Is_OK_Object_Reference (Nod : Node_Id) return Boolean;
6482 -- Determine whether arbitrary node Nod denotes a source object that
6483 -- may safely act as prefix of attribute 'Valid.
6485 ----------------------------
6486 -- Is_OK_Object_Reference --
6487 ----------------------------
6489 function Is_OK_Object_Reference (Nod : Node_Id) return Boolean is
6490 Obj_Ref : Node_Id;
6492 begin
6493 -- Inspect the original operand
6495 Obj_Ref := Original_Node (Nod);
6497 -- The object reference must be a source construct, otherwise the
6498 -- codefix suggestion may refer to nonexistent code from a user
6499 -- perspective.
6501 if Comes_From_Source (Obj_Ref) then
6502 loop
6503 if Nkind (Obj_Ref) in
6504 N_Type_Conversion |
6505 N_Unchecked_Type_Conversion |
6506 N_Qualified_Expression
6507 then
6508 Obj_Ref := Expression (Obj_Ref);
6509 else
6510 exit;
6511 end if;
6512 end loop;
6514 return Is_Object_Reference (Obj_Ref);
6515 end if;
6517 return False;
6518 end Is_OK_Object_Reference;
6520 -- Start of processing for Substitute_Valid_Test
6522 begin
6523 Rewrite (N,
6524 Make_Attribute_Reference (Loc,
6525 Prefix => Relocate_Node (Lop),
6526 Attribute_Name => Name_Valid));
6528 Analyze_And_Resolve (N, Restyp);
6530 -- Emit a warning when the left-hand operand of the membership test
6531 -- is a source object, otherwise the use of attribute 'Valid would be
6532 -- illegal. The warning is not given when overflow checking is either
6533 -- MINIMIZED or ELIMINATED, as the danger of optimization has been
6534 -- eliminated above.
6536 if Is_OK_Object_Reference (Lop)
6537 and then Overflow_Check_Mode not in Minimized_Or_Eliminated
6538 then
6539 Error_Msg_N
6540 ("??explicit membership test may be optimized away", N);
6541 Error_Msg_N -- CODEFIX
6542 ("\??use ''Valid attribute instead", N);
6543 end if;
6544 end Substitute_Valid_Test;
6546 -- Local variables
6548 Ltyp : Entity_Id;
6549 Rtyp : Entity_Id;
6551 -- Start of processing for Expand_N_In
6553 begin
6554 -- If set membership case, expand with separate procedure
6556 if Present (Alternatives (N)) then
6557 Expand_Set_Membership (N);
6558 return;
6559 end if;
6561 -- Not set membership, proceed with expansion
6563 Ltyp := Etype (Left_Opnd (N));
6564 Rtyp := Etype (Right_Opnd (N));
6566 -- If MINIMIZED/ELIMINATED overflow mode and type is a signed integer
6567 -- type, then expand with a separate procedure. Note the use of the
6568 -- flag No_Minimize_Eliminate to prevent infinite recursion.
6570 if Minimized_Eliminated_Overflow_Check (Left_Opnd (N))
6571 and then not No_Minimize_Eliminate (N)
6572 then
6573 Expand_Membership_Minimize_Eliminate_Overflow (N);
6574 return;
6575 end if;
6577 -- Check case of explicit test for an expression in range of its
6578 -- subtype. This is suspicious usage and we replace it with a 'Valid
6579 -- test and give a warning for scalar types.
6581 if Is_Scalar_Type (Ltyp)
6583 -- Only relevant for source comparisons
6585 and then Comes_From_Source (N)
6587 -- In floating-point this is a standard way to check for finite values
6588 -- and using 'Valid would typically be a pessimization.
6590 and then not Is_Floating_Point_Type (Ltyp)
6592 -- Don't give the message unless right operand is a type entity and
6593 -- the type of the left operand matches this type. Note that this
6594 -- eliminates the cases where MINIMIZED/ELIMINATED mode overflow
6595 -- checks have changed the type of the left operand.
6597 and then Is_Entity_Name (Rop)
6598 and then Ltyp = Entity (Rop)
6600 -- Skip this for predicated types, where such expressions are a
6601 -- reasonable way of testing if something meets the predicate.
6603 and then No (Predicate_Function (Ltyp))
6604 then
6605 Substitute_Valid_Test;
6606 return;
6607 end if;
6609 -- Do validity check on operands
6611 if Validity_Checks_On and Validity_Check_Operands then
6612 Ensure_Valid (Left_Opnd (N));
6613 Validity_Check_Range (Right_Opnd (N));
6614 end if;
6616 -- Case of explicit range
6618 if Nkind (Rop) = N_Range then
6619 declare
6620 Lo : constant Node_Id := Low_Bound (Rop);
6621 Hi : constant Node_Id := High_Bound (Rop);
6623 Lo_Orig : constant Node_Id := Original_Node (Lo);
6624 Hi_Orig : constant Node_Id := Original_Node (Hi);
6625 Rop_Orig : constant Node_Id := Original_Node (Rop);
6627 Comes_From_Simple_Range_In_Source : constant Boolean :=
6628 Comes_From_Source (N)
6629 and then not
6630 (Is_Entity_Name (Rop_Orig)
6631 and then Is_Type (Entity (Rop_Orig))
6632 and then Present (Predicate_Function (Entity (Rop_Orig))));
6633 -- This is true for a membership test present in the source with a
6634 -- range or mark for a subtype that is not predicated. As already
6635 -- explained a few lines above, we do not want to give warnings on
6636 -- a test with a mark for a subtype that is predicated.
6638 Warn : constant Boolean :=
6639 Constant_Condition_Warnings
6640 and then Comes_From_Simple_Range_In_Source
6641 and then not In_Instance;
6642 -- This must be true for any of the optimization warnings, we
6643 -- clearly want to give them only for source with the flag on. We
6644 -- also skip these warnings in an instance since it may be the
6645 -- case that different instantiations have different ranges.
6647 Lcheck : Compare_Result;
6648 Ucheck : Compare_Result;
6650 begin
6651 -- If test is explicit x'First .. x'Last, replace by 'Valid test
6653 if Is_Scalar_Type (Ltyp)
6655 -- Only relevant for source comparisons
6657 and then Comes_From_Simple_Range_In_Source
6659 -- And left operand is X'First where X matches left operand
6660 -- type (this eliminates cases of type mismatch, including
6661 -- the cases where ELIMINATED/MINIMIZED mode has changed the
6662 -- type of the left operand.
6664 and then Nkind (Lo_Orig) = N_Attribute_Reference
6665 and then Attribute_Name (Lo_Orig) = Name_First
6666 and then Is_Entity_Name (Prefix (Lo_Orig))
6667 and then Entity (Prefix (Lo_Orig)) = Ltyp
6669 -- Same tests for right operand
6671 and then Nkind (Hi_Orig) = N_Attribute_Reference
6672 and then Attribute_Name (Hi_Orig) = Name_Last
6673 and then Is_Entity_Name (Prefix (Hi_Orig))
6674 and then Entity (Prefix (Hi_Orig)) = Ltyp
6675 then
6676 Substitute_Valid_Test;
6677 goto Leave;
6678 end if;
6680 -- If bounds of type are known at compile time, and the end points
6681 -- are known at compile time and identical, this is another case
6682 -- for substituting a valid test. We only do this for discrete
6683 -- types, since it won't arise in practice for float types.
6685 if Comes_From_Simple_Range_In_Source
6686 and then Is_Discrete_Type (Ltyp)
6687 and then Compile_Time_Known_Value (Type_High_Bound (Ltyp))
6688 and then Compile_Time_Known_Value (Type_Low_Bound (Ltyp))
6689 and then Compile_Time_Known_Value (Lo)
6690 and then Compile_Time_Known_Value (Hi)
6691 and then Expr_Value (Type_High_Bound (Ltyp)) = Expr_Value (Hi)
6692 and then Expr_Value (Type_Low_Bound (Ltyp)) = Expr_Value (Lo)
6694 -- Kill warnings in instances, since they may be cases where we
6695 -- have a test in the generic that makes sense with some types
6696 -- and not with other types.
6698 -- Similarly, do not rewrite membership as a 'Valid test if
6699 -- within the predicate function for the type.
6701 -- Finally, if the original bounds are type conversions, even
6702 -- if they have been folded into constants, there are different
6703 -- types involved and 'Valid is not appropriate.
6705 then
6706 if In_Instance
6707 or else (Ekind (Current_Scope) = E_Function
6708 and then Is_Predicate_Function (Current_Scope))
6709 then
6710 null;
6712 elsif Nkind (Lo_Orig) = N_Type_Conversion
6713 or else Nkind (Hi_Orig) = N_Type_Conversion
6714 then
6715 null;
6717 else
6718 Substitute_Valid_Test;
6719 goto Leave;
6720 end if;
6721 end if;
6723 -- If we have an explicit range, do a bit of optimization based on
6724 -- range analysis (we may be able to kill one or both checks).
6726 Lcheck := Compile_Time_Compare (Lop, Lo, Assume_Valid => False);
6727 Ucheck := Compile_Time_Compare (Lop, Hi, Assume_Valid => False);
6729 -- If either check is known to fail, replace result by False since
6730 -- the other check does not matter. Preserve the static flag for
6731 -- legality checks, because we are constant-folding beyond RM 4.9.
6733 if Lcheck = LT or else Ucheck = GT then
6734 if Warn then
6735 Error_Msg_N ("?c?range test optimized away", N);
6736 Error_Msg_N ("\?c?value is known to be out of range", N);
6737 end if;
6739 Rewrite (N, New_Occurrence_Of (Standard_False, Loc));
6740 Analyze_And_Resolve (N, Restyp);
6741 Set_Is_Static_Expression (N, Static);
6742 goto Leave;
6744 -- If both checks are known to succeed, replace result by True,
6745 -- since we know we are in range.
6747 elsif Lcheck in Compare_GE and then Ucheck in Compare_LE then
6748 if Warn then
6749 Error_Msg_N ("?c?range test optimized away", N);
6750 Error_Msg_N ("\?c?value is known to be in range", N);
6751 end if;
6753 Rewrite (N, New_Occurrence_Of (Standard_True, Loc));
6754 Analyze_And_Resolve (N, Restyp);
6755 Set_Is_Static_Expression (N, Static);
6756 goto Leave;
6758 -- If lower bound check succeeds and upper bound check is not
6759 -- known to succeed or fail, then replace the range check with
6760 -- a comparison against the upper bound.
6762 elsif Lcheck in Compare_GE then
6763 Rewrite (N,
6764 Make_Op_Le (Loc,
6765 Left_Opnd => Lop,
6766 Right_Opnd => High_Bound (Rop)));
6767 Analyze_And_Resolve (N, Restyp);
6768 goto Leave;
6770 -- Inverse of previous case.
6772 elsif Ucheck in Compare_LE then
6773 Rewrite (N,
6774 Make_Op_Ge (Loc,
6775 Left_Opnd => Lop,
6776 Right_Opnd => Low_Bound (Rop)));
6777 Analyze_And_Resolve (N, Restyp);
6778 goto Leave;
6779 end if;
6781 -- We couldn't optimize away the range check, but there is one
6782 -- more issue. If we are checking constant conditionals, then we
6783 -- see if we can determine the outcome assuming everything is
6784 -- valid, and if so give an appropriate warning.
6786 if Warn and then not Assume_No_Invalid_Values then
6787 Lcheck := Compile_Time_Compare (Lop, Lo, Assume_Valid => True);
6788 Ucheck := Compile_Time_Compare (Lop, Hi, Assume_Valid => True);
6790 -- Result is out of range for valid value
6792 if Lcheck = LT or else Ucheck = GT then
6793 Error_Msg_N
6794 ("?c?value can only be in range if it is invalid", N);
6796 -- Result is in range for valid value
6798 elsif Lcheck in Compare_GE and then Ucheck in Compare_LE then
6799 Error_Msg_N
6800 ("?c?value can only be out of range if it is invalid", N);
6801 end if;
6802 end if;
6803 end;
6805 -- Try to narrow the operation
6807 if Ltyp = Universal_Integer and then Nkind (N) = N_In then
6808 Narrow_Large_Operation (N);
6809 end if;
6811 -- For all other cases of an explicit range, nothing to be done
6813 goto Leave;
6815 -- Here right operand is a subtype mark
6817 else
6818 declare
6819 Typ : Entity_Id := Etype (Rop);
6820 Is_Acc : constant Boolean := Is_Access_Type (Typ);
6821 Check_Null_Exclusion : Boolean;
6822 Cond : Node_Id := Empty;
6823 New_N : Node_Id;
6824 Obj : Node_Id := Lop;
6825 SCIL_Node : Node_Id;
6827 begin
6828 Remove_Side_Effects (Obj);
6830 -- For tagged type, do tagged membership operation
6832 if Is_Tagged_Type (Typ) then
6834 -- No expansion will be performed for VM targets, as the VM
6835 -- back ends will handle the membership tests directly.
6837 if Tagged_Type_Expansion then
6838 Tagged_Membership (N, SCIL_Node, New_N);
6839 Rewrite (N, New_N);
6840 Analyze_And_Resolve (N, Restyp, Suppress => All_Checks);
6842 -- Update decoration of relocated node referenced by the
6843 -- SCIL node.
6845 if Generate_SCIL and then Present (SCIL_Node) then
6846 Set_SCIL_Node (N, SCIL_Node);
6847 end if;
6848 end if;
6850 goto Leave;
6852 -- If type is scalar type, rewrite as x in t'First .. t'Last.
6853 -- The reason we do this is that the bounds may have the wrong
6854 -- type if they come from the original type definition. Also this
6855 -- way we get all the processing above for an explicit range.
6857 -- Don't do this for predicated types, since in this case we want
6858 -- to generate the predicate check at the end of the function.
6860 elsif Is_Scalar_Type (Typ) then
6861 if No (Predicate_Function (Typ)) then
6862 Rewrite (Rop,
6863 Make_Range (Loc,
6864 Low_Bound =>
6865 Make_Attribute_Reference (Loc,
6866 Attribute_Name => Name_First,
6867 Prefix => New_Occurrence_Of (Typ, Loc)),
6869 High_Bound =>
6870 Make_Attribute_Reference (Loc,
6871 Attribute_Name => Name_Last,
6872 Prefix => New_Occurrence_Of (Typ, Loc))));
6874 Analyze_And_Resolve (N, Restyp);
6875 end if;
6877 goto Leave;
6879 -- Ada 2005 (AI95-0216 amended by AI12-0162): Program_Error is
6880 -- raised when evaluating an individual membership test if the
6881 -- subtype mark denotes a constrained Unchecked_Union subtype
6882 -- and the expression lacks inferable discriminants.
6884 elsif Is_Unchecked_Union (Base_Type (Typ))
6885 and then Is_Constrained (Typ)
6886 and then not Has_Inferable_Discriminants (Lop)
6887 then
6888 Rewrite (N,
6889 Make_Expression_With_Actions (Loc,
6890 Actions =>
6891 New_List (Make_Raise_Program_Error (Loc,
6892 Reason => PE_Unchecked_Union_Restriction)),
6893 Expression =>
6894 New_Occurrence_Of (Standard_False, Loc)));
6895 Analyze_And_Resolve (N, Restyp);
6897 goto Leave;
6898 end if;
6900 -- Here we have a non-scalar type
6902 if Is_Acc then
6904 -- If the null exclusion checks are not compatible, need to
6905 -- perform further checks. In other words, we cannot have
6906 -- Ltyp including null and Typ excluding null. All other cases
6907 -- are OK.
6909 Check_Null_Exclusion :=
6910 Can_Never_Be_Null (Typ) and then not Can_Never_Be_Null (Ltyp);
6911 Typ := Designated_Type (Typ);
6912 end if;
6914 if not Is_Constrained (Typ) then
6915 Cond := New_Occurrence_Of (Standard_True, Loc);
6917 -- For the constrained array case, we have to check the subscripts
6918 -- for an exact match if the lengths are non-zero (the lengths
6919 -- must match in any case).
6921 elsif Is_Array_Type (Typ) then
6922 Check_Subscripts : declare
6923 function Build_Attribute_Reference
6924 (E : Node_Id;
6925 Nam : Name_Id;
6926 Dim : Nat) return Node_Id;
6927 -- Build attribute reference E'Nam (Dim)
6929 -------------------------------
6930 -- Build_Attribute_Reference --
6931 -------------------------------
6933 function Build_Attribute_Reference
6934 (E : Node_Id;
6935 Nam : Name_Id;
6936 Dim : Nat) return Node_Id
6938 begin
6939 return
6940 Make_Attribute_Reference (Loc,
6941 Prefix => E,
6942 Attribute_Name => Nam,
6943 Expressions => New_List (
6944 Make_Integer_Literal (Loc, Dim)));
6945 end Build_Attribute_Reference;
6947 -- Start of processing for Check_Subscripts
6949 begin
6950 for J in 1 .. Number_Dimensions (Typ) loop
6951 Evolve_And_Then (Cond,
6952 Make_Op_Eq (Loc,
6953 Left_Opnd =>
6954 Build_Attribute_Reference
6955 (Duplicate_Subexpr_No_Checks (Obj),
6956 Name_First, J),
6957 Right_Opnd =>
6958 Build_Attribute_Reference
6959 (New_Occurrence_Of (Typ, Loc), Name_First, J)));
6961 Evolve_And_Then (Cond,
6962 Make_Op_Eq (Loc,
6963 Left_Opnd =>
6964 Build_Attribute_Reference
6965 (Duplicate_Subexpr_No_Checks (Obj),
6966 Name_Last, J),
6967 Right_Opnd =>
6968 Build_Attribute_Reference
6969 (New_Occurrence_Of (Typ, Loc), Name_Last, J)));
6970 end loop;
6971 end Check_Subscripts;
6973 -- These are the cases where constraint checks may be required,
6974 -- e.g. records with possible discriminants
6976 else
6977 -- Expand the test into a series of discriminant comparisons.
6978 -- The expression that is built is the negation of the one that
6979 -- is used for checking discriminant constraints.
6981 Obj := Relocate_Node (Left_Opnd (N));
6983 if Has_Discriminants (Typ) then
6984 Cond := Make_Op_Not (Loc,
6985 Right_Opnd => Build_Discriminant_Checks (Obj, Typ));
6986 else
6987 Cond := New_Occurrence_Of (Standard_True, Loc);
6988 end if;
6989 end if;
6991 if Is_Acc then
6992 if Check_Null_Exclusion then
6993 Cond := Make_And_Then (Loc,
6994 Left_Opnd =>
6995 Make_Op_Ne (Loc,
6996 Left_Opnd => Obj,
6997 Right_Opnd => Make_Null (Loc)),
6998 Right_Opnd => Cond);
6999 else
7000 Cond := Make_Or_Else (Loc,
7001 Left_Opnd =>
7002 Make_Op_Eq (Loc,
7003 Left_Opnd => Obj,
7004 Right_Opnd => Make_Null (Loc)),
7005 Right_Opnd => Cond);
7006 end if;
7007 end if;
7009 Rewrite (N, Cond);
7010 Analyze_And_Resolve (N, Restyp);
7012 -- Ada 2012 (AI05-0149): Handle membership tests applied to an
7013 -- expression of an anonymous access type. This can involve an
7014 -- accessibility test and a tagged type membership test in the
7015 -- case of tagged designated types.
7017 if Ada_Version >= Ada_2012
7018 and then Is_Acc
7019 and then Ekind (Ltyp) = E_Anonymous_Access_Type
7020 then
7021 declare
7022 Expr_Entity : Entity_Id := Empty;
7023 New_N : Node_Id;
7024 Param_Level : Node_Id;
7025 Type_Level : Node_Id;
7027 begin
7028 if Is_Entity_Name (Lop) then
7029 Expr_Entity := Param_Entity (Lop);
7031 if No (Expr_Entity) then
7032 Expr_Entity := Entity (Lop);
7033 end if;
7034 end if;
7036 -- When restriction No_Dynamic_Accessibility_Checks is in
7037 -- effect, expand the membership test to a static value
7038 -- since we cannot rely on dynamic levels.
7040 if No_Dynamic_Accessibility_Checks_Enabled (Lop) then
7041 if Static_Accessibility_Level
7042 (Lop, Object_Decl_Level)
7043 > Type_Access_Level (Rtyp)
7044 then
7045 Rewrite (N, New_Occurrence_Of (Standard_False, Loc));
7046 else
7047 Rewrite (N, New_Occurrence_Of (Standard_True, Loc));
7048 end if;
7049 Analyze_And_Resolve (N, Restyp);
7051 -- If a conversion of the anonymous access value to the
7052 -- tested type would be illegal, then the result is False.
7054 elsif not Valid_Conversion
7055 (Lop, Rtyp, Lop, Report_Errs => False)
7056 then
7057 Rewrite (N, New_Occurrence_Of (Standard_False, Loc));
7058 Analyze_And_Resolve (N, Restyp);
7060 -- Apply an accessibility check if the access object has an
7061 -- associated access level and when the level of the type is
7062 -- less deep than the level of the access parameter. This
7063 -- can only occur for access parameters and stand-alone
7064 -- objects of an anonymous access type.
7066 else
7067 Param_Level := Accessibility_Level
7068 (Expr_Entity, Dynamic_Level);
7070 Type_Level :=
7071 Make_Integer_Literal (Loc, Type_Access_Level (Rtyp));
7073 -- Return True only if the accessibility level of the
7074 -- expression entity is not deeper than the level of
7075 -- the tested access type.
7077 Rewrite (N,
7078 Make_And_Then (Loc,
7079 Left_Opnd => Relocate_Node (N),
7080 Right_Opnd => Make_Op_Le (Loc,
7081 Left_Opnd => Param_Level,
7082 Right_Opnd => Type_Level)));
7084 Analyze_And_Resolve (N);
7086 -- If the designated type is tagged, do tagged membership
7087 -- operation.
7089 if Is_Tagged_Type (Typ) then
7091 -- No expansion will be performed for VM targets, as
7092 -- the VM back ends will handle the membership tests
7093 -- directly.
7095 if Tagged_Type_Expansion then
7097 -- Note that we have to pass Original_Node, because
7098 -- the membership test might already have been
7099 -- rewritten by earlier parts of membership test.
7101 Tagged_Membership
7102 (Original_Node (N), SCIL_Node, New_N);
7104 -- Update decoration of relocated node referenced
7105 -- by the SCIL node.
7107 if Generate_SCIL and then Present (SCIL_Node) then
7108 Set_SCIL_Node (New_N, SCIL_Node);
7109 end if;
7111 Rewrite (N,
7112 Make_And_Then (Loc,
7113 Left_Opnd => Relocate_Node (N),
7114 Right_Opnd => New_N));
7116 Analyze_And_Resolve (N, Restyp);
7117 end if;
7118 end if;
7119 end if;
7120 end;
7121 end if;
7122 end;
7123 end if;
7125 -- At this point, we have done the processing required for the basic
7126 -- membership test, but not yet dealt with the predicate.
7128 <<Leave>>
7130 -- If a predicate is present, then we do the predicate test, but we
7131 -- most certainly want to omit this if we are within the predicate
7132 -- function itself, since otherwise we have an infinite recursion.
7133 -- The check should also not be emitted when testing against a range
7134 -- (the check is only done when the right operand is a subtype; see
7135 -- RM12-4.5.2 (28.1/3-30/3)).
7137 Predicate_Check : declare
7138 function In_Range_Check return Boolean;
7139 -- Within an expanded range check that may raise Constraint_Error do
7140 -- not generate a predicate check as well. It is redundant because
7141 -- the context will add an explicit predicate check, and it will
7142 -- raise the wrong exception if it fails.
7144 --------------------
7145 -- In_Range_Check --
7146 --------------------
7148 function In_Range_Check return Boolean is
7149 P : Node_Id;
7150 begin
7151 P := Parent (N);
7152 while Present (P) loop
7153 if Nkind (P) = N_Raise_Constraint_Error then
7154 return True;
7156 elsif Nkind (P) in N_Statement_Other_Than_Procedure_Call
7157 or else Nkind (P) = N_Procedure_Call_Statement
7158 or else Nkind (P) in N_Declaration
7159 then
7160 return False;
7161 end if;
7163 P := Parent (P);
7164 end loop;
7166 return False;
7167 end In_Range_Check;
7169 -- Local variables
7171 PFunc : constant Entity_Id := Predicate_Function (Rtyp);
7172 R_Op : Node_Id;
7174 -- Start of processing for Predicate_Check
7176 begin
7177 if Present (PFunc)
7178 and then Current_Scope /= PFunc
7179 and then Nkind (Rop) /= N_Range
7180 then
7181 -- First apply the transformation that was skipped above
7183 if Is_Scalar_Type (Rtyp) then
7184 Rewrite (Rop,
7185 Make_Range (Loc,
7186 Low_Bound =>
7187 Make_Attribute_Reference (Loc,
7188 Attribute_Name => Name_First,
7189 Prefix => New_Occurrence_Of (Rtyp, Loc)),
7191 High_Bound =>
7192 Make_Attribute_Reference (Loc,
7193 Attribute_Name => Name_Last,
7194 Prefix => New_Occurrence_Of (Rtyp, Loc))));
7196 Analyze_And_Resolve (N, Restyp);
7197 end if;
7199 if not In_Range_Check then
7200 -- Indicate via Static_Mem parameter that this predicate
7201 -- evaluation is for a membership test.
7202 R_Op := Make_Predicate_Call (Rtyp, Lop, Static_Mem => True);
7203 else
7204 R_Op := New_Occurrence_Of (Standard_True, Loc);
7205 end if;
7207 Rewrite (N,
7208 Make_And_Then (Loc,
7209 Left_Opnd => Relocate_Node (N),
7210 Right_Opnd => R_Op));
7212 -- Analyze new expression, mark left operand as analyzed to
7213 -- avoid infinite recursion adding predicate calls. Similarly,
7214 -- suppress further range checks on the call.
7216 Set_Analyzed (Left_Opnd (N));
7217 Analyze_And_Resolve (N, Standard_Boolean, Suppress => All_Checks);
7218 end if;
7219 end Predicate_Check;
7220 end Expand_N_In;
7222 --------------------------------
7223 -- Expand_N_Indexed_Component --
7224 --------------------------------
7226 procedure Expand_N_Indexed_Component (N : Node_Id) is
7228 Wild_Reads_May_Have_Bad_Side_Effects : Boolean
7229 renames Validity_Check_Subscripts;
7230 -- This Boolean needs to be True if reading from a bad address can
7231 -- have a bad side effect (e.g., a segmentation fault that is not
7232 -- transformed into a Storage_Error exception, or interactions with
7233 -- memory-mapped I/O) that needs to be prevented. This refers to the
7234 -- act of reading itself, not to any damage that might be caused later
7235 -- by making use of whatever value was read. We assume here that
7236 -- Validity_Check_Subscripts meets this requirement, but introduce
7237 -- this declaration in order to document this assumption.
7239 function Is_Renamed_Variable_Name (N : Node_Id) return Boolean;
7240 -- Returns True if the given name occurs as part of the renaming
7241 -- of a variable. In this case, the indexing operation should be
7242 -- treated as a write, rather than a read, with respect to validity
7243 -- checking. This is because the renamed variable can later be
7244 -- written to.
7246 function Type_Requires_Subscript_Validity_Checks_For_Reads
7247 (Typ : Entity_Id) return Boolean;
7248 -- If Wild_Reads_May_Have_Bad_Side_Effects is False and we are indexing
7249 -- into an array of characters in order to read an element, it is ok
7250 -- if an invalid index value goes undetected. But if it is an array of
7251 -- pointers or an array of tasks, the consequences of such a read are
7252 -- potentially more severe and so we want to detect an invalid index
7253 -- value. This function captures that distinction; this is intended to
7254 -- be consistent with the "but does not by itself lead to erroneous
7255 -- ... execution" rule of RM 13.9.1(11).
7257 ------------------------------
7258 -- Is_Renamed_Variable_Name --
7259 ------------------------------
7261 function Is_Renamed_Variable_Name (N : Node_Id) return Boolean is
7262 Rover : Node_Id := N;
7263 begin
7264 if Is_Variable (N) then
7265 loop
7266 declare
7267 Rover_Parent : constant Node_Id := Parent (Rover);
7268 begin
7269 case Nkind (Rover_Parent) is
7270 when N_Object_Renaming_Declaration =>
7271 return Rover = Name (Rover_Parent);
7273 when N_Indexed_Component
7274 | N_Slice
7275 | N_Selected_Component
7277 exit when Rover /= Prefix (Rover_Parent);
7278 Rover := Rover_Parent;
7280 -- No need to check for qualified expressions or type
7281 -- conversions here, mostly because of the Is_Variable
7282 -- test. It is possible to have a view conversion for
7283 -- which Is_Variable yields True and which occurs as
7284 -- part of an object renaming, but only if the type is
7285 -- tagged; in that case this function will not be called.
7287 when others =>
7288 exit;
7289 end case;
7290 end;
7291 end loop;
7292 end if;
7293 return False;
7294 end Is_Renamed_Variable_Name;
7296 -------------------------------------------------------
7297 -- Type_Requires_Subscript_Validity_Checks_For_Reads --
7298 -------------------------------------------------------
7300 function Type_Requires_Subscript_Validity_Checks_For_Reads
7301 (Typ : Entity_Id) return Boolean
7303 -- a shorter name for recursive calls
7304 function Needs_Check (Typ : Entity_Id) return Boolean renames
7305 Type_Requires_Subscript_Validity_Checks_For_Reads;
7306 begin
7307 if Is_Access_Type (Typ)
7308 or else Is_Tagged_Type (Typ)
7309 or else Is_Concurrent_Type (Typ)
7310 or else (Is_Array_Type (Typ)
7311 and then Needs_Check (Component_Type (Typ)))
7312 or else (Is_Scalar_Type (Typ)
7313 and then Has_Aspect (Typ, Aspect_Default_Value))
7314 then
7315 return True;
7316 end if;
7318 if Is_Record_Type (Typ) then
7319 declare
7320 Comp : Entity_Id := First_Component_Or_Discriminant (Typ);
7321 begin
7322 while Present (Comp) loop
7323 if Needs_Check (Etype (Comp)) then
7324 return True;
7325 end if;
7327 Next_Component_Or_Discriminant (Comp);
7328 end loop;
7329 end;
7330 end if;
7332 return False;
7333 end Type_Requires_Subscript_Validity_Checks_For_Reads;
7335 -- Local constants
7337 Loc : constant Source_Ptr := Sloc (N);
7338 Typ : constant Entity_Id := Etype (N);
7339 P : constant Node_Id := Prefix (N);
7340 T : constant Entity_Id := Etype (P);
7342 -- Start of processing for Expand_N_Indexed_Component
7344 begin
7345 -- A special optimization, if we have an indexed component that is
7346 -- selecting from a slice, then we can eliminate the slice, since, for
7347 -- example, x (i .. j)(k) is identical to x(k). The only difference is
7348 -- the range check required by the slice. The range check for the slice
7349 -- itself has already been generated. The range check for the
7350 -- subscripting operation is ensured by converting the subject to
7351 -- the subtype of the slice.
7353 -- This optimization not only generates better code, avoiding slice
7354 -- messing especially in the packed case, but more importantly bypasses
7355 -- some problems in handling this peculiar case, for example, the issue
7356 -- of dealing specially with object renamings.
7358 if Nkind (P) = N_Slice
7360 -- This optimization is disabled for CodePeer because it can transform
7361 -- an index-check constraint_error into a range-check constraint_error
7362 -- and CodePeer cares about that distinction.
7364 and then not CodePeer_Mode
7365 then
7366 Rewrite (N,
7367 Make_Indexed_Component (Loc,
7368 Prefix => Prefix (P),
7369 Expressions => New_List (
7370 Convert_To
7371 (Etype (First_Index (Etype (P))),
7372 First (Expressions (N))))));
7373 Analyze_And_Resolve (N, Typ);
7374 return;
7375 end if;
7377 -- Ada 2005 (AI-318-02): If the prefix is a call to a build-in-place
7378 -- function, then additional actuals must be passed.
7380 if Is_Build_In_Place_Function_Call (P) then
7381 Make_Build_In_Place_Call_In_Anonymous_Context (P);
7383 -- Ada 2005 (AI-318-02): Specialization of the previous case for prefix
7384 -- containing build-in-place function calls whose returned object covers
7385 -- interface types.
7387 elsif Present (Unqual_BIP_Iface_Function_Call (P)) then
7388 Make_Build_In_Place_Iface_Call_In_Anonymous_Context (P);
7389 end if;
7391 -- Generate index and validity checks
7393 declare
7394 Dims_Checked : Dimension_Set (Dimensions =>
7395 (if Is_Array_Type (T)
7396 then Number_Dimensions (T)
7397 else 1));
7398 -- Dims_Checked is used to avoid generating two checks (one in
7399 -- Generate_Index_Checks, one in Apply_Subscript_Validity_Checks)
7400 -- for the same index value in cases where the index check eliminates
7401 -- the need for the validity check. The Is_Array_Type test avoids
7402 -- cascading errors.
7404 begin
7405 Generate_Index_Checks (N, Checks_Generated => Dims_Checked);
7407 if Validity_Checks_On
7408 and then (Validity_Check_Subscripts
7409 or else Wild_Reads_May_Have_Bad_Side_Effects
7410 or else Type_Requires_Subscript_Validity_Checks_For_Reads
7411 (Typ)
7412 or else Is_Renamed_Variable_Name (N))
7413 then
7414 if Validity_Check_Subscripts then
7415 -- If we index into an array with an uninitialized variable
7416 -- and we generate an index check that passes at run time,
7417 -- passing that check does not ensure that the variable is
7418 -- valid (although it does in the common case where the
7419 -- object's subtype matches the index subtype).
7420 -- Consider an uninitialized variable with subtype 1 .. 10
7421 -- used to index into an array with bounds 1 .. 20 when the
7422 -- value of the uninitialized variable happens to be 15.
7423 -- The index check will succeed but the variable is invalid.
7424 -- If Validity_Check_Subscripts is True then we need to
7425 -- ensure validity, so we adjust Dims_Checked accordingly.
7426 Dims_Checked.Elements := (others => False);
7428 elsif Is_Array_Type (T) then
7429 -- We are only adding extra validity checks here to
7430 -- deal with uninitialized variables (but this includes
7431 -- assigning one uninitialized variable to another). Other
7432 -- ways of producing invalid objects imply erroneousness, so
7433 -- the compiler can do whatever it wants for those cases.
7434 -- If an index type has the Default_Value aspect specified,
7435 -- then we don't have to worry about the possibility of an
7436 -- uninitialized variable, so no need for these extra
7437 -- validity checks.
7439 declare
7440 Idx : Node_Id := First_Index (T);
7441 begin
7442 for No_Check_Needed of Dims_Checked.Elements loop
7443 No_Check_Needed := No_Check_Needed
7444 or else Has_Aspect (Etype (Idx), Aspect_Default_Value);
7445 Next_Index (Idx);
7446 end loop;
7447 end;
7448 end if;
7450 Apply_Subscript_Validity_Checks
7451 (N, No_Check_Needed => Dims_Checked);
7452 end if;
7453 end;
7455 -- If selecting from an array with atomic components, and atomic sync
7456 -- is not suppressed for this array type, set atomic sync flag.
7458 if (Has_Atomic_Components (T)
7459 and then not Atomic_Synchronization_Disabled (T))
7460 or else (Is_Atomic (Typ)
7461 and then not Atomic_Synchronization_Disabled (Typ))
7462 or else (Is_Entity_Name (P)
7463 and then Has_Atomic_Components (Entity (P))
7464 and then not Atomic_Synchronization_Disabled (Entity (P)))
7465 then
7466 Activate_Atomic_Synchronization (N);
7467 end if;
7469 -- All done if the prefix is not a packed array implemented specially
7471 if not (Is_Packed (Etype (Prefix (N)))
7472 and then Present (Packed_Array_Impl_Type (Etype (Prefix (N)))))
7473 then
7474 return;
7475 end if;
7477 -- For packed arrays that are not bit-packed (i.e. the case of an array
7478 -- with one or more index types with a non-contiguous enumeration type),
7479 -- we can always use the normal packed element get circuit.
7481 if not Is_Bit_Packed_Array (Etype (Prefix (N))) then
7482 Expand_Packed_Element_Reference (N);
7483 return;
7484 end if;
7486 -- For a reference to a component of a bit packed array, we convert it
7487 -- to a reference to the corresponding Packed_Array_Impl_Type. We only
7488 -- want to do this for simple references, and not for:
7490 -- Left side of assignment, or prefix of left side of assignment, or
7491 -- prefix of the prefix, to handle packed arrays of packed arrays,
7492 -- This case is handled in Exp_Ch5.Expand_N_Assignment_Statement
7494 -- Renaming objects in renaming associations
7495 -- This case is handled when a use of the renamed variable occurs
7497 -- Actual parameters for a subprogram call
7498 -- This case is handled in Exp_Ch6.Expand_Actuals
7500 -- The second expression in a 'Read attribute reference
7502 -- The prefix of an address or bit or size attribute reference
7504 -- The following circuit detects these exceptions. Note that we need to
7505 -- deal with implicit dereferences when climbing up the parent chain,
7506 -- with the additional difficulty that the type of parents may have yet
7507 -- to be resolved since prefixes are usually resolved first.
7509 declare
7510 Child : Node_Id := N;
7511 Parnt : Node_Id := Parent (N);
7513 begin
7514 loop
7515 if Nkind (Parnt) = N_Unchecked_Expression then
7516 null;
7518 elsif Nkind (Parnt) = N_Object_Renaming_Declaration then
7519 return;
7521 elsif Nkind (Parnt) in N_Subprogram_Call
7522 or else (Nkind (Parnt) = N_Parameter_Association
7523 and then Nkind (Parent (Parnt)) in N_Subprogram_Call)
7524 then
7525 return;
7527 elsif Nkind (Parnt) = N_Attribute_Reference
7528 and then Attribute_Name (Parnt) in Name_Address
7529 | Name_Bit
7530 | Name_Size
7531 and then Prefix (Parnt) = Child
7532 then
7533 return;
7535 elsif Nkind (Parnt) = N_Assignment_Statement
7536 and then Name (Parnt) = Child
7537 then
7538 return;
7540 -- If the expression is an index of an indexed component, it must
7541 -- be expanded regardless of context.
7543 elsif Nkind (Parnt) = N_Indexed_Component
7544 and then Child /= Prefix (Parnt)
7545 then
7546 Expand_Packed_Element_Reference (N);
7547 return;
7549 elsif Nkind (Parent (Parnt)) = N_Assignment_Statement
7550 and then Name (Parent (Parnt)) = Parnt
7551 then
7552 return;
7554 elsif Nkind (Parnt) = N_Attribute_Reference
7555 and then Attribute_Name (Parnt) = Name_Read
7556 and then Next (First (Expressions (Parnt))) = Child
7557 then
7558 return;
7560 elsif Nkind (Parnt) = N_Indexed_Component
7561 and then Prefix (Parnt) = Child
7562 then
7563 null;
7565 elsif Nkind (Parnt) = N_Selected_Component
7566 and then Prefix (Parnt) = Child
7567 and then not (Present (Etype (Selector_Name (Parnt)))
7568 and then
7569 Is_Access_Type (Etype (Selector_Name (Parnt))))
7570 then
7571 null;
7573 -- If the parent is a dereference, either implicit or explicit,
7574 -- then the packed reference needs to be expanded.
7576 else
7577 Expand_Packed_Element_Reference (N);
7578 return;
7579 end if;
7581 -- Keep looking up tree for unchecked expression, or if we are the
7582 -- prefix of a possible assignment left side.
7584 Child := Parnt;
7585 Parnt := Parent (Child);
7586 end loop;
7587 end;
7588 end Expand_N_Indexed_Component;
7590 ---------------------
7591 -- Expand_N_Not_In --
7592 ---------------------
7594 -- Replace a not in b by not (a in b) so that the expansions for (a in b)
7595 -- can be done. This avoids needing to duplicate this expansion code.
7597 procedure Expand_N_Not_In (N : Node_Id) is
7598 Loc : constant Source_Ptr := Sloc (N);
7599 Typ : constant Entity_Id := Etype (N);
7600 Cfs : constant Boolean := Comes_From_Source (N);
7602 begin
7603 Rewrite (N,
7604 Make_Op_Not (Loc,
7605 Right_Opnd =>
7606 Make_In (Loc,
7607 Left_Opnd => Left_Opnd (N),
7608 Right_Opnd => Right_Opnd (N))));
7610 -- If this is a set membership, preserve list of alternatives
7612 Set_Alternatives (Right_Opnd (N), Alternatives (Original_Node (N)));
7614 -- We want this to appear as coming from source if original does (see
7615 -- transformations in Expand_N_In).
7617 Set_Comes_From_Source (N, Cfs);
7618 Set_Comes_From_Source (Right_Opnd (N), Cfs);
7620 -- Now analyze transformed node
7622 Analyze_And_Resolve (N, Typ);
7623 end Expand_N_Not_In;
7625 -------------------
7626 -- Expand_N_Null --
7627 -------------------
7629 -- The only replacement required is for the case of a null of a type that
7630 -- is an access to protected subprogram, or a subtype thereof. We represent
7631 -- such access values as a record, and so we must replace the occurrence of
7632 -- null by the equivalent record (with a null address and a null pointer in
7633 -- it), so that the back end creates the proper value.
7635 procedure Expand_N_Null (N : Node_Id) is
7636 Loc : constant Source_Ptr := Sloc (N);
7637 Typ : constant Entity_Id := Base_Type (Etype (N));
7638 Agg : Node_Id;
7640 begin
7641 if Is_Access_Protected_Subprogram_Type (Typ) then
7642 Agg :=
7643 Make_Aggregate (Loc,
7644 Expressions => New_List (
7645 New_Occurrence_Of (RTE (RE_Null_Address), Loc),
7646 Make_Null (Loc)));
7648 Rewrite (N, Agg);
7649 Analyze_And_Resolve (N, Equivalent_Type (Typ));
7651 -- For subsequent semantic analysis, the node must retain its type.
7652 -- Gigi in any case replaces this type by the corresponding record
7653 -- type before processing the node.
7655 Set_Etype (N, Typ);
7656 end if;
7658 exception
7659 when RE_Not_Available =>
7660 return;
7661 end Expand_N_Null;
7663 ---------------------
7664 -- Expand_N_Op_Abs --
7665 ---------------------
7667 procedure Expand_N_Op_Abs (N : Node_Id) is
7668 Loc : constant Source_Ptr := Sloc (N);
7669 Expr : constant Node_Id := Right_Opnd (N);
7670 Typ : constant Entity_Id := Etype (N);
7672 begin
7673 Unary_Op_Validity_Checks (N);
7675 -- Check for MINIMIZED/ELIMINATED overflow mode
7677 if Minimized_Eliminated_Overflow_Check (N) then
7678 Apply_Arithmetic_Overflow_Check (N);
7679 return;
7680 end if;
7682 -- Try to narrow the operation
7684 if Typ = Universal_Integer then
7685 Narrow_Large_Operation (N);
7687 if Nkind (N) /= N_Op_Abs then
7688 return;
7689 end if;
7690 end if;
7692 -- Deal with software overflow checking
7694 if Is_Signed_Integer_Type (Typ)
7695 and then Do_Overflow_Check (N)
7696 then
7697 -- The only case to worry about is when the argument is equal to the
7698 -- largest negative number, so what we do is to insert the check:
7700 -- [constraint_error when Expr = typ'Base'First]
7702 -- with the usual Duplicate_Subexpr use coding for expr
7704 Insert_Action (N,
7705 Make_Raise_Constraint_Error (Loc,
7706 Condition =>
7707 Make_Op_Eq (Loc,
7708 Left_Opnd => Duplicate_Subexpr (Expr),
7709 Right_Opnd =>
7710 Make_Attribute_Reference (Loc,
7711 Prefix =>
7712 New_Occurrence_Of (Base_Type (Etype (Expr)), Loc),
7713 Attribute_Name => Name_First)),
7714 Reason => CE_Overflow_Check_Failed));
7716 Set_Do_Overflow_Check (N, False);
7717 end if;
7718 end Expand_N_Op_Abs;
7720 ---------------------
7721 -- Expand_N_Op_Add --
7722 ---------------------
7724 procedure Expand_N_Op_Add (N : Node_Id) is
7725 Typ : constant Entity_Id := Etype (N);
7727 begin
7728 Binary_Op_Validity_Checks (N);
7730 -- Check for MINIMIZED/ELIMINATED overflow mode
7732 if Minimized_Eliminated_Overflow_Check (N) then
7733 Apply_Arithmetic_Overflow_Check (N);
7734 return;
7735 end if;
7737 -- N + 0 = 0 + N = N for integer types
7739 if Is_Integer_Type (Typ) then
7740 if Compile_Time_Known_Value (Right_Opnd (N))
7741 and then Expr_Value (Right_Opnd (N)) = Uint_0
7742 then
7743 Rewrite (N, Left_Opnd (N));
7744 return;
7746 elsif Compile_Time_Known_Value (Left_Opnd (N))
7747 and then Expr_Value (Left_Opnd (N)) = Uint_0
7748 then
7749 Rewrite (N, Right_Opnd (N));
7750 return;
7751 end if;
7752 end if;
7754 -- Try to narrow the operation
7756 if Typ = Universal_Integer then
7757 Narrow_Large_Operation (N);
7759 if Nkind (N) /= N_Op_Add then
7760 return;
7761 end if;
7762 end if;
7764 -- Arithmetic overflow checks for signed integer/fixed point types
7766 if Is_Signed_Integer_Type (Typ) or else Is_Fixed_Point_Type (Typ) then
7767 Apply_Arithmetic_Overflow_Check (N);
7768 return;
7769 end if;
7771 -- Overflow checks for floating-point if -gnateF mode active
7773 Check_Float_Op_Overflow (N);
7775 Expand_Nonbinary_Modular_Op (N);
7776 end Expand_N_Op_Add;
7778 ---------------------
7779 -- Expand_N_Op_And --
7780 ---------------------
7782 procedure Expand_N_Op_And (N : Node_Id) is
7783 Typ : constant Entity_Id := Etype (N);
7785 begin
7786 Binary_Op_Validity_Checks (N);
7788 if Is_Array_Type (Etype (N)) then
7789 Expand_Boolean_Operator (N);
7791 elsif Is_Boolean_Type (Etype (N)) then
7792 Adjust_Condition (Left_Opnd (N));
7793 Adjust_Condition (Right_Opnd (N));
7794 Set_Etype (N, Standard_Boolean);
7795 Adjust_Result_Type (N, Typ);
7797 elsif Is_Intrinsic_Subprogram (Entity (N)) then
7798 Expand_Intrinsic_Call (N, Entity (N));
7799 end if;
7801 Expand_Nonbinary_Modular_Op (N);
7802 end Expand_N_Op_And;
7804 ------------------------
7805 -- Expand_N_Op_Concat --
7806 ------------------------
7808 procedure Expand_N_Op_Concat (N : Node_Id) is
7809 Opnds : List_Id;
7810 -- List of operands to be concatenated
7812 Cnode : Node_Id;
7813 -- Node which is to be replaced by the result of concatenating the nodes
7814 -- in the list Opnds.
7816 begin
7817 -- Ensure validity of both operands
7819 Binary_Op_Validity_Checks (N);
7821 -- If we are the left operand of a concatenation higher up the tree,
7822 -- then do nothing for now, since we want to deal with a series of
7823 -- concatenations as a unit.
7825 if Nkind (Parent (N)) = N_Op_Concat
7826 and then N = Left_Opnd (Parent (N))
7827 then
7828 return;
7829 end if;
7831 -- We get here with a concatenation whose left operand may be a
7832 -- concatenation itself with a consistent type. We need to process
7833 -- these concatenation operands from left to right, which means
7834 -- from the deepest node in the tree to the highest node.
7836 Cnode := N;
7837 while Nkind (Left_Opnd (Cnode)) = N_Op_Concat loop
7838 Cnode := Left_Opnd (Cnode);
7839 end loop;
7841 -- Now Cnode is the deepest concatenation, and its parents are the
7842 -- concatenation nodes above, so now we process bottom up, doing the
7843 -- operands.
7845 -- The outer loop runs more than once if more than one concatenation
7846 -- type is involved.
7848 Outer : loop
7849 Opnds := New_List (Left_Opnd (Cnode), Right_Opnd (Cnode));
7850 Set_Parent (Opnds, N);
7852 -- The inner loop gathers concatenation operands
7854 Inner : while Cnode /= N
7855 and then Base_Type (Etype (Cnode)) =
7856 Base_Type (Etype (Parent (Cnode)))
7857 loop
7858 Cnode := Parent (Cnode);
7859 Append (Right_Opnd (Cnode), Opnds);
7860 end loop Inner;
7862 -- Note: The following code is a temporary workaround for N731-034
7863 -- and N829-028 and will be kept until the general issue of internal
7864 -- symbol serialization is addressed. The workaround is kept under a
7865 -- debug switch to avoid permiating into the general case.
7867 -- Wrap the node to concatenate into an expression actions node to
7868 -- keep it nicely packaged. This is useful in the case of an assert
7869 -- pragma with a concatenation where we want to be able to delete
7870 -- the concatenation and all its expansion stuff.
7872 if Debug_Flag_Dot_H then
7873 declare
7874 Cnod : constant Node_Id := New_Copy_Tree (Cnode);
7875 Typ : constant Entity_Id := Base_Type (Etype (Cnode));
7877 begin
7878 -- Note: use Rewrite rather than Replace here, so that for
7879 -- example Why_Not_Static can find the original concatenation
7880 -- node OK!
7882 Rewrite (Cnode,
7883 Make_Expression_With_Actions (Sloc (Cnode),
7884 Actions => New_List (Make_Null_Statement (Sloc (Cnode))),
7885 Expression => Cnod));
7887 Expand_Concatenate (Cnod, Opnds);
7888 Analyze_And_Resolve (Cnode, Typ);
7889 end;
7891 -- Default case
7893 else
7894 Expand_Concatenate (Cnode, Opnds);
7895 end if;
7897 exit Outer when Cnode = N;
7898 Cnode := Parent (Cnode);
7899 end loop Outer;
7900 end Expand_N_Op_Concat;
7902 ------------------------
7903 -- Expand_N_Op_Divide --
7904 ------------------------
7906 procedure Expand_N_Op_Divide (N : Node_Id) is
7907 Loc : constant Source_Ptr := Sloc (N);
7908 Lopnd : constant Node_Id := Left_Opnd (N);
7909 Ropnd : constant Node_Id := Right_Opnd (N);
7910 Ltyp : constant Entity_Id := Etype (Lopnd);
7911 Rtyp : constant Entity_Id := Etype (Ropnd);
7912 Typ : Entity_Id := Etype (N);
7913 Rknow : constant Boolean := Is_Integer_Type (Typ)
7914 and then
7915 Compile_Time_Known_Value (Ropnd);
7916 Rval : Uint;
7918 begin
7919 Binary_Op_Validity_Checks (N);
7921 -- Check for MINIMIZED/ELIMINATED overflow mode
7923 if Minimized_Eliminated_Overflow_Check (N) then
7924 Apply_Arithmetic_Overflow_Check (N);
7925 return;
7926 end if;
7928 -- Otherwise proceed with expansion of division
7930 if Rknow then
7931 Rval := Expr_Value (Ropnd);
7932 end if;
7934 -- N / 1 = N for integer types
7936 if Rknow and then Rval = Uint_1 then
7937 Rewrite (N, Lopnd);
7938 return;
7939 end if;
7941 -- Try to narrow the operation
7943 if Typ = Universal_Integer then
7944 Narrow_Large_Operation (N);
7946 if Nkind (N) /= N_Op_Divide then
7947 return;
7948 end if;
7949 end if;
7951 -- Convert x / 2 ** y to Shift_Right (x, y). Note that the fact that
7952 -- Is_Power_Of_2_For_Shift is set means that we know that our left
7953 -- operand is an unsigned integer, as required for this to work.
7955 if Nkind (Ropnd) = N_Op_Expon
7956 and then Is_Power_Of_2_For_Shift (Ropnd)
7958 -- We cannot do this transformation in configurable run time mode if we
7959 -- have 64-bit integers and long shifts are not available.
7961 and then (Esize (Ltyp) <= 32 or else Support_Long_Shifts_On_Target)
7962 then
7963 Rewrite (N,
7964 Make_Op_Shift_Right (Loc,
7965 Left_Opnd => Lopnd,
7966 Right_Opnd =>
7967 Convert_To (Standard_Natural, Right_Opnd (Ropnd))));
7968 Analyze_And_Resolve (N, Typ);
7969 return;
7970 end if;
7972 -- Do required fixup of universal fixed operation
7974 if Typ = Universal_Fixed then
7975 Fixup_Universal_Fixed_Operation (N);
7976 Typ := Etype (N);
7977 end if;
7979 -- Divisions with fixed-point results
7981 if Is_Fixed_Point_Type (Typ) then
7983 if Is_Integer_Type (Rtyp) then
7984 Expand_Divide_Fixed_By_Integer_Giving_Fixed (N);
7985 else
7986 Expand_Divide_Fixed_By_Fixed_Giving_Fixed (N);
7987 end if;
7989 -- Deal with divide-by-zero check if back end cannot handle them
7990 -- and the flag is set indicating that we need such a check. Note
7991 -- that we don't need to bother here with the case of mixed-mode
7992 -- (Right operand an integer type), since these will be rewritten
7993 -- with conversions to a divide with a fixed-point right operand.
7995 if Nkind (N) = N_Op_Divide
7996 and then Do_Division_Check (N)
7997 and then not Backend_Divide_Checks_On_Target
7998 and then not Is_Integer_Type (Rtyp)
7999 then
8000 Set_Do_Division_Check (N, False);
8001 Insert_Action (N,
8002 Make_Raise_Constraint_Error (Loc,
8003 Condition =>
8004 Make_Op_Eq (Loc,
8005 Left_Opnd => Duplicate_Subexpr_Move_Checks (Ropnd),
8006 Right_Opnd => Make_Real_Literal (Loc, Ureal_0)),
8007 Reason => CE_Divide_By_Zero));
8008 end if;
8010 -- Other cases of division of fixed-point operands
8012 elsif Is_Fixed_Point_Type (Ltyp) or else Is_Fixed_Point_Type (Rtyp) then
8013 if Is_Integer_Type (Typ) then
8014 Expand_Divide_Fixed_By_Fixed_Giving_Integer (N);
8015 else
8016 pragma Assert (Is_Floating_Point_Type (Typ));
8017 Expand_Divide_Fixed_By_Fixed_Giving_Float (N);
8018 end if;
8020 -- Mixed-mode operations can appear in a non-static universal context,
8021 -- in which case the integer argument must be converted explicitly.
8023 elsif Typ = Universal_Real and then Is_Integer_Type (Rtyp) then
8024 Rewrite (Ropnd,
8025 Convert_To (Universal_Real, Relocate_Node (Ropnd)));
8027 Analyze_And_Resolve (Ropnd, Universal_Real);
8029 elsif Typ = Universal_Real and then Is_Integer_Type (Ltyp) then
8030 Rewrite (Lopnd,
8031 Convert_To (Universal_Real, Relocate_Node (Lopnd)));
8033 Analyze_And_Resolve (Lopnd, Universal_Real);
8035 -- Non-fixed point cases, do integer zero divide and overflow checks
8037 elsif Is_Integer_Type (Typ) then
8038 Apply_Divide_Checks (N);
8039 end if;
8041 -- Overflow checks for floating-point if -gnateF mode active
8043 Check_Float_Op_Overflow (N);
8045 Expand_Nonbinary_Modular_Op (N);
8046 end Expand_N_Op_Divide;
8048 --------------------
8049 -- Expand_N_Op_Eq --
8050 --------------------
8052 procedure Expand_N_Op_Eq (N : Node_Id) is
8053 Loc : constant Source_Ptr := Sloc (N);
8054 Typ : constant Entity_Id := Etype (N);
8055 Lhs : constant Node_Id := Left_Opnd (N);
8056 Rhs : constant Node_Id := Right_Opnd (N);
8057 Bodies : constant List_Id := New_List;
8058 A_Typ : constant Entity_Id := Etype (Lhs);
8060 procedure Build_Equality_Call (Eq : Entity_Id);
8061 -- If a constructed equality exists for the type or for its parent,
8062 -- build and analyze call, adding conversions if the operation is
8063 -- inherited.
8065 function Find_Equality (Prims : Elist_Id) return Entity_Id;
8066 -- Find a primitive equality function within primitive operation list
8067 -- Prims.
8069 function Has_Unconstrained_UU_Component (Typ : Entity_Id) return Boolean;
8070 -- Determines whether a type has a subcomponent of an unconstrained
8071 -- Unchecked_Union subtype. Typ is a record type.
8073 -------------------------
8074 -- Build_Equality_Call --
8075 -------------------------
8077 procedure Build_Equality_Call (Eq : Entity_Id) is
8078 Op_Type : constant Entity_Id := Etype (First_Formal (Eq));
8079 L_Exp : Node_Id := Relocate_Node (Lhs);
8080 R_Exp : Node_Id := Relocate_Node (Rhs);
8082 begin
8083 -- Adjust operands if necessary to comparison type
8085 if Base_Type (Op_Type) /= Base_Type (A_Typ)
8086 and then not Is_Class_Wide_Type (A_Typ)
8087 then
8088 L_Exp := OK_Convert_To (Op_Type, L_Exp);
8089 R_Exp := OK_Convert_To (Op_Type, R_Exp);
8090 end if;
8092 -- If we have an Unchecked_Union, we need to add the inferred
8093 -- discriminant values as actuals in the function call. At this
8094 -- point, the expansion has determined that both operands have
8095 -- inferable discriminants.
8097 if Is_Unchecked_Union (Op_Type) then
8098 declare
8099 Lhs_Type : constant Entity_Id := Etype (L_Exp);
8100 Rhs_Type : constant Entity_Id := Etype (R_Exp);
8102 Lhs_Discr_Vals : Elist_Id;
8103 -- List of inferred discriminant values for left operand.
8105 Rhs_Discr_Vals : Elist_Id;
8106 -- List of inferred discriminant values for right operand.
8108 Discr : Entity_Id;
8110 begin
8111 Lhs_Discr_Vals := New_Elmt_List;
8112 Rhs_Discr_Vals := New_Elmt_List;
8114 -- Per-object constrained selected components require special
8115 -- attention. If the enclosing scope of the component is an
8116 -- Unchecked_Union, we cannot reference its discriminants
8117 -- directly. This is why we use the extra parameters of the
8118 -- equality function of the enclosing Unchecked_Union.
8120 -- type UU_Type (Discr : Integer := 0) is
8121 -- . . .
8122 -- end record;
8123 -- pragma Unchecked_Union (UU_Type);
8125 -- 1. Unchecked_Union enclosing record:
8127 -- type Enclosing_UU_Type (Discr : Integer := 0) is record
8128 -- . . .
8129 -- Comp : UU_Type (Discr);
8130 -- . . .
8131 -- end Enclosing_UU_Type;
8132 -- pragma Unchecked_Union (Enclosing_UU_Type);
8134 -- Obj1 : Enclosing_UU_Type;
8135 -- Obj2 : Enclosing_UU_Type (1);
8137 -- [. . .] Obj1 = Obj2 [. . .]
8139 -- Generated code:
8141 -- if not (uu_typeEQ (obj1.comp, obj2.comp, a, b)) then
8143 -- A and B are the formal parameters of the equality function
8144 -- of Enclosing_UU_Type. The function always has two extra
8145 -- formals to capture the inferred discriminant values for
8146 -- each discriminant of the type.
8148 -- 2. Non-Unchecked_Union enclosing record:
8150 -- type
8151 -- Enclosing_Non_UU_Type (Discr : Integer := 0)
8152 -- is record
8153 -- . . .
8154 -- Comp : UU_Type (Discr);
8155 -- . . .
8156 -- end Enclosing_Non_UU_Type;
8158 -- Obj1 : Enclosing_Non_UU_Type;
8159 -- Obj2 : Enclosing_Non_UU_Type (1);
8161 -- ... Obj1 = Obj2 ...
8163 -- Generated code:
8165 -- if not (uu_typeEQ (obj1.comp, obj2.comp,
8166 -- obj1.discr, obj2.discr)) then
8168 -- In this case we can directly reference the discriminants of
8169 -- the enclosing record.
8171 -- Process left operand of equality
8173 if Nkind (Lhs) = N_Selected_Component
8174 and then
8175 Has_Per_Object_Constraint (Entity (Selector_Name (Lhs)))
8176 then
8177 -- If enclosing record is an Unchecked_Union, use formals
8178 -- corresponding to each discriminant. The name of the
8179 -- formal is that of the discriminant, with added suffix,
8180 -- see Exp_Ch3.Build_Record_Equality for details.
8182 if Is_Unchecked_Union (Scope (Entity (Selector_Name (Lhs))))
8183 then
8184 Discr :=
8185 First_Discriminant
8186 (Scope (Entity (Selector_Name (Lhs))));
8187 while Present (Discr) loop
8188 Append_Elmt
8189 (Make_Identifier (Loc,
8190 Chars => New_External_Name (Chars (Discr), 'A')),
8191 To => Lhs_Discr_Vals);
8192 Next_Discriminant (Discr);
8193 end loop;
8195 -- If enclosing record is of a non-Unchecked_Union type, it
8196 -- is possible to reference its discriminants directly.
8198 else
8199 Discr := First_Discriminant (Lhs_Type);
8200 while Present (Discr) loop
8201 Append_Elmt
8202 (Make_Selected_Component (Loc,
8203 Prefix => Prefix (Lhs),
8204 Selector_Name =>
8205 New_Copy
8206 (Get_Discriminant_Value (Discr,
8207 Lhs_Type,
8208 Stored_Constraint (Lhs_Type)))),
8209 To => Lhs_Discr_Vals);
8210 Next_Discriminant (Discr);
8211 end loop;
8212 end if;
8214 -- Otherwise operand is on object with a constrained type.
8215 -- Infer the discriminant values from the constraint.
8217 else
8218 Discr := First_Discriminant (Lhs_Type);
8219 while Present (Discr) loop
8220 Append_Elmt
8221 (New_Copy
8222 (Get_Discriminant_Value (Discr,
8223 Lhs_Type,
8224 Stored_Constraint (Lhs_Type))),
8225 To => Lhs_Discr_Vals);
8226 Next_Discriminant (Discr);
8227 end loop;
8228 end if;
8230 -- Similar processing for right operand of equality
8232 if Nkind (Rhs) = N_Selected_Component
8233 and then
8234 Has_Per_Object_Constraint (Entity (Selector_Name (Rhs)))
8235 then
8236 if Is_Unchecked_Union
8237 (Scope (Entity (Selector_Name (Rhs))))
8238 then
8239 Discr :=
8240 First_Discriminant
8241 (Scope (Entity (Selector_Name (Rhs))));
8242 while Present (Discr) loop
8243 Append_Elmt
8244 (Make_Identifier (Loc,
8245 Chars => New_External_Name (Chars (Discr), 'B')),
8246 To => Rhs_Discr_Vals);
8247 Next_Discriminant (Discr);
8248 end loop;
8250 else
8251 Discr := First_Discriminant (Rhs_Type);
8252 while Present (Discr) loop
8253 Append_Elmt
8254 (Make_Selected_Component (Loc,
8255 Prefix => Prefix (Rhs),
8256 Selector_Name =>
8257 New_Copy (Get_Discriminant_Value
8258 (Discr,
8259 Rhs_Type,
8260 Stored_Constraint (Rhs_Type)))),
8261 To => Rhs_Discr_Vals);
8262 Next_Discriminant (Discr);
8263 end loop;
8264 end if;
8266 else
8267 Discr := First_Discriminant (Rhs_Type);
8268 while Present (Discr) loop
8269 Append_Elmt
8270 (New_Copy (Get_Discriminant_Value
8271 (Discr,
8272 Rhs_Type,
8273 Stored_Constraint (Rhs_Type))),
8274 To => Rhs_Discr_Vals);
8275 Next_Discriminant (Discr);
8276 end loop;
8277 end if;
8279 -- Now merge the list of discriminant values so that values
8280 -- of corresponding discriminants are adjacent.
8282 declare
8283 Params : List_Id;
8284 L_Elmt : Elmt_Id;
8285 R_Elmt : Elmt_Id;
8287 begin
8288 Params := New_List (L_Exp, R_Exp);
8289 L_Elmt := First_Elmt (Lhs_Discr_Vals);
8290 R_Elmt := First_Elmt (Rhs_Discr_Vals);
8291 while Present (L_Elmt) loop
8292 Append_To (Params, Node (L_Elmt));
8293 Append_To (Params, Node (R_Elmt));
8294 Next_Elmt (L_Elmt);
8295 Next_Elmt (R_Elmt);
8296 end loop;
8298 Rewrite (N,
8299 Make_Function_Call (Loc,
8300 Name => New_Occurrence_Of (Eq, Loc),
8301 Parameter_Associations => Params));
8302 end;
8303 end;
8305 -- Normal case, not an unchecked union
8307 else
8308 Rewrite (N,
8309 Make_Function_Call (Loc,
8310 Name => New_Occurrence_Of (Eq, Loc),
8311 Parameter_Associations => New_List (L_Exp, R_Exp)));
8312 end if;
8314 Analyze_And_Resolve (N, Standard_Boolean, Suppress => All_Checks);
8315 end Build_Equality_Call;
8317 -------------------
8318 -- Find_Equality --
8319 -------------------
8321 function Find_Equality (Prims : Elist_Id) return Entity_Id is
8322 function Find_Aliased_Equality (Prim : Entity_Id) return Entity_Id;
8323 -- Find an equality in a possible alias chain starting from primitive
8324 -- operation Prim.
8326 ---------------------------
8327 -- Find_Aliased_Equality --
8328 ---------------------------
8330 function Find_Aliased_Equality (Prim : Entity_Id) return Entity_Id is
8331 Candid : Entity_Id;
8333 begin
8334 -- Inspect each candidate in the alias chain, checking whether it
8335 -- denotes an equality.
8337 Candid := Prim;
8338 while Present (Candid) loop
8339 if Is_User_Defined_Equality (Candid) then
8340 return Candid;
8341 end if;
8343 Candid := Alias (Candid);
8344 end loop;
8346 return Empty;
8347 end Find_Aliased_Equality;
8349 -- Local variables
8351 Eq_Prim : Entity_Id;
8352 Prim_Elmt : Elmt_Id;
8354 -- Start of processing for Find_Equality
8356 begin
8357 -- Assume that the tagged type lacks an equality
8359 Eq_Prim := Empty;
8361 -- Inspect the list of primitives looking for a suitable equality
8362 -- within a possible chain of aliases.
8364 Prim_Elmt := First_Elmt (Prims);
8365 while Present (Prim_Elmt) and then No (Eq_Prim) loop
8366 Eq_Prim := Find_Aliased_Equality (Node (Prim_Elmt));
8368 Next_Elmt (Prim_Elmt);
8369 end loop;
8371 -- A tagged type should always have an equality
8373 pragma Assert (Present (Eq_Prim));
8375 return Eq_Prim;
8376 end Find_Equality;
8378 ------------------------------------
8379 -- Has_Unconstrained_UU_Component --
8380 ------------------------------------
8382 function Has_Unconstrained_UU_Component
8383 (Typ : Entity_Id) return Boolean
8385 function Unconstrained_UU_In_Component_Declaration
8386 (N : Node_Id) return Boolean;
8388 function Unconstrained_UU_In_Component_Items
8389 (L : List_Id) return Boolean;
8391 function Unconstrained_UU_In_Component_List
8392 (N : Node_Id) return Boolean;
8394 function Unconstrained_UU_In_Variant_Part
8395 (N : Node_Id) return Boolean;
8396 -- A family of routines that determine whether a particular construct
8397 -- of a record type definition contains a subcomponent of an
8398 -- unchecked union type whose nominal subtype is unconstrained.
8400 -- Individual routines correspond to the production rules of the Ada
8401 -- grammar, as described in the Ada RM (P).
8403 -----------------------------------------------
8404 -- Unconstrained_UU_In_Component_Declaration --
8405 -----------------------------------------------
8407 function Unconstrained_UU_In_Component_Declaration
8408 (N : Node_Id) return Boolean
8410 pragma Assert (Nkind (N) = N_Component_Declaration);
8412 Sindic : constant Node_Id :=
8413 Subtype_Indication (Component_Definition (N));
8414 begin
8415 -- If the component declaration includes a subtype indication
8416 -- it is not an unchecked_union. Otherwise verify that it carries
8417 -- the Unchecked_Union flag and is either a record or a private
8418 -- type. A Record_Subtype declared elsewhere does not qualify,
8419 -- even if its parent type carries the flag.
8421 return Nkind (Sindic) in N_Expanded_Name | N_Identifier
8422 and then Is_Unchecked_Union (Base_Type (Etype (Sindic)))
8423 and then Ekind (Entity (Sindic)) in
8424 E_Private_Type | E_Record_Type;
8425 end Unconstrained_UU_In_Component_Declaration;
8427 -----------------------------------------
8428 -- Unconstrained_UU_In_Component_Items --
8429 -----------------------------------------
8431 function Unconstrained_UU_In_Component_Items
8432 (L : List_Id) return Boolean
8434 N : Node_Id := First (L);
8435 begin
8436 while Present (N) loop
8437 if Nkind (N) = N_Component_Declaration
8438 and then Unconstrained_UU_In_Component_Declaration (N)
8439 then
8440 return True;
8441 end if;
8443 Next (N);
8444 end loop;
8446 return False;
8447 end Unconstrained_UU_In_Component_Items;
8449 ----------------------------------------
8450 -- Unconstrained_UU_In_Component_List --
8451 ----------------------------------------
8453 function Unconstrained_UU_In_Component_List
8454 (N : Node_Id) return Boolean
8456 pragma Assert (Nkind (N) = N_Component_List);
8458 Optional_Variant_Part : Node_Id;
8459 begin
8460 if Unconstrained_UU_In_Component_Items (Component_Items (N)) then
8461 return True;
8462 end if;
8464 Optional_Variant_Part := Variant_Part (N);
8466 return
8467 Present (Optional_Variant_Part)
8468 and then
8469 Unconstrained_UU_In_Variant_Part (Optional_Variant_Part);
8470 end Unconstrained_UU_In_Component_List;
8472 --------------------------------------
8473 -- Unconstrained_UU_In_Variant_Part --
8474 --------------------------------------
8476 function Unconstrained_UU_In_Variant_Part
8477 (N : Node_Id) return Boolean
8479 pragma Assert (Nkind (N) = N_Variant_Part);
8481 Variant : Node_Id := First (Variants (N));
8482 begin
8483 loop
8484 if Unconstrained_UU_In_Component_List (Component_List (Variant))
8485 then
8486 return True;
8487 end if;
8489 Next (Variant);
8490 exit when No (Variant);
8491 end loop;
8493 return False;
8494 end Unconstrained_UU_In_Variant_Part;
8496 Typ_Def : constant Node_Id :=
8497 Type_Definition (Declaration_Node (Base_Type (Typ)));
8499 Optional_Component_List : constant Node_Id :=
8500 Component_List (Typ_Def);
8502 -- Start of processing for Has_Unconstrained_UU_Component
8504 begin
8505 return Present (Optional_Component_List)
8506 and then
8507 Unconstrained_UU_In_Component_List (Optional_Component_List);
8508 end Has_Unconstrained_UU_Component;
8510 -- Local variables
8512 Typl : Entity_Id;
8514 -- Start of processing for Expand_N_Op_Eq
8516 begin
8517 Binary_Op_Validity_Checks (N);
8519 -- Deal with private types
8521 Typl := Underlying_Type (A_Typ);
8523 -- It may happen in error situations that the underlying type is not
8524 -- set. The error will be detected later, here we just defend the
8525 -- expander code.
8527 if No (Typl) then
8528 return;
8529 end if;
8531 -- Now get the implementation base type (note that plain Base_Type here
8532 -- might lead us back to the private type, which is not what we want!)
8534 Typl := Implementation_Base_Type (Typl);
8536 -- Equality between variant records results in a call to a routine
8537 -- that has conditional tests of the discriminant value(s), and hence
8538 -- violates the No_Implicit_Conditionals restriction.
8540 if Has_Variant_Part (Typl) then
8541 declare
8542 Msg : Boolean;
8544 begin
8545 Check_Restriction (Msg, No_Implicit_Conditionals, N);
8547 if Msg then
8548 Error_Msg_N
8549 ("\comparison of variant records tests discriminants", N);
8550 return;
8551 end if;
8552 end;
8553 end if;
8555 -- Deal with overflow checks in MINIMIZED/ELIMINATED mode and if that
8556 -- means we no longer have a comparison operation, we are all done.
8558 if Minimized_Eliminated_Overflow_Check (Left_Opnd (N)) then
8559 Expand_Compare_Minimize_Eliminate_Overflow (N);
8560 end if;
8562 if Nkind (N) /= N_Op_Eq then
8563 return;
8564 end if;
8566 -- Boolean types (requiring handling of non-standard case)
8568 if Is_Boolean_Type (Typl) then
8569 Adjust_Condition (Left_Opnd (N));
8570 Adjust_Condition (Right_Opnd (N));
8571 Set_Etype (N, Standard_Boolean);
8572 Adjust_Result_Type (N, Typ);
8574 -- Array types
8576 elsif Is_Array_Type (Typl) then
8578 -- If we are doing full validity checking, and it is possible for the
8579 -- array elements to be invalid then expand out array comparisons to
8580 -- make sure that we check the array elements.
8582 if Validity_Check_Operands
8583 and then not Is_Known_Valid (Component_Type (Typl))
8584 then
8585 declare
8586 Save_Force_Validity_Checks : constant Boolean :=
8587 Force_Validity_Checks;
8588 begin
8589 Force_Validity_Checks := True;
8590 Rewrite (N,
8591 Expand_Array_Equality
8593 Relocate_Node (Lhs),
8594 Relocate_Node (Rhs),
8595 Bodies,
8596 Typl));
8597 Insert_Actions (N, Bodies);
8598 Analyze_And_Resolve (N, Standard_Boolean);
8599 Force_Validity_Checks := Save_Force_Validity_Checks;
8600 end;
8602 -- Packed case where both operands are known aligned
8604 elsif Is_Bit_Packed_Array (Typl)
8605 and then not Is_Possibly_Unaligned_Object (Lhs)
8606 and then not Is_Possibly_Unaligned_Object (Rhs)
8607 then
8608 Expand_Packed_Eq (N);
8610 -- Where the component type is elementary we can use a block bit
8611 -- comparison (if supported on the target) exception in the case
8612 -- of floating-point (negative zero issues require element by
8613 -- element comparison), and full access types (where we must be sure
8614 -- to load elements independently) and possibly unaligned arrays.
8616 elsif Is_Elementary_Type (Component_Type (Typl))
8617 and then not Is_Floating_Point_Type (Component_Type (Typl))
8618 and then not Is_Full_Access (Component_Type (Typl))
8619 and then not Is_Possibly_Unaligned_Object (Lhs)
8620 and then not Is_Possibly_Unaligned_Slice (Lhs)
8621 and then not Is_Possibly_Unaligned_Object (Rhs)
8622 and then not Is_Possibly_Unaligned_Slice (Rhs)
8623 and then Support_Composite_Compare_On_Target
8624 then
8625 null;
8627 -- For composite and floating-point cases, expand equality loop to
8628 -- make sure of using proper comparisons for tagged types, and
8629 -- correctly handling the floating-point case.
8631 else
8632 Rewrite (N,
8633 Expand_Array_Equality
8635 Relocate_Node (Lhs),
8636 Relocate_Node (Rhs),
8637 Bodies,
8638 Typl));
8639 Insert_Actions (N, Bodies, Suppress => All_Checks);
8640 Analyze_And_Resolve (N, Standard_Boolean, Suppress => All_Checks);
8641 end if;
8643 -- Record Types
8645 elsif Is_Record_Type (Typl) then
8647 -- For tagged types, use the primitive "="
8649 if Is_Tagged_Type (Typl) then
8651 -- No need to do anything else compiling under restriction
8652 -- No_Dispatching_Calls. During the semantic analysis we
8653 -- already notified such violation.
8655 if Restriction_Active (No_Dispatching_Calls) then
8656 return;
8657 end if;
8659 -- If this is an untagged private type completed with a derivation
8660 -- of an untagged private type whose full view is a tagged type,
8661 -- we use the primitive operations of the private type (since it
8662 -- does not have a full view, and also because its equality
8663 -- primitive may have been overridden in its untagged full view).
8665 if Inherits_From_Tagged_Full_View (A_Typ) then
8666 Build_Equality_Call
8667 (Find_Equality (Collect_Primitive_Operations (A_Typ)));
8669 -- Find the type's predefined equality or an overriding
8670 -- user-defined equality. The reason for not simply calling
8671 -- Find_Prim_Op here is that there may be a user-defined
8672 -- overloaded equality op that precedes the equality that we
8673 -- want, so we have to explicitly search (e.g., there could be
8674 -- an equality with two different parameter types).
8676 else
8677 if Is_Class_Wide_Type (Typl) then
8678 Typl := Find_Specific_Type (Typl);
8679 end if;
8681 Build_Equality_Call
8682 (Find_Equality (Primitive_Operations (Typl)));
8683 end if;
8685 -- Ada 2005 (AI-216): Program_Error is raised when evaluating the
8686 -- predefined equality operator for a type which has a subcomponent
8687 -- of an Unchecked_Union type whose nominal subtype is unconstrained.
8689 elsif Has_Unconstrained_UU_Component (Typl) then
8690 Insert_Action (N,
8691 Make_Raise_Program_Error (Loc,
8692 Reason => PE_Unchecked_Union_Restriction));
8694 -- Prevent Gigi from generating incorrect code by rewriting the
8695 -- equality as a standard False. (is this documented somewhere???)
8697 Rewrite (N,
8698 New_Occurrence_Of (Standard_False, Loc));
8700 elsif Is_Unchecked_Union (Typl) then
8702 -- If we can infer the discriminants of the operands, we make a
8703 -- call to the TSS equality function.
8705 if Has_Inferable_Discriminants (Lhs)
8706 and then
8707 Has_Inferable_Discriminants (Rhs)
8708 then
8709 Build_Equality_Call
8710 (TSS (Root_Type (Typl), TSS_Composite_Equality));
8712 else
8713 -- Ada 2005 (AI-216): Program_Error is raised when evaluating
8714 -- the predefined equality operator for an Unchecked_Union type
8715 -- if either of the operands lack inferable discriminants.
8717 Insert_Action (N,
8718 Make_Raise_Program_Error (Loc,
8719 Reason => PE_Unchecked_Union_Restriction));
8721 -- Emit a warning on source equalities only, otherwise the
8722 -- message may appear out of place due to internal use. The
8723 -- warning is unconditional because it is required by the
8724 -- language.
8726 if Comes_From_Source (N) then
8727 Error_Msg_N
8728 ("Unchecked_Union discriminants cannot be determined??",
8730 Error_Msg_N
8731 ("\Program_Error will be raised for equality operation??",
8733 end if;
8735 -- Prevent Gigi from generating incorrect code by rewriting
8736 -- the equality as a standard False (documented where???).
8738 Rewrite (N,
8739 New_Occurrence_Of (Standard_False, Loc));
8740 end if;
8742 -- If a type support function is present (for complex cases), use it
8744 elsif Present (TSS (Root_Type (Typl), TSS_Composite_Equality)) then
8745 Build_Equality_Call
8746 (TSS (Root_Type (Typl), TSS_Composite_Equality));
8748 -- When comparing two Bounded_Strings, use the primitive equality of
8749 -- the root Super_String type.
8751 elsif Is_Bounded_String (Typl) then
8752 Build_Equality_Call
8753 (Find_Equality
8754 (Collect_Primitive_Operations (Root_Type (Typl))));
8756 -- Otherwise expand the component by component equality. Note that
8757 -- we never use block-bit comparisons for records, because of the
8758 -- problems with gaps. The back end will often be able to recombine
8759 -- the separate comparisons that we generate here.
8761 else
8762 Remove_Side_Effects (Lhs);
8763 Remove_Side_Effects (Rhs);
8764 Rewrite (N, Expand_Record_Equality (N, Typl, Lhs, Rhs));
8766 Analyze_And_Resolve (N, Standard_Boolean, Suppress => All_Checks);
8767 end if;
8769 -- If unnesting, handle elementary types whose Equivalent_Types are
8770 -- records because there may be padding or undefined fields.
8772 elsif Unnest_Subprogram_Mode
8773 and then Ekind (Typl) in E_Class_Wide_Type
8774 | E_Class_Wide_Subtype
8775 | E_Access_Subprogram_Type
8776 | E_Access_Protected_Subprogram_Type
8777 | E_Anonymous_Access_Protected_Subprogram_Type
8778 | E_Exception_Type
8779 and then Present (Equivalent_Type (Typl))
8780 and then Is_Record_Type (Equivalent_Type (Typl))
8781 then
8782 Typl := Equivalent_Type (Typl);
8783 Remove_Side_Effects (Lhs);
8784 Remove_Side_Effects (Rhs);
8785 Rewrite (N,
8786 Expand_Record_Equality (N, Typl,
8787 Unchecked_Convert_To (Typl, Lhs),
8788 Unchecked_Convert_To (Typl, Rhs)));
8790 Analyze_And_Resolve (N, Standard_Boolean, Suppress => All_Checks);
8791 end if;
8793 -- Test if result is known at compile time
8795 Rewrite_Comparison (N);
8797 -- Try to narrow the operation
8799 if Typl = Universal_Integer and then Nkind (N) = N_Op_Eq then
8800 Narrow_Large_Operation (N);
8801 end if;
8803 -- Special optimization of length comparison
8805 Optimize_Length_Comparison (N);
8807 -- One more special case: if we have a comparison of X'Result = expr
8808 -- in floating-point, then if not already there, change expr to be
8809 -- f'Machine (expr) to eliminate surprise from extra precision.
8811 if Is_Floating_Point_Type (Typl)
8812 and then Is_Attribute_Result (Original_Node (Lhs))
8813 then
8814 -- Stick in the Typ'Machine call if not already there
8816 if Nkind (Rhs) /= N_Attribute_Reference
8817 or else Attribute_Name (Rhs) /= Name_Machine
8818 then
8819 Rewrite (Rhs,
8820 Make_Attribute_Reference (Loc,
8821 Prefix => New_Occurrence_Of (Typl, Loc),
8822 Attribute_Name => Name_Machine,
8823 Expressions => New_List (Relocate_Node (Rhs))));
8824 Analyze_And_Resolve (Rhs, Typl);
8825 end if;
8826 end if;
8827 end Expand_N_Op_Eq;
8829 -----------------------
8830 -- Expand_N_Op_Expon --
8831 -----------------------
8833 procedure Expand_N_Op_Expon (N : Node_Id) is
8834 Loc : constant Source_Ptr := Sloc (N);
8835 Ovflo : constant Boolean := Do_Overflow_Check (N);
8836 Typ : constant Entity_Id := Etype (N);
8837 Rtyp : constant Entity_Id := Root_Type (Typ);
8839 Bastyp : Entity_Id;
8841 function Wrap_MA (Exp : Node_Id) return Node_Id;
8842 -- Given an expression Exp, if the root type is Float or Long_Float,
8843 -- then wrap the expression in a call of Bastyp'Machine, to stop any
8844 -- extra precision. This is done to ensure that X**A = X**B when A is
8845 -- a static constant and B is a variable with the same value. For any
8846 -- other type, the node Exp is returned unchanged.
8848 -------------
8849 -- Wrap_MA --
8850 -------------
8852 function Wrap_MA (Exp : Node_Id) return Node_Id is
8853 Loc : constant Source_Ptr := Sloc (Exp);
8855 begin
8856 if Rtyp = Standard_Float or else Rtyp = Standard_Long_Float then
8857 return
8858 Make_Attribute_Reference (Loc,
8859 Attribute_Name => Name_Machine,
8860 Prefix => New_Occurrence_Of (Bastyp, Loc),
8861 Expressions => New_List (Relocate_Node (Exp)));
8862 else
8863 return Exp;
8864 end if;
8865 end Wrap_MA;
8867 -- Local variables
8869 Base : Node_Id;
8870 Ent : Entity_Id;
8871 Etyp : Entity_Id;
8872 Exp : Node_Id;
8873 Exptyp : Entity_Id;
8874 Expv : Uint;
8875 Rent : RE_Id;
8876 Temp : Node_Id;
8877 Xnode : Node_Id;
8879 -- Start of processing for Expand_N_Op_Expon
8881 begin
8882 Binary_Op_Validity_Checks (N);
8884 -- CodePeer wants to see the unexpanded N_Op_Expon node
8886 if CodePeer_Mode then
8887 return;
8888 end if;
8890 -- Relocation of left and right operands must be done after performing
8891 -- the validity checks since the generation of validation checks may
8892 -- remove side effects.
8894 Base := Relocate_Node (Left_Opnd (N));
8895 Bastyp := Etype (Base);
8896 Exp := Relocate_Node (Right_Opnd (N));
8897 Exptyp := Etype (Exp);
8899 -- If either operand is of a private type, then we have the use of an
8900 -- intrinsic operator, and we get rid of the privateness, by using root
8901 -- types of underlying types for the actual operation. Otherwise the
8902 -- private types will cause trouble if we expand multiplications or
8903 -- shifts etc. We also do this transformation if the result type is
8904 -- different from the base type.
8906 if Is_Private_Type (Etype (Base))
8907 or else Is_Private_Type (Typ)
8908 or else Is_Private_Type (Exptyp)
8909 or else Rtyp /= Root_Type (Bastyp)
8910 then
8911 declare
8912 Bt : constant Entity_Id := Root_Type (Underlying_Type (Bastyp));
8913 Et : constant Entity_Id := Root_Type (Underlying_Type (Exptyp));
8914 begin
8915 Rewrite (N,
8916 Unchecked_Convert_To (Typ,
8917 Make_Op_Expon (Loc,
8918 Left_Opnd => Unchecked_Convert_To (Bt, Base),
8919 Right_Opnd => Unchecked_Convert_To (Et, Exp))));
8920 Analyze_And_Resolve (N, Typ);
8921 return;
8922 end;
8923 end if;
8925 -- Check for MINIMIZED/ELIMINATED overflow mode
8927 if Minimized_Eliminated_Overflow_Check (N) then
8928 Apply_Arithmetic_Overflow_Check (N);
8929 return;
8930 end if;
8932 -- Test for case of known right argument where we can replace the
8933 -- exponentiation by an equivalent expression using multiplication.
8935 -- Note: use CRT_Safe version of Compile_Time_Known_Value because in
8936 -- configurable run-time mode, we may not have the exponentiation
8937 -- routine available, and we don't want the legality of the program
8938 -- to depend on how clever the compiler is in knowing values.
8940 if CRT_Safe_Compile_Time_Known_Value (Exp) then
8941 Expv := Expr_Value (Exp);
8943 -- We only fold small non-negative exponents. You might think we
8944 -- could fold small negative exponents for the real case, but we
8945 -- can't because we are required to raise Constraint_Error for
8946 -- the case of 0.0 ** (negative) even if Machine_Overflows = False.
8947 -- See ACVC test C4A012B, and it is not worth generating the test.
8949 -- For small negative exponents, we return the reciprocal of
8950 -- the folding of the exponentiation for the opposite (positive)
8951 -- exponent, as required by Ada RM 4.5.6(11/3).
8953 if abs Expv <= 4 then
8955 -- X ** 0 = 1 (or 1.0)
8957 if Expv = 0 then
8959 -- Call Remove_Side_Effects to ensure that any side effects
8960 -- in the ignored left operand (in particular function calls
8961 -- to user defined functions) are properly executed.
8963 Remove_Side_Effects (Base);
8965 if Ekind (Typ) in Integer_Kind then
8966 Xnode := Make_Integer_Literal (Loc, Intval => 1);
8967 else
8968 Xnode := Make_Real_Literal (Loc, Ureal_1);
8969 end if;
8971 -- X ** 1 = X
8973 elsif Expv = 1 then
8974 Xnode := Base;
8976 -- X ** 2 = X * X
8978 elsif Expv = 2 then
8979 Xnode :=
8980 Wrap_MA (
8981 Make_Op_Multiply (Loc,
8982 Left_Opnd => Duplicate_Subexpr (Base),
8983 Right_Opnd => Duplicate_Subexpr_No_Checks (Base)));
8985 -- X ** 3 = X * X * X
8987 elsif Expv = 3 then
8988 Xnode :=
8989 Wrap_MA (
8990 Make_Op_Multiply (Loc,
8991 Left_Opnd =>
8992 Make_Op_Multiply (Loc,
8993 Left_Opnd => Duplicate_Subexpr (Base),
8994 Right_Opnd => Duplicate_Subexpr_No_Checks (Base)),
8995 Right_Opnd => Duplicate_Subexpr_No_Checks (Base)));
8997 -- X ** 4 ->
8999 -- do
9000 -- En : constant base'type := base * base;
9001 -- in
9002 -- En * En
9004 elsif Expv = 4 then
9005 Temp := Make_Temporary (Loc, 'E', Base);
9007 Xnode :=
9008 Make_Expression_With_Actions (Loc,
9009 Actions => New_List (
9010 Make_Object_Declaration (Loc,
9011 Defining_Identifier => Temp,
9012 Constant_Present => True,
9013 Object_Definition => New_Occurrence_Of (Typ, Loc),
9014 Expression =>
9015 Wrap_MA (
9016 Make_Op_Multiply (Loc,
9017 Left_Opnd =>
9018 Duplicate_Subexpr (Base),
9019 Right_Opnd =>
9020 Duplicate_Subexpr_No_Checks (Base))))),
9022 Expression =>
9023 Wrap_MA (
9024 Make_Op_Multiply (Loc,
9025 Left_Opnd => New_Occurrence_Of (Temp, Loc),
9026 Right_Opnd => New_Occurrence_Of (Temp, Loc))));
9028 -- X ** N = 1.0 / X ** (-N)
9029 -- N in -4 .. -1
9031 else
9032 pragma Assert
9033 (Expv = -1 or Expv = -2 or Expv = -3 or Expv = -4);
9035 Xnode :=
9036 Make_Op_Divide (Loc,
9037 Left_Opnd =>
9038 Make_Float_Literal (Loc,
9039 Radix => Uint_1,
9040 Significand => Uint_1,
9041 Exponent => Uint_0),
9042 Right_Opnd =>
9043 Make_Op_Expon (Loc,
9044 Left_Opnd => Duplicate_Subexpr (Base),
9045 Right_Opnd =>
9046 Make_Integer_Literal (Loc,
9047 Intval => -Expv)));
9048 end if;
9050 Rewrite (N, Xnode);
9051 Analyze_And_Resolve (N, Typ);
9052 return;
9053 end if;
9054 end if;
9056 -- Optimize 2 ** expression to shift where possible
9058 -- Note: we used to check that Exptyp was an unsigned type. But that is
9059 -- an unnecessary check, since if Exp is negative, we have a run-time
9060 -- error that is either caught (so we get the right result) or we have
9061 -- suppressed the check, in which case the code is erroneous anyway.
9063 if Is_Integer_Type (Rtyp)
9065 -- The base value must be "safe compile-time known", and exactly 2
9067 and then Nkind (Base) = N_Integer_Literal
9068 and then CRT_Safe_Compile_Time_Known_Value (Base)
9069 and then Expr_Value (Base) = Uint_2
9071 -- This transformation is not applicable for a modular type with a
9072 -- nonbinary modulus because shifting makes no sense in that case.
9074 and then not Non_Binary_Modulus (Typ)
9075 then
9076 -- Handle the cases where our parent is a division or multiplication
9077 -- specially. In these cases we can convert to using a shift at the
9078 -- parent level if we are not doing overflow checking, since it is
9079 -- too tricky to combine the overflow check at the parent level.
9081 if not Ovflo
9082 and then Nkind (Parent (N)) in N_Op_Divide | N_Op_Multiply
9083 then
9084 declare
9085 P : constant Node_Id := Parent (N);
9086 L : constant Node_Id := Left_Opnd (P);
9087 R : constant Node_Id := Right_Opnd (P);
9089 begin
9090 if (Nkind (P) = N_Op_Multiply
9091 and then
9092 ((Is_Integer_Type (Etype (L)) and then R = N)
9093 or else
9094 (Is_Integer_Type (Etype (R)) and then L = N))
9095 and then not Do_Overflow_Check (P))
9097 or else
9098 (Nkind (P) = N_Op_Divide
9099 and then Is_Integer_Type (Etype (L))
9100 and then Is_Unsigned_Type (Etype (L))
9101 and then R = N
9102 and then not Do_Overflow_Check (P))
9103 then
9104 Set_Is_Power_Of_2_For_Shift (N);
9105 return;
9106 end if;
9107 end;
9109 -- Here we have 2 ** N on its own, so we can convert this into a
9110 -- shift.
9112 else
9113 -- Op_Shift_Left (generated below) has modular-shift semantics;
9114 -- therefore we might need to generate an overflow check here
9115 -- if the type is signed.
9117 if Is_Signed_Integer_Type (Typ) and then Ovflo then
9118 declare
9119 OK : Boolean;
9120 Lo : Uint;
9121 Hi : Uint;
9123 MaxS : constant Uint := Esize (Rtyp) - 2;
9124 -- Maximum shift count with no overflow
9125 begin
9126 Determine_Range (Exp, OK, Lo, Hi, Assume_Valid => True);
9128 if not OK or else Hi > MaxS then
9129 Insert_Action (N,
9130 Make_Raise_Constraint_Error (Loc,
9131 Condition =>
9132 Make_Op_Gt (Loc,
9133 Left_Opnd => Duplicate_Subexpr (Exp),
9134 Right_Opnd => Make_Integer_Literal (Loc, MaxS)),
9135 Reason => CE_Overflow_Check_Failed));
9136 end if;
9137 end;
9138 end if;
9140 -- Generate Shift_Left (1, Exp)
9142 Rewrite (N,
9143 Make_Op_Shift_Left (Loc,
9144 Left_Opnd => Make_Integer_Literal (Loc, Uint_1),
9145 Right_Opnd => Exp));
9147 Analyze_And_Resolve (N, Typ);
9148 return;
9149 end if;
9150 end if;
9152 -- Fall through if exponentiation must be done using a runtime routine
9154 -- First deal with modular case
9156 if Is_Modular_Integer_Type (Rtyp) then
9158 -- Nonbinary modular case, we call the special exponentiation
9159 -- routine for the nonbinary case, converting the argument to
9160 -- Long_Long_Integer and passing the modulus value. Then the
9161 -- result is converted back to the base type.
9163 if Non_Binary_Modulus (Rtyp) then
9164 Rewrite (N,
9165 Convert_To (Typ,
9166 Make_Function_Call (Loc,
9167 Name =>
9168 New_Occurrence_Of (RTE (RE_Exp_Modular), Loc),
9169 Parameter_Associations => New_List (
9170 Convert_To (RTE (RE_Unsigned), Base),
9171 Make_Integer_Literal (Loc, Modulus (Rtyp)),
9172 Exp))));
9174 -- Binary modular case, in this case, we call one of three routines,
9175 -- either the unsigned integer case, or the unsigned long long
9176 -- integer case, or the unsigned long long long integer case, with a
9177 -- final "and" operation to do the required mod.
9179 else
9180 if Esize (Rtyp) <= Standard_Integer_Size then
9181 Ent := RTE (RE_Exp_Unsigned);
9182 elsif Esize (Rtyp) <= Standard_Long_Long_Integer_Size then
9183 Ent := RTE (RE_Exp_Long_Long_Unsigned);
9184 else
9185 Ent := RTE (RE_Exp_Long_Long_Long_Unsigned);
9186 end if;
9188 Rewrite (N,
9189 Convert_To (Typ,
9190 Make_Op_And (Loc,
9191 Left_Opnd =>
9192 Make_Function_Call (Loc,
9193 Name => New_Occurrence_Of (Ent, Loc),
9194 Parameter_Associations => New_List (
9195 Convert_To (Etype (First_Formal (Ent)), Base),
9196 Exp)),
9197 Right_Opnd =>
9198 Make_Integer_Literal (Loc, Modulus (Rtyp) - 1))));
9200 end if;
9202 -- Common exit point for modular type case
9204 Analyze_And_Resolve (N, Typ);
9205 return;
9207 -- Signed integer cases, using either Integer, Long_Long_Integer or
9208 -- Long_Long_Long_Integer. It is not worth also having routines for
9209 -- Short_[Short_]Integer, since for most machines it would not help,
9210 -- and it would generate more code that might need certification when
9211 -- a certified run time is required.
9213 -- In the integer cases, we have two routines, one for when overflow
9214 -- checks are required, and one when they are not required, since there
9215 -- is a real gain in omitting checks on many machines.
9217 elsif Is_Signed_Integer_Type (Rtyp) then
9218 if Esize (Rtyp) <= Standard_Integer_Size then
9219 Etyp := Standard_Integer;
9221 if Ovflo then
9222 Rent := RE_Exp_Integer;
9223 else
9224 Rent := RE_Exn_Integer;
9225 end if;
9227 elsif Esize (Rtyp) <= Standard_Long_Long_Integer_Size then
9228 Etyp := Standard_Long_Long_Integer;
9230 if Ovflo then
9231 Rent := RE_Exp_Long_Long_Integer;
9232 else
9233 Rent := RE_Exn_Long_Long_Integer;
9234 end if;
9236 else
9237 Etyp := Standard_Long_Long_Long_Integer;
9239 if Ovflo then
9240 Rent := RE_Exp_Long_Long_Long_Integer;
9241 else
9242 Rent := RE_Exn_Long_Long_Long_Integer;
9243 end if;
9244 end if;
9246 -- Floating-point cases. We do not need separate routines for the
9247 -- overflow case here, since in the case of floating-point, we generate
9248 -- infinities anyway as a rule (either that or we automatically trap
9249 -- overflow), and if there is an infinity generated and a range check
9250 -- is required, the check will fail anyway.
9252 else
9253 pragma Assert (Is_Floating_Point_Type (Rtyp));
9255 -- Short_Float and Float are the same type for GNAT
9257 if Rtyp = Standard_Short_Float or else Rtyp = Standard_Float then
9258 Etyp := Standard_Float;
9259 Rent := RE_Exn_Float;
9261 elsif Rtyp = Standard_Long_Float then
9262 Etyp := Standard_Long_Float;
9263 Rent := RE_Exn_Long_Float;
9265 else
9266 Etyp := Standard_Long_Long_Float;
9267 Rent := RE_Exn_Long_Long_Float;
9268 end if;
9269 end if;
9271 -- Common processing for integer cases and floating-point cases.
9272 -- If we are in the right type, we can call runtime routine directly
9274 if Typ = Etyp
9275 and then not Is_Universal_Numeric_Type (Rtyp)
9276 then
9277 Rewrite (N,
9278 Wrap_MA (
9279 Make_Function_Call (Loc,
9280 Name => New_Occurrence_Of (RTE (Rent), Loc),
9281 Parameter_Associations => New_List (Base, Exp))));
9283 -- Otherwise we have to introduce conversions (conversions are also
9284 -- required in the universal cases, since the runtime routine is
9285 -- typed using one of the standard types).
9287 else
9288 Rewrite (N,
9289 Convert_To (Typ,
9290 Make_Function_Call (Loc,
9291 Name => New_Occurrence_Of (RTE (Rent), Loc),
9292 Parameter_Associations => New_List (
9293 Convert_To (Etyp, Base),
9294 Exp))));
9295 end if;
9297 Analyze_And_Resolve (N, Typ);
9298 return;
9300 exception
9301 when RE_Not_Available =>
9302 return;
9303 end Expand_N_Op_Expon;
9305 --------------------
9306 -- Expand_N_Op_Ge --
9307 --------------------
9309 procedure Expand_N_Op_Ge (N : Node_Id) is
9310 Typ : constant Entity_Id := Etype (N);
9311 Op1 : constant Node_Id := Left_Opnd (N);
9312 Op2 : constant Node_Id := Right_Opnd (N);
9313 Typ1 : constant Entity_Id := Base_Type (Etype (Op1));
9315 begin
9316 Binary_Op_Validity_Checks (N);
9318 -- Deal with overflow checks in MINIMIZED/ELIMINATED mode and if that
9319 -- means we no longer have a comparison operation, we are all done.
9321 if Minimized_Eliminated_Overflow_Check (Op1) then
9322 Expand_Compare_Minimize_Eliminate_Overflow (N);
9323 end if;
9325 if Nkind (N) /= N_Op_Ge then
9326 return;
9327 end if;
9329 -- Array type case
9331 if Is_Array_Type (Typ1) then
9332 Expand_Array_Comparison (N);
9333 return;
9334 end if;
9336 -- Deal with boolean operands
9338 if Is_Boolean_Type (Typ1) then
9339 Adjust_Condition (Op1);
9340 Adjust_Condition (Op2);
9341 Set_Etype (N, Standard_Boolean);
9342 Adjust_Result_Type (N, Typ);
9343 end if;
9345 Rewrite_Comparison (N);
9347 -- Try to narrow the operation
9349 if Typ1 = Universal_Integer and then Nkind (N) = N_Op_Ge then
9350 Narrow_Large_Operation (N);
9351 end if;
9353 Optimize_Length_Comparison (N);
9354 end Expand_N_Op_Ge;
9356 --------------------
9357 -- Expand_N_Op_Gt --
9358 --------------------
9360 procedure Expand_N_Op_Gt (N : Node_Id) is
9361 Typ : constant Entity_Id := Etype (N);
9362 Op1 : constant Node_Id := Left_Opnd (N);
9363 Op2 : constant Node_Id := Right_Opnd (N);
9364 Typ1 : constant Entity_Id := Base_Type (Etype (Op1));
9366 begin
9367 Binary_Op_Validity_Checks (N);
9369 -- Deal with overflow checks in MINIMIZED/ELIMINATED mode and if that
9370 -- means we no longer have a comparison operation, we are all done.
9372 if Minimized_Eliminated_Overflow_Check (Op1) then
9373 Expand_Compare_Minimize_Eliminate_Overflow (N);
9374 end if;
9376 if Nkind (N) /= N_Op_Gt then
9377 return;
9378 end if;
9380 -- Deal with array type operands
9382 if Is_Array_Type (Typ1) then
9383 Expand_Array_Comparison (N);
9384 return;
9385 end if;
9387 -- Deal with boolean type operands
9389 if Is_Boolean_Type (Typ1) then
9390 Adjust_Condition (Op1);
9391 Adjust_Condition (Op2);
9392 Set_Etype (N, Standard_Boolean);
9393 Adjust_Result_Type (N, Typ);
9394 end if;
9396 Rewrite_Comparison (N);
9398 -- Try to narrow the operation
9400 if Typ1 = Universal_Integer and then Nkind (N) = N_Op_Gt then
9401 Narrow_Large_Operation (N);
9402 end if;
9404 Optimize_Length_Comparison (N);
9405 end Expand_N_Op_Gt;
9407 --------------------
9408 -- Expand_N_Op_Le --
9409 --------------------
9411 procedure Expand_N_Op_Le (N : Node_Id) is
9412 Typ : constant Entity_Id := Etype (N);
9413 Op1 : constant Node_Id := Left_Opnd (N);
9414 Op2 : constant Node_Id := Right_Opnd (N);
9415 Typ1 : constant Entity_Id := Base_Type (Etype (Op1));
9417 begin
9418 Binary_Op_Validity_Checks (N);
9420 -- Deal with overflow checks in MINIMIZED/ELIMINATED mode and if that
9421 -- means we no longer have a comparison operation, we are all done.
9423 if Minimized_Eliminated_Overflow_Check (Op1) then
9424 Expand_Compare_Minimize_Eliminate_Overflow (N);
9425 end if;
9427 if Nkind (N) /= N_Op_Le then
9428 return;
9429 end if;
9431 -- Deal with array type operands
9433 if Is_Array_Type (Typ1) then
9434 Expand_Array_Comparison (N);
9435 return;
9436 end if;
9438 -- Deal with Boolean type operands
9440 if Is_Boolean_Type (Typ1) then
9441 Adjust_Condition (Op1);
9442 Adjust_Condition (Op2);
9443 Set_Etype (N, Standard_Boolean);
9444 Adjust_Result_Type (N, Typ);
9445 end if;
9447 Rewrite_Comparison (N);
9449 -- Try to narrow the operation
9451 if Typ1 = Universal_Integer and then Nkind (N) = N_Op_Le then
9452 Narrow_Large_Operation (N);
9453 end if;
9455 Optimize_Length_Comparison (N);
9456 end Expand_N_Op_Le;
9458 --------------------
9459 -- Expand_N_Op_Lt --
9460 --------------------
9462 procedure Expand_N_Op_Lt (N : Node_Id) is
9463 Typ : constant Entity_Id := Etype (N);
9464 Op1 : constant Node_Id := Left_Opnd (N);
9465 Op2 : constant Node_Id := Right_Opnd (N);
9466 Typ1 : constant Entity_Id := Base_Type (Etype (Op1));
9468 begin
9469 Binary_Op_Validity_Checks (N);
9471 -- Deal with overflow checks in MINIMIZED/ELIMINATED mode and if that
9472 -- means we no longer have a comparison operation, we are all done.
9474 if Minimized_Eliminated_Overflow_Check (Op1) then
9475 Expand_Compare_Minimize_Eliminate_Overflow (N);
9476 end if;
9478 if Nkind (N) /= N_Op_Lt then
9479 return;
9480 end if;
9482 -- Deal with array type operands
9484 if Is_Array_Type (Typ1) then
9485 Expand_Array_Comparison (N);
9486 return;
9487 end if;
9489 -- Deal with Boolean type operands
9491 if Is_Boolean_Type (Typ1) then
9492 Adjust_Condition (Op1);
9493 Adjust_Condition (Op2);
9494 Set_Etype (N, Standard_Boolean);
9495 Adjust_Result_Type (N, Typ);
9496 end if;
9498 Rewrite_Comparison (N);
9500 -- Try to narrow the operation
9502 if Typ1 = Universal_Integer and then Nkind (N) = N_Op_Lt then
9503 Narrow_Large_Operation (N);
9504 end if;
9506 Optimize_Length_Comparison (N);
9507 end Expand_N_Op_Lt;
9509 -----------------------
9510 -- Expand_N_Op_Minus --
9511 -----------------------
9513 procedure Expand_N_Op_Minus (N : Node_Id) is
9514 Loc : constant Source_Ptr := Sloc (N);
9515 Typ : constant Entity_Id := Etype (N);
9517 begin
9518 Unary_Op_Validity_Checks (N);
9520 -- Check for MINIMIZED/ELIMINATED overflow mode
9522 if Minimized_Eliminated_Overflow_Check (N) then
9523 Apply_Arithmetic_Overflow_Check (N);
9524 return;
9525 end if;
9527 -- Try to narrow the operation
9529 if Typ = Universal_Integer then
9530 Narrow_Large_Operation (N);
9532 if Nkind (N) /= N_Op_Minus then
9533 return;
9534 end if;
9535 end if;
9537 if not Backend_Overflow_Checks_On_Target
9538 and then Is_Signed_Integer_Type (Typ)
9539 and then Do_Overflow_Check (N)
9540 then
9541 -- Software overflow checking expands -expr into (0 - expr)
9543 Rewrite (N,
9544 Make_Op_Subtract (Loc,
9545 Left_Opnd => Make_Integer_Literal (Loc, 0),
9546 Right_Opnd => Right_Opnd (N)));
9548 Analyze_And_Resolve (N, Typ);
9549 end if;
9551 Expand_Nonbinary_Modular_Op (N);
9552 end Expand_N_Op_Minus;
9554 ---------------------
9555 -- Expand_N_Op_Mod --
9556 ---------------------
9558 procedure Expand_N_Op_Mod (N : Node_Id) is
9559 Loc : constant Source_Ptr := Sloc (N);
9560 Typ : constant Entity_Id := Etype (N);
9561 DDC : constant Boolean := Do_Division_Check (N);
9563 Left : Node_Id;
9564 Right : Node_Id;
9566 LLB : Uint;
9567 Llo : Uint;
9568 Lhi : Uint;
9569 LOK : Boolean;
9570 Rlo : Uint;
9571 Rhi : Uint;
9572 ROK : Boolean;
9574 pragma Warnings (Off, Lhi);
9576 begin
9577 Binary_Op_Validity_Checks (N);
9579 -- Check for MINIMIZED/ELIMINATED overflow mode
9581 if Minimized_Eliminated_Overflow_Check (N) then
9582 Apply_Arithmetic_Overflow_Check (N);
9583 return;
9584 end if;
9586 -- Try to narrow the operation
9588 if Typ = Universal_Integer then
9589 Narrow_Large_Operation (N);
9591 if Nkind (N) /= N_Op_Mod then
9592 return;
9593 end if;
9594 end if;
9596 if Is_Integer_Type (Typ) then
9597 Apply_Divide_Checks (N);
9599 -- All done if we don't have a MOD any more, which can happen as a
9600 -- result of overflow expansion in MINIMIZED or ELIMINATED modes.
9602 if Nkind (N) /= N_Op_Mod then
9603 return;
9604 end if;
9605 end if;
9607 -- Proceed with expansion of mod operator
9609 Left := Left_Opnd (N);
9610 Right := Right_Opnd (N);
9612 Determine_Range (Right, ROK, Rlo, Rhi, Assume_Valid => True);
9613 Determine_Range (Left, LOK, Llo, Lhi, Assume_Valid => True);
9615 -- Convert mod to rem if operands are both known to be non-negative, or
9616 -- both known to be non-positive (these are the cases in which rem and
9617 -- mod are the same, see (RM 4.5.5(28-30)). We do this since it is quite
9618 -- likely that this will improve the quality of code, (the operation now
9619 -- corresponds to the hardware remainder), and it does not seem likely
9620 -- that it could be harmful. It also avoids some cases of the elaborate
9621 -- expansion in Modify_Tree_For_C mode below (since Ada rem = C %).
9623 if (LOK and ROK)
9624 and then ((Llo >= 0 and then Rlo >= 0)
9625 or else
9626 (Lhi <= 0 and then Rhi <= 0))
9627 then
9628 Rewrite (N,
9629 Make_Op_Rem (Sloc (N),
9630 Left_Opnd => Left_Opnd (N),
9631 Right_Opnd => Right_Opnd (N)));
9633 -- Instead of reanalyzing the node we do the analysis manually. This
9634 -- avoids anomalies when the replacement is done in an instance and
9635 -- is epsilon more efficient.
9637 pragma Assert (Entity (N) = Standard_Op_Rem);
9638 Set_Etype (N, Typ);
9639 Set_Do_Division_Check (N, DDC);
9640 Expand_N_Op_Rem (N);
9641 Set_Analyzed (N);
9642 return;
9644 -- Otherwise, normal mod processing
9646 else
9647 -- Apply optimization x mod 1 = 0. We don't really need that with
9648 -- gcc, but it is useful with other back ends and is certainly
9649 -- harmless.
9651 if Is_Integer_Type (Etype (N))
9652 and then Compile_Time_Known_Value (Right)
9653 and then Expr_Value (Right) = Uint_1
9654 then
9655 -- Call Remove_Side_Effects to ensure that any side effects in
9656 -- the ignored left operand (in particular function calls to
9657 -- user defined functions) are properly executed.
9659 Remove_Side_Effects (Left);
9661 Rewrite (N, Make_Integer_Literal (Loc, 0));
9662 Analyze_And_Resolve (N, Typ);
9663 return;
9664 end if;
9666 -- If we still have a mod operator and we are in Modify_Tree_For_C
9667 -- mode, and we have a signed integer type, then here is where we do
9668 -- the rewrite in terms of Rem. Note this rewrite bypasses the need
9669 -- for the special handling of the annoying case of largest negative
9670 -- number mod minus one.
9672 if Nkind (N) = N_Op_Mod
9673 and then Is_Signed_Integer_Type (Typ)
9674 and then Modify_Tree_For_C
9675 then
9676 -- In the general case, we expand A mod B as
9678 -- Tnn : constant typ := A rem B;
9679 -- ..
9680 -- (if (A >= 0) = (B >= 0) then Tnn
9681 -- elsif Tnn = 0 then 0
9682 -- else Tnn + B)
9684 -- The comparison can be written simply as A >= 0 if we know that
9685 -- B >= 0 which is a very common case.
9687 -- An important optimization is when B is known at compile time
9688 -- to be 2**K for some constant. In this case we can simply AND
9689 -- the left operand with the bit string 2**K-1 (i.e. K 1-bits)
9690 -- and that works for both the positive and negative cases.
9692 declare
9693 P2 : constant Nat := Power_Of_Two (Right);
9695 begin
9696 if P2 /= 0 then
9697 Rewrite (N,
9698 Unchecked_Convert_To (Typ,
9699 Make_Op_And (Loc,
9700 Left_Opnd =>
9701 Unchecked_Convert_To
9702 (Corresponding_Unsigned_Type (Typ), Left),
9703 Right_Opnd =>
9704 Make_Integer_Literal (Loc, 2 ** P2 - 1))));
9705 Analyze_And_Resolve (N, Typ);
9706 return;
9707 end if;
9708 end;
9710 -- Here for the full rewrite
9712 declare
9713 Tnn : constant Entity_Id := Make_Temporary (Sloc (N), 'T', N);
9714 Cmp : Node_Id;
9716 begin
9717 Cmp :=
9718 Make_Op_Ge (Loc,
9719 Left_Opnd => Duplicate_Subexpr_No_Checks (Left),
9720 Right_Opnd => Make_Integer_Literal (Loc, 0));
9722 if not LOK or else Rlo < 0 then
9723 Cmp :=
9724 Make_Op_Eq (Loc,
9725 Left_Opnd => Cmp,
9726 Right_Opnd =>
9727 Make_Op_Ge (Loc,
9728 Left_Opnd => Duplicate_Subexpr_No_Checks (Right),
9729 Right_Opnd => Make_Integer_Literal (Loc, 0)));
9730 end if;
9732 Insert_Action (N,
9733 Make_Object_Declaration (Loc,
9734 Defining_Identifier => Tnn,
9735 Constant_Present => True,
9736 Object_Definition => New_Occurrence_Of (Typ, Loc),
9737 Expression =>
9738 Make_Op_Rem (Loc,
9739 Left_Opnd => Left,
9740 Right_Opnd => Right)));
9742 Rewrite (N,
9743 Make_If_Expression (Loc,
9744 Expressions => New_List (
9745 Cmp,
9746 New_Occurrence_Of (Tnn, Loc),
9747 Make_If_Expression (Loc,
9748 Is_Elsif => True,
9749 Expressions => New_List (
9750 Make_Op_Eq (Loc,
9751 Left_Opnd => New_Occurrence_Of (Tnn, Loc),
9752 Right_Opnd => Make_Integer_Literal (Loc, 0)),
9753 Make_Integer_Literal (Loc, 0),
9754 Make_Op_Add (Loc,
9755 Left_Opnd => New_Occurrence_Of (Tnn, Loc),
9756 Right_Opnd =>
9757 Duplicate_Subexpr_No_Checks (Right)))))));
9759 Analyze_And_Resolve (N, Typ);
9760 return;
9761 end;
9762 end if;
9764 -- Deal with annoying case of largest negative number mod minus one.
9765 -- Gigi may not handle this case correctly, because on some targets,
9766 -- the mod value is computed using a divide instruction which gives
9767 -- an overflow trap for this case.
9769 -- It would be a bit more efficient to figure out which targets
9770 -- this is really needed for, but in practice it is reasonable
9771 -- to do the following special check in all cases, since it means
9772 -- we get a clearer message, and also the overhead is minimal given
9773 -- that division is expensive in any case.
9775 -- In fact the check is quite easy, if the right operand is -1, then
9776 -- the mod value is always 0, and we can just ignore the left operand
9777 -- completely in this case.
9779 -- This only applies if we still have a mod operator. Skip if we
9780 -- have already rewritten this (e.g. in the case of eliminated
9781 -- overflow checks which have driven us into bignum mode).
9783 if Nkind (N) = N_Op_Mod then
9785 -- The operand type may be private (e.g. in the expansion of an
9786 -- intrinsic operation) so we must use the underlying type to get
9787 -- the bounds, and convert the literals explicitly.
9789 LLB :=
9790 Expr_Value
9791 (Type_Low_Bound (Base_Type (Underlying_Type (Etype (Left)))));
9793 if (not ROK or else (Rlo <= (-1) and then (-1) <= Rhi))
9794 and then (not LOK or else Llo = LLB)
9795 and then not CodePeer_Mode
9796 then
9797 Rewrite (N,
9798 Make_If_Expression (Loc,
9799 Expressions => New_List (
9800 Make_Op_Eq (Loc,
9801 Left_Opnd => Duplicate_Subexpr (Right),
9802 Right_Opnd =>
9803 Unchecked_Convert_To (Typ,
9804 Make_Integer_Literal (Loc, -1))),
9805 Unchecked_Convert_To (Typ,
9806 Make_Integer_Literal (Loc, Uint_0)),
9807 Relocate_Node (N))));
9809 Set_Analyzed (Next (Next (First (Expressions (N)))));
9810 Analyze_And_Resolve (N, Typ);
9811 end if;
9812 end if;
9813 end if;
9814 end Expand_N_Op_Mod;
9816 --------------------------
9817 -- Expand_N_Op_Multiply --
9818 --------------------------
9820 procedure Expand_N_Op_Multiply (N : Node_Id) is
9821 Loc : constant Source_Ptr := Sloc (N);
9822 Lop : constant Node_Id := Left_Opnd (N);
9823 Rop : constant Node_Id := Right_Opnd (N);
9825 Lp2 : constant Boolean :=
9826 Nkind (Lop) = N_Op_Expon and then Is_Power_Of_2_For_Shift (Lop);
9827 Rp2 : constant Boolean :=
9828 Nkind (Rop) = N_Op_Expon and then Is_Power_Of_2_For_Shift (Rop);
9830 Ltyp : constant Entity_Id := Etype (Lop);
9831 Rtyp : constant Entity_Id := Etype (Rop);
9832 Typ : Entity_Id := Etype (N);
9834 begin
9835 Binary_Op_Validity_Checks (N);
9837 -- Check for MINIMIZED/ELIMINATED overflow mode
9839 if Minimized_Eliminated_Overflow_Check (N) then
9840 Apply_Arithmetic_Overflow_Check (N);
9841 return;
9842 end if;
9844 -- Special optimizations for integer types
9846 if Is_Integer_Type (Typ) then
9848 -- N * 0 = 0 for integer types
9850 if Compile_Time_Known_Value (Rop)
9851 and then Expr_Value (Rop) = Uint_0
9852 then
9853 -- Call Remove_Side_Effects to ensure that any side effects in
9854 -- the ignored left operand (in particular function calls to
9855 -- user defined functions) are properly executed.
9857 Remove_Side_Effects (Lop);
9859 Rewrite (N, Make_Integer_Literal (Loc, Uint_0));
9860 Analyze_And_Resolve (N, Typ);
9861 return;
9862 end if;
9864 -- Similar handling for 0 * N = 0
9866 if Compile_Time_Known_Value (Lop)
9867 and then Expr_Value (Lop) = Uint_0
9868 then
9869 Remove_Side_Effects (Rop);
9870 Rewrite (N, Make_Integer_Literal (Loc, Uint_0));
9871 Analyze_And_Resolve (N, Typ);
9872 return;
9873 end if;
9875 -- N * 1 = 1 * N = N for integer types
9877 -- This optimisation is not done if we are going to
9878 -- rewrite the product 1 * 2 ** N to a shift.
9880 if Compile_Time_Known_Value (Rop)
9881 and then Expr_Value (Rop) = Uint_1
9882 and then not Lp2
9883 then
9884 Rewrite (N, Lop);
9885 return;
9887 elsif Compile_Time_Known_Value (Lop)
9888 and then Expr_Value (Lop) = Uint_1
9889 and then not Rp2
9890 then
9891 Rewrite (N, Rop);
9892 return;
9893 end if;
9894 end if;
9896 -- Convert x * 2 ** y to Shift_Left (x, y). Note that the fact that
9897 -- Is_Power_Of_2_For_Shift is set means that we know that our left
9898 -- operand is an integer, as required for this to work.
9900 if Rp2 then
9901 if Lp2 then
9903 -- Convert 2 ** A * 2 ** B into 2 ** (A + B)
9905 Rewrite (N,
9906 Make_Op_Expon (Loc,
9907 Left_Opnd => Make_Integer_Literal (Loc, 2),
9908 Right_Opnd =>
9909 Make_Op_Add (Loc,
9910 Left_Opnd => Right_Opnd (Lop),
9911 Right_Opnd => Right_Opnd (Rop))));
9912 Analyze_And_Resolve (N, Typ);
9913 return;
9915 else
9916 -- If the result is modular, perform the reduction of the result
9917 -- appropriately.
9919 if Is_Modular_Integer_Type (Typ)
9920 and then not Non_Binary_Modulus (Typ)
9921 then
9922 Rewrite (N,
9923 Make_Op_And (Loc,
9924 Left_Opnd =>
9925 Make_Op_Shift_Left (Loc,
9926 Left_Opnd => Lop,
9927 Right_Opnd =>
9928 Convert_To (Standard_Natural, Right_Opnd (Rop))),
9929 Right_Opnd =>
9930 Make_Integer_Literal (Loc, Modulus (Typ) - 1)));
9932 else
9933 Rewrite (N,
9934 Make_Op_Shift_Left (Loc,
9935 Left_Opnd => Lop,
9936 Right_Opnd =>
9937 Convert_To (Standard_Natural, Right_Opnd (Rop))));
9938 end if;
9940 Analyze_And_Resolve (N, Typ);
9941 return;
9942 end if;
9944 -- Same processing for the operands the other way round
9946 elsif Lp2 then
9947 if Is_Modular_Integer_Type (Typ)
9948 and then not Non_Binary_Modulus (Typ)
9949 then
9950 Rewrite (N,
9951 Make_Op_And (Loc,
9952 Left_Opnd =>
9953 Make_Op_Shift_Left (Loc,
9954 Left_Opnd => Rop,
9955 Right_Opnd =>
9956 Convert_To (Standard_Natural, Right_Opnd (Lop))),
9957 Right_Opnd =>
9958 Make_Integer_Literal (Loc, Modulus (Typ) - 1)));
9960 else
9961 Rewrite (N,
9962 Make_Op_Shift_Left (Loc,
9963 Left_Opnd => Rop,
9964 Right_Opnd =>
9965 Convert_To (Standard_Natural, Right_Opnd (Lop))));
9966 end if;
9968 Analyze_And_Resolve (N, Typ);
9969 return;
9970 end if;
9972 -- Try to narrow the operation
9974 if Typ = Universal_Integer then
9975 Narrow_Large_Operation (N);
9977 if Nkind (N) /= N_Op_Multiply then
9978 return;
9979 end if;
9980 end if;
9982 -- Do required fixup of universal fixed operation
9984 if Typ = Universal_Fixed then
9985 Fixup_Universal_Fixed_Operation (N);
9986 Typ := Etype (N);
9987 end if;
9989 -- Multiplications with fixed-point results
9991 if Is_Fixed_Point_Type (Typ) then
9993 -- Case of fixed * integer => fixed
9995 if Is_Integer_Type (Rtyp) then
9996 Expand_Multiply_Fixed_By_Integer_Giving_Fixed (N);
9998 -- Case of integer * fixed => fixed
10000 elsif Is_Integer_Type (Ltyp) then
10001 Expand_Multiply_Integer_By_Fixed_Giving_Fixed (N);
10003 -- Case of fixed * fixed => fixed
10005 else
10006 Expand_Multiply_Fixed_By_Fixed_Giving_Fixed (N);
10007 end if;
10009 -- Other cases of multiplication of fixed-point operands
10011 elsif Is_Fixed_Point_Type (Ltyp) or else Is_Fixed_Point_Type (Rtyp) then
10012 if Is_Integer_Type (Typ) then
10013 Expand_Multiply_Fixed_By_Fixed_Giving_Integer (N);
10014 else
10015 pragma Assert (Is_Floating_Point_Type (Typ));
10016 Expand_Multiply_Fixed_By_Fixed_Giving_Float (N);
10017 end if;
10019 -- Mixed-mode operations can appear in a non-static universal context,
10020 -- in which case the integer argument must be converted explicitly.
10022 elsif Typ = Universal_Real and then Is_Integer_Type (Rtyp) then
10023 Rewrite (Rop, Convert_To (Universal_Real, Relocate_Node (Rop)));
10024 Analyze_And_Resolve (Rop, Universal_Real);
10026 elsif Typ = Universal_Real and then Is_Integer_Type (Ltyp) then
10027 Rewrite (Lop, Convert_To (Universal_Real, Relocate_Node (Lop)));
10028 Analyze_And_Resolve (Lop, Universal_Real);
10030 -- Non-fixed point cases, check software overflow checking required
10032 elsif Is_Signed_Integer_Type (Etype (N)) then
10033 Apply_Arithmetic_Overflow_Check (N);
10034 end if;
10036 -- Overflow checks for floating-point if -gnateF mode active
10038 Check_Float_Op_Overflow (N);
10040 Expand_Nonbinary_Modular_Op (N);
10041 end Expand_N_Op_Multiply;
10043 --------------------
10044 -- Expand_N_Op_Ne --
10045 --------------------
10047 procedure Expand_N_Op_Ne (N : Node_Id) is
10048 Typ : constant Entity_Id := Etype (Left_Opnd (N));
10050 begin
10051 -- Case of elementary type with standard operator. But if unnesting,
10052 -- handle elementary types whose Equivalent_Types are records because
10053 -- there may be padding or undefined fields.
10055 if Is_Elementary_Type (Typ)
10056 and then Sloc (Entity (N)) = Standard_Location
10057 and then not (Ekind (Typ) in E_Class_Wide_Type
10058 | E_Class_Wide_Subtype
10059 | E_Access_Subprogram_Type
10060 | E_Access_Protected_Subprogram_Type
10061 | E_Anonymous_Access_Protected_Subprogram_Type
10062 | E_Exception_Type
10063 and then Present (Equivalent_Type (Typ))
10064 and then Is_Record_Type (Equivalent_Type (Typ)))
10065 then
10066 Binary_Op_Validity_Checks (N);
10068 -- Deal with overflow checks in MINIMIZED/ELIMINATED mode and if
10069 -- means we no longer have a /= operation, we are all done.
10071 if Minimized_Eliminated_Overflow_Check (Left_Opnd (N)) then
10072 Expand_Compare_Minimize_Eliminate_Overflow (N);
10073 end if;
10075 if Nkind (N) /= N_Op_Ne then
10076 return;
10077 end if;
10079 -- Boolean types (requiring handling of non-standard case)
10081 if Is_Boolean_Type (Typ) then
10082 Adjust_Condition (Left_Opnd (N));
10083 Adjust_Condition (Right_Opnd (N));
10084 Set_Etype (N, Standard_Boolean);
10085 Adjust_Result_Type (N, Typ);
10086 end if;
10088 Rewrite_Comparison (N);
10090 -- Try to narrow the operation
10092 if Typ = Universal_Integer and then Nkind (N) = N_Op_Ne then
10093 Narrow_Large_Operation (N);
10094 end if;
10096 -- For all cases other than elementary types, we rewrite node as the
10097 -- negation of an equality operation, and reanalyze. The equality to be
10098 -- used is defined in the same scope and has the same signature. This
10099 -- signature must be set explicitly since in an instance it may not have
10100 -- the same visibility as in the generic unit. This avoids duplicating
10101 -- or factoring the complex code for record/array equality tests etc.
10103 -- This case is also used for the minimal expansion performed in
10104 -- GNATprove mode.
10106 else
10107 declare
10108 Loc : constant Source_Ptr := Sloc (N);
10109 Neg : Node_Id;
10110 Ne : constant Entity_Id := Entity (N);
10112 begin
10113 Binary_Op_Validity_Checks (N);
10115 Neg :=
10116 Make_Op_Not (Loc,
10117 Right_Opnd =>
10118 Make_Op_Eq (Loc,
10119 Left_Opnd => Left_Opnd (N),
10120 Right_Opnd => Right_Opnd (N)));
10122 -- The level of parentheses is useless in GNATprove mode, and
10123 -- bumping its level here leads to wrong columns being used in
10124 -- check messages, hence skip it in this mode.
10126 if not GNATprove_Mode then
10127 Set_Paren_Count (Right_Opnd (Neg), 1);
10128 end if;
10130 if Scope (Ne) /= Standard_Standard then
10131 Set_Entity (Right_Opnd (Neg), Corresponding_Equality (Ne));
10132 end if;
10134 -- For navigation purposes, we want to treat the inequality as an
10135 -- implicit reference to the corresponding equality. Preserve the
10136 -- Comes_From_ source flag to generate proper Xref entries.
10138 Preserve_Comes_From_Source (Neg, N);
10139 Preserve_Comes_From_Source (Right_Opnd (Neg), N);
10140 Rewrite (N, Neg);
10141 Analyze_And_Resolve (N, Standard_Boolean);
10142 end;
10143 end if;
10145 -- No need for optimization in GNATprove mode, where we would rather see
10146 -- the original source expression.
10148 if not GNATprove_Mode then
10149 Optimize_Length_Comparison (N);
10150 end if;
10151 end Expand_N_Op_Ne;
10153 ---------------------
10154 -- Expand_N_Op_Not --
10155 ---------------------
10157 -- If the argument is other than a Boolean array type, there is no special
10158 -- expansion required, except for dealing with validity checks, and non-
10159 -- standard boolean representations.
10161 -- For the packed array case, we call the special routine in Exp_Pakd,
10162 -- except that if the component size is greater than one, we use the
10163 -- standard routine generating a gruesome loop (it is so peculiar to have
10164 -- packed arrays with non-standard Boolean representations anyway, so it
10165 -- does not matter that we do not handle this case efficiently).
10167 -- For the unpacked array case (and for the special packed case where we
10168 -- have non standard Booleans, as discussed above), we generate and insert
10169 -- into the tree the following function definition:
10171 -- function Nnnn (A : arr) is
10172 -- B : arr;
10173 -- begin
10174 -- for J in a'range loop
10175 -- B (J) := not A (J);
10176 -- end loop;
10177 -- return B;
10178 -- end Nnnn;
10180 -- or in the case of Transform_Function_Array:
10182 -- procedure Nnnn (A : arr; RESULT : out arr) is
10183 -- begin
10184 -- for J in a'range loop
10185 -- RESULT (J) := not A (J);
10186 -- end loop;
10187 -- end Nnnn;
10189 -- Here arr is the actual subtype of the parameter (and hence always
10190 -- constrained). Then we replace the not with a call to this subprogram.
10192 procedure Expand_N_Op_Not (N : Node_Id) is
10193 Loc : constant Source_Ptr := Sloc (N);
10194 Typ : constant Entity_Id := Etype (Right_Opnd (N));
10195 Opnd : Node_Id;
10196 Arr : Entity_Id;
10197 A : Entity_Id;
10198 B : Entity_Id;
10199 J : Entity_Id;
10200 A_J : Node_Id;
10201 B_J : Node_Id;
10203 Func_Name : Entity_Id;
10204 Loop_Statement : Node_Id;
10206 begin
10207 Unary_Op_Validity_Checks (N);
10209 -- For boolean operand, deal with non-standard booleans
10211 if Is_Boolean_Type (Typ) then
10212 Adjust_Condition (Right_Opnd (N));
10213 Set_Etype (N, Standard_Boolean);
10214 Adjust_Result_Type (N, Typ);
10215 return;
10216 end if;
10218 -- Only array types need any other processing
10220 if not Is_Array_Type (Typ) then
10221 return;
10222 end if;
10224 -- Case of array operand. If bit packed with a component size of 1,
10225 -- handle it in Exp_Pakd if the operand is known to be aligned.
10227 if Is_Bit_Packed_Array (Typ)
10228 and then Component_Size (Typ) = 1
10229 and then not Is_Possibly_Unaligned_Object (Right_Opnd (N))
10230 then
10231 Expand_Packed_Not (N);
10232 return;
10233 end if;
10235 -- Case of array operand which is not bit-packed. If the context is
10236 -- a safe assignment, call in-place operation, If context is a larger
10237 -- boolean expression in the context of a safe assignment, expansion is
10238 -- done by enclosing operation.
10240 Opnd := Relocate_Node (Right_Opnd (N));
10241 Convert_To_Actual_Subtype (Opnd);
10242 Arr := Etype (Opnd);
10243 Ensure_Defined (Arr, N);
10244 Silly_Boolean_Array_Not_Test (N, Arr);
10246 if Nkind (Parent (N)) = N_Assignment_Statement then
10247 if Safe_In_Place_Array_Op (Name (Parent (N)), N, Empty) then
10248 Build_Boolean_Array_Proc_Call (Parent (N), Opnd, Empty);
10249 return;
10251 -- Special case the negation of a binary operation
10253 elsif Nkind (Opnd) in N_Op_And | N_Op_Or | N_Op_Xor
10254 and then Safe_In_Place_Array_Op
10255 (Name (Parent (N)), Left_Opnd (Opnd), Right_Opnd (Opnd))
10256 then
10257 Build_Boolean_Array_Proc_Call (Parent (N), Opnd, Empty);
10258 return;
10259 end if;
10261 elsif Nkind (Parent (N)) in N_Binary_Op
10262 and then Nkind (Parent (Parent (N))) = N_Assignment_Statement
10263 then
10264 declare
10265 Op1 : constant Node_Id := Left_Opnd (Parent (N));
10266 Op2 : constant Node_Id := Right_Opnd (Parent (N));
10267 Lhs : constant Node_Id := Name (Parent (Parent (N)));
10269 begin
10270 if Safe_In_Place_Array_Op (Lhs, Op1, Op2) then
10272 -- (not A) op (not B) can be reduced to a single call
10274 if N = Op1 and then Nkind (Op2) = N_Op_Not then
10275 return;
10277 elsif N = Op2 and then Nkind (Op1) = N_Op_Not then
10278 return;
10280 -- A xor (not B) can also be special-cased
10282 elsif N = Op2 and then Nkind (Parent (N)) = N_Op_Xor then
10283 return;
10284 end if;
10285 end if;
10286 end;
10287 end if;
10289 A := Make_Defining_Identifier (Loc, Name_uA);
10291 if Transform_Function_Array then
10292 B := Make_Defining_Identifier (Loc, Name_UP_RESULT);
10293 else
10294 B := Make_Defining_Identifier (Loc, Name_uB);
10295 end if;
10297 J := Make_Defining_Identifier (Loc, Name_uJ);
10299 A_J :=
10300 Make_Indexed_Component (Loc,
10301 Prefix => New_Occurrence_Of (A, Loc),
10302 Expressions => New_List (New_Occurrence_Of (J, Loc)));
10304 B_J :=
10305 Make_Indexed_Component (Loc,
10306 Prefix => New_Occurrence_Of (B, Loc),
10307 Expressions => New_List (New_Occurrence_Of (J, Loc)));
10309 Loop_Statement :=
10310 Make_Implicit_Loop_Statement (N,
10311 Identifier => Empty,
10313 Iteration_Scheme =>
10314 Make_Iteration_Scheme (Loc,
10315 Loop_Parameter_Specification =>
10316 Make_Loop_Parameter_Specification (Loc,
10317 Defining_Identifier => J,
10318 Discrete_Subtype_Definition =>
10319 Make_Attribute_Reference (Loc,
10320 Prefix => Make_Identifier (Loc, Chars (A)),
10321 Attribute_Name => Name_Range))),
10323 Statements => New_List (
10324 Make_Assignment_Statement (Loc,
10325 Name => B_J,
10326 Expression => Make_Op_Not (Loc, A_J))));
10328 Func_Name := Make_Temporary (Loc, 'N');
10329 Set_Is_Inlined (Func_Name);
10331 if Transform_Function_Array then
10332 Insert_Action (N,
10333 Make_Subprogram_Body (Loc,
10334 Specification =>
10335 Make_Procedure_Specification (Loc,
10336 Defining_Unit_Name => Func_Name,
10337 Parameter_Specifications => New_List (
10338 Make_Parameter_Specification (Loc,
10339 Defining_Identifier => A,
10340 Parameter_Type => New_Occurrence_Of (Typ, Loc)),
10341 Make_Parameter_Specification (Loc,
10342 Defining_Identifier => B,
10343 Out_Present => True,
10344 Parameter_Type => New_Occurrence_Of (Typ, Loc)))),
10346 Declarations => New_List,
10348 Handled_Statement_Sequence =>
10349 Make_Handled_Sequence_Of_Statements (Loc,
10350 Statements => New_List (Loop_Statement))));
10352 declare
10353 Temp_Id : constant Entity_Id := Make_Temporary (Loc, 'T');
10354 Call : Node_Id;
10355 Decl : Node_Id;
10357 begin
10358 -- Generate:
10359 -- Temp : ...;
10361 Decl :=
10362 Make_Object_Declaration (Loc,
10363 Defining_Identifier => Temp_Id,
10364 Object_Definition => New_Occurrence_Of (Typ, Loc));
10366 -- Generate:
10367 -- Proc_Call (Opnd, Temp);
10369 Call :=
10370 Make_Procedure_Call_Statement (Loc,
10371 Name => New_Occurrence_Of (Func_Name, Loc),
10372 Parameter_Associations =>
10373 New_List (Opnd, New_Occurrence_Of (Temp_Id, Loc)));
10375 Insert_Actions (Parent (N), New_List (Decl, Call));
10376 Rewrite (N, New_Occurrence_Of (Temp_Id, Loc));
10377 end;
10378 else
10379 Insert_Action (N,
10380 Make_Subprogram_Body (Loc,
10381 Specification =>
10382 Make_Function_Specification (Loc,
10383 Defining_Unit_Name => Func_Name,
10384 Parameter_Specifications => New_List (
10385 Make_Parameter_Specification (Loc,
10386 Defining_Identifier => A,
10387 Parameter_Type => New_Occurrence_Of (Typ, Loc))),
10388 Result_Definition => New_Occurrence_Of (Typ, Loc)),
10390 Declarations => New_List (
10391 Make_Object_Declaration (Loc,
10392 Defining_Identifier => B,
10393 Object_Definition => New_Occurrence_Of (Arr, Loc))),
10395 Handled_Statement_Sequence =>
10396 Make_Handled_Sequence_Of_Statements (Loc,
10397 Statements => New_List (
10398 Loop_Statement,
10399 Make_Simple_Return_Statement (Loc,
10400 Expression => Make_Identifier (Loc, Chars (B)))))));
10402 Rewrite (N,
10403 Make_Function_Call (Loc,
10404 Name => New_Occurrence_Of (Func_Name, Loc),
10405 Parameter_Associations => New_List (Opnd)));
10406 end if;
10408 Analyze_And_Resolve (N, Typ);
10409 end Expand_N_Op_Not;
10411 --------------------
10412 -- Expand_N_Op_Or --
10413 --------------------
10415 procedure Expand_N_Op_Or (N : Node_Id) is
10416 Typ : constant Entity_Id := Etype (N);
10418 begin
10419 Binary_Op_Validity_Checks (N);
10421 if Is_Array_Type (Etype (N)) then
10422 Expand_Boolean_Operator (N);
10424 elsif Is_Boolean_Type (Etype (N)) then
10425 Adjust_Condition (Left_Opnd (N));
10426 Adjust_Condition (Right_Opnd (N));
10427 Set_Etype (N, Standard_Boolean);
10428 Adjust_Result_Type (N, Typ);
10430 elsif Is_Intrinsic_Subprogram (Entity (N)) then
10431 Expand_Intrinsic_Call (N, Entity (N));
10432 end if;
10434 Expand_Nonbinary_Modular_Op (N);
10435 end Expand_N_Op_Or;
10437 ----------------------
10438 -- Expand_N_Op_Plus --
10439 ----------------------
10441 procedure Expand_N_Op_Plus (N : Node_Id) is
10442 Typ : constant Entity_Id := Etype (N);
10444 begin
10445 Unary_Op_Validity_Checks (N);
10447 -- Check for MINIMIZED/ELIMINATED overflow mode
10449 if Minimized_Eliminated_Overflow_Check (N) then
10450 Apply_Arithmetic_Overflow_Check (N);
10451 return;
10452 end if;
10454 -- Try to narrow the operation
10456 if Typ = Universal_Integer then
10457 Narrow_Large_Operation (N);
10458 end if;
10459 end Expand_N_Op_Plus;
10461 ---------------------
10462 -- Expand_N_Op_Rem --
10463 ---------------------
10465 procedure Expand_N_Op_Rem (N : Node_Id) is
10466 Loc : constant Source_Ptr := Sloc (N);
10467 Typ : constant Entity_Id := Etype (N);
10469 Left : Node_Id;
10470 Right : Node_Id;
10472 Lo : Uint;
10473 Hi : Uint;
10474 OK : Boolean;
10476 Lneg : Boolean;
10477 Rneg : Boolean;
10478 -- Set if corresponding operand can be negative
10480 begin
10481 Binary_Op_Validity_Checks (N);
10483 -- Check for MINIMIZED/ELIMINATED overflow mode
10485 if Minimized_Eliminated_Overflow_Check (N) then
10486 Apply_Arithmetic_Overflow_Check (N);
10487 return;
10488 end if;
10490 -- Try to narrow the operation
10492 if Typ = Universal_Integer then
10493 Narrow_Large_Operation (N);
10495 if Nkind (N) /= N_Op_Rem then
10496 return;
10497 end if;
10498 end if;
10500 if Is_Integer_Type (Etype (N)) then
10501 Apply_Divide_Checks (N);
10503 -- All done if we don't have a REM any more, which can happen as a
10504 -- result of overflow expansion in MINIMIZED or ELIMINATED modes.
10506 if Nkind (N) /= N_Op_Rem then
10507 return;
10508 end if;
10509 end if;
10511 -- Proceed with expansion of REM
10513 Left := Left_Opnd (N);
10514 Right := Right_Opnd (N);
10516 -- Apply optimization x rem 1 = 0. We don't really need that with gcc,
10517 -- but it is useful with other back ends, and is certainly harmless.
10519 if Is_Integer_Type (Etype (N))
10520 and then Compile_Time_Known_Value (Right)
10521 and then Expr_Value (Right) = Uint_1
10522 then
10523 -- Call Remove_Side_Effects to ensure that any side effects in the
10524 -- ignored left operand (in particular function calls to user defined
10525 -- functions) are properly executed.
10527 Remove_Side_Effects (Left);
10529 Rewrite (N, Make_Integer_Literal (Loc, 0));
10530 Analyze_And_Resolve (N, Typ);
10531 return;
10532 end if;
10534 -- Deal with annoying case of largest negative number remainder minus
10535 -- one. Gigi may not handle this case correctly, because on some
10536 -- targets, the mod value is computed using a divide instruction
10537 -- which gives an overflow trap for this case.
10539 -- It would be a bit more efficient to figure out which targets this
10540 -- is really needed for, but in practice it is reasonable to do the
10541 -- following special check in all cases, since it means we get a clearer
10542 -- message, and also the overhead is minimal given that division is
10543 -- expensive in any case.
10545 -- In fact the check is quite easy, if the right operand is -1, then
10546 -- the remainder is always 0, and we can just ignore the left operand
10547 -- completely in this case.
10549 Determine_Range (Right, OK, Lo, Hi, Assume_Valid => True);
10550 Lneg := not OK or else Lo < 0;
10552 Determine_Range (Left, OK, Lo, Hi, Assume_Valid => True);
10553 Rneg := not OK or else Lo < 0;
10555 -- We won't mess with trying to find out if the left operand can really
10556 -- be the largest negative number (that's a pain in the case of private
10557 -- types and this is really marginal). We will just assume that we need
10558 -- the test if the left operand can be negative at all.
10560 if (Lneg and Rneg)
10561 and then not CodePeer_Mode
10562 then
10563 Rewrite (N,
10564 Make_If_Expression (Loc,
10565 Expressions => New_List (
10566 Make_Op_Eq (Loc,
10567 Left_Opnd => Duplicate_Subexpr (Right),
10568 Right_Opnd =>
10569 Unchecked_Convert_To (Typ, Make_Integer_Literal (Loc, -1))),
10571 Unchecked_Convert_To (Typ,
10572 Make_Integer_Literal (Loc, Uint_0)),
10574 Relocate_Node (N))));
10576 Set_Analyzed (Next (Next (First (Expressions (N)))));
10577 Analyze_And_Resolve (N, Typ);
10578 end if;
10579 end Expand_N_Op_Rem;
10581 -----------------------------
10582 -- Expand_N_Op_Rotate_Left --
10583 -----------------------------
10585 procedure Expand_N_Op_Rotate_Left (N : Node_Id) is
10586 begin
10587 Binary_Op_Validity_Checks (N);
10589 -- If we are in Modify_Tree_For_C mode, there is no rotate left in C,
10590 -- so we rewrite in terms of logical shifts
10592 -- Shift_Left (Num, Bits) or Shift_Right (num, Esize - Bits)
10594 -- where Bits is the shift count mod Esize (the mod operation here
10595 -- deals with ludicrous large shift counts, which are apparently OK).
10597 if Modify_Tree_For_C then
10598 declare
10599 Loc : constant Source_Ptr := Sloc (N);
10600 Rtp : constant Entity_Id := Etype (Right_Opnd (N));
10601 Typ : constant Entity_Id := Etype (N);
10603 begin
10604 -- Sem_Intr should prevent getting there with a non binary modulus
10606 pragma Assert (not Non_Binary_Modulus (Typ));
10608 Rewrite (Right_Opnd (N),
10609 Make_Op_Rem (Loc,
10610 Left_Opnd => Relocate_Node (Right_Opnd (N)),
10611 Right_Opnd => Make_Integer_Literal (Loc, Esize (Typ))));
10613 Analyze_And_Resolve (Right_Opnd (N), Rtp);
10615 Rewrite (N,
10616 Make_Op_Or (Loc,
10617 Left_Opnd =>
10618 Make_Op_Shift_Left (Loc,
10619 Left_Opnd => Left_Opnd (N),
10620 Right_Opnd => Right_Opnd (N)),
10622 Right_Opnd =>
10623 Make_Op_Shift_Right (Loc,
10624 Left_Opnd => Duplicate_Subexpr_No_Checks (Left_Opnd (N)),
10625 Right_Opnd =>
10626 Make_Op_Subtract (Loc,
10627 Left_Opnd => Make_Integer_Literal (Loc, Esize (Typ)),
10628 Right_Opnd =>
10629 Duplicate_Subexpr_No_Checks (Right_Opnd (N))))));
10631 Analyze_And_Resolve (N, Typ);
10632 end;
10633 end if;
10634 end Expand_N_Op_Rotate_Left;
10636 ------------------------------
10637 -- Expand_N_Op_Rotate_Right --
10638 ------------------------------
10640 procedure Expand_N_Op_Rotate_Right (N : Node_Id) is
10641 begin
10642 Binary_Op_Validity_Checks (N);
10644 -- If we are in Modify_Tree_For_C mode, there is no rotate right in C,
10645 -- so we rewrite in terms of logical shifts
10647 -- Shift_Right (Num, Bits) or Shift_Left (num, Esize - Bits)
10649 -- where Bits is the shift count mod Esize (the mod operation here
10650 -- deals with ludicrous large shift counts, which are apparently OK).
10652 if Modify_Tree_For_C then
10653 declare
10654 Loc : constant Source_Ptr := Sloc (N);
10655 Rtp : constant Entity_Id := Etype (Right_Opnd (N));
10656 Typ : constant Entity_Id := Etype (N);
10658 begin
10659 -- Sem_Intr should prevent getting there with a non binary modulus
10661 pragma Assert (not Non_Binary_Modulus (Typ));
10663 Rewrite (Right_Opnd (N),
10664 Make_Op_Rem (Loc,
10665 Left_Opnd => Relocate_Node (Right_Opnd (N)),
10666 Right_Opnd => Make_Integer_Literal (Loc, Esize (Typ))));
10668 Analyze_And_Resolve (Right_Opnd (N), Rtp);
10670 Rewrite (N,
10671 Make_Op_Or (Loc,
10672 Left_Opnd =>
10673 Make_Op_Shift_Right (Loc,
10674 Left_Opnd => Left_Opnd (N),
10675 Right_Opnd => Right_Opnd (N)),
10677 Right_Opnd =>
10678 Make_Op_Shift_Left (Loc,
10679 Left_Opnd => Duplicate_Subexpr_No_Checks (Left_Opnd (N)),
10680 Right_Opnd =>
10681 Make_Op_Subtract (Loc,
10682 Left_Opnd => Make_Integer_Literal (Loc, Esize (Typ)),
10683 Right_Opnd =>
10684 Duplicate_Subexpr_No_Checks (Right_Opnd (N))))));
10686 Analyze_And_Resolve (N, Typ);
10687 end;
10688 end if;
10689 end Expand_N_Op_Rotate_Right;
10691 ----------------------------
10692 -- Expand_N_Op_Shift_Left --
10693 ----------------------------
10695 -- Note: nothing in this routine depends on left as opposed to right shifts
10696 -- so we share the routine for expanding shift right operations.
10698 procedure Expand_N_Op_Shift_Left (N : Node_Id) is
10699 begin
10700 Binary_Op_Validity_Checks (N);
10702 -- If we are in Modify_Tree_For_C mode, then ensure that the right
10703 -- operand is not greater than the word size (since that would not
10704 -- be defined properly by the corresponding C shift operator).
10706 if Modify_Tree_For_C then
10707 declare
10708 Right : constant Node_Id := Right_Opnd (N);
10709 Loc : constant Source_Ptr := Sloc (Right);
10710 Typ : constant Entity_Id := Etype (N);
10711 Siz : constant Uint := Esize (Typ);
10712 Orig : Node_Id;
10713 OK : Boolean;
10714 Lo : Uint;
10715 Hi : Uint;
10717 begin
10718 -- Sem_Intr should prevent getting there with a non binary modulus
10720 pragma Assert (not Non_Binary_Modulus (Typ));
10722 if Compile_Time_Known_Value (Right) then
10723 if Expr_Value (Right) >= Siz then
10724 Rewrite (N, Make_Integer_Literal (Loc, 0));
10725 Analyze_And_Resolve (N, Typ);
10726 end if;
10728 -- Not compile time known, find range
10730 else
10731 Determine_Range (Right, OK, Lo, Hi, Assume_Valid => True);
10733 -- Nothing to do if known to be OK range, otherwise expand
10735 if not OK or else Hi >= Siz then
10737 -- Prevent recursion on copy of shift node
10739 Orig := Relocate_Node (N);
10740 Set_Analyzed (Orig);
10742 -- Now do the rewrite
10744 Rewrite (N,
10745 Make_If_Expression (Loc,
10746 Expressions => New_List (
10747 Make_Op_Ge (Loc,
10748 Left_Opnd => Duplicate_Subexpr_Move_Checks (Right),
10749 Right_Opnd => Make_Integer_Literal (Loc, Siz)),
10750 Make_Integer_Literal (Loc, 0),
10751 Orig)));
10752 Analyze_And_Resolve (N, Typ);
10753 end if;
10754 end if;
10755 end;
10756 end if;
10757 end Expand_N_Op_Shift_Left;
10759 -----------------------------
10760 -- Expand_N_Op_Shift_Right --
10761 -----------------------------
10763 procedure Expand_N_Op_Shift_Right (N : Node_Id) is
10764 begin
10765 -- Share shift left circuit
10767 Expand_N_Op_Shift_Left (N);
10768 end Expand_N_Op_Shift_Right;
10770 ----------------------------------------
10771 -- Expand_N_Op_Shift_Right_Arithmetic --
10772 ----------------------------------------
10774 procedure Expand_N_Op_Shift_Right_Arithmetic (N : Node_Id) is
10775 begin
10776 Binary_Op_Validity_Checks (N);
10778 -- If we are in Modify_Tree_For_C mode, there is no shift right
10779 -- arithmetic in C, so we rewrite in terms of logical shifts for
10780 -- modular integers, and keep the Shift_Right intrinsic for signed
10781 -- integers: even though doing a shift on a signed integer is not
10782 -- fully guaranteed by the C standard, this is what C compilers
10783 -- implement in practice.
10784 -- Consider also taking advantage of this for modular integers by first
10785 -- performing an unchecked conversion of the modular integer to a signed
10786 -- integer of the same sign, and then convert back.
10788 -- Shift_Right (Num, Bits) or
10789 -- (if Num >= Sign
10790 -- then not (Shift_Right (Mask, bits))
10791 -- else 0)
10793 -- Here Mask is all 1 bits (2**size - 1), and Sign is 2**(size - 1)
10795 -- Note: the above works fine for shift counts greater than or equal
10796 -- to the word size, since in this case (not (Shift_Right (Mask, bits)))
10797 -- generates all 1'bits.
10799 if Modify_Tree_For_C and then Is_Modular_Integer_Type (Etype (N)) then
10800 declare
10801 Loc : constant Source_Ptr := Sloc (N);
10802 Typ : constant Entity_Id := Etype (N);
10803 Sign : constant Uint := 2 ** (Esize (Typ) - 1);
10804 Mask : constant Uint := (2 ** Esize (Typ)) - 1;
10805 Left : constant Node_Id := Left_Opnd (N);
10806 Right : constant Node_Id := Right_Opnd (N);
10807 Maskx : Node_Id;
10809 begin
10810 -- Sem_Intr should prevent getting there with a non binary modulus
10812 pragma Assert (not Non_Binary_Modulus (Typ));
10814 -- Here if not (Shift_Right (Mask, bits)) can be computed at
10815 -- compile time as a single constant.
10817 if Compile_Time_Known_Value (Right) then
10818 declare
10819 Val : constant Uint := Expr_Value (Right);
10821 begin
10822 if Val >= Esize (Typ) then
10823 Maskx := Make_Integer_Literal (Loc, Mask);
10825 else
10826 Maskx :=
10827 Make_Integer_Literal (Loc,
10828 Intval => Mask - (Mask / (2 ** Expr_Value (Right))));
10829 end if;
10830 end;
10832 else
10833 Maskx :=
10834 Make_Op_Not (Loc,
10835 Right_Opnd =>
10836 Make_Op_Shift_Right (Loc,
10837 Left_Opnd => Make_Integer_Literal (Loc, Mask),
10838 Right_Opnd => Duplicate_Subexpr_No_Checks (Right)));
10839 end if;
10841 -- Now do the rewrite
10843 Rewrite (N,
10844 Make_Op_Or (Loc,
10845 Left_Opnd =>
10846 Make_Op_Shift_Right (Loc,
10847 Left_Opnd => Left,
10848 Right_Opnd => Right),
10849 Right_Opnd =>
10850 Make_If_Expression (Loc,
10851 Expressions => New_List (
10852 Make_Op_Ge (Loc,
10853 Left_Opnd => Duplicate_Subexpr_No_Checks (Left),
10854 Right_Opnd => Make_Integer_Literal (Loc, Sign)),
10855 Maskx,
10856 Make_Integer_Literal (Loc, 0)))));
10857 Analyze_And_Resolve (N, Typ);
10858 end;
10859 end if;
10860 end Expand_N_Op_Shift_Right_Arithmetic;
10862 --------------------------
10863 -- Expand_N_Op_Subtract --
10864 --------------------------
10866 procedure Expand_N_Op_Subtract (N : Node_Id) is
10867 Typ : constant Entity_Id := Etype (N);
10869 begin
10870 Binary_Op_Validity_Checks (N);
10872 -- Check for MINIMIZED/ELIMINATED overflow mode
10874 if Minimized_Eliminated_Overflow_Check (N) then
10875 Apply_Arithmetic_Overflow_Check (N);
10876 return;
10877 end if;
10879 -- Try to narrow the operation
10881 if Typ = Universal_Integer then
10882 Narrow_Large_Operation (N);
10884 if Nkind (N) /= N_Op_Subtract then
10885 return;
10886 end if;
10887 end if;
10889 -- N - 0 = N for integer types
10891 if Is_Integer_Type (Typ)
10892 and then Compile_Time_Known_Value (Right_Opnd (N))
10893 and then Expr_Value (Right_Opnd (N)) = 0
10894 then
10895 Rewrite (N, Left_Opnd (N));
10896 return;
10897 end if;
10899 -- Arithmetic overflow checks for signed integer/fixed point types
10901 if Is_Signed_Integer_Type (Typ) or else Is_Fixed_Point_Type (Typ) then
10902 Apply_Arithmetic_Overflow_Check (N);
10903 end if;
10905 -- Overflow checks for floating-point if -gnateF mode active
10907 Check_Float_Op_Overflow (N);
10909 Expand_Nonbinary_Modular_Op (N);
10910 end Expand_N_Op_Subtract;
10912 ---------------------
10913 -- Expand_N_Op_Xor --
10914 ---------------------
10916 procedure Expand_N_Op_Xor (N : Node_Id) is
10917 Typ : constant Entity_Id := Etype (N);
10919 begin
10920 Binary_Op_Validity_Checks (N);
10922 if Is_Array_Type (Etype (N)) then
10923 Expand_Boolean_Operator (N);
10925 elsif Is_Boolean_Type (Etype (N)) then
10926 Adjust_Condition (Left_Opnd (N));
10927 Adjust_Condition (Right_Opnd (N));
10928 Set_Etype (N, Standard_Boolean);
10929 Adjust_Result_Type (N, Typ);
10931 elsif Is_Intrinsic_Subprogram (Entity (N)) then
10932 Expand_Intrinsic_Call (N, Entity (N));
10933 end if;
10935 Expand_Nonbinary_Modular_Op (N);
10936 end Expand_N_Op_Xor;
10938 ----------------------
10939 -- Expand_N_Or_Else --
10940 ----------------------
10942 procedure Expand_N_Or_Else (N : Node_Id)
10943 renames Expand_Short_Circuit_Operator;
10945 -----------------------------------
10946 -- Expand_N_Qualified_Expression --
10947 -----------------------------------
10949 procedure Expand_N_Qualified_Expression (N : Node_Id) is
10950 Operand : constant Node_Id := Expression (N);
10951 Target_Type : constant Entity_Id := Entity (Subtype_Mark (N));
10953 begin
10954 -- Do validity check if validity checking operands
10956 if Validity_Checks_On and Validity_Check_Operands then
10957 Ensure_Valid (Operand);
10958 end if;
10960 Freeze_Before (Operand, Target_Type);
10962 -- Apply possible constraint check
10964 Apply_Constraint_Check (Operand, Target_Type, No_Sliding => True);
10966 -- Apply possible predicate check
10968 Apply_Predicate_Check (Operand, Target_Type);
10970 if Do_Range_Check (Operand) then
10971 Generate_Range_Check (Operand, Target_Type, CE_Range_Check_Failed);
10972 end if;
10973 end Expand_N_Qualified_Expression;
10975 ------------------------------------
10976 -- Expand_N_Quantified_Expression --
10977 ------------------------------------
10979 -- We expand:
10981 -- for all X in range => Cond
10983 -- into:
10985 -- T := True;
10986 -- for X in range loop
10987 -- if not Cond then
10988 -- T := False;
10989 -- exit;
10990 -- end if;
10991 -- end loop;
10993 -- Similarly, an existentially quantified expression:
10995 -- for some X in range => Cond
10997 -- becomes:
10999 -- T := False;
11000 -- for X in range loop
11001 -- if Cond then
11002 -- T := True;
11003 -- exit;
11004 -- end if;
11005 -- end loop;
11007 -- In both cases, the iteration may be over a container in which case it is
11008 -- given by an iterator specification, not a loop parameter specification.
11010 procedure Expand_N_Quantified_Expression (N : Node_Id) is
11011 Actions : constant List_Id := New_List;
11012 For_All : constant Boolean := All_Present (N);
11013 Iter_Spec : constant Node_Id := Iterator_Specification (N);
11014 Loc : constant Source_Ptr := Sloc (N);
11015 Loop_Spec : constant Node_Id := Loop_Parameter_Specification (N);
11016 Cond : Node_Id;
11017 Flag : Entity_Id;
11018 Scheme : Node_Id;
11019 Stmts : List_Id;
11020 Var : Entity_Id;
11022 begin
11023 -- Ensure that the bound variable as well as the type of Name of the
11024 -- Iter_Spec if present are properly frozen. We must do this before
11025 -- expansion because the expression is about to be converted into a
11026 -- loop, and resulting freeze nodes may end up in the wrong place in the
11027 -- tree.
11029 if Present (Iter_Spec) then
11030 Var := Defining_Identifier (Iter_Spec);
11031 else
11032 Var := Defining_Identifier (Loop_Spec);
11033 end if;
11035 declare
11036 P : Node_Id := Parent (N);
11037 begin
11038 while Nkind (P) in N_Subexpr loop
11039 P := Parent (P);
11040 end loop;
11042 if Present (Iter_Spec) then
11043 Freeze_Before (P, Etype (Name (Iter_Spec)));
11044 end if;
11046 Freeze_Before (P, Etype (Var));
11047 end;
11049 -- Create the declaration of the flag which tracks the status of the
11050 -- quantified expression. Generate:
11052 -- Flag : Boolean := (True | False);
11054 Flag := Make_Temporary (Loc, 'T', N);
11056 Append_To (Actions,
11057 Make_Object_Declaration (Loc,
11058 Defining_Identifier => Flag,
11059 Object_Definition => New_Occurrence_Of (Standard_Boolean, Loc),
11060 Expression =>
11061 New_Occurrence_Of (Boolean_Literals (For_All), Loc)));
11063 -- Construct the circuitry which tracks the status of the quantified
11064 -- expression. Generate:
11066 -- if [not] Cond then
11067 -- Flag := (False | True);
11068 -- exit;
11069 -- end if;
11071 Cond := Relocate_Node (Condition (N));
11073 if For_All then
11074 Cond := Make_Op_Not (Loc, Cond);
11075 end if;
11077 Stmts := New_List (
11078 Make_Implicit_If_Statement (N,
11079 Condition => Cond,
11080 Then_Statements => New_List (
11081 Make_Assignment_Statement (Loc,
11082 Name => New_Occurrence_Of (Flag, Loc),
11083 Expression =>
11084 New_Occurrence_Of (Boolean_Literals (not For_All), Loc)),
11085 Make_Exit_Statement (Loc))));
11087 -- Build the loop equivalent of the quantified expression
11089 if Present (Iter_Spec) then
11090 Scheme :=
11091 Make_Iteration_Scheme (Loc,
11092 Iterator_Specification => Iter_Spec);
11093 else
11094 Scheme :=
11095 Make_Iteration_Scheme (Loc,
11096 Loop_Parameter_Specification => Loop_Spec);
11097 end if;
11099 Append_To (Actions,
11100 Make_Loop_Statement (Loc,
11101 Iteration_Scheme => Scheme,
11102 Statements => Stmts,
11103 End_Label => Empty));
11105 -- Transform the quantified expression
11107 Rewrite (N,
11108 Make_Expression_With_Actions (Loc,
11109 Expression => New_Occurrence_Of (Flag, Loc),
11110 Actions => Actions));
11111 Analyze_And_Resolve (N, Standard_Boolean);
11112 end Expand_N_Quantified_Expression;
11114 ---------------------------------
11115 -- Expand_N_Selected_Component --
11116 ---------------------------------
11118 procedure Expand_N_Selected_Component (N : Node_Id) is
11119 Loc : constant Source_Ptr := Sloc (N);
11120 Par : constant Node_Id := Parent (N);
11121 P : constant Node_Id := Prefix (N);
11122 S : constant Node_Id := Selector_Name (N);
11123 Ptyp : constant Entity_Id := Underlying_Type (Etype (P));
11124 Disc : Entity_Id;
11125 New_N : Node_Id;
11126 Dcon : Elmt_Id;
11127 Dval : Node_Id;
11129 function In_Left_Hand_Side (Comp : Node_Id) return Boolean;
11130 -- Gigi needs a temporary for prefixes that depend on a discriminant,
11131 -- unless the context of an assignment can provide size information.
11132 -- Don't we have a general routine that does this???
11134 function Is_Subtype_Declaration return Boolean;
11135 -- The replacement of a discriminant reference by its value is required
11136 -- if this is part of the initialization of an temporary generated by a
11137 -- change of representation. This shows up as the construction of a
11138 -- discriminant constraint for a subtype declared at the same point as
11139 -- the entity in the prefix of the selected component. We recognize this
11140 -- case when the context of the reference is:
11141 -- subtype ST is T(Obj.D);
11142 -- where the entity for Obj comes from source, and ST has the same sloc.
11144 -----------------------
11145 -- In_Left_Hand_Side --
11146 -----------------------
11148 function In_Left_Hand_Side (Comp : Node_Id) return Boolean is
11149 begin
11150 return (Nkind (Parent (Comp)) = N_Assignment_Statement
11151 and then Comp = Name (Parent (Comp)))
11152 or else (Present (Parent (Comp))
11153 and then Nkind (Parent (Comp)) in N_Subexpr
11154 and then In_Left_Hand_Side (Parent (Comp)));
11155 end In_Left_Hand_Side;
11157 -----------------------------
11158 -- Is_Subtype_Declaration --
11159 -----------------------------
11161 function Is_Subtype_Declaration return Boolean is
11162 Par : constant Node_Id := Parent (N);
11163 begin
11164 return
11165 Nkind (Par) = N_Index_Or_Discriminant_Constraint
11166 and then Nkind (Parent (Parent (Par))) = N_Subtype_Declaration
11167 and then Comes_From_Source (Entity (Prefix (N)))
11168 and then Sloc (Par) = Sloc (Entity (Prefix (N)));
11169 end Is_Subtype_Declaration;
11171 -- Start of processing for Expand_N_Selected_Component
11173 begin
11174 -- Deal with discriminant check required
11176 if Do_Discriminant_Check (N) then
11177 if Present (Discriminant_Checking_Func
11178 (Original_Record_Component (Entity (S))))
11179 then
11180 -- Present the discriminant checking function to the backend, so
11181 -- that it can inline the call to the function.
11183 Add_Inlined_Body
11184 (Discriminant_Checking_Func
11185 (Original_Record_Component (Entity (S))),
11188 -- Now reset the flag and generate the call
11190 Set_Do_Discriminant_Check (N, False);
11191 Generate_Discriminant_Check (N);
11193 -- In the case of Unchecked_Union, no discriminant checking is
11194 -- actually performed.
11196 else
11197 if not Is_Unchecked_Union
11198 (Implementation_Base_Type (Etype (Prefix (N))))
11199 and then not Is_Predefined_Unit (Get_Source_Unit (N))
11200 then
11201 Error_Msg_N
11202 ("sorry - unable to generate discriminant check for" &
11203 " reference to variant component &",
11204 Selector_Name (N));
11205 end if;
11207 Set_Do_Discriminant_Check (N, False);
11208 end if;
11209 end if;
11211 -- Ada 2005 (AI-318-02): If the prefix is a call to a build-in-place
11212 -- function, then additional actuals must be passed.
11214 if Is_Build_In_Place_Function_Call (P) then
11215 Make_Build_In_Place_Call_In_Anonymous_Context (P);
11217 -- Ada 2005 (AI-318-02): Specialization of the previous case for prefix
11218 -- containing build-in-place function calls whose returned object covers
11219 -- interface types.
11221 elsif Present (Unqual_BIP_Iface_Function_Call (P)) then
11222 Make_Build_In_Place_Iface_Call_In_Anonymous_Context (P);
11223 end if;
11225 -- Gigi cannot handle unchecked conversions that are the prefix of a
11226 -- selected component with discriminants. This must be checked during
11227 -- expansion, because during analysis the type of the selector is not
11228 -- known at the point the prefix is analyzed. If the conversion is the
11229 -- target of an assignment, then we cannot force the evaluation.
11231 if Nkind (Prefix (N)) = N_Unchecked_Type_Conversion
11232 and then Has_Discriminants (Etype (N))
11233 and then not In_Left_Hand_Side (N)
11234 then
11235 Force_Evaluation (Prefix (N));
11236 end if;
11238 -- Remaining processing applies only if selector is a discriminant
11240 if Ekind (Entity (Selector_Name (N))) = E_Discriminant then
11242 -- If the selector is a discriminant of a constrained record type,
11243 -- we may be able to rewrite the expression with the actual value
11244 -- of the discriminant, a useful optimization in some cases.
11246 if Is_Record_Type (Ptyp)
11247 and then Has_Discriminants (Ptyp)
11248 and then Is_Constrained (Ptyp)
11249 then
11250 -- Do this optimization for discrete types only, and not for
11251 -- access types (access discriminants get us into trouble).
11253 if not Is_Discrete_Type (Etype (N)) then
11254 null;
11256 -- Don't do this on the left-hand side of an assignment statement.
11257 -- Normally one would think that references like this would not
11258 -- occur, but they do in generated code, and mean that we really
11259 -- do want to assign the discriminant.
11261 elsif Nkind (Par) = N_Assignment_Statement
11262 and then Name (Par) = N
11263 then
11264 null;
11266 -- Don't do this optimization for the prefix of an attribute or
11267 -- the name of an object renaming declaration since these are
11268 -- contexts where we do not want the value anyway.
11270 elsif (Nkind (Par) = N_Attribute_Reference
11271 and then Prefix (Par) = N)
11272 or else Is_Renamed_Object (N)
11273 then
11274 null;
11276 -- Don't do this optimization if we are within the code for a
11277 -- discriminant check, since the whole point of such a check may
11278 -- be to verify the condition on which the code below depends.
11280 elsif Is_In_Discriminant_Check (N) then
11281 null;
11283 -- Green light to see if we can do the optimization. There is
11284 -- still one condition that inhibits the optimization below but
11285 -- now is the time to check the particular discriminant.
11287 else
11288 -- Loop through discriminants to find the matching discriminant
11289 -- constraint to see if we can copy it.
11291 Disc := First_Discriminant (Ptyp);
11292 Dcon := First_Elmt (Discriminant_Constraint (Ptyp));
11293 Discr_Loop : while Present (Dcon) loop
11294 Dval := Node (Dcon);
11296 -- Check if this is the matching discriminant and if the
11297 -- discriminant value is simple enough to make sense to
11298 -- copy. We don't want to copy complex expressions, and
11299 -- indeed to do so can cause trouble (before we put in
11300 -- this guard, a discriminant expression containing an
11301 -- AND THEN was copied, causing problems for coverage
11302 -- analysis tools).
11304 -- However, if the reference is part of the initialization
11305 -- code generated for an object declaration, we must use
11306 -- the discriminant value from the subtype constraint,
11307 -- because the selected component may be a reference to the
11308 -- object being initialized, whose discriminant is not yet
11309 -- set. This only happens in complex cases involving changes
11310 -- of representation.
11312 if Disc = Entity (Selector_Name (N))
11313 and then (Is_Entity_Name (Dval)
11314 or else Compile_Time_Known_Value (Dval)
11315 or else Is_Subtype_Declaration)
11316 then
11317 -- Here we have the matching discriminant. Check for
11318 -- the case of a discriminant of a component that is
11319 -- constrained by an outer discriminant, which cannot
11320 -- be optimized away.
11322 if Denotes_Discriminant (Dval, Check_Concurrent => True)
11323 then
11324 exit Discr_Loop;
11326 -- Do not retrieve value if constraint is not static. It
11327 -- is generally not useful, and the constraint may be a
11328 -- rewritten outer discriminant in which case it is in
11329 -- fact incorrect.
11331 elsif Is_Entity_Name (Dval)
11332 and then
11333 Nkind (Parent (Entity (Dval))) = N_Object_Declaration
11334 and then Present (Expression (Parent (Entity (Dval))))
11335 and then not
11336 Is_OK_Static_Expression
11337 (Expression (Parent (Entity (Dval))))
11338 then
11339 exit Discr_Loop;
11341 -- In the context of a case statement, the expression may
11342 -- have the base type of the discriminant, and we need to
11343 -- preserve the constraint to avoid spurious errors on
11344 -- missing cases.
11346 elsif Nkind (Parent (N)) = N_Case_Statement
11347 and then Etype (Dval) /= Etype (Disc)
11348 then
11349 Rewrite (N,
11350 Make_Qualified_Expression (Loc,
11351 Subtype_Mark =>
11352 New_Occurrence_Of (Etype (Disc), Loc),
11353 Expression =>
11354 New_Copy_Tree (Dval)));
11355 Analyze_And_Resolve (N, Etype (Disc));
11357 -- In case that comes out as a static expression,
11358 -- reset it (a selected component is never static).
11360 Set_Is_Static_Expression (N, False);
11361 return;
11363 -- Otherwise we can just copy the constraint, but the
11364 -- result is certainly not static. In some cases the
11365 -- discriminant constraint has been analyzed in the
11366 -- context of the original subtype indication, but for
11367 -- itypes the constraint might not have been analyzed
11368 -- yet, and this must be done now.
11370 else
11371 Rewrite (N, New_Copy_Tree (Dval));
11372 Analyze_And_Resolve (N);
11373 Set_Is_Static_Expression (N, False);
11374 return;
11375 end if;
11376 end if;
11378 Next_Elmt (Dcon);
11379 Next_Discriminant (Disc);
11380 end loop Discr_Loop;
11382 -- Note: the above loop should always find a matching
11383 -- discriminant, but if it does not, we just missed an
11384 -- optimization due to some glitch (perhaps a previous
11385 -- error), so ignore.
11387 end if;
11388 end if;
11390 -- The only remaining processing is in the case of a discriminant of
11391 -- a concurrent object, where we rewrite the prefix to denote the
11392 -- corresponding record type. If the type is derived and has renamed
11393 -- discriminants, use corresponding discriminant, which is the one
11394 -- that appears in the corresponding record.
11396 if not Is_Concurrent_Type (Ptyp) then
11397 return;
11398 end if;
11400 Disc := Entity (Selector_Name (N));
11402 if Is_Derived_Type (Ptyp)
11403 and then Present (Corresponding_Discriminant (Disc))
11404 then
11405 Disc := Corresponding_Discriminant (Disc);
11406 end if;
11408 New_N :=
11409 Make_Selected_Component (Loc,
11410 Prefix =>
11411 Unchecked_Convert_To (Corresponding_Record_Type (Ptyp),
11412 New_Copy_Tree (P)),
11413 Selector_Name => Make_Identifier (Loc, Chars (Disc)));
11415 Rewrite (N, New_N);
11416 Analyze (N);
11417 end if;
11419 -- Set Atomic_Sync_Required if necessary for atomic component
11421 if Nkind (N) = N_Selected_Component then
11422 declare
11423 E : constant Entity_Id := Entity (Selector_Name (N));
11424 Set : Boolean;
11426 begin
11427 -- If component is atomic, but type is not, setting depends on
11428 -- disable/enable state for the component.
11430 if Is_Atomic (E) and then not Is_Atomic (Etype (E)) then
11431 Set := not Atomic_Synchronization_Disabled (E);
11433 -- If component is not atomic, but its type is atomic, setting
11434 -- depends on disable/enable state for the type.
11436 elsif not Is_Atomic (E) and then Is_Atomic (Etype (E)) then
11437 Set := not Atomic_Synchronization_Disabled (Etype (E));
11439 -- If both component and type are atomic, we disable if either
11440 -- component or its type have sync disabled.
11442 elsif Is_Atomic (E) and then Is_Atomic (Etype (E)) then
11443 Set := not Atomic_Synchronization_Disabled (E)
11444 and then
11445 not Atomic_Synchronization_Disabled (Etype (E));
11447 else
11448 Set := False;
11449 end if;
11451 -- Set flag if required
11453 if Set then
11454 Activate_Atomic_Synchronization (N);
11455 end if;
11456 end;
11457 end if;
11458 end Expand_N_Selected_Component;
11460 --------------------
11461 -- Expand_N_Slice --
11462 --------------------
11464 procedure Expand_N_Slice (N : Node_Id) is
11465 Loc : constant Source_Ptr := Sloc (N);
11466 Typ : constant Entity_Id := Etype (N);
11468 function Is_Procedure_Actual (N : Node_Id) return Boolean;
11469 -- Check whether the argument is an actual for a procedure call, in
11470 -- which case the expansion of a bit-packed slice is deferred until the
11471 -- call itself is expanded. The reason this is required is that we might
11472 -- have an IN OUT or OUT parameter, and the copy out is essential, and
11473 -- that copy out would be missed if we created a temporary here in
11474 -- Expand_N_Slice. Note that we don't bother to test specifically for an
11475 -- IN OUT or OUT mode parameter, since it is a bit tricky to do, and it
11476 -- is harmless to defer expansion in the IN case, since the call
11477 -- processing will still generate the appropriate copy in operation,
11478 -- which will take care of the slice.
11480 procedure Make_Temporary_For_Slice;
11481 -- Create a named variable for the value of the slice, in cases where
11482 -- the back end cannot handle it properly, e.g. when packed types or
11483 -- unaligned slices are involved.
11485 -------------------------
11486 -- Is_Procedure_Actual --
11487 -------------------------
11489 function Is_Procedure_Actual (N : Node_Id) return Boolean is
11490 Par : Node_Id := Parent (N);
11492 begin
11493 loop
11494 -- If our parent is a procedure call we can return
11496 if Nkind (Par) = N_Procedure_Call_Statement then
11497 return True;
11499 -- If our parent is a type conversion, keep climbing the tree,
11500 -- since a type conversion can be a procedure actual. Also keep
11501 -- climbing if parameter association or a qualified expression,
11502 -- since these are additional cases that do can appear on
11503 -- procedure actuals.
11505 elsif Nkind (Par) in N_Type_Conversion
11506 | N_Parameter_Association
11507 | N_Qualified_Expression
11508 then
11509 Par := Parent (Par);
11511 -- Any other case is not what we are looking for
11513 else
11514 return False;
11515 end if;
11516 end loop;
11517 end Is_Procedure_Actual;
11519 ------------------------------
11520 -- Make_Temporary_For_Slice --
11521 ------------------------------
11523 procedure Make_Temporary_For_Slice is
11524 Ent : constant Entity_Id := Make_Temporary (Loc, 'T', N);
11525 Decl : Node_Id;
11527 begin
11528 Decl :=
11529 Make_Object_Declaration (Loc,
11530 Defining_Identifier => Ent,
11531 Object_Definition => New_Occurrence_Of (Typ, Loc));
11533 Set_No_Initialization (Decl);
11535 Insert_Actions (N, New_List (
11536 Decl,
11537 Make_Assignment_Statement (Loc,
11538 Name => New_Occurrence_Of (Ent, Loc),
11539 Expression => Relocate_Node (N))));
11541 Rewrite (N, New_Occurrence_Of (Ent, Loc));
11542 Analyze_And_Resolve (N, Typ);
11543 end Make_Temporary_For_Slice;
11545 -- Local variables
11547 Pref : constant Node_Id := Prefix (N);
11549 -- Start of processing for Expand_N_Slice
11551 begin
11552 -- Ada 2005 (AI-318-02): If the prefix is a call to a build-in-place
11553 -- function, then additional actuals must be passed.
11555 if Is_Build_In_Place_Function_Call (Pref) then
11556 Make_Build_In_Place_Call_In_Anonymous_Context (Pref);
11558 -- Ada 2005 (AI-318-02): Specialization of the previous case for prefix
11559 -- containing build-in-place function calls whose returned object covers
11560 -- interface types.
11562 elsif Present (Unqual_BIP_Iface_Function_Call (Pref)) then
11563 Make_Build_In_Place_Iface_Call_In_Anonymous_Context (Pref);
11564 end if;
11566 -- The remaining case to be handled is packed slices. We can leave
11567 -- packed slices as they are in the following situations:
11569 -- 1. Right or left side of an assignment (we can handle this
11570 -- situation correctly in the assignment statement expansion).
11572 -- 2. Prefix of indexed component (the slide is optimized away in this
11573 -- case, see the start of Expand_N_Indexed_Component.)
11575 -- 3. Object renaming declaration, since we want the name of the
11576 -- slice, not the value.
11578 -- 4. Argument to procedure call, since copy-in/copy-out handling may
11579 -- be required, and this is handled in the expansion of call
11580 -- itself.
11582 -- 5. Prefix of an address attribute (this is an error which is caught
11583 -- elsewhere, and the expansion would interfere with generating the
11584 -- error message) or of a size attribute (because 'Size may change
11585 -- when applied to the temporary instead of the slice directly).
11587 if not Is_Packed (Typ) then
11589 -- Apply transformation for actuals of a function call, where
11590 -- Expand_Actuals is not used.
11592 if Nkind (Parent (N)) = N_Function_Call
11593 and then Is_Possibly_Unaligned_Slice (N)
11594 then
11595 Make_Temporary_For_Slice;
11596 end if;
11598 elsif Nkind (Parent (N)) = N_Assignment_Statement
11599 or else (Nkind (Parent (Parent (N))) = N_Assignment_Statement
11600 and then Parent (N) = Name (Parent (Parent (N))))
11601 then
11602 return;
11604 elsif Nkind (Parent (N)) = N_Indexed_Component
11605 or else Is_Renamed_Object (N)
11606 or else Is_Procedure_Actual (N)
11607 then
11608 return;
11610 elsif Nkind (Parent (N)) = N_Attribute_Reference
11611 and then (Attribute_Name (Parent (N)) = Name_Address
11612 or else Attribute_Name (Parent (N)) = Name_Size)
11613 then
11614 return;
11616 else
11617 Make_Temporary_For_Slice;
11618 end if;
11619 end Expand_N_Slice;
11621 ------------------------------
11622 -- Expand_N_Type_Conversion --
11623 ------------------------------
11625 procedure Expand_N_Type_Conversion (N : Node_Id) is
11626 Loc : constant Source_Ptr := Sloc (N);
11627 Operand : constant Node_Id := Expression (N);
11628 Operand_Acc : Node_Id := Operand;
11629 Target_Type : Entity_Id := Etype (N);
11630 Operand_Type : Entity_Id := Etype (Operand);
11632 procedure Discrete_Range_Check;
11633 -- Handles generation of range check for discrete target value
11635 procedure Handle_Changed_Representation;
11636 -- This is called in the case of record and array type conversions to
11637 -- see if there is a change of representation to be handled. Change of
11638 -- representation is actually handled at the assignment statement level,
11639 -- and what this procedure does is rewrite node N conversion as an
11640 -- assignment to temporary. If there is no change of representation,
11641 -- then the conversion node is unchanged.
11643 procedure Raise_Accessibility_Error;
11644 -- Called when we know that an accessibility check will fail. Rewrites
11645 -- node N to an appropriate raise statement and outputs warning msgs.
11646 -- The Etype of the raise node is set to Target_Type. Note that in this
11647 -- case the rest of the processing should be skipped (i.e. the call to
11648 -- this procedure will be followed by "goto Done").
11650 procedure Real_Range_Check;
11651 -- Handles generation of range check for real target value
11653 function Has_Extra_Accessibility (Id : Entity_Id) return Boolean;
11654 -- True iff Present (Effective_Extra_Accessibility (Id)) successfully
11655 -- evaluates to True.
11657 function Statically_Deeper_Relation_Applies (Targ_Typ : Entity_Id)
11658 return Boolean;
11659 -- Given a target type for a conversion, determine whether the
11660 -- statically deeper accessibility rules apply to it.
11662 --------------------------
11663 -- Discrete_Range_Check --
11664 --------------------------
11666 -- Case of conversions to a discrete type. We let Generate_Range_Check
11667 -- do the heavy lifting, after converting a fixed-point operand to an
11668 -- appropriate integer type.
11670 procedure Discrete_Range_Check is
11671 Expr : Node_Id;
11672 Ityp : Entity_Id;
11674 procedure Generate_Temporary;
11675 -- Generate a temporary to facilitate in the C backend the code
11676 -- generation of the unchecked conversion since the size of the
11677 -- source type may differ from the size of the target type.
11679 ------------------------
11680 -- Generate_Temporary --
11681 ------------------------
11683 procedure Generate_Temporary is
11684 begin
11685 if Esize (Etype (Expr)) < Esize (Etype (Ityp)) then
11686 declare
11687 Exp_Type : constant Entity_Id := Ityp;
11688 Def_Id : constant Entity_Id :=
11689 Make_Temporary (Loc, 'R', Expr);
11690 E : Node_Id;
11691 Res : Node_Id;
11693 begin
11694 Set_Is_Internal (Def_Id);
11695 Set_Etype (Def_Id, Exp_Type);
11696 Res := New_Occurrence_Of (Def_Id, Loc);
11698 E :=
11699 Make_Object_Declaration (Loc,
11700 Defining_Identifier => Def_Id,
11701 Object_Definition => New_Occurrence_Of
11702 (Exp_Type, Loc),
11703 Constant_Present => True,
11704 Expression => Relocate_Node (Expr));
11706 Set_Assignment_OK (E);
11707 Insert_Action (Expr, E);
11709 Set_Assignment_OK (Res, Assignment_OK (Expr));
11711 Rewrite (Expr, Res);
11712 Analyze_And_Resolve (Expr, Exp_Type);
11713 end;
11714 end if;
11715 end Generate_Temporary;
11717 -- Start of processing for Discrete_Range_Check
11719 begin
11720 -- Nothing more to do if conversion was rewritten
11722 if Nkind (N) /= N_Type_Conversion then
11723 return;
11724 end if;
11726 Expr := Expression (N);
11728 -- Clear the Do_Range_Check flag on Expr
11730 Set_Do_Range_Check (Expr, False);
11732 -- Nothing to do if range checks suppressed
11734 if Range_Checks_Suppressed (Target_Type) then
11735 return;
11736 end if;
11738 -- Nothing to do if expression is an entity on which checks have been
11739 -- suppressed.
11741 if Is_Entity_Name (Expr)
11742 and then Range_Checks_Suppressed (Entity (Expr))
11743 then
11744 return;
11745 end if;
11747 -- Before we do a range check, we have to deal with treating
11748 -- a fixed-point operand as an integer. The way we do this
11749 -- is simply to do an unchecked conversion to an appropriate
11750 -- integer type with the smallest size, so that we can suppress
11751 -- trivial checks.
11753 if Is_Fixed_Point_Type (Etype (Expr)) then
11754 Ityp := Small_Integer_Type_For
11755 (Esize (Base_Type (Etype (Expr))), Uns => False);
11757 -- Generate a temporary with the integer type to facilitate in the
11758 -- C backend the code generation for the unchecked conversion.
11760 if Modify_Tree_For_C then
11761 Generate_Temporary;
11762 end if;
11764 Rewrite (Expr, Unchecked_Convert_To (Ityp, Expr));
11765 end if;
11767 -- Reset overflow flag, since the range check will include
11768 -- dealing with possible overflow, and generate the check.
11770 Set_Do_Overflow_Check (N, False);
11772 Generate_Range_Check (Expr, Target_Type, CE_Range_Check_Failed);
11773 end Discrete_Range_Check;
11775 -----------------------------------
11776 -- Handle_Changed_Representation --
11777 -----------------------------------
11779 procedure Handle_Changed_Representation is
11780 Temp : Entity_Id;
11781 Decl : Node_Id;
11782 Odef : Node_Id;
11783 N_Ix : Node_Id;
11784 Cons : List_Id;
11786 begin
11787 -- Nothing else to do if no change of representation
11789 if Has_Compatible_Representation (Target_Type, Operand_Type) then
11790 return;
11792 -- The real change of representation work is done by the assignment
11793 -- statement processing. So if this type conversion is appearing as
11794 -- the expression of an assignment statement, nothing needs to be
11795 -- done to the conversion.
11797 elsif Nkind (Parent (N)) = N_Assignment_Statement then
11798 return;
11800 -- Otherwise we need to generate a temporary variable, and do the
11801 -- change of representation assignment into that temporary variable.
11802 -- The conversion is then replaced by a reference to this variable.
11804 else
11805 Cons := No_List;
11807 -- If type is unconstrained we have to add a constraint, copied
11808 -- from the actual value of the left-hand side.
11810 if not Is_Constrained (Target_Type) then
11811 if Has_Discriminants (Operand_Type) then
11813 -- A change of representation can only apply to untagged
11814 -- types. We need to build the constraint that applies to
11815 -- the target type, using the constraints of the operand.
11816 -- The analysis is complicated if there are both inherited
11817 -- discriminants and constrained discriminants.
11818 -- We iterate over the discriminants of the target, and
11819 -- find the discriminant of the same name:
11821 -- a) If there is a corresponding discriminant in the object
11822 -- then the value is a selected component of the operand.
11824 -- b) Otherwise the value of a constrained discriminant is
11825 -- found in the stored constraint of the operand.
11827 declare
11828 Stored : constant Elist_Id :=
11829 Stored_Constraint (Operand_Type);
11830 -- Stored constraints of the operand. If present, they
11831 -- correspond to the discriminants of the parent type.
11833 Disc_O : Entity_Id;
11834 -- Discriminant of the operand type. Its value in the
11835 -- object is captured in a selected component.
11837 Disc_T : Entity_Id;
11838 -- Discriminant of the target type
11840 Elmt : Elmt_Id;
11842 begin
11843 Disc_O := First_Discriminant (Operand_Type);
11844 Disc_T := First_Discriminant (Target_Type);
11845 Elmt := (if Present (Stored)
11846 then First_Elmt (Stored)
11847 else No_Elmt);
11849 Cons := New_List;
11850 while Present (Disc_T) loop
11851 if Present (Disc_O)
11852 and then Chars (Disc_T) = Chars (Disc_O)
11853 then
11854 Append_To (Cons,
11855 Make_Selected_Component (Loc,
11856 Prefix =>
11857 Duplicate_Subexpr_Move_Checks (Operand),
11858 Selector_Name =>
11859 Make_Identifier (Loc, Chars (Disc_O))));
11860 Next_Discriminant (Disc_O);
11862 elsif Present (Elmt) then
11863 Append_To (Cons, New_Copy_Tree (Node (Elmt)));
11864 end if;
11866 if Present (Elmt) then
11867 Next_Elmt (Elmt);
11868 end if;
11870 Next_Discriminant (Disc_T);
11871 end loop;
11872 end;
11874 elsif Is_Array_Type (Operand_Type) then
11875 N_Ix := First_Index (Target_Type);
11876 Cons := New_List;
11878 for J in 1 .. Number_Dimensions (Operand_Type) loop
11880 -- We convert the bounds explicitly. We use an unchecked
11881 -- conversion because bounds checks are done elsewhere.
11883 Append_To (Cons,
11884 Make_Range (Loc,
11885 Low_Bound =>
11886 Unchecked_Convert_To (Etype (N_Ix),
11887 Make_Attribute_Reference (Loc,
11888 Prefix =>
11889 Duplicate_Subexpr_No_Checks
11890 (Operand, Name_Req => True),
11891 Attribute_Name => Name_First,
11892 Expressions => New_List (
11893 Make_Integer_Literal (Loc, J)))),
11895 High_Bound =>
11896 Unchecked_Convert_To (Etype (N_Ix),
11897 Make_Attribute_Reference (Loc,
11898 Prefix =>
11899 Duplicate_Subexpr_No_Checks
11900 (Operand, Name_Req => True),
11901 Attribute_Name => Name_Last,
11902 Expressions => New_List (
11903 Make_Integer_Literal (Loc, J))))));
11905 Next_Index (N_Ix);
11906 end loop;
11907 end if;
11908 end if;
11910 Odef := New_Occurrence_Of (Target_Type, Loc);
11912 if Present (Cons) then
11913 Odef :=
11914 Make_Subtype_Indication (Loc,
11915 Subtype_Mark => Odef,
11916 Constraint =>
11917 Make_Index_Or_Discriminant_Constraint (Loc,
11918 Constraints => Cons));
11919 end if;
11921 Temp := Make_Temporary (Loc, 'C');
11922 Decl :=
11923 Make_Object_Declaration (Loc,
11924 Defining_Identifier => Temp,
11925 Object_Definition => Odef);
11927 Set_No_Initialization (Decl, True);
11929 -- Insert required actions. It is essential to suppress checks
11930 -- since we have suppressed default initialization, which means
11931 -- that the variable we create may have no discriminants.
11933 Insert_Actions (N,
11934 New_List (
11935 Decl,
11936 Make_Assignment_Statement (Loc,
11937 Name => New_Occurrence_Of (Temp, Loc),
11938 Expression => Relocate_Node (N))),
11939 Suppress => All_Checks);
11941 Rewrite (N, New_Occurrence_Of (Temp, Loc));
11942 return;
11943 end if;
11944 end Handle_Changed_Representation;
11946 -------------------------------
11947 -- Raise_Accessibility_Error --
11948 -------------------------------
11950 procedure Raise_Accessibility_Error is
11951 begin
11952 Error_Msg_Warn := SPARK_Mode /= On;
11953 Rewrite (N,
11954 Make_Raise_Program_Error (Sloc (N),
11955 Reason => PE_Accessibility_Check_Failed));
11956 Set_Etype (N, Target_Type);
11958 Error_Msg_N ("accessibility check failure<<", N);
11959 Error_Msg_N ("\Program_Error [<<", N);
11960 end Raise_Accessibility_Error;
11962 ----------------------
11963 -- Real_Range_Check --
11964 ----------------------
11966 -- Case of conversions to floating-point or fixed-point. If range checks
11967 -- are enabled and the target type has a range constraint, we convert:
11969 -- typ (x)
11971 -- to
11973 -- Tnn : typ'Base := typ'Base (x);
11974 -- [constraint_error when Tnn < typ'First or else Tnn > typ'Last]
11975 -- typ (Tnn)
11977 -- This is necessary when there is a conversion of integer to float or
11978 -- to fixed-point to ensure that the correct checks are made. It is not
11979 -- necessary for the float-to-float case where it is enough to just set
11980 -- the Do_Range_Check flag on the expression.
11982 procedure Real_Range_Check is
11983 Btyp : constant Entity_Id := Base_Type (Target_Type);
11984 Lo : constant Node_Id := Type_Low_Bound (Target_Type);
11985 Hi : constant Node_Id := Type_High_Bound (Target_Type);
11987 Conv : Node_Id;
11988 Hi_Arg : Node_Id;
11989 Hi_Val : Node_Id;
11990 Lo_Arg : Node_Id;
11991 Lo_Val : Node_Id;
11992 Expr : Entity_Id;
11993 Tnn : Entity_Id;
11995 begin
11996 -- Nothing more to do if conversion was rewritten
11998 if Nkind (N) /= N_Type_Conversion then
11999 return;
12000 end if;
12002 Expr := Expression (N);
12004 -- Clear the Do_Range_Check flag on Expr
12006 Set_Do_Range_Check (Expr, False);
12008 -- Nothing to do if range checks suppressed, or target has the same
12009 -- range as the base type (or is the base type).
12011 if Range_Checks_Suppressed (Target_Type)
12012 or else (Lo = Type_Low_Bound (Btyp)
12013 and then
12014 Hi = Type_High_Bound (Btyp))
12015 then
12016 return;
12017 end if;
12019 -- Nothing to do if expression is an entity on which checks have been
12020 -- suppressed.
12022 if Is_Entity_Name (Expr)
12023 and then Range_Checks_Suppressed (Entity (Expr))
12024 then
12025 return;
12026 end if;
12028 -- Nothing to do if expression was rewritten into a float-to-float
12029 -- conversion, since this kind of conversion is handled elsewhere.
12031 if Is_Floating_Point_Type (Etype (Expr))
12032 and then Is_Floating_Point_Type (Target_Type)
12033 then
12034 return;
12035 end if;
12037 -- Nothing to do if bounds are all static and we can tell that the
12038 -- expression is within the bounds of the target. Note that if the
12039 -- operand is of an unconstrained floating-point type, then we do
12040 -- not trust it to be in range (might be infinite)
12042 declare
12043 S_Lo : constant Node_Id := Type_Low_Bound (Etype (Expr));
12044 S_Hi : constant Node_Id := Type_High_Bound (Etype (Expr));
12046 begin
12047 if (not Is_Floating_Point_Type (Etype (Expr))
12048 or else Is_Constrained (Etype (Expr)))
12049 and then Compile_Time_Known_Value (S_Lo)
12050 and then Compile_Time_Known_Value (S_Hi)
12051 and then Compile_Time_Known_Value (Hi)
12052 and then Compile_Time_Known_Value (Lo)
12053 then
12054 declare
12055 D_Lov : constant Ureal := Expr_Value_R (Lo);
12056 D_Hiv : constant Ureal := Expr_Value_R (Hi);
12057 S_Lov : Ureal;
12058 S_Hiv : Ureal;
12060 begin
12061 if Is_Real_Type (Etype (Expr)) then
12062 S_Lov := Expr_Value_R (S_Lo);
12063 S_Hiv := Expr_Value_R (S_Hi);
12064 else
12065 S_Lov := UR_From_Uint (Expr_Value (S_Lo));
12066 S_Hiv := UR_From_Uint (Expr_Value (S_Hi));
12067 end if;
12069 if D_Hiv > D_Lov
12070 and then S_Lov >= D_Lov
12071 and then S_Hiv <= D_Hiv
12072 then
12073 return;
12074 end if;
12075 end;
12076 end if;
12077 end;
12079 -- Otherwise rewrite the conversion as described above
12081 Conv := Convert_To (Btyp, Expr);
12083 -- If a conversion is necessary, then copy the specific flags from
12084 -- the original one and also move the Do_Overflow_Check flag since
12085 -- this new conversion is to the base type.
12087 if Nkind (Conv) = N_Type_Conversion then
12088 Set_Conversion_OK (Conv, Conversion_OK (N));
12089 Set_Float_Truncate (Conv, Float_Truncate (N));
12090 Set_Rounded_Result (Conv, Rounded_Result (N));
12092 if Do_Overflow_Check (N) then
12093 Set_Do_Overflow_Check (Conv);
12094 Set_Do_Overflow_Check (N, False);
12095 end if;
12096 end if;
12098 Tnn := Make_Temporary (Loc, 'T', Conv);
12100 -- For a conversion from Float to Fixed where the bounds of the
12101 -- fixed-point type are static, we can obtain a more accurate
12102 -- fixed-point value by converting the result of the floating-
12103 -- point expression to an appropriate integer type, and then
12104 -- performing an unchecked conversion to the target fixed-point
12105 -- type. The range check can then use the corresponding integer
12106 -- value of the bounds instead of requiring further conversions.
12107 -- This preserves the identity:
12109 -- Fix_Val = Fixed_Type (Float_Type (Fix_Val))
12111 -- which used to fail when Fix_Val was a bound of the type and
12112 -- the 'Small was not a representable number.
12113 -- This transformation requires an integer type large enough to
12114 -- accommodate a fixed-point value.
12116 if Is_Ordinary_Fixed_Point_Type (Target_Type)
12117 and then Is_Floating_Point_Type (Etype (Expr))
12118 and then RM_Size (Btyp) <= System_Max_Integer_Size
12119 and then Nkind (Lo) = N_Real_Literal
12120 and then Nkind (Hi) = N_Real_Literal
12121 then
12122 declare
12123 Expr_Id : constant Entity_Id := Make_Temporary (Loc, 'T', Conv);
12124 Int_Typ : constant Entity_Id :=
12125 Small_Integer_Type_For (RM_Size (Btyp), Uns => False);
12127 begin
12128 -- Generate a temporary with the integer value. Required in the
12129 -- CCG compiler to ensure that run-time checks reference this
12130 -- integer expression (instead of the resulting fixed-point
12131 -- value because fixed-point values are handled by means of
12132 -- unsigned integer types).
12134 Insert_Action (N,
12135 Make_Object_Declaration (Loc,
12136 Defining_Identifier => Expr_Id,
12137 Object_Definition => New_Occurrence_Of (Int_Typ, Loc),
12138 Constant_Present => True,
12139 Expression =>
12140 Convert_To (Int_Typ, Expression (Conv))));
12142 -- Create integer objects for range checking of result.
12144 Lo_Arg :=
12145 Unchecked_Convert_To
12146 (Int_Typ, New_Occurrence_Of (Expr_Id, Loc));
12148 Lo_Val :=
12149 Make_Integer_Literal (Loc, Corresponding_Integer_Value (Lo));
12151 Hi_Arg :=
12152 Unchecked_Convert_To
12153 (Int_Typ, New_Occurrence_Of (Expr_Id, Loc));
12155 Hi_Val :=
12156 Make_Integer_Literal (Loc, Corresponding_Integer_Value (Hi));
12158 -- Rewrite conversion as an integer conversion of the
12159 -- original floating-point expression, followed by an
12160 -- unchecked conversion to the target fixed-point type.
12162 Conv :=
12163 Unchecked_Convert_To
12164 (Target_Type, New_Occurrence_Of (Expr_Id, Loc));
12165 end;
12167 -- All other conversions
12169 else
12170 Lo_Arg := New_Occurrence_Of (Tnn, Loc);
12171 Lo_Val :=
12172 Make_Attribute_Reference (Loc,
12173 Prefix => New_Occurrence_Of (Target_Type, Loc),
12174 Attribute_Name => Name_First);
12176 Hi_Arg := New_Occurrence_Of (Tnn, Loc);
12177 Hi_Val :=
12178 Make_Attribute_Reference (Loc,
12179 Prefix => New_Occurrence_Of (Target_Type, Loc),
12180 Attribute_Name => Name_Last);
12181 end if;
12183 -- Build code for range checking. Note that checks are suppressed
12184 -- here since we don't want a recursive range check popping up.
12186 Insert_Actions (N, New_List (
12187 Make_Object_Declaration (Loc,
12188 Defining_Identifier => Tnn,
12189 Object_Definition => New_Occurrence_Of (Btyp, Loc),
12190 Constant_Present => True,
12191 Expression => Conv),
12193 Make_Raise_Constraint_Error (Loc,
12194 Condition =>
12195 Make_Or_Else (Loc,
12196 Left_Opnd =>
12197 Make_Op_Lt (Loc,
12198 Left_Opnd => Lo_Arg,
12199 Right_Opnd => Lo_Val),
12201 Right_Opnd =>
12202 Make_Op_Gt (Loc,
12203 Left_Opnd => Hi_Arg,
12204 Right_Opnd => Hi_Val)),
12205 Reason => CE_Range_Check_Failed)),
12206 Suppress => All_Checks);
12208 Rewrite (Expr, New_Occurrence_Of (Tnn, Loc));
12209 end Real_Range_Check;
12211 -----------------------------
12212 -- Has_Extra_Accessibility --
12213 -----------------------------
12215 -- Returns true for a formal of an anonymous access type or for an Ada
12216 -- 2012-style stand-alone object of an anonymous access type.
12218 function Has_Extra_Accessibility (Id : Entity_Id) return Boolean is
12219 begin
12220 if Is_Formal (Id) or else Ekind (Id) in E_Constant | E_Variable then
12221 return Present (Effective_Extra_Accessibility (Id));
12222 else
12223 return False;
12224 end if;
12225 end Has_Extra_Accessibility;
12227 ----------------------------------------
12228 -- Statically_Deeper_Relation_Applies --
12229 ----------------------------------------
12231 function Statically_Deeper_Relation_Applies (Targ_Typ : Entity_Id)
12232 return Boolean
12234 begin
12235 -- The case where the target type is an anonymous access type is
12236 -- ignored since they have different semantics and get covered by
12237 -- various runtime checks depending on context.
12239 -- Note, the current implementation of this predicate is incomplete
12240 -- and doesn't fully reflect the rules given in RM 3.10.2 (19) and
12241 -- (19.1) ???
12243 return Ekind (Targ_Typ) /= E_Anonymous_Access_Type;
12244 end Statically_Deeper_Relation_Applies;
12246 -- Start of processing for Expand_N_Type_Conversion
12248 begin
12249 -- First remove check marks put by the semantic analysis on the type
12250 -- conversion between array types. We need these checks, and they will
12251 -- be generated by this expansion routine, but we do not depend on these
12252 -- flags being set, and since we do intend to expand the checks in the
12253 -- front end, we don't want them on the tree passed to the back end.
12255 if Is_Array_Type (Target_Type) then
12256 if Is_Constrained (Target_Type) then
12257 Set_Do_Length_Check (N, False);
12258 else
12259 Set_Do_Range_Check (Operand, False);
12260 end if;
12261 end if;
12263 -- Nothing at all to do if conversion is to the identical type so remove
12264 -- the conversion completely, it is useless, except that it may carry
12265 -- an Assignment_OK attribute, which must be propagated to the operand
12266 -- and the Do_Range_Check flag on the operand must be cleared, if any.
12268 if Operand_Type = Target_Type then
12269 if Assignment_OK (N) then
12270 Set_Assignment_OK (Operand);
12271 end if;
12273 Set_Do_Range_Check (Operand, False);
12275 Rewrite (N, Relocate_Node (Operand));
12277 goto Done;
12278 end if;
12280 -- Nothing to do if this is the second argument of read. This is a
12281 -- "backwards" conversion that will be handled by the specialized code
12282 -- in attribute processing.
12284 if Nkind (Parent (N)) = N_Attribute_Reference
12285 and then Attribute_Name (Parent (N)) = Name_Read
12286 and then Next (First (Expressions (Parent (N)))) = N
12287 then
12288 goto Done;
12289 end if;
12291 -- Check for case of converting to a type that has an invariant
12292 -- associated with it. This requires an invariant check. We insert
12293 -- a call:
12295 -- invariant_check (typ (expr))
12297 -- in the code, after removing side effects from the expression.
12298 -- This is clearer than replacing the conversion into an expression
12299 -- with actions, because the context may impose additional actions
12300 -- (tag checks, membership tests, etc.) that conflict with this
12301 -- rewriting (used previously).
12303 -- Note: the Comes_From_Source check, and then the resetting of this
12304 -- flag prevents what would otherwise be an infinite recursion.
12306 if Has_Invariants (Target_Type)
12307 and then Present (Invariant_Procedure (Target_Type))
12308 and then Comes_From_Source (N)
12309 then
12310 Set_Comes_From_Source (N, False);
12311 Remove_Side_Effects (N);
12312 Insert_Action (N, Make_Invariant_Call (Duplicate_Subexpr (N)));
12313 goto Done;
12315 -- AI12-0042: For a view conversion to a class-wide type occurring
12316 -- within the immediate scope of T, from a specific type that is
12317 -- a descendant of T (including T itself), an invariant check is
12318 -- performed on the part of the object that is of type T. (We don't
12319 -- need to explicitly check for the operand type being a descendant,
12320 -- just that it's a specific type, because the conversion would be
12321 -- illegal if it's specific and not a descendant -- downward conversion
12322 -- is not allowed).
12324 elsif Is_Class_Wide_Type (Target_Type)
12325 and then not Is_Class_Wide_Type (Etype (Expression (N)))
12326 and then Present (Invariant_Procedure (Root_Type (Target_Type)))
12327 and then Comes_From_Source (N)
12328 and then Within_Scope (Find_Enclosing_Scope (N), Scope (Target_Type))
12329 then
12330 Remove_Side_Effects (N);
12332 -- Perform the invariant check on a conversion to the class-wide
12333 -- type's root type.
12335 declare
12336 Root_Conv : constant Node_Id :=
12337 Make_Type_Conversion (Loc,
12338 Subtype_Mark =>
12339 New_Occurrence_Of (Root_Type (Target_Type), Loc),
12340 Expression => Duplicate_Subexpr (Expression (N)));
12341 begin
12342 Set_Etype (Root_Conv, Root_Type (Target_Type));
12344 Insert_Action (N, Make_Invariant_Call (Root_Conv));
12345 goto Done;
12346 end;
12347 end if;
12349 -- Here if we may need to expand conversion
12351 -- If the operand of the type conversion is an arithmetic operation on
12352 -- signed integers, and the based type of the signed integer type in
12353 -- question is smaller than Standard.Integer, we promote both of the
12354 -- operands to type Integer.
12356 -- For example, if we have
12358 -- target-type (opnd1 + opnd2)
12360 -- and opnd1 and opnd2 are of type short integer, then we rewrite
12361 -- this as:
12363 -- target-type (integer(opnd1) + integer(opnd2))
12365 -- We do this because we are always allowed to compute in a larger type
12366 -- if we do the right thing with the result, and in this case we are
12367 -- going to do a conversion which will do an appropriate check to make
12368 -- sure that things are in range of the target type in any case. This
12369 -- avoids some unnecessary intermediate overflows.
12371 -- We might consider a similar transformation in the case where the
12372 -- target is a real type or a 64-bit integer type, and the operand
12373 -- is an arithmetic operation using a 32-bit integer type. However,
12374 -- we do not bother with this case, because it could cause significant
12375 -- inefficiencies on 32-bit machines. On a 64-bit machine it would be
12376 -- much cheaper, but we don't want different behavior on 32-bit and
12377 -- 64-bit machines. Note that the exclusion of the 64-bit case also
12378 -- handles the configurable run-time cases where 64-bit arithmetic
12379 -- may simply be unavailable.
12381 -- Note: this circuit is partially redundant with respect to the circuit
12382 -- in Checks.Apply_Arithmetic_Overflow_Check, but we catch more cases in
12383 -- the processing here. Also we still need the Checks circuit, since we
12384 -- have to be sure not to generate junk overflow checks in the first
12385 -- place, since it would be tricky to remove them here.
12387 if Integer_Promotion_Possible (N) then
12389 -- All conditions met, go ahead with transformation
12391 declare
12392 Opnd : Node_Id;
12393 L, R : Node_Id;
12395 begin
12396 Opnd := New_Op_Node (Nkind (Operand), Loc);
12398 R := Convert_To (Standard_Integer, Right_Opnd (Operand));
12399 Set_Right_Opnd (Opnd, R);
12401 if Nkind (Operand) in N_Binary_Op then
12402 L := Convert_To (Standard_Integer, Left_Opnd (Operand));
12403 Set_Left_Opnd (Opnd, L);
12404 end if;
12406 Rewrite (N,
12407 Make_Type_Conversion (Loc,
12408 Subtype_Mark => Relocate_Node (Subtype_Mark (N)),
12409 Expression => Opnd));
12411 Analyze_And_Resolve (N, Target_Type);
12412 goto Done;
12413 end;
12414 end if;
12416 -- If the conversion is from Universal_Integer and requires an overflow
12417 -- check, try to do an intermediate conversion to a narrower type first
12418 -- without overflow check, in order to avoid doing the overflow check
12419 -- in Universal_Integer, which can be a very large type.
12421 if Operand_Type = Universal_Integer and then Do_Overflow_Check (N) then
12422 declare
12423 Lo, Hi, Siz : Uint;
12424 OK : Boolean;
12425 Typ : Entity_Id;
12427 begin
12428 Determine_Range (Operand, OK, Lo, Hi, Assume_Valid => True);
12430 if OK then
12431 Siz := Get_Size_For_Range (Lo, Hi);
12433 -- We use the base type instead of the first subtype because
12434 -- overflow checks are done in the base type, so this avoids
12435 -- the need for useless conversions.
12437 if Siz < System_Max_Integer_Size then
12438 Typ := Etype (Integer_Type_For (Siz, Uns => False));
12440 Convert_To_And_Rewrite (Typ, Operand);
12441 Analyze_And_Resolve
12442 (Operand, Typ, Suppress => Overflow_Check);
12444 Analyze_And_Resolve (N, Target_Type);
12445 goto Done;
12446 end if;
12447 end if;
12448 end;
12449 end if;
12451 -- Do validity check if validity checking operands
12453 if Validity_Checks_On and Validity_Check_Operands then
12454 Ensure_Valid (Operand);
12455 end if;
12457 -- Special case of converting from non-standard boolean type
12459 if Is_Boolean_Type (Operand_Type)
12460 and then Nonzero_Is_True (Operand_Type)
12461 then
12462 Adjust_Condition (Operand);
12463 Set_Etype (Operand, Standard_Boolean);
12464 Operand_Type := Standard_Boolean;
12465 end if;
12467 -- Case of converting to an access type
12469 if Is_Access_Type (Target_Type) then
12470 -- In terms of accessibility rules, an anonymous access discriminant
12471 -- is not considered separate from its parent object.
12473 if Nkind (Operand) = N_Selected_Component
12474 and then Ekind (Entity (Selector_Name (Operand))) = E_Discriminant
12475 and then Ekind (Operand_Type) = E_Anonymous_Access_Type
12476 then
12477 Operand_Acc := Original_Node (Prefix (Operand));
12478 end if;
12480 -- If this type conversion was internally generated by the front end
12481 -- to displace the pointer to the object to reference an interface
12482 -- type and the original node was an Unrestricted_Access attribute,
12483 -- then skip applying accessibility checks (because, according to the
12484 -- GNAT Reference Manual, this attribute is similar to 'Access except
12485 -- that all accessibility and aliased view checks are omitted).
12487 if not Comes_From_Source (N)
12488 and then Is_Interface (Designated_Type (Target_Type))
12489 and then Nkind (Original_Node (N)) = N_Attribute_Reference
12490 and then Attribute_Name (Original_Node (N)) =
12491 Name_Unrestricted_Access
12492 then
12493 null;
12495 -- Apply an accessibility check when the conversion operand is an
12496 -- access parameter (or a renaming thereof), unless conversion was
12497 -- expanded from an Unchecked_ or Unrestricted_Access attribute,
12498 -- or for the actual of a class-wide interface parameter. Note that
12499 -- other checks may still need to be applied below (such as tagged
12500 -- type checks).
12502 elsif Is_Entity_Name (Operand_Acc)
12503 and then Has_Extra_Accessibility (Entity (Operand_Acc))
12504 and then Ekind (Etype (Operand_Acc)) = E_Anonymous_Access_Type
12505 and then (Nkind (Original_Node (N)) /= N_Attribute_Reference
12506 or else Attribute_Name (Original_Node (N)) = Name_Access)
12507 and then not No_Dynamic_Accessibility_Checks_Enabled (N)
12508 then
12509 if not Comes_From_Source (N)
12510 and then Nkind (Parent (N)) in N_Function_Call
12511 | N_Parameter_Association
12512 | N_Procedure_Call_Statement
12513 and then Is_Interface (Designated_Type (Target_Type))
12514 and then Is_Class_Wide_Type (Designated_Type (Target_Type))
12515 then
12516 null;
12518 else
12519 Apply_Accessibility_Check
12520 (Operand, Target_Type, Insert_Node => Operand);
12521 end if;
12523 -- If the level of the operand type is statically deeper than the
12524 -- level of the target type, then force Program_Error. Note that this
12525 -- can only occur for cases where the attribute is within the body of
12526 -- an instantiation, otherwise the conversion will already have been
12527 -- rejected as illegal.
12529 -- Note: warnings are issued by the analyzer for the instance cases,
12530 -- and, since we are late in expansion, a check is performed to
12531 -- verify that neither the target type nor the operand type are
12532 -- internally generated - as this can lead to spurious errors when,
12533 -- for example, the operand type is a result of BIP expansion.
12535 elsif In_Instance_Body
12536 and then Statically_Deeper_Relation_Applies (Target_Type)
12537 and then not Is_Internal (Target_Type)
12538 and then not Is_Internal (Operand_Type)
12539 and then
12540 Type_Access_Level (Operand_Type) > Type_Access_Level (Target_Type)
12541 then
12542 Raise_Accessibility_Error;
12543 goto Done;
12545 -- When the operand is a selected access discriminant the check needs
12546 -- to be made against the level of the object denoted by the prefix
12547 -- of the selected name. Force Program_Error for this case as well
12548 -- (this accessibility violation can only happen if within the body
12549 -- of an instantiation).
12551 elsif In_Instance_Body
12552 and then Ekind (Operand_Type) = E_Anonymous_Access_Type
12553 and then Nkind (Operand) = N_Selected_Component
12554 and then Ekind (Entity (Selector_Name (Operand))) = E_Discriminant
12555 and then Static_Accessibility_Level (Operand, Zero_On_Dynamic_Level)
12556 > Type_Access_Level (Target_Type)
12557 then
12558 Raise_Accessibility_Error;
12559 goto Done;
12560 end if;
12561 end if;
12563 -- Case of conversions of tagged types and access to tagged types
12565 -- When needed, that is to say when the expression is class-wide, Add
12566 -- runtime a tag check for (strict) downward conversion by using the
12567 -- membership test, generating:
12569 -- [constraint_error when Operand not in Target_Type'Class]
12571 -- or in the access type case
12573 -- [constraint_error
12574 -- when Operand /= null
12575 -- and then Operand.all not in
12576 -- Designated_Type (Target_Type)'Class]
12578 if (Is_Access_Type (Target_Type)
12579 and then Is_Tagged_Type (Designated_Type (Target_Type)))
12580 or else Is_Tagged_Type (Target_Type)
12581 then
12582 -- Do not do any expansion in the access type case if the parent is a
12583 -- renaming, since this is an error situation which will be caught by
12584 -- Sem_Ch8, and the expansion can interfere with this error check.
12586 if Is_Access_Type (Target_Type) and then Is_Renamed_Object (N) then
12587 goto Done;
12588 end if;
12590 -- Otherwise, proceed with processing tagged conversion
12592 Tagged_Conversion : declare
12593 Actual_Op_Typ : Entity_Id;
12594 Actual_Targ_Typ : Entity_Id;
12595 Root_Op_Typ : Entity_Id;
12597 procedure Make_Tag_Check (Targ_Typ : Entity_Id);
12598 -- Create a membership check to test whether Operand is a member
12599 -- of Targ_Typ. If the original Target_Type is an access, include
12600 -- a test for null value. The check is inserted at N.
12602 --------------------
12603 -- Make_Tag_Check --
12604 --------------------
12606 procedure Make_Tag_Check (Targ_Typ : Entity_Id) is
12607 Cond : Node_Id;
12609 begin
12610 -- Generate:
12611 -- [Constraint_Error
12612 -- when Operand /= null
12613 -- and then Operand.all not in Targ_Typ]
12615 if Is_Access_Type (Target_Type) then
12616 Cond :=
12617 Make_And_Then (Loc,
12618 Left_Opnd =>
12619 Make_Op_Ne (Loc,
12620 Left_Opnd => Duplicate_Subexpr_No_Checks (Operand),
12621 Right_Opnd => Make_Null (Loc)),
12623 Right_Opnd =>
12624 Make_Not_In (Loc,
12625 Left_Opnd =>
12626 Make_Explicit_Dereference (Loc,
12627 Prefix => Duplicate_Subexpr_No_Checks (Operand)),
12628 Right_Opnd => New_Occurrence_Of (Targ_Typ, Loc)));
12630 -- Generate:
12631 -- [Constraint_Error when Operand not in Targ_Typ]
12633 else
12634 Cond :=
12635 Make_Not_In (Loc,
12636 Left_Opnd => Duplicate_Subexpr_No_Checks (Operand),
12637 Right_Opnd => New_Occurrence_Of (Targ_Typ, Loc));
12638 end if;
12640 Insert_Action (N,
12641 Make_Raise_Constraint_Error (Loc,
12642 Condition => Cond,
12643 Reason => CE_Tag_Check_Failed),
12644 Suppress => All_Checks);
12645 end Make_Tag_Check;
12647 -- Start of processing for Tagged_Conversion
12649 begin
12650 -- Handle entities from the limited view
12652 if Is_Access_Type (Operand_Type) then
12653 Actual_Op_Typ :=
12654 Available_View (Designated_Type (Operand_Type));
12655 else
12656 Actual_Op_Typ := Operand_Type;
12657 end if;
12659 if Is_Access_Type (Target_Type) then
12660 Actual_Targ_Typ :=
12661 Available_View (Designated_Type (Target_Type));
12662 else
12663 Actual_Targ_Typ := Target_Type;
12664 end if;
12666 Root_Op_Typ := Root_Type (Actual_Op_Typ);
12668 -- Ada 2005 (AI-251): Handle interface type conversion
12670 if Is_Interface (Actual_Op_Typ)
12671 or else
12672 Is_Interface (Actual_Targ_Typ)
12673 then
12674 Expand_Interface_Conversion (N);
12675 goto Done;
12676 end if;
12678 -- Create a runtime tag check for a downward CW type conversion
12680 if Is_Class_Wide_Type (Actual_Op_Typ)
12681 and then Actual_Op_Typ /= Actual_Targ_Typ
12682 and then Root_Op_Typ /= Actual_Targ_Typ
12683 and then Is_Ancestor
12684 (Root_Op_Typ, Actual_Targ_Typ, Use_Full_View => True)
12685 and then not Tag_Checks_Suppressed (Actual_Targ_Typ)
12686 then
12687 declare
12688 Conv : Node_Id;
12689 begin
12690 Make_Tag_Check (Class_Wide_Type (Actual_Targ_Typ));
12691 Conv := Unchecked_Convert_To (Target_Type, Expression (N));
12692 Rewrite (N, Conv);
12693 Analyze_And_Resolve (N, Target_Type);
12694 end;
12695 end if;
12696 end Tagged_Conversion;
12698 -- Case of other access type conversions
12700 elsif Is_Access_Type (Target_Type) then
12701 Apply_Constraint_Check (Operand, Target_Type);
12703 -- Case of conversions from a fixed-point type
12705 -- These conversions require special expansion and processing, found in
12706 -- the Exp_Fixd package. We ignore cases where Conversion_OK is set,
12707 -- since from a semantic point of view, these are simple integer
12708 -- conversions, which do not need further processing except for the
12709 -- generation of range checks, which is performed at the end of this
12710 -- procedure.
12712 elsif Is_Fixed_Point_Type (Operand_Type)
12713 and then not Conversion_OK (N)
12714 then
12715 -- We should never see universal fixed at this case, since the
12716 -- expansion of the constituent divide or multiply should have
12717 -- eliminated the explicit mention of universal fixed.
12719 pragma Assert (Operand_Type /= Universal_Fixed);
12721 -- Check for special case of the conversion to universal real that
12722 -- occurs as a result of the use of a round attribute. In this case,
12723 -- the real type for the conversion is taken from the target type of
12724 -- the Round attribute and the result must be marked as rounded.
12726 if Target_Type = Universal_Real
12727 and then Nkind (Parent (N)) = N_Attribute_Reference
12728 and then Attribute_Name (Parent (N)) = Name_Round
12729 then
12730 Set_Etype (N, Etype (Parent (N)));
12731 Target_Type := Etype (N);
12732 Set_Rounded_Result (N);
12733 end if;
12735 if Is_Fixed_Point_Type (Target_Type) then
12736 Expand_Convert_Fixed_To_Fixed (N);
12737 elsif Is_Integer_Type (Target_Type) then
12738 Expand_Convert_Fixed_To_Integer (N);
12739 else
12740 pragma Assert (Is_Floating_Point_Type (Target_Type));
12741 Expand_Convert_Fixed_To_Float (N);
12742 end if;
12744 -- Case of conversions to a fixed-point type
12746 -- These conversions require special expansion and processing, found in
12747 -- the Exp_Fixd package. Again, ignore cases where Conversion_OK is set,
12748 -- since from a semantic point of view, these are simple integer
12749 -- conversions, which do not need further processing.
12751 elsif Is_Fixed_Point_Type (Target_Type)
12752 and then not Conversion_OK (N)
12753 then
12754 if Is_Integer_Type (Operand_Type) then
12755 Expand_Convert_Integer_To_Fixed (N);
12756 else
12757 pragma Assert (Is_Floating_Point_Type (Operand_Type));
12758 Expand_Convert_Float_To_Fixed (N);
12759 end if;
12761 -- Case of array conversions
12763 -- Expansion of array conversions, add required length/range checks but
12764 -- only do this if there is no change of representation. For handling of
12765 -- this case, see Handle_Changed_Representation.
12767 elsif Is_Array_Type (Target_Type) then
12768 if Is_Constrained (Target_Type) then
12769 Apply_Length_Check (Operand, Target_Type);
12770 else
12771 -- If the object has an unconstrained array subtype with fixed
12772 -- lower bound, then sliding to that bound may be needed.
12774 if Is_Fixed_Lower_Bound_Array_Subtype (Target_Type) then
12775 Expand_Sliding_Conversion (Operand, Target_Type);
12776 end if;
12778 Apply_Range_Check (Operand, Target_Type);
12779 end if;
12781 Handle_Changed_Representation;
12783 -- Case of conversions of discriminated types
12785 -- Add required discriminant checks if target is constrained. Again this
12786 -- change is skipped if we have a change of representation.
12788 elsif Has_Discriminants (Target_Type)
12789 and then Is_Constrained (Target_Type)
12790 then
12791 Apply_Discriminant_Check (Operand, Target_Type);
12792 Handle_Changed_Representation;
12794 -- Case of all other record conversions. The only processing required
12795 -- is to check for a change of representation requiring the special
12796 -- assignment processing.
12798 elsif Is_Record_Type (Target_Type) then
12800 -- Ada 2005 (AI-216): Program_Error is raised when converting from
12801 -- a derived Unchecked_Union type to an unconstrained type that is
12802 -- not Unchecked_Union if the operand lacks inferable discriminants.
12804 if Is_Derived_Type (Operand_Type)
12805 and then Is_Unchecked_Union (Base_Type (Operand_Type))
12806 and then not Is_Constrained (Target_Type)
12807 and then not Is_Unchecked_Union (Base_Type (Target_Type))
12808 and then not Has_Inferable_Discriminants (Operand)
12809 then
12810 -- To prevent Gigi from generating illegal code, we generate a
12811 -- Program_Error node, but we give it the target type of the
12812 -- conversion (is this requirement documented somewhere ???)
12814 declare
12815 PE : constant Node_Id := Make_Raise_Program_Error (Loc,
12816 Reason => PE_Unchecked_Union_Restriction);
12818 begin
12819 Set_Etype (PE, Target_Type);
12820 Rewrite (N, PE);
12822 end;
12823 else
12824 Handle_Changed_Representation;
12825 end if;
12827 -- Case of conversions of enumeration types
12829 elsif Is_Enumeration_Type (Target_Type) then
12831 -- Special processing is required if there is a change of
12832 -- representation (from enumeration representation clauses).
12834 if not Has_Compatible_Representation (Target_Type, Operand_Type)
12835 and then not Conversion_OK (N)
12836 then
12837 if Optimization_Level > 0
12838 and then Is_Boolean_Type (Target_Type)
12839 then
12840 -- Convert x(y) to (if y then x'(True) else x'(False)).
12841 -- Use literals, instead of indexing x'val, to enable
12842 -- further optimizations in the middle-end.
12844 Rewrite (N,
12845 Make_If_Expression (Loc,
12846 Expressions => New_List (
12847 Operand,
12848 Convert_To (Target_Type,
12849 New_Occurrence_Of (Standard_True, Loc)),
12850 Convert_To (Target_Type,
12851 New_Occurrence_Of (Standard_False, Loc)))));
12853 else
12854 -- Convert: x(y) to x'val (ytyp'pos (y))
12856 Rewrite (N,
12857 Make_Attribute_Reference (Loc,
12858 Prefix => New_Occurrence_Of (Target_Type, Loc),
12859 Attribute_Name => Name_Val,
12860 Expressions => New_List (
12861 Make_Attribute_Reference (Loc,
12862 Prefix => New_Occurrence_Of (Operand_Type, Loc),
12863 Attribute_Name => Name_Pos,
12864 Expressions => New_List (Operand)))));
12865 end if;
12867 Analyze_And_Resolve (N, Target_Type);
12868 end if;
12869 end if;
12871 -- At this stage, either the conversion node has been transformed into
12872 -- some other equivalent expression, or left as a conversion that can be
12873 -- handled by Gigi.
12875 -- The only remaining step is to generate a range check if we still have
12876 -- a type conversion at this stage and Do_Range_Check is set. Note that
12877 -- we need to deal with at most 8 out of the 9 possible cases of numeric
12878 -- conversions here, because the float-to-integer case is entirely dealt
12879 -- with by Apply_Float_Conversion_Check.
12881 if Nkind (N) = N_Type_Conversion
12882 and then Do_Range_Check (Expression (N))
12883 then
12884 -- Float-to-float conversions
12886 if Is_Floating_Point_Type (Target_Type)
12887 and then Is_Floating_Point_Type (Etype (Expression (N)))
12888 then
12889 -- Reset overflow flag, since the range check will include
12890 -- dealing with possible overflow, and generate the check.
12892 Set_Do_Overflow_Check (N, False);
12894 Generate_Range_Check
12895 (Expression (N), Target_Type, CE_Range_Check_Failed);
12897 -- Discrete-to-discrete conversions or fixed-point-to-discrete
12898 -- conversions when Conversion_OK is set.
12900 elsif Is_Discrete_Type (Target_Type)
12901 and then (Is_Discrete_Type (Etype (Expression (N)))
12902 or else (Is_Fixed_Point_Type (Etype (Expression (N)))
12903 and then Conversion_OK (N)))
12904 then
12905 -- If Address is either a source type or target type,
12906 -- suppress range check to avoid typing anomalies when
12907 -- it is a visible integer type.
12909 if Is_Descendant_Of_Address (Etype (Expression (N)))
12910 or else Is_Descendant_Of_Address (Target_Type)
12911 then
12912 Set_Do_Range_Check (Expression (N), False);
12913 else
12914 Discrete_Range_Check;
12915 end if;
12917 -- Conversions to floating- or fixed-point when Conversion_OK is set
12919 elsif Is_Floating_Point_Type (Target_Type)
12920 or else (Is_Fixed_Point_Type (Target_Type)
12921 and then Conversion_OK (N))
12922 then
12923 Real_Range_Check;
12924 end if;
12926 pragma Assert (not Do_Range_Check (Expression (N)));
12927 end if;
12929 -- Here at end of processing
12931 <<Done>>
12932 -- Apply predicate check if required. Note that we can't just call
12933 -- Apply_Predicate_Check here, because the type looks right after
12934 -- the conversion and it would omit the check. The Comes_From_Source
12935 -- guard is necessary to prevent infinite recursions when we generate
12936 -- internal conversions for the purpose of checking predicates.
12938 -- A view conversion of a tagged object is an object and can appear
12939 -- in an assignment context, in which case no predicate check applies
12940 -- to the now-dead value.
12942 if Nkind (Parent (N)) = N_Assignment_Statement
12943 and then N = Name (Parent (N))
12944 then
12945 null;
12947 elsif Predicate_Enabled (Target_Type)
12948 and then Target_Type /= Operand_Type
12949 and then Comes_From_Source (N)
12950 then
12951 declare
12952 New_Expr : constant Node_Id := Duplicate_Subexpr (N);
12954 begin
12955 -- Avoid infinite recursion on the subsequent expansion of the
12956 -- copy of the original type conversion. When needed, a range
12957 -- check has already been applied to the expression.
12959 Set_Comes_From_Source (New_Expr, False);
12960 Insert_Action (N,
12961 Make_Predicate_Check (Target_Type, New_Expr),
12962 Suppress => Range_Check);
12963 end;
12964 end if;
12965 end Expand_N_Type_Conversion;
12967 -----------------------------------
12968 -- Expand_N_Unchecked_Expression --
12969 -----------------------------------
12971 -- Remove the unchecked expression node from the tree. Its job was simply
12972 -- to make sure that its constituent expression was handled with checks
12973 -- off, and now that is done, we can remove it from the tree, and indeed
12974 -- must, since Gigi does not expect to see these nodes.
12976 procedure Expand_N_Unchecked_Expression (N : Node_Id) is
12977 Exp : constant Node_Id := Expression (N);
12978 begin
12979 Set_Assignment_OK (Exp, Assignment_OK (N) or else Assignment_OK (Exp));
12980 Rewrite (N, Exp);
12981 end Expand_N_Unchecked_Expression;
12983 ----------------------------------------
12984 -- Expand_N_Unchecked_Type_Conversion --
12985 ----------------------------------------
12987 -- If this cannot be handled by Gigi and we haven't already made a
12988 -- temporary for it, do it now.
12990 procedure Expand_N_Unchecked_Type_Conversion (N : Node_Id) is
12991 Target_Type : constant Entity_Id := Etype (N);
12992 Operand : constant Node_Id := Expression (N);
12993 Operand_Type : constant Entity_Id := Etype (Operand);
12995 begin
12996 -- Nothing at all to do if conversion is to the identical type so remove
12997 -- the conversion completely, it is useless, except that it may carry
12998 -- an Assignment_OK indication which must be propagated to the operand.
13000 if Operand_Type = Target_Type then
13001 Expand_N_Unchecked_Expression (N);
13002 return;
13003 end if;
13005 -- Generate an extra temporary for cases unsupported by the C backend
13007 if Modify_Tree_For_C then
13008 declare
13009 Source : constant Node_Id := Unqual_Conv (Expression (N));
13010 Source_Typ : Entity_Id := Get_Full_View (Etype (Source));
13012 begin
13013 if Is_Packed_Array (Source_Typ) then
13014 Source_Typ := Packed_Array_Impl_Type (Source_Typ);
13015 end if;
13017 if Nkind (Source) = N_Function_Call
13018 and then (Is_Composite_Type (Etype (Source))
13019 or else Is_Composite_Type (Target_Type))
13020 then
13021 Force_Evaluation (Source);
13022 end if;
13023 end;
13024 end if;
13026 -- Nothing to do if conversion is safe
13028 if Safe_Unchecked_Type_Conversion (N) then
13029 return;
13030 end if;
13032 if Assignment_OK (N) then
13033 null;
13034 else
13035 Force_Evaluation (N);
13036 end if;
13037 end Expand_N_Unchecked_Type_Conversion;
13039 ----------------------------
13040 -- Expand_Record_Equality --
13041 ----------------------------
13043 -- For non-variant records, Equality is expanded when needed into:
13045 -- and then Lhs.Discr1 = Rhs.Discr1
13046 -- and then ...
13047 -- and then Lhs.Discrn = Rhs.Discrn
13048 -- and then Lhs.Cmp1 = Rhs.Cmp1
13049 -- and then ...
13050 -- and then Lhs.Cmpn = Rhs.Cmpn
13052 -- The expression is folded by the back end for adjacent fields. This
13053 -- function is called for tagged record in only one occasion: for imple-
13054 -- menting predefined primitive equality (see Predefined_Primitives_Bodies)
13055 -- otherwise the primitive "=" is used directly.
13057 function Expand_Record_Equality
13058 (Nod : Node_Id;
13059 Typ : Entity_Id;
13060 Lhs : Node_Id;
13061 Rhs : Node_Id) return Node_Id
13063 Loc : constant Source_Ptr := Sloc (Nod);
13065 Result : Node_Id;
13066 C : Entity_Id;
13068 First_Time : Boolean := True;
13070 function Element_To_Compare (C : Entity_Id) return Entity_Id;
13071 -- Return the next discriminant or component to compare, starting with
13072 -- C, skipping inherited components.
13074 ------------------------
13075 -- Element_To_Compare --
13076 ------------------------
13078 function Element_To_Compare (C : Entity_Id) return Entity_Id is
13079 Comp : Entity_Id := C;
13081 begin
13082 while Present (Comp) loop
13083 -- Skip inherited components
13085 -- Note: for a tagged type, we always generate the "=" primitive
13086 -- for the base type (not on the first subtype), so the test for
13087 -- Comp /= Original_Record_Component (Comp) is True for inherited
13088 -- components only.
13090 if (Is_Tagged_Type (Typ)
13091 and then Comp /= Original_Record_Component (Comp))
13093 -- Skip _Tag
13095 or else Chars (Comp) = Name_uTag
13097 -- Skip interface elements (secondary tags???)
13099 or else Is_Interface (Etype (Comp))
13100 then
13101 Next_Component_Or_Discriminant (Comp);
13102 else
13103 return Comp;
13104 end if;
13105 end loop;
13107 return Empty;
13108 end Element_To_Compare;
13110 -- Start of processing for Expand_Record_Equality
13112 begin
13113 -- Generates the following code: (assuming that Typ has one Discr and
13114 -- component C2 is also a record)
13116 -- Lhs.Discr1 = Rhs.Discr1
13117 -- and then Lhs.C1 = Rhs.C1
13118 -- and then Lhs.C2.C1=Rhs.C2.C1 and then ... Lhs.C2.Cn=Rhs.C2.Cn
13119 -- and then ...
13120 -- and then Lhs.Cmpn = Rhs.Cmpn
13122 Result := New_Occurrence_Of (Standard_True, Loc);
13123 C := Element_To_Compare (First_Component_Or_Discriminant (Typ));
13124 while Present (C) loop
13125 declare
13126 New_Lhs : Node_Id;
13127 New_Rhs : Node_Id;
13128 Check : Node_Id;
13130 begin
13131 if First_Time then
13132 New_Lhs := Lhs;
13133 New_Rhs := Rhs;
13134 else
13135 New_Lhs := New_Copy_Tree (Lhs);
13136 New_Rhs := New_Copy_Tree (Rhs);
13137 end if;
13139 Check :=
13140 Expand_Composite_Equality
13141 (Outer_Type => Typ, Nod => Nod, Comp_Type => Etype (C),
13142 Lhs =>
13143 Make_Selected_Component (Loc,
13144 Prefix => New_Lhs,
13145 Selector_Name => New_Occurrence_Of (C, Loc)),
13146 Rhs =>
13147 Make_Selected_Component (Loc,
13148 Prefix => New_Rhs,
13149 Selector_Name => New_Occurrence_Of (C, Loc)));
13151 -- If some (sub)component is an unchecked_union, the whole
13152 -- operation will raise program error.
13154 if Nkind (Check) = N_Raise_Program_Error then
13155 Result := Check;
13156 Set_Etype (Result, Standard_Boolean);
13157 exit;
13158 else
13159 if First_Time then
13160 Result := Check;
13162 -- Generate logical "and" for CodePeer to simplify the
13163 -- generated code and analysis.
13165 elsif CodePeer_Mode then
13166 Result :=
13167 Make_Op_And (Loc,
13168 Left_Opnd => Result,
13169 Right_Opnd => Check);
13171 else
13172 Result :=
13173 Make_And_Then (Loc,
13174 Left_Opnd => Result,
13175 Right_Opnd => Check);
13176 end if;
13177 end if;
13178 end;
13180 First_Time := False;
13181 C := Element_To_Compare (Next_Component_Or_Discriminant (C));
13182 end loop;
13184 return Result;
13185 end Expand_Record_Equality;
13187 ---------------------------
13188 -- Expand_Set_Membership --
13189 ---------------------------
13191 procedure Expand_Set_Membership (N : Node_Id) is
13192 Lop : constant Node_Id := Left_Opnd (N);
13193 Alt : Node_Id;
13194 Res : Node_Id;
13196 function Make_Cond (Alt : Node_Id) return Node_Id;
13197 -- If the alternative is a subtype mark, create a simple membership
13198 -- test. Otherwise create an equality test for it.
13200 ---------------
13201 -- Make_Cond --
13202 ---------------
13204 function Make_Cond (Alt : Node_Id) return Node_Id is
13205 Cond : Node_Id;
13206 L : constant Node_Id := New_Copy_Tree (Lop);
13207 R : constant Node_Id := Relocate_Node (Alt);
13209 begin
13210 if (Is_Entity_Name (Alt) and then Is_Type (Entity (Alt)))
13211 or else Nkind (Alt) = N_Range
13212 then
13213 Cond := Make_In (Sloc (Alt), Left_Opnd => L, Right_Opnd => R);
13215 else
13216 Cond := Make_Op_Eq (Sloc (Alt), Left_Opnd => L, Right_Opnd => R);
13217 Resolve_Membership_Equality (Cond, Etype (Alt));
13218 end if;
13220 return Cond;
13221 end Make_Cond;
13223 -- Start of processing for Expand_Set_Membership
13225 begin
13226 Remove_Side_Effects (Lop);
13228 Alt := First (Alternatives (N));
13229 Res := Make_Cond (Alt);
13230 Next (Alt);
13232 -- We use left associativity as in the equivalent boolean case. This
13233 -- kind of canonicalization helps the optimizer of the code generator.
13235 while Present (Alt) loop
13236 Res :=
13237 Make_Or_Else (Sloc (Alt),
13238 Left_Opnd => Res,
13239 Right_Opnd => Make_Cond (Alt));
13240 Next (Alt);
13241 end loop;
13243 Rewrite (N, Res);
13244 Analyze_And_Resolve (N, Standard_Boolean);
13245 end Expand_Set_Membership;
13247 -----------------------------------
13248 -- Expand_Short_Circuit_Operator --
13249 -----------------------------------
13251 -- Deal with special expansion if actions are present for the right operand
13252 -- and deal with optimizing case of arguments being True or False. We also
13253 -- deal with the special case of non-standard boolean values.
13255 procedure Expand_Short_Circuit_Operator (N : Node_Id) is
13256 Loc : constant Source_Ptr := Sloc (N);
13257 Typ : constant Entity_Id := Etype (N);
13258 Left : constant Node_Id := Left_Opnd (N);
13259 Right : constant Node_Id := Right_Opnd (N);
13260 LocR : constant Source_Ptr := Sloc (Right);
13261 Actlist : List_Id;
13263 Shortcut_Value : constant Boolean := Nkind (N) = N_Or_Else;
13264 Shortcut_Ent : constant Entity_Id := Boolean_Literals (Shortcut_Value);
13265 -- If Left = Shortcut_Value then Right need not be evaluated
13267 function Make_Test_Expr (Opnd : Node_Id) return Node_Id;
13268 -- For Opnd a boolean expression, return a Boolean expression equivalent
13269 -- to Opnd /= Shortcut_Value.
13271 function Useful (Actions : List_Id) return Boolean;
13272 -- Return True if Actions is not empty and contains useful nodes to
13273 -- process.
13275 --------------------
13276 -- Make_Test_Expr --
13277 --------------------
13279 function Make_Test_Expr (Opnd : Node_Id) return Node_Id is
13280 begin
13281 if Shortcut_Value then
13282 return Make_Op_Not (Sloc (Opnd), Opnd);
13283 else
13284 return Opnd;
13285 end if;
13286 end Make_Test_Expr;
13288 ------------
13289 -- Useful --
13290 ------------
13292 function Useful (Actions : List_Id) return Boolean is
13293 L : Node_Id;
13294 begin
13295 if Present (Actions) then
13296 L := First (Actions);
13298 -- For now "useful" means not N_Variable_Reference_Marker.
13299 -- Consider stripping other nodes in the future.
13301 while Present (L) loop
13302 if Nkind (L) /= N_Variable_Reference_Marker then
13303 return True;
13304 end if;
13306 Next (L);
13307 end loop;
13308 end if;
13310 return False;
13311 end Useful;
13313 -- Local variables
13315 Op_Var : Entity_Id;
13316 -- Entity for a temporary variable holding the value of the operator,
13317 -- used for expansion in the case where actions are present.
13319 -- Start of processing for Expand_Short_Circuit_Operator
13321 begin
13322 -- Deal with non-standard booleans
13324 if Is_Boolean_Type (Typ) then
13325 Adjust_Condition (Left);
13326 Adjust_Condition (Right);
13327 Set_Etype (N, Standard_Boolean);
13328 end if;
13330 -- Check for cases where left argument is known to be True or False
13332 if Compile_Time_Known_Value (Left) then
13334 -- Mark SCO for left condition as compile time known
13336 if Generate_SCO and then Comes_From_Source (Left) then
13337 Set_SCO_Condition (Left, Expr_Value_E (Left) = Standard_True);
13338 end if;
13340 -- Rewrite True AND THEN Right / False OR ELSE Right to Right.
13341 -- Any actions associated with Right will be executed unconditionally
13342 -- and can thus be inserted into the tree unconditionally.
13344 if Expr_Value_E (Left) /= Shortcut_Ent then
13345 if Present (Actions (N)) then
13346 Insert_Actions (N, Actions (N));
13347 end if;
13349 Rewrite (N, Right);
13351 -- Rewrite False AND THEN Right / True OR ELSE Right to Left.
13352 -- In this case we can forget the actions associated with Right,
13353 -- since they will never be executed.
13355 else
13356 Kill_Dead_Code (Right);
13357 Kill_Dead_Code (Actions (N));
13358 Rewrite (N, New_Occurrence_Of (Shortcut_Ent, Loc));
13359 end if;
13361 Adjust_Result_Type (N, Typ);
13362 return;
13363 end if;
13365 -- If Actions are present for the right operand, we have to do some
13366 -- special processing. We can't just let these actions filter back into
13367 -- code preceding the short circuit (which is what would have happened
13368 -- if we had not trapped them in the short-circuit form), since they
13369 -- must only be executed if the right operand of the short circuit is
13370 -- executed and not otherwise.
13372 if Useful (Actions (N)) then
13373 Actlist := Actions (N);
13375 -- The old approach is to expand:
13377 -- left AND THEN right
13379 -- into
13381 -- C : Boolean := False;
13382 -- IF left THEN
13383 -- Actions;
13384 -- IF right THEN
13385 -- C := True;
13386 -- END IF;
13387 -- END IF;
13389 -- and finally rewrite the operator into a reference to C. Similarly
13390 -- for left OR ELSE right, with negated values. Note that this
13391 -- rewrite causes some difficulties for coverage analysis because
13392 -- of the introduction of the new variable C, which obscures the
13393 -- structure of the test.
13395 -- We use this "old approach" if Minimize_Expression_With_Actions
13396 -- is True.
13398 if Minimize_Expression_With_Actions then
13399 Op_Var := Make_Temporary (Loc, 'C', Related_Node => N);
13401 Insert_Action (N,
13402 Make_Object_Declaration (Loc,
13403 Defining_Identifier => Op_Var,
13404 Object_Definition =>
13405 New_Occurrence_Of (Standard_Boolean, Loc),
13406 Expression =>
13407 New_Occurrence_Of (Shortcut_Ent, Loc)));
13409 Append_To (Actlist,
13410 Make_Implicit_If_Statement (Right,
13411 Condition => Make_Test_Expr (Right),
13412 Then_Statements => New_List (
13413 Make_Assignment_Statement (LocR,
13414 Name => New_Occurrence_Of (Op_Var, LocR),
13415 Expression =>
13416 New_Occurrence_Of
13417 (Boolean_Literals (not Shortcut_Value), LocR)))));
13419 Insert_Action (N,
13420 Make_Implicit_If_Statement (Left,
13421 Condition => Make_Test_Expr (Left),
13422 Then_Statements => Actlist));
13424 Rewrite (N, New_Occurrence_Of (Op_Var, Loc));
13425 Analyze_And_Resolve (N, Standard_Boolean);
13427 -- The new approach (the default) is to use an
13428 -- Expression_With_Actions node for the right operand of the
13429 -- short-circuit form. Note that this solves the traceability
13430 -- problems for coverage analysis.
13432 else
13433 Rewrite (Right,
13434 Make_Expression_With_Actions (LocR,
13435 Expression => Relocate_Node (Right),
13436 Actions => Actlist));
13438 Set_Actions (N, No_List);
13439 Analyze_And_Resolve (Right, Standard_Boolean);
13440 end if;
13442 Adjust_Result_Type (N, Typ);
13443 return;
13444 end if;
13446 -- No actions present, check for cases of right argument True/False
13448 if Compile_Time_Known_Value (Right) then
13450 -- Mark SCO for left condition as compile time known
13452 if Generate_SCO and then Comes_From_Source (Right) then
13453 Set_SCO_Condition (Right, Expr_Value_E (Right) = Standard_True);
13454 end if;
13456 -- Change (Left and then True), (Left or else False) to Left. Note
13457 -- that we know there are no actions associated with the right
13458 -- operand, since we just checked for this case above.
13460 if Expr_Value_E (Right) /= Shortcut_Ent then
13461 Rewrite (N, Left);
13463 -- Change (Left and then False), (Left or else True) to Right,
13464 -- making sure to preserve any side effects associated with the Left
13465 -- operand.
13467 else
13468 Remove_Side_Effects (Left);
13469 Rewrite (N, New_Occurrence_Of (Shortcut_Ent, Loc));
13470 end if;
13471 end if;
13473 Adjust_Result_Type (N, Typ);
13474 end Expand_Short_Circuit_Operator;
13476 ------------------------------------
13477 -- Fixup_Universal_Fixed_Operation --
13478 -------------------------------------
13480 procedure Fixup_Universal_Fixed_Operation (N : Node_Id) is
13481 Conv : constant Node_Id := Parent (N);
13483 begin
13484 -- We must have a type conversion immediately above us
13486 pragma Assert (Nkind (Conv) = N_Type_Conversion);
13488 -- Normally the type conversion gives our target type. The exception
13489 -- occurs in the case of the Round attribute, where the conversion
13490 -- will be to universal real, and our real type comes from the Round
13491 -- attribute (as well as an indication that we must round the result)
13493 if Etype (Conv) = Universal_Real
13494 and then Nkind (Parent (Conv)) = N_Attribute_Reference
13495 and then Attribute_Name (Parent (Conv)) = Name_Round
13496 then
13497 Set_Etype (N, Base_Type (Etype (Parent (Conv))));
13498 Set_Rounded_Result (N);
13500 -- Normal case where type comes from conversion above us
13502 else
13503 Set_Etype (N, Base_Type (Etype (Conv)));
13504 end if;
13505 end Fixup_Universal_Fixed_Operation;
13507 ----------------------------
13508 -- Get_First_Index_Bounds --
13509 ----------------------------
13511 procedure Get_First_Index_Bounds (T : Entity_Id; Lo, Hi : out Uint) is
13512 Typ : Entity_Id;
13514 begin
13515 pragma Assert (Is_Array_Type (T));
13517 -- This follows Sem_Eval.Compile_Time_Known_Bounds
13519 if Ekind (T) = E_String_Literal_Subtype then
13520 Lo := Expr_Value (String_Literal_Low_Bound (T));
13521 Hi := Lo + String_Literal_Length (T) - 1;
13523 else
13524 Typ := Underlying_Type (Etype (First_Index (T)));
13526 Lo := Expr_Value (Type_Low_Bound (Typ));
13527 Hi := Expr_Value (Type_High_Bound (Typ));
13528 end if;
13529 end Get_First_Index_Bounds;
13531 ------------------------
13532 -- Get_Size_For_Range --
13533 ------------------------
13535 function Get_Size_For_Range (Lo, Hi : Uint) return Uint is
13537 function Is_OK_For_Range (Siz : Uint) return Boolean;
13538 -- Return True if a signed integer with given size can cover Lo .. Hi
13540 --------------------------
13541 -- Is_OK_For_Range --
13542 --------------------------
13544 function Is_OK_For_Range (Siz : Uint) return Boolean is
13545 B : constant Uint := Uint_2 ** (Siz - 1);
13547 begin
13548 -- Test B = 2 ** (size - 1) (can accommodate -B .. +(B - 1))
13550 return Lo >= -B and then Hi >= -B and then Lo < B and then Hi < B;
13551 end Is_OK_For_Range;
13553 begin
13554 -- This is (almost always) the size of Integer
13556 if Is_OK_For_Range (Uint_32) then
13557 return Uint_32;
13559 -- Check 63
13561 elsif Is_OK_For_Range (Uint_63) then
13562 return Uint_63;
13564 -- This is (almost always) the size of Long_Long_Integer
13566 elsif Is_OK_For_Range (Uint_64) then
13567 return Uint_64;
13569 -- Check 127
13571 elsif Is_OK_For_Range (Uint_127) then
13572 return Uint_127;
13574 else
13575 return Uint_128;
13576 end if;
13577 end Get_Size_For_Range;
13579 -------------------------------
13580 -- Insert_Dereference_Action --
13581 -------------------------------
13583 procedure Insert_Dereference_Action (N : Node_Id) is
13584 function Is_Checked_Storage_Pool (P : Entity_Id) return Boolean;
13585 -- Return true if type of P is derived from Checked_Pool;
13587 -----------------------------
13588 -- Is_Checked_Storage_Pool --
13589 -----------------------------
13591 function Is_Checked_Storage_Pool (P : Entity_Id) return Boolean is
13592 T : Entity_Id;
13594 begin
13595 if No (P) then
13596 return False;
13597 end if;
13599 T := Etype (P);
13600 while T /= Etype (T) loop
13601 if Is_RTE (T, RE_Checked_Pool) then
13602 return True;
13603 else
13604 T := Etype (T);
13605 end if;
13606 end loop;
13608 return False;
13609 end Is_Checked_Storage_Pool;
13611 -- Local variables
13613 Context : constant Node_Id := Parent (N);
13614 Ptr_Typ : constant Entity_Id := Etype (N);
13615 Desig_Typ : constant Entity_Id :=
13616 Available_View (Designated_Type (Ptr_Typ));
13617 Loc : constant Source_Ptr := Sloc (N);
13618 Pool : constant Entity_Id := Associated_Storage_Pool (Ptr_Typ);
13620 Addr : Entity_Id;
13621 Alig : Entity_Id;
13622 Deref : Node_Id;
13623 Size : Entity_Id;
13624 Size_Bits : Node_Id;
13625 Stmt : Node_Id;
13627 -- Start of processing for Insert_Dereference_Action
13629 begin
13630 pragma Assert (Nkind (Context) = N_Explicit_Dereference);
13632 -- Do not re-expand a dereference which has already been processed by
13633 -- this routine.
13635 if Has_Dereference_Action (Context) then
13636 return;
13638 -- Do not perform this type of expansion for internally-generated
13639 -- dereferences.
13641 elsif not Comes_From_Source (Original_Node (Context)) then
13642 return;
13644 -- A dereference action is only applicable to objects which have been
13645 -- allocated on a checked pool.
13647 elsif not Is_Checked_Storage_Pool (Pool) then
13648 return;
13649 end if;
13651 -- Extract the address of the dereferenced object. Generate:
13653 -- Addr : System.Address := <N>'Pool_Address;
13655 Addr := Make_Temporary (Loc, 'P');
13657 Insert_Action (N,
13658 Make_Object_Declaration (Loc,
13659 Defining_Identifier => Addr,
13660 Object_Definition =>
13661 New_Occurrence_Of (RTE (RE_Address), Loc),
13662 Expression =>
13663 Make_Attribute_Reference (Loc,
13664 Prefix => Duplicate_Subexpr_Move_Checks (N),
13665 Attribute_Name => Name_Pool_Address)));
13667 -- Calculate the size of the dereferenced object. Generate:
13669 -- Size : Storage_Count := <N>.all'Size / Storage_Unit;
13671 Deref :=
13672 Make_Explicit_Dereference (Loc,
13673 Prefix => Duplicate_Subexpr_Move_Checks (N));
13674 Set_Has_Dereference_Action (Deref);
13676 Size_Bits :=
13677 Make_Attribute_Reference (Loc,
13678 Prefix => Deref,
13679 Attribute_Name => Name_Size);
13681 -- Special case of an unconstrained array: need to add descriptor size
13683 if Is_Array_Type (Desig_Typ)
13684 and then not Is_Constrained (First_Subtype (Desig_Typ))
13685 then
13686 Size_Bits :=
13687 Make_Op_Add (Loc,
13688 Left_Opnd =>
13689 Make_Attribute_Reference (Loc,
13690 Prefix =>
13691 New_Occurrence_Of (First_Subtype (Desig_Typ), Loc),
13692 Attribute_Name => Name_Descriptor_Size),
13693 Right_Opnd => Size_Bits);
13694 end if;
13696 Size := Make_Temporary (Loc, 'S');
13697 Insert_Action (N,
13698 Make_Object_Declaration (Loc,
13699 Defining_Identifier => Size,
13700 Object_Definition =>
13701 New_Occurrence_Of (RTE (RE_Storage_Count), Loc),
13702 Expression =>
13703 Make_Op_Divide (Loc,
13704 Left_Opnd => Size_Bits,
13705 Right_Opnd => Make_Integer_Literal (Loc, System_Storage_Unit))));
13707 -- Calculate the alignment of the dereferenced object. Generate:
13708 -- Alig : constant Storage_Count := <N>.all'Alignment;
13710 Deref :=
13711 Make_Explicit_Dereference (Loc,
13712 Prefix => Duplicate_Subexpr_Move_Checks (N));
13713 Set_Has_Dereference_Action (Deref);
13715 Alig := Make_Temporary (Loc, 'A');
13716 Insert_Action (N,
13717 Make_Object_Declaration (Loc,
13718 Defining_Identifier => Alig,
13719 Object_Definition =>
13720 New_Occurrence_Of (RTE (RE_Storage_Count), Loc),
13721 Expression =>
13722 Make_Attribute_Reference (Loc,
13723 Prefix => Deref,
13724 Attribute_Name => Name_Alignment)));
13726 -- A dereference of a controlled object requires special processing. The
13727 -- finalization machinery requests additional space from the underlying
13728 -- pool to allocate and hide two pointers. As a result, a checked pool
13729 -- may mark the wrong memory as valid. Since checked pools do not have
13730 -- knowledge of hidden pointers, we have to bring the two pointers back
13731 -- in view in order to restore the original state of the object.
13733 -- The address manipulation is not performed for access types that are
13734 -- subject to pragma No_Heap_Finalization because the two pointers do
13735 -- not exist in the first place.
13737 if No_Heap_Finalization (Ptr_Typ) then
13738 null;
13740 elsif Needs_Finalization (Desig_Typ) then
13742 -- Adjust the address and size of the dereferenced object. Generate:
13743 -- Adjust_Controlled_Dereference (Addr, Size, Alig);
13745 Stmt :=
13746 Make_Procedure_Call_Statement (Loc,
13747 Name =>
13748 New_Occurrence_Of (RTE (RE_Adjust_Controlled_Dereference), Loc),
13749 Parameter_Associations => New_List (
13750 New_Occurrence_Of (Addr, Loc),
13751 New_Occurrence_Of (Size, Loc),
13752 New_Occurrence_Of (Alig, Loc)));
13754 -- Class-wide types complicate things because we cannot determine
13755 -- statically whether the actual object is truly controlled. We must
13756 -- generate a runtime check to detect this property. Generate:
13758 -- if Needs_Finalization (<N>.all'Tag) then
13759 -- <Stmt>;
13760 -- end if;
13762 if Is_Class_Wide_Type (Desig_Typ) then
13763 Deref :=
13764 Make_Explicit_Dereference (Loc,
13765 Prefix => Duplicate_Subexpr_Move_Checks (N));
13766 Set_Has_Dereference_Action (Deref);
13768 Stmt :=
13769 Make_Implicit_If_Statement (N,
13770 Condition =>
13771 Make_Function_Call (Loc,
13772 Name =>
13773 New_Occurrence_Of (RTE (RE_Needs_Finalization), Loc),
13774 Parameter_Associations => New_List (
13775 Make_Attribute_Reference (Loc,
13776 Prefix => Deref,
13777 Attribute_Name => Name_Tag))),
13778 Then_Statements => New_List (Stmt));
13779 end if;
13781 Insert_Action (N, Stmt);
13782 end if;
13784 -- Generate:
13785 -- Dereference (Pool, Addr, Size, Alig);
13787 Insert_Action (N,
13788 Make_Procedure_Call_Statement (Loc,
13789 Name =>
13790 New_Occurrence_Of
13791 (Find_Prim_Op (Etype (Pool), Name_Dereference), Loc),
13792 Parameter_Associations => New_List (
13793 New_Occurrence_Of (Pool, Loc),
13794 New_Occurrence_Of (Addr, Loc),
13795 New_Occurrence_Of (Size, Loc),
13796 New_Occurrence_Of (Alig, Loc))));
13798 -- Mark the explicit dereference as processed to avoid potential
13799 -- infinite expansion.
13801 Set_Has_Dereference_Action (Context);
13803 exception
13804 when RE_Not_Available =>
13805 return;
13806 end Insert_Dereference_Action;
13808 --------------------------------
13809 -- Integer_Promotion_Possible --
13810 --------------------------------
13812 function Integer_Promotion_Possible (N : Node_Id) return Boolean is
13813 Operand : constant Node_Id := Expression (N);
13814 Operand_Type : constant Entity_Id := Etype (Operand);
13815 Root_Operand_Type : constant Entity_Id := Root_Type (Operand_Type);
13817 begin
13818 pragma Assert (Nkind (N) = N_Type_Conversion);
13820 return
13822 -- We only do the transformation for source constructs. We assume
13823 -- that the expander knows what it is doing when it generates code.
13825 Comes_From_Source (N)
13827 -- If the operand type is Short_Integer or Short_Short_Integer,
13828 -- then we will promote to Integer, which is available on all
13829 -- targets, and is sufficient to ensure no intermediate overflow.
13830 -- Furthermore it is likely to be as efficient or more efficient
13831 -- than using the smaller type for the computation so we do this
13832 -- unconditionally.
13834 and then
13835 (Root_Operand_Type = Base_Type (Standard_Short_Integer)
13836 or else
13837 Root_Operand_Type = Base_Type (Standard_Short_Short_Integer))
13839 -- Test for interesting operation, which includes addition,
13840 -- division, exponentiation, multiplication, subtraction, absolute
13841 -- value and unary negation. Unary "+" is omitted since it is a
13842 -- no-op and thus can't overflow.
13844 and then Nkind (Operand) in
13845 N_Op_Abs | N_Op_Add | N_Op_Divide | N_Op_Expon |
13846 N_Op_Minus | N_Op_Multiply | N_Op_Subtract;
13847 end Integer_Promotion_Possible;
13849 ------------------------------
13850 -- Make_Array_Comparison_Op --
13851 ------------------------------
13853 -- This is a hand-coded expansion of the following generic function:
13855 -- generic
13856 -- type elem is (<>);
13857 -- type index is (<>);
13858 -- type a is array (index range <>) of elem;
13860 -- function Gnnn (X : a; Y: a) return boolean is
13861 -- J : index := Y'first;
13863 -- begin
13864 -- if X'length = 0 then
13865 -- return false;
13867 -- elsif Y'length = 0 then
13868 -- return true;
13870 -- else
13871 -- for I in X'range loop
13872 -- if X (I) = Y (J) then
13873 -- if J = Y'last then
13874 -- exit;
13875 -- else
13876 -- J := index'succ (J);
13877 -- end if;
13879 -- else
13880 -- return X (I) > Y (J);
13881 -- end if;
13882 -- end loop;
13884 -- return X'length > Y'length;
13885 -- end if;
13886 -- end Gnnn;
13888 -- Note that since we are essentially doing this expansion by hand, we
13889 -- do not need to generate an actual or formal generic part, just the
13890 -- instantiated function itself.
13892 function Make_Array_Comparison_Op
13893 (Typ : Entity_Id;
13894 Nod : Node_Id) return Node_Id
13896 Loc : constant Source_Ptr := Sloc (Nod);
13898 X : constant Entity_Id := Make_Defining_Identifier (Loc, Name_uX);
13899 Y : constant Entity_Id := Make_Defining_Identifier (Loc, Name_uY);
13900 I : constant Entity_Id := Make_Defining_Identifier (Loc, Name_uI);
13901 J : constant Entity_Id := Make_Defining_Identifier (Loc, Name_uJ);
13903 Index : constant Entity_Id := Base_Type (Etype (First_Index (Typ)));
13905 Loop_Statement : Node_Id;
13906 Loop_Body : Node_Id;
13907 If_Stat : Node_Id;
13908 Inner_If : Node_Id;
13909 Final_Expr : Node_Id;
13910 Func_Body : Node_Id;
13911 Func_Name : Entity_Id;
13912 Formals : List_Id;
13913 Length1 : Node_Id;
13914 Length2 : Node_Id;
13916 begin
13917 -- if J = Y'last then
13918 -- exit;
13919 -- else
13920 -- J := index'succ (J);
13921 -- end if;
13923 Inner_If :=
13924 Make_Implicit_If_Statement (Nod,
13925 Condition =>
13926 Make_Op_Eq (Loc,
13927 Left_Opnd => New_Occurrence_Of (J, Loc),
13928 Right_Opnd =>
13929 Make_Attribute_Reference (Loc,
13930 Prefix => New_Occurrence_Of (Y, Loc),
13931 Attribute_Name => Name_Last)),
13933 Then_Statements => New_List (
13934 Make_Exit_Statement (Loc)),
13936 Else_Statements =>
13937 New_List (
13938 Make_Assignment_Statement (Loc,
13939 Name => New_Occurrence_Of (J, Loc),
13940 Expression =>
13941 Make_Attribute_Reference (Loc,
13942 Prefix => New_Occurrence_Of (Index, Loc),
13943 Attribute_Name => Name_Succ,
13944 Expressions => New_List (New_Occurrence_Of (J, Loc))))));
13946 -- if X (I) = Y (J) then
13947 -- if ... end if;
13948 -- else
13949 -- return X (I) > Y (J);
13950 -- end if;
13952 Loop_Body :=
13953 Make_Implicit_If_Statement (Nod,
13954 Condition =>
13955 Make_Op_Eq (Loc,
13956 Left_Opnd =>
13957 Make_Indexed_Component (Loc,
13958 Prefix => New_Occurrence_Of (X, Loc),
13959 Expressions => New_List (New_Occurrence_Of (I, Loc))),
13961 Right_Opnd =>
13962 Make_Indexed_Component (Loc,
13963 Prefix => New_Occurrence_Of (Y, Loc),
13964 Expressions => New_List (New_Occurrence_Of (J, Loc)))),
13966 Then_Statements => New_List (Inner_If),
13968 Else_Statements => New_List (
13969 Make_Simple_Return_Statement (Loc,
13970 Expression =>
13971 Make_Op_Gt (Loc,
13972 Left_Opnd =>
13973 Make_Indexed_Component (Loc,
13974 Prefix => New_Occurrence_Of (X, Loc),
13975 Expressions => New_List (New_Occurrence_Of (I, Loc))),
13977 Right_Opnd =>
13978 Make_Indexed_Component (Loc,
13979 Prefix => New_Occurrence_Of (Y, Loc),
13980 Expressions => New_List (
13981 New_Occurrence_Of (J, Loc)))))));
13983 -- for I in X'range loop
13984 -- if ... end if;
13985 -- end loop;
13987 Loop_Statement :=
13988 Make_Implicit_Loop_Statement (Nod,
13989 Identifier => Empty,
13991 Iteration_Scheme =>
13992 Make_Iteration_Scheme (Loc,
13993 Loop_Parameter_Specification =>
13994 Make_Loop_Parameter_Specification (Loc,
13995 Defining_Identifier => I,
13996 Discrete_Subtype_Definition =>
13997 Make_Attribute_Reference (Loc,
13998 Prefix => New_Occurrence_Of (X, Loc),
13999 Attribute_Name => Name_Range))),
14001 Statements => New_List (Loop_Body));
14003 -- if X'length = 0 then
14004 -- return false;
14005 -- elsif Y'length = 0 then
14006 -- return true;
14007 -- else
14008 -- for ... loop ... end loop;
14009 -- return X'length > Y'length;
14010 -- end if;
14012 Length1 :=
14013 Make_Attribute_Reference (Loc,
14014 Prefix => New_Occurrence_Of (X, Loc),
14015 Attribute_Name => Name_Length);
14017 Length2 :=
14018 Make_Attribute_Reference (Loc,
14019 Prefix => New_Occurrence_Of (Y, Loc),
14020 Attribute_Name => Name_Length);
14022 Final_Expr :=
14023 Make_Op_Gt (Loc,
14024 Left_Opnd => Length1,
14025 Right_Opnd => Length2);
14027 If_Stat :=
14028 Make_Implicit_If_Statement (Nod,
14029 Condition =>
14030 Make_Op_Eq (Loc,
14031 Left_Opnd =>
14032 Make_Attribute_Reference (Loc,
14033 Prefix => New_Occurrence_Of (X, Loc),
14034 Attribute_Name => Name_Length),
14035 Right_Opnd =>
14036 Make_Integer_Literal (Loc, 0)),
14038 Then_Statements =>
14039 New_List (
14040 Make_Simple_Return_Statement (Loc,
14041 Expression => New_Occurrence_Of (Standard_False, Loc))),
14043 Elsif_Parts => New_List (
14044 Make_Elsif_Part (Loc,
14045 Condition =>
14046 Make_Op_Eq (Loc,
14047 Left_Opnd =>
14048 Make_Attribute_Reference (Loc,
14049 Prefix => New_Occurrence_Of (Y, Loc),
14050 Attribute_Name => Name_Length),
14051 Right_Opnd =>
14052 Make_Integer_Literal (Loc, 0)),
14054 Then_Statements =>
14055 New_List (
14056 Make_Simple_Return_Statement (Loc,
14057 Expression => New_Occurrence_Of (Standard_True, Loc))))),
14059 Else_Statements => New_List (
14060 Loop_Statement,
14061 Make_Simple_Return_Statement (Loc,
14062 Expression => Final_Expr)));
14064 -- (X : a; Y: a)
14066 Formals := New_List (
14067 Make_Parameter_Specification (Loc,
14068 Defining_Identifier => X,
14069 Parameter_Type => New_Occurrence_Of (Typ, Loc)),
14071 Make_Parameter_Specification (Loc,
14072 Defining_Identifier => Y,
14073 Parameter_Type => New_Occurrence_Of (Typ, Loc)));
14075 -- function Gnnn (...) return boolean is
14076 -- J : index := Y'first;
14077 -- begin
14078 -- if ... end if;
14079 -- end Gnnn;
14081 Func_Name := Make_Temporary (Loc, 'G');
14083 Func_Body :=
14084 Make_Subprogram_Body (Loc,
14085 Specification =>
14086 Make_Function_Specification (Loc,
14087 Defining_Unit_Name => Func_Name,
14088 Parameter_Specifications => Formals,
14089 Result_Definition => New_Occurrence_Of (Standard_Boolean, Loc)),
14091 Declarations => New_List (
14092 Make_Object_Declaration (Loc,
14093 Defining_Identifier => J,
14094 Object_Definition => New_Occurrence_Of (Index, Loc),
14095 Expression =>
14096 Make_Attribute_Reference (Loc,
14097 Prefix => New_Occurrence_Of (Y, Loc),
14098 Attribute_Name => Name_First))),
14100 Handled_Statement_Sequence =>
14101 Make_Handled_Sequence_Of_Statements (Loc,
14102 Statements => New_List (If_Stat)));
14104 return Func_Body;
14105 end Make_Array_Comparison_Op;
14107 ---------------------------
14108 -- Make_Boolean_Array_Op --
14109 ---------------------------
14111 -- For logical operations on boolean arrays, expand in line the following,
14112 -- replacing 'and' with 'or' or 'xor' where needed:
14114 -- function Annn (A : typ; B: typ) return typ is
14115 -- C : typ;
14116 -- begin
14117 -- for J in A'range loop
14118 -- C (J) := A (J) op B (J);
14119 -- end loop;
14120 -- return C;
14121 -- end Annn;
14123 -- or in the case of Transform_Function_Array:
14125 -- procedure Annn (A : typ; B: typ; RESULT: out typ) is
14126 -- begin
14127 -- for J in A'range loop
14128 -- RESULT (J) := A (J) op B (J);
14129 -- end loop;
14130 -- end Annn;
14132 -- Here typ is the boolean array type
14134 function Make_Boolean_Array_Op
14135 (Typ : Entity_Id;
14136 N : Node_Id) return Node_Id
14138 Loc : constant Source_Ptr := Sloc (N);
14140 A : constant Entity_Id := Make_Defining_Identifier (Loc, Name_uA);
14141 B : constant Entity_Id := Make_Defining_Identifier (Loc, Name_uB);
14142 J : constant Entity_Id := Make_Defining_Identifier (Loc, Name_uJ);
14144 C : Entity_Id;
14146 A_J : Node_Id;
14147 B_J : Node_Id;
14148 C_J : Node_Id;
14149 Op : Node_Id;
14151 Formals : List_Id;
14152 Func_Name : Entity_Id;
14153 Func_Body : Node_Id;
14154 Loop_Statement : Node_Id;
14156 begin
14157 if Transform_Function_Array then
14158 C := Make_Defining_Identifier (Loc, Name_UP_RESULT);
14159 else
14160 C := Make_Defining_Identifier (Loc, Name_uC);
14161 end if;
14163 A_J :=
14164 Make_Indexed_Component (Loc,
14165 Prefix => New_Occurrence_Of (A, Loc),
14166 Expressions => New_List (New_Occurrence_Of (J, Loc)));
14168 B_J :=
14169 Make_Indexed_Component (Loc,
14170 Prefix => New_Occurrence_Of (B, Loc),
14171 Expressions => New_List (New_Occurrence_Of (J, Loc)));
14173 C_J :=
14174 Make_Indexed_Component (Loc,
14175 Prefix => New_Occurrence_Of (C, Loc),
14176 Expressions => New_List (New_Occurrence_Of (J, Loc)));
14178 if Nkind (N) = N_Op_And then
14179 Op :=
14180 Make_Op_And (Loc,
14181 Left_Opnd => A_J,
14182 Right_Opnd => B_J);
14184 elsif Nkind (N) = N_Op_Or then
14185 Op :=
14186 Make_Op_Or (Loc,
14187 Left_Opnd => A_J,
14188 Right_Opnd => B_J);
14190 else
14191 Op :=
14192 Make_Op_Xor (Loc,
14193 Left_Opnd => A_J,
14194 Right_Opnd => B_J);
14195 end if;
14197 Loop_Statement :=
14198 Make_Implicit_Loop_Statement (N,
14199 Identifier => Empty,
14201 Iteration_Scheme =>
14202 Make_Iteration_Scheme (Loc,
14203 Loop_Parameter_Specification =>
14204 Make_Loop_Parameter_Specification (Loc,
14205 Defining_Identifier => J,
14206 Discrete_Subtype_Definition =>
14207 Make_Attribute_Reference (Loc,
14208 Prefix => New_Occurrence_Of (A, Loc),
14209 Attribute_Name => Name_Range))),
14211 Statements => New_List (
14212 Make_Assignment_Statement (Loc,
14213 Name => C_J,
14214 Expression => Op)));
14216 Formals := New_List (
14217 Make_Parameter_Specification (Loc,
14218 Defining_Identifier => A,
14219 Parameter_Type => New_Occurrence_Of (Typ, Loc)),
14221 Make_Parameter_Specification (Loc,
14222 Defining_Identifier => B,
14223 Parameter_Type => New_Occurrence_Of (Typ, Loc)));
14225 if Transform_Function_Array then
14226 Append_To (Formals,
14227 Make_Parameter_Specification (Loc,
14228 Defining_Identifier => C,
14229 Out_Present => True,
14230 Parameter_Type => New_Occurrence_Of (Typ, Loc)));
14231 end if;
14233 Func_Name := Make_Temporary (Loc, 'A');
14234 Set_Is_Inlined (Func_Name);
14236 if Transform_Function_Array then
14237 Func_Body :=
14238 Make_Subprogram_Body (Loc,
14239 Specification =>
14240 Make_Procedure_Specification (Loc,
14241 Defining_Unit_Name => Func_Name,
14242 Parameter_Specifications => Formals),
14244 Declarations => New_List,
14246 Handled_Statement_Sequence =>
14247 Make_Handled_Sequence_Of_Statements (Loc,
14248 Statements => New_List (Loop_Statement)));
14250 else
14251 Func_Body :=
14252 Make_Subprogram_Body (Loc,
14253 Specification =>
14254 Make_Function_Specification (Loc,
14255 Defining_Unit_Name => Func_Name,
14256 Parameter_Specifications => Formals,
14257 Result_Definition => New_Occurrence_Of (Typ, Loc)),
14259 Declarations => New_List (
14260 Make_Object_Declaration (Loc,
14261 Defining_Identifier => C,
14262 Object_Definition => New_Occurrence_Of (Typ, Loc))),
14264 Handled_Statement_Sequence =>
14265 Make_Handled_Sequence_Of_Statements (Loc,
14266 Statements => New_List (
14267 Loop_Statement,
14268 Make_Simple_Return_Statement (Loc,
14269 Expression => New_Occurrence_Of (C, Loc)))));
14270 end if;
14272 return Func_Body;
14273 end Make_Boolean_Array_Op;
14275 -----------------------------------------
14276 -- Minimized_Eliminated_Overflow_Check --
14277 -----------------------------------------
14279 function Minimized_Eliminated_Overflow_Check (N : Node_Id) return Boolean is
14280 begin
14281 -- The MINIMIZED mode operates in Long_Long_Integer so we cannot use it
14282 -- if the type of the expression is already larger.
14284 return
14285 Is_Signed_Integer_Type (Etype (N))
14286 and then Overflow_Check_Mode in Minimized_Or_Eliminated
14287 and then not (Overflow_Check_Mode = Minimized
14288 and then
14289 Esize (Etype (N)) > Standard_Long_Long_Integer_Size);
14290 end Minimized_Eliminated_Overflow_Check;
14292 ----------------------------
14293 -- Narrow_Large_Operation --
14294 ----------------------------
14296 procedure Narrow_Large_Operation (N : Node_Id) is
14297 Kind : constant Node_Kind := Nkind (N);
14298 Otyp : constant Entity_Id := Etype (N);
14299 In_Rng : constant Boolean := Kind = N_In;
14300 Binary : constant Boolean := Kind in N_Binary_Op or else In_Rng;
14301 Compar : constant Boolean := Kind in N_Op_Compare or else In_Rng;
14302 R : constant Node_Id := Right_Opnd (N);
14303 Typ : constant Entity_Id := Etype (R);
14304 Tsiz : constant Uint := RM_Size (Typ);
14306 -- Local variables
14308 L : Node_Id;
14309 Llo, Lhi : Uint;
14310 Rlo, Rhi : Uint;
14311 Lsiz, Rsiz : Uint;
14312 Nlo, Nhi : Uint;
14313 Nsiz : Uint;
14314 Ntyp : Entity_Id;
14315 Nop : Node_Id;
14316 OK : Boolean;
14318 -- Start of processing for Narrow_Large_Operation
14320 begin
14321 -- First, determine the range of the left operand, if any
14323 if Binary then
14324 L := Left_Opnd (N);
14325 Determine_Range (L, OK, Llo, Lhi, Assume_Valid => True);
14326 if not OK then
14327 return;
14328 end if;
14330 else
14331 L := Empty;
14332 Llo := Uint_0;
14333 Lhi := Uint_0;
14334 end if;
14336 -- Second, determine the range of the right operand, which can itself
14337 -- be a range, in which case we take the lower bound of the low bound
14338 -- and the upper bound of the high bound.
14340 if In_Rng then
14341 declare
14342 Zlo, Zhi : Uint;
14344 begin
14345 Determine_Range
14346 (Low_Bound (R), OK, Rlo, Zhi, Assume_Valid => True);
14347 if not OK then
14348 return;
14349 end if;
14351 Determine_Range
14352 (High_Bound (R), OK, Zlo, Rhi, Assume_Valid => True);
14353 if not OK then
14354 return;
14355 end if;
14356 end;
14358 else
14359 Determine_Range (R, OK, Rlo, Rhi, Assume_Valid => True);
14360 if not OK then
14361 return;
14362 end if;
14363 end if;
14365 -- Then compute a size suitable for each range
14367 if Binary then
14368 Lsiz := Get_Size_For_Range (Llo, Lhi);
14369 else
14370 Lsiz := Uint_0;
14371 end if;
14373 Rsiz := Get_Size_For_Range (Rlo, Rhi);
14375 -- Now compute the size of the narrower type
14377 if Compar then
14378 -- The type must be able to accommodate the operands
14380 Nsiz := UI_Max (Lsiz, Rsiz);
14382 else
14383 -- The type must be able to accommodate the operand(s) and result.
14385 -- Note that Determine_Range typically does not report the bounds of
14386 -- the value as being larger than those of the base type, which means
14387 -- that it does not report overflow (see also Enable_Overflow_Check).
14389 Determine_Range (N, OK, Nlo, Nhi, Assume_Valid => True);
14390 if not OK then
14391 return;
14392 end if;
14394 -- Therefore, if Nsiz is not lower than the size of the original type
14395 -- here, we cannot be sure that the operation does not overflow.
14397 Nsiz := Get_Size_For_Range (Nlo, Nhi);
14398 Nsiz := UI_Max (Nsiz, Lsiz);
14399 Nsiz := UI_Max (Nsiz, Rsiz);
14400 end if;
14402 -- If the size is not lower than the size of the original type, then
14403 -- there is no point in changing the type, except in the case where
14404 -- we can remove a conversion to the original type from an operand.
14406 if Nsiz >= Tsiz
14407 and then not (Binary
14408 and then Nkind (L) = N_Type_Conversion
14409 and then Entity (Subtype_Mark (L)) = Typ)
14410 and then not (Nkind (R) = N_Type_Conversion
14411 and then Entity (Subtype_Mark (R)) = Typ)
14412 then
14413 return;
14414 end if;
14416 -- Now pick the narrower type according to the size. We use the base
14417 -- type instead of the first subtype because operations are done in
14418 -- the base type, so this avoids the need for useless conversions.
14420 if Nsiz <= System_Max_Integer_Size then
14421 Ntyp := Etype (Integer_Type_For (Nsiz, Uns => False));
14422 else
14423 return;
14424 end if;
14426 -- Finally, rewrite the operation in the narrower type, but make sure
14427 -- not to perform name resolution for the operator again.
14429 Nop := New_Op_Node (Kind, Sloc (N));
14430 if Nkind (N) in N_Has_Entity then
14431 Set_Entity (Nop, Entity (N));
14432 end if;
14434 if Binary then
14435 Set_Left_Opnd (Nop, Convert_To (Ntyp, L));
14436 end if;
14438 if In_Rng then
14439 Set_Right_Opnd (Nop,
14440 Make_Range (Sloc (N),
14441 Convert_To (Ntyp, Low_Bound (R)),
14442 Convert_To (Ntyp, High_Bound (R))));
14443 else
14444 Set_Right_Opnd (Nop, Convert_To (Ntyp, R));
14445 end if;
14447 Rewrite (N, Nop);
14449 if Compar then
14450 -- Analyze it with the comparison type and checks suppressed since
14451 -- the conversions of the operands cannot overflow.
14453 Analyze_And_Resolve (N, Otyp, Suppress => Overflow_Check);
14455 else
14456 -- Analyze it with the narrower type and checks suppressed, but only
14457 -- when we are sure that the operation does not overflow, see above.
14459 if Nsiz < Tsiz then
14460 Analyze_And_Resolve (N, Ntyp, Suppress => Overflow_Check);
14461 else
14462 Analyze_And_Resolve (N, Ntyp);
14463 end if;
14465 -- Put back a conversion to the original type
14467 Convert_To_And_Rewrite (Typ, N);
14468 end if;
14469 end Narrow_Large_Operation;
14471 --------------------------------
14472 -- Optimize_Length_Comparison --
14473 --------------------------------
14475 procedure Optimize_Length_Comparison (N : Node_Id) is
14476 Loc : constant Source_Ptr := Sloc (N);
14477 Typ : constant Entity_Id := Etype (N);
14478 Result : Node_Id;
14480 Left : Node_Id;
14481 Right : Node_Id;
14482 -- First and Last attribute reference nodes, which end up as left and
14483 -- right operands of the optimized result.
14485 Is_Zero : Boolean;
14486 -- True for comparison operand of zero
14488 Maybe_Superflat : Boolean;
14489 -- True if we may be in the dynamic superflat case, i.e. Is_Zero is set
14490 -- to false but the comparison operand can be zero at run time. In this
14491 -- case, we normally cannot do anything because the canonical formula of
14492 -- the length is not valid, but there is one exception: when the operand
14493 -- is itself the length of an array with the same bounds as the array on
14494 -- the LHS, we can entirely optimize away the comparison.
14496 Comp : Node_Id;
14497 -- Comparison operand, set only if Is_Zero is false
14499 Ent : array (Pos range 1 .. 2) of Entity_Id := (Empty, Empty);
14500 -- Entities whose length is being compared
14502 Index : array (Pos range 1 .. 2) of Node_Id := (Empty, Empty);
14503 -- Integer_Literal nodes for length attribute expressions, or Empty
14504 -- if there is no such expression present.
14506 Op : Node_Kind := Nkind (N);
14507 -- Kind of comparison operator, gets flipped if operands backwards
14509 function Convert_To_Long_Long_Integer (N : Node_Id) return Node_Id;
14510 -- Given a discrete expression, returns a Long_Long_Integer typed
14511 -- expression representing the underlying value of the expression.
14512 -- This is done with an unchecked conversion to Long_Long_Integer.
14513 -- We use unchecked conversion to handle the enumeration type case.
14515 function Is_Entity_Length (N : Node_Id; Num : Pos) return Boolean;
14516 -- Tests if N is a length attribute applied to a simple entity. If so,
14517 -- returns True, and sets Ent to the entity, and Index to the integer
14518 -- literal provided as an attribute expression, or to Empty if none.
14519 -- Num is the index designating the relevant slot in Ent and Index.
14520 -- Also returns True if the expression is a generated type conversion
14521 -- whose expression is of the desired form. This latter case arises
14522 -- when Apply_Universal_Integer_Attribute_Check installs a conversion
14523 -- to check for being in range, which is not needed in this context.
14524 -- Returns False if neither condition holds.
14526 function Is_Optimizable (N : Node_Id) return Boolean;
14527 -- Tests N to see if it is an optimizable comparison value (defined as
14528 -- constant zero or one, or something else where the value is known to
14529 -- be nonnegative and in the 32-bit range and where the corresponding
14530 -- Length value is also known to be 32 bits). If result is true, sets
14531 -- Is_Zero, Maybe_Superflat and Comp accordingly.
14533 procedure Rewrite_For_Equal_Lengths;
14534 -- Rewrite the comparison of two equal lengths into either True or False
14536 ----------------------------------
14537 -- Convert_To_Long_Long_Integer --
14538 ----------------------------------
14540 function Convert_To_Long_Long_Integer (N : Node_Id) return Node_Id is
14541 begin
14542 return Unchecked_Convert_To (Standard_Long_Long_Integer, N);
14543 end Convert_To_Long_Long_Integer;
14545 ----------------------
14546 -- Is_Entity_Length --
14547 ----------------------
14549 function Is_Entity_Length (N : Node_Id; Num : Pos) return Boolean is
14550 begin
14551 if Nkind (N) = N_Attribute_Reference
14552 and then Attribute_Name (N) = Name_Length
14553 and then Is_Entity_Name (Prefix (N))
14554 then
14555 Ent (Num) := Entity (Prefix (N));
14557 if Present (Expressions (N)) then
14558 Index (Num) := First (Expressions (N));
14559 else
14560 Index (Num) := Empty;
14561 end if;
14563 return True;
14565 elsif Nkind (N) = N_Type_Conversion
14566 and then not Comes_From_Source (N)
14567 then
14568 return Is_Entity_Length (Expression (N), Num);
14570 else
14571 return False;
14572 end if;
14573 end Is_Entity_Length;
14575 --------------------
14576 -- Is_Optimizable --
14577 --------------------
14579 function Is_Optimizable (N : Node_Id) return Boolean is
14580 Val : Uint;
14581 OK : Boolean;
14582 Lo : Uint;
14583 Hi : Uint;
14584 Indx : Node_Id;
14585 Dbl : Boolean;
14586 Ityp : Entity_Id;
14588 begin
14589 if Compile_Time_Known_Value (N) then
14590 Val := Expr_Value (N);
14592 if Val = Uint_0 then
14593 Is_Zero := True;
14594 Maybe_Superflat := False;
14595 Comp := Empty;
14596 return True;
14598 elsif Val = Uint_1 then
14599 Is_Zero := False;
14600 Maybe_Superflat := False;
14601 Comp := Empty;
14602 return True;
14603 end if;
14604 end if;
14606 -- Here we have to make sure of being within a 32-bit range (take the
14607 -- full unsigned range so the length of 32-bit arrays is accepted).
14609 Determine_Range (N, OK, Lo, Hi, Assume_Valid => True);
14611 if not OK
14612 or else Lo < Uint_0
14613 or else Hi > Uint_2 ** 32
14614 then
14615 return False;
14616 end if;
14618 Maybe_Superflat := (Lo = Uint_0);
14620 -- Tests if N is also a length attribute applied to a simple entity
14622 Dbl := Is_Entity_Length (N, 2);
14624 -- We can deal with the superflat case only if N is also a length
14626 if Maybe_Superflat and then not Dbl then
14627 return False;
14628 end if;
14630 -- Comparison value was within range, so now we must check the index
14631 -- value to make sure it is also within 32 bits.
14633 for K in Pos range 1 .. 2 loop
14634 Indx := First_Index (Etype (Ent (K)));
14636 if Present (Index (K)) then
14637 for J in 2 .. UI_To_Int (Intval (Index (K))) loop
14638 Next_Index (Indx);
14639 end loop;
14640 end if;
14642 Ityp := Etype (Indx);
14644 if Esize (Ityp) > 32 then
14645 return False;
14646 end if;
14648 exit when not Dbl;
14649 end loop;
14651 Is_Zero := False;
14652 Comp := N;
14653 return True;
14654 end Is_Optimizable;
14656 -------------------------------
14657 -- Rewrite_For_Equal_Lengths --
14658 -------------------------------
14660 procedure Rewrite_For_Equal_Lengths is
14661 begin
14662 case Op is
14663 when N_Op_Eq
14664 | N_Op_Ge
14665 | N_Op_Le
14667 Rewrite (N,
14668 Convert_To (Typ,
14669 New_Occurrence_Of (Standard_True, Sloc (N))));
14671 when N_Op_Ne
14672 | N_Op_Gt
14673 | N_Op_Lt
14675 Rewrite (N,
14676 Convert_To (Typ,
14677 New_Occurrence_Of (Standard_False, Sloc (N))));
14679 when others =>
14680 raise Program_Error;
14681 end case;
14683 Analyze_And_Resolve (N, Typ);
14684 end Rewrite_For_Equal_Lengths;
14686 -- Start of processing for Optimize_Length_Comparison
14688 begin
14689 -- Nothing to do if not a comparison
14691 if Op not in N_Op_Compare then
14692 return;
14693 end if;
14695 -- Nothing to do if special -gnatd.P debug flag set.
14697 if Debug_Flag_Dot_PP then
14698 return;
14699 end if;
14701 -- Ent'Length op 0/1
14703 if Is_Entity_Length (Left_Opnd (N), 1)
14704 and then Is_Optimizable (Right_Opnd (N))
14705 then
14706 null;
14708 -- 0/1 op Ent'Length
14710 elsif Is_Entity_Length (Right_Opnd (N), 1)
14711 and then Is_Optimizable (Left_Opnd (N))
14712 then
14713 -- Flip comparison to opposite sense
14715 case Op is
14716 when N_Op_Lt => Op := N_Op_Gt;
14717 when N_Op_Le => Op := N_Op_Ge;
14718 when N_Op_Gt => Op := N_Op_Lt;
14719 when N_Op_Ge => Op := N_Op_Le;
14720 when others => null;
14721 end case;
14723 -- Else optimization not possible
14725 else
14726 return;
14727 end if;
14729 -- Fall through if we will do the optimization
14731 -- Cases to handle:
14733 -- X'Length = 0 => X'First > X'Last
14734 -- X'Length = 1 => X'First = X'Last
14735 -- X'Length = n => X'First + (n - 1) = X'Last
14737 -- X'Length /= 0 => X'First <= X'Last
14738 -- X'Length /= 1 => X'First /= X'Last
14739 -- X'Length /= n => X'First + (n - 1) /= X'Last
14741 -- X'Length >= 0 => always true, warn
14742 -- X'Length >= 1 => X'First <= X'Last
14743 -- X'Length >= n => X'First + (n - 1) <= X'Last
14745 -- X'Length > 0 => X'First <= X'Last
14746 -- X'Length > 1 => X'First < X'Last
14747 -- X'Length > n => X'First + (n - 1) < X'Last
14749 -- X'Length <= 0 => X'First > X'Last (warn, could be =)
14750 -- X'Length <= 1 => X'First >= X'Last
14751 -- X'Length <= n => X'First + (n - 1) >= X'Last
14753 -- X'Length < 0 => always false (warn)
14754 -- X'Length < 1 => X'First > X'Last
14755 -- X'Length < n => X'First + (n - 1) > X'Last
14757 -- Note: for the cases of n (not constant 0,1), we require that the
14758 -- corresponding index type be integer or shorter (i.e. not 64-bit),
14759 -- and the same for the comparison value. Then we do the comparison
14760 -- using 64-bit arithmetic (actually long long integer), so that we
14761 -- cannot have overflow intefering with the result.
14763 -- First deal with warning cases
14765 if Is_Zero then
14766 case Op is
14768 -- X'Length >= 0
14770 when N_Op_Ge =>
14771 Rewrite (N,
14772 Convert_To (Typ, New_Occurrence_Of (Standard_True, Loc)));
14773 Analyze_And_Resolve (N, Typ);
14774 Warn_On_Known_Condition (N);
14775 return;
14777 -- X'Length < 0
14779 when N_Op_Lt =>
14780 Rewrite (N,
14781 Convert_To (Typ, New_Occurrence_Of (Standard_False, Loc)));
14782 Analyze_And_Resolve (N, Typ);
14783 Warn_On_Known_Condition (N);
14784 return;
14786 when N_Op_Le =>
14787 if Constant_Condition_Warnings
14788 and then Comes_From_Source (Original_Node (N))
14789 then
14790 Error_Msg_N ("could replace by ""'=""?c?", N);
14791 end if;
14793 Op := N_Op_Eq;
14795 when others =>
14796 null;
14797 end case;
14798 end if;
14800 -- Build the First reference we will use
14802 Left :=
14803 Make_Attribute_Reference (Loc,
14804 Prefix => New_Occurrence_Of (Ent (1), Loc),
14805 Attribute_Name => Name_First);
14807 if Present (Index (1)) then
14808 Set_Expressions (Left, New_List (New_Copy (Index (1))));
14809 end if;
14811 -- Build the Last reference we will use
14813 Right :=
14814 Make_Attribute_Reference (Loc,
14815 Prefix => New_Occurrence_Of (Ent (1), Loc),
14816 Attribute_Name => Name_Last);
14818 if Present (Index (1)) then
14819 Set_Expressions (Right, New_List (New_Copy (Index (1))));
14820 end if;
14822 -- If general value case, then do the addition of (n - 1), and
14823 -- also add the needed conversions to type Long_Long_Integer.
14825 -- If n = Y'Length, we rewrite X'First + (n - 1) op X'Last into:
14827 -- Y'Last + (X'First - Y'First) op X'Last
14829 -- in the hope that X'First - Y'First can be computed statically.
14831 if Present (Comp) then
14832 if Present (Ent (2)) then
14833 declare
14834 Y_First : constant Node_Id :=
14835 Make_Attribute_Reference (Loc,
14836 Prefix => New_Occurrence_Of (Ent (2), Loc),
14837 Attribute_Name => Name_First);
14838 Y_Last : constant Node_Id :=
14839 Make_Attribute_Reference (Loc,
14840 Prefix => New_Occurrence_Of (Ent (2), Loc),
14841 Attribute_Name => Name_Last);
14842 R : Compare_Result;
14844 begin
14845 if Present (Index (2)) then
14846 Set_Expressions (Y_First, New_List (New_Copy (Index (2))));
14847 Set_Expressions (Y_Last, New_List (New_Copy (Index (2))));
14848 end if;
14850 Analyze (Left);
14851 Analyze (Y_First);
14853 -- If X'First = Y'First, simplify the above formula into a
14854 -- direct comparison of Y'Last and X'Last.
14856 R := Compile_Time_Compare (Left, Y_First, Assume_Valid => True);
14858 if R = EQ then
14859 Analyze (Right);
14860 Analyze (Y_Last);
14862 R := Compile_Time_Compare
14863 (Right, Y_Last, Assume_Valid => True);
14865 -- If the pairs of attributes are equal, we are done
14867 if R = EQ then
14868 Rewrite_For_Equal_Lengths;
14869 return;
14870 end if;
14872 -- If the base types are different, convert both operands to
14873 -- Long_Long_Integer, else compare them directly.
14875 if Base_Type (Etype (Right)) /= Base_Type (Etype (Y_Last))
14876 then
14877 Left := Convert_To_Long_Long_Integer (Y_Last);
14878 else
14879 Left := Y_Last;
14880 Comp := Empty;
14881 end if;
14883 -- Otherwise, use the above formula as-is
14885 else
14886 Left :=
14887 Make_Op_Add (Loc,
14888 Left_Opnd =>
14889 Convert_To_Long_Long_Integer (Y_Last),
14890 Right_Opnd =>
14891 Make_Op_Subtract (Loc,
14892 Left_Opnd =>
14893 Convert_To_Long_Long_Integer (Left),
14894 Right_Opnd =>
14895 Convert_To_Long_Long_Integer (Y_First)));
14896 end if;
14897 end;
14899 -- General value case
14901 else
14902 Left :=
14903 Make_Op_Add (Loc,
14904 Left_Opnd => Convert_To_Long_Long_Integer (Left),
14905 Right_Opnd =>
14906 Make_Op_Subtract (Loc,
14907 Left_Opnd => Convert_To_Long_Long_Integer (Comp),
14908 Right_Opnd => Make_Integer_Literal (Loc, 1)));
14909 end if;
14910 end if;
14912 -- We cannot do anything in the superflat case past this point
14914 if Maybe_Superflat then
14915 return;
14916 end if;
14918 -- If general operand, convert Last reference to Long_Long_Integer
14920 if Present (Comp) then
14921 Right := Convert_To_Long_Long_Integer (Right);
14922 end if;
14924 -- Check for cases to optimize
14926 -- X'Length = 0 => X'First > X'Last
14927 -- X'Length < 1 => X'First > X'Last
14928 -- X'Length < n => X'First + (n - 1) > X'Last
14930 if (Is_Zero and then Op = N_Op_Eq)
14931 or else (not Is_Zero and then Op = N_Op_Lt)
14932 then
14933 Result :=
14934 Make_Op_Gt (Loc,
14935 Left_Opnd => Left,
14936 Right_Opnd => Right);
14938 -- X'Length = 1 => X'First = X'Last
14939 -- X'Length = n => X'First + (n - 1) = X'Last
14941 elsif not Is_Zero and then Op = N_Op_Eq then
14942 Result :=
14943 Make_Op_Eq (Loc,
14944 Left_Opnd => Left,
14945 Right_Opnd => Right);
14947 -- X'Length /= 0 => X'First <= X'Last
14948 -- X'Length > 0 => X'First <= X'Last
14950 elsif Is_Zero and (Op = N_Op_Ne or else Op = N_Op_Gt) then
14951 Result :=
14952 Make_Op_Le (Loc,
14953 Left_Opnd => Left,
14954 Right_Opnd => Right);
14956 -- X'Length /= 1 => X'First /= X'Last
14957 -- X'Length /= n => X'First + (n - 1) /= X'Last
14959 elsif not Is_Zero and then Op = N_Op_Ne then
14960 Result :=
14961 Make_Op_Ne (Loc,
14962 Left_Opnd => Left,
14963 Right_Opnd => Right);
14965 -- X'Length >= 1 => X'First <= X'Last
14966 -- X'Length >= n => X'First + (n - 1) <= X'Last
14968 elsif not Is_Zero and then Op = N_Op_Ge then
14969 Result :=
14970 Make_Op_Le (Loc,
14971 Left_Opnd => Left,
14972 Right_Opnd => Right);
14974 -- X'Length > 1 => X'First < X'Last
14975 -- X'Length > n => X'First + (n = 1) < X'Last
14977 elsif not Is_Zero and then Op = N_Op_Gt then
14978 Result :=
14979 Make_Op_Lt (Loc,
14980 Left_Opnd => Left,
14981 Right_Opnd => Right);
14983 -- X'Length <= 1 => X'First >= X'Last
14984 -- X'Length <= n => X'First + (n - 1) >= X'Last
14986 elsif not Is_Zero and then Op = N_Op_Le then
14987 Result :=
14988 Make_Op_Ge (Loc,
14989 Left_Opnd => Left,
14990 Right_Opnd => Right);
14992 -- Should not happen at this stage
14994 else
14995 raise Program_Error;
14996 end if;
14998 -- Rewrite and finish up (we can suppress overflow checks, see above)
15000 Rewrite (N, Result);
15001 Analyze_And_Resolve (N, Typ, Suppress => Overflow_Check);
15002 end Optimize_Length_Comparison;
15004 --------------------------------
15005 -- Process_If_Case_Statements --
15006 --------------------------------
15008 procedure Process_If_Case_Statements (N : Node_Id; Stmts : List_Id) is
15009 Decl : Node_Id;
15011 begin
15012 Decl := First (Stmts);
15013 while Present (Decl) loop
15014 if Nkind (Decl) = N_Object_Declaration
15015 and then Is_Finalizable_Transient (Decl, N)
15016 then
15017 Process_Transient_In_Expression (Decl, N, Stmts);
15018 end if;
15020 Next (Decl);
15021 end loop;
15022 end Process_If_Case_Statements;
15024 -------------------------------------
15025 -- Process_Transient_In_Expression --
15026 -------------------------------------
15028 procedure Process_Transient_In_Expression
15029 (Obj_Decl : Node_Id;
15030 Expr : Node_Id;
15031 Stmts : List_Id)
15033 Loc : constant Source_Ptr := Sloc (Obj_Decl);
15034 Obj_Id : constant Entity_Id := Defining_Identifier (Obj_Decl);
15036 Hook_Context : constant Node_Id := Find_Hook_Context (Expr);
15037 -- The node on which to insert the hook as an action. This is usually
15038 -- the innermost enclosing non-transient construct.
15040 Fin_Call : Node_Id;
15041 Hook_Assign : Node_Id;
15042 Hook_Clear : Node_Id;
15043 Hook_Decl : Node_Id;
15044 Hook_Insert : Node_Id;
15045 Ptr_Decl : Node_Id;
15047 Fin_Context : Node_Id;
15048 -- The node after which to insert the finalization actions of the
15049 -- transient object.
15051 begin
15052 pragma Assert (Nkind (Expr) in N_Case_Expression
15053 | N_Expression_With_Actions
15054 | N_If_Expression);
15056 -- When the context is a Boolean evaluation, all three nodes capture the
15057 -- result of their computation in a local temporary:
15059 -- do
15060 -- Trans_Id : Ctrl_Typ := ...;
15061 -- Result : constant Boolean := ... Trans_Id ...;
15062 -- <finalize Trans_Id>
15063 -- in Result end;
15065 -- As a result, the finalization of any transient objects can safely
15066 -- take place after the result capture.
15068 -- ??? could this be extended to elementary types?
15070 if Is_Boolean_Type (Etype (Expr)) then
15071 Fin_Context := Last (Stmts);
15073 -- Otherwise the immediate context may not be safe enough to carry
15074 -- out transient object finalization due to aliasing and nesting of
15075 -- constructs. Insert calls to [Deep_]Finalize after the innermost
15076 -- enclosing non-transient construct.
15078 else
15079 Fin_Context := Hook_Context;
15080 end if;
15082 -- Mark the transient object as successfully processed to avoid double
15083 -- finalization.
15085 Set_Is_Finalized_Transient (Obj_Id);
15087 -- Construct all the pieces necessary to hook and finalize a transient
15088 -- object.
15090 Build_Transient_Object_Statements
15091 (Obj_Decl => Obj_Decl,
15092 Fin_Call => Fin_Call,
15093 Hook_Assign => Hook_Assign,
15094 Hook_Clear => Hook_Clear,
15095 Hook_Decl => Hook_Decl,
15096 Ptr_Decl => Ptr_Decl,
15097 Finalize_Obj => False);
15099 -- Add the access type which provides a reference to the transient
15100 -- object. Generate:
15102 -- type Ptr_Typ is access all Desig_Typ;
15104 Insert_Action (Hook_Context, Ptr_Decl);
15106 -- Add the temporary which acts as a hook to the transient object.
15107 -- Generate:
15109 -- Hook : Ptr_Id := null;
15111 Insert_Action (Hook_Context, Hook_Decl);
15113 -- When the transient object is initialized by an aggregate, the hook
15114 -- must capture the object after the last aggregate assignment takes
15115 -- place. Only then is the object considered initialized. Generate:
15117 -- Hook := Ptr_Typ (Obj_Id);
15118 -- <or>
15119 -- Hook := Obj_Id'Unrestricted_Access;
15121 if Ekind (Obj_Id) in E_Constant | E_Variable
15122 and then Present (Last_Aggregate_Assignment (Obj_Id))
15123 then
15124 Hook_Insert := Last_Aggregate_Assignment (Obj_Id);
15126 -- Otherwise the hook seizes the related object immediately
15128 else
15129 Hook_Insert := Obj_Decl;
15130 end if;
15132 Insert_After_And_Analyze (Hook_Insert, Hook_Assign);
15134 -- When the node is part of a return statement, there is no need to
15135 -- insert a finalization call, as the general finalization mechanism
15136 -- (see Build_Finalizer) would take care of the transient object on
15137 -- subprogram exit. Note that it would also be impossible to insert the
15138 -- finalization code after the return statement as this will render it
15139 -- unreachable.
15141 if Nkind (Fin_Context) = N_Simple_Return_Statement then
15142 null;
15144 -- Finalize the hook after the context has been evaluated. Generate:
15146 -- if Hook /= null then
15147 -- [Deep_]Finalize (Hook.all);
15148 -- Hook := null;
15149 -- end if;
15151 -- Note that the value returned by Find_Hook_Context may be an operator
15152 -- node, which is not a list member. We must locate the proper node in
15153 -- in the tree after which to insert the finalization code.
15155 else
15156 while not Is_List_Member (Fin_Context) loop
15157 Fin_Context := Parent (Fin_Context);
15158 end loop;
15160 pragma Assert (Present (Fin_Context));
15162 Insert_Action_After (Fin_Context,
15163 Make_Implicit_If_Statement (Obj_Decl,
15164 Condition =>
15165 Make_Op_Ne (Loc,
15166 Left_Opnd =>
15167 New_Occurrence_Of (Defining_Entity (Hook_Decl), Loc),
15168 Right_Opnd => Make_Null (Loc)),
15170 Then_Statements => New_List (
15171 Fin_Call,
15172 Hook_Clear)));
15173 end if;
15174 end Process_Transient_In_Expression;
15176 ------------------------
15177 -- Rewrite_Comparison --
15178 ------------------------
15180 procedure Rewrite_Comparison (N : Node_Id) is
15181 Typ : constant Entity_Id := Etype (N);
15183 False_Result : Boolean;
15184 True_Result : Boolean;
15186 begin
15187 if Nkind (N) = N_Type_Conversion then
15188 Rewrite_Comparison (Expression (N));
15189 return;
15191 elsif Nkind (N) not in N_Op_Compare then
15192 return;
15193 end if;
15195 -- If both operands are static, then the comparison has been already
15196 -- folded in evaluation.
15198 pragma Assert
15199 (not Is_Static_Expression (Left_Opnd (N))
15200 or else
15201 not Is_Static_Expression (Right_Opnd (N)));
15203 -- Determine the potential outcome of the comparison assuming that the
15204 -- operands are valid and emit a warning when the comparison evaluates
15205 -- to True or False only in the presence of invalid values.
15207 Warn_On_Constant_Valid_Condition (N);
15209 -- Determine the potential outcome of the comparison assuming that the
15210 -- operands are not valid.
15212 Test_Comparison
15213 (Op => N,
15214 Assume_Valid => False,
15215 True_Result => True_Result,
15216 False_Result => False_Result);
15218 -- The outcome is a decisive False or True, rewrite the operator into a
15219 -- non-static literal.
15221 if False_Result or True_Result then
15222 Rewrite (N,
15223 Convert_To (Typ,
15224 New_Occurrence_Of (Boolean_Literals (True_Result), Sloc (N))));
15226 Analyze_And_Resolve (N, Typ);
15227 Set_Is_Static_Expression (N, False);
15228 Warn_On_Known_Condition (N);
15229 end if;
15230 end Rewrite_Comparison;
15232 ----------------------------
15233 -- Safe_In_Place_Array_Op --
15234 ----------------------------
15236 function Safe_In_Place_Array_Op
15237 (Lhs : Node_Id;
15238 Op1 : Node_Id;
15239 Op2 : Node_Id) return Boolean
15241 Target : Entity_Id;
15243 function Is_Safe_Operand (Op : Node_Id) return Boolean;
15244 -- Operand is safe if it cannot overlap part of the target of the
15245 -- operation. If the operand and the target are identical, the operand
15246 -- is safe. The operand can be empty in the case of negation.
15248 function Is_Unaliased (N : Node_Id) return Boolean;
15249 -- Check that N is a stand-alone entity
15251 ------------------
15252 -- Is_Unaliased --
15253 ------------------
15255 function Is_Unaliased (N : Node_Id) return Boolean is
15256 begin
15257 return
15258 Is_Entity_Name (N)
15259 and then No (Address_Clause (Entity (N)))
15260 and then No (Renamed_Object (Entity (N)));
15261 end Is_Unaliased;
15263 ---------------------
15264 -- Is_Safe_Operand --
15265 ---------------------
15267 function Is_Safe_Operand (Op : Node_Id) return Boolean is
15268 begin
15269 if No (Op) then
15270 return True;
15272 elsif Is_Entity_Name (Op) then
15273 return Is_Unaliased (Op);
15275 elsif Nkind (Op) in N_Indexed_Component | N_Selected_Component then
15276 return Is_Unaliased (Prefix (Op));
15278 elsif Nkind (Op) = N_Slice then
15279 return
15280 Is_Unaliased (Prefix (Op))
15281 and then Entity (Prefix (Op)) /= Target;
15283 elsif Nkind (Op) = N_Op_Not then
15284 return Is_Safe_Operand (Right_Opnd (Op));
15286 else
15287 return False;
15288 end if;
15289 end Is_Safe_Operand;
15291 -- Start of processing for Safe_In_Place_Array_Op
15293 begin
15294 -- Skip this processing if the component size is different from system
15295 -- storage unit (since at least for NOT this would cause problems).
15297 if Component_Size (Etype (Lhs)) /= System_Storage_Unit then
15298 return False;
15300 -- Cannot do in place stuff if non-standard Boolean representation
15302 elsif Has_Non_Standard_Rep (Component_Type (Etype (Lhs))) then
15303 return False;
15305 elsif not Is_Unaliased (Lhs) then
15306 return False;
15308 else
15309 Target := Entity (Lhs);
15310 return Is_Safe_Operand (Op1) and then Is_Safe_Operand (Op2);
15311 end if;
15312 end Safe_In_Place_Array_Op;
15314 -----------------------
15315 -- Tagged_Membership --
15316 -----------------------
15318 -- There are two different cases to consider depending on whether the right
15319 -- operand is a class-wide type or not. If not we just compare the actual
15320 -- tag of the left expr to the target type tag:
15322 -- Left_Expr.Tag = Right_Type'Tag;
15324 -- If it is a class-wide type we use the RT function CW_Membership which is
15325 -- usually implemented by looking in the ancestor tables contained in the
15326 -- dispatch table pointed by Left_Expr.Tag for Typ'Tag
15328 -- In both cases if Left_Expr is an access type, we first check whether it
15329 -- is null.
15331 -- Ada 2005 (AI-251): If it is a class-wide interface type we use the RT
15332 -- function IW_Membership which is usually implemented by looking in the
15333 -- table of abstract interface types plus the ancestor table contained in
15334 -- the dispatch table pointed by Left_Expr.Tag for Typ'Tag
15336 procedure Tagged_Membership
15337 (N : Node_Id;
15338 SCIL_Node : out Node_Id;
15339 Result : out Node_Id)
15341 Left : constant Node_Id := Left_Opnd (N);
15342 Right : constant Node_Id := Right_Opnd (N);
15343 Loc : constant Source_Ptr := Sloc (N);
15345 -- Handle entities from the limited view
15347 Orig_Right_Type : constant Entity_Id := Available_View (Etype (Right));
15349 Full_R_Typ : Entity_Id;
15350 Left_Type : Entity_Id := Available_View (Etype (Left));
15351 Right_Type : Entity_Id := Orig_Right_Type;
15352 Obj_Tag : Node_Id;
15354 begin
15355 SCIL_Node := Empty;
15357 -- We have to examine the corresponding record type when dealing with
15358 -- protected types instead of the original, unexpanded, type.
15360 if Ekind (Right_Type) = E_Protected_Type then
15361 Right_Type := Corresponding_Record_Type (Right_Type);
15362 end if;
15364 if Ekind (Left_Type) = E_Protected_Type then
15365 Left_Type := Corresponding_Record_Type (Left_Type);
15366 end if;
15368 -- In the case where the type is an access type, the test is applied
15369 -- using the designated types (needed in Ada 2012 for implicit anonymous
15370 -- access conversions, for AI05-0149).
15372 if Is_Access_Type (Right_Type) then
15373 Left_Type := Designated_Type (Left_Type);
15374 Right_Type := Designated_Type (Right_Type);
15375 end if;
15377 if Is_Class_Wide_Type (Left_Type) then
15378 Left_Type := Root_Type (Left_Type);
15379 end if;
15381 if Is_Class_Wide_Type (Right_Type) then
15382 Full_R_Typ := Underlying_Type (Root_Type (Right_Type));
15383 else
15384 Full_R_Typ := Underlying_Type (Right_Type);
15385 end if;
15387 Obj_Tag :=
15388 Make_Selected_Component (Loc,
15389 Prefix => Relocate_Node (Left),
15390 Selector_Name =>
15391 New_Occurrence_Of (First_Tag_Component (Left_Type), Loc));
15393 if Is_Class_Wide_Type (Right_Type) then
15395 -- No need to issue a run-time check if we statically know that the
15396 -- result of this membership test is always true. For example,
15397 -- considering the following declarations:
15399 -- type Iface is interface;
15400 -- type T is tagged null record;
15401 -- type DT is new T and Iface with null record;
15403 -- Obj1 : T;
15404 -- Obj2 : DT;
15406 -- These membership tests are always true:
15408 -- Obj1 in T'Class
15409 -- Obj2 in T'Class;
15410 -- Obj2 in Iface'Class;
15412 -- We do not need to handle cases where the membership is illegal.
15413 -- For example:
15415 -- Obj1 in DT'Class; -- Compile time error
15416 -- Obj1 in Iface'Class; -- Compile time error
15418 if not Is_Interface (Left_Type)
15419 and then not Is_Class_Wide_Type (Left_Type)
15420 and then (Is_Ancestor (Etype (Right_Type), Left_Type,
15421 Use_Full_View => True)
15422 or else (Is_Interface (Etype (Right_Type))
15423 and then Interface_Present_In_Ancestor
15424 (Typ => Left_Type,
15425 Iface => Etype (Right_Type))))
15426 then
15427 Result := New_Occurrence_Of (Standard_True, Loc);
15428 return;
15429 end if;
15431 -- Ada 2005 (AI-251): Class-wide applied to interfaces
15433 if Is_Interface (Etype (Class_Wide_Type (Right_Type)))
15435 -- Support to: "Iface_CW_Typ in Typ'Class"
15437 or else Is_Interface (Left_Type)
15438 then
15439 -- Issue error if IW_Membership operation not available in a
15440 -- configurable run-time setting.
15442 if not RTE_Available (RE_IW_Membership) then
15443 Error_Msg_CRT
15444 ("dynamic membership test on interface types", N);
15445 Result := Empty;
15446 return;
15447 end if;
15449 Result :=
15450 Make_Function_Call (Loc,
15451 Name => New_Occurrence_Of (RTE (RE_IW_Membership), Loc),
15452 Parameter_Associations => New_List (
15453 Make_Attribute_Reference (Loc,
15454 Prefix => Obj_Tag,
15455 Attribute_Name => Name_Address),
15456 New_Occurrence_Of (
15457 Node (First_Elmt (Access_Disp_Table (Full_R_Typ))),
15458 Loc)));
15460 -- Ada 95: Normal case
15462 else
15463 -- Issue error if CW_Membership operation not available in a
15464 -- configurable run-time setting.
15466 if not RTE_Available (RE_CW_Membership) then
15467 Error_Msg_CRT
15468 ("dynamic membership test on tagged types", N);
15469 Result := Empty;
15470 return;
15471 end if;
15473 Result :=
15474 Make_Function_Call (Loc,
15475 Name => New_Occurrence_Of (RTE (RE_CW_Membership), Loc),
15476 Parameter_Associations => New_List (
15477 Obj_Tag,
15478 New_Occurrence_Of (
15479 Node (First_Elmt (Access_Disp_Table (Full_R_Typ))),
15480 Loc)));
15482 -- Generate the SCIL node for this class-wide membership test.
15484 if Generate_SCIL then
15485 SCIL_Node := Make_SCIL_Membership_Test (Sloc (N));
15486 Set_SCIL_Entity (SCIL_Node, Etype (Right_Type));
15487 Set_SCIL_Tag_Value (SCIL_Node, Obj_Tag);
15488 end if;
15489 end if;
15491 -- Right_Type is not a class-wide type
15493 else
15494 -- No need to check the tag of the object if Right_Typ is abstract
15496 if Is_Abstract_Type (Right_Type) then
15497 Result := New_Occurrence_Of (Standard_False, Loc);
15499 else
15500 Result :=
15501 Make_Op_Eq (Loc,
15502 Left_Opnd => Obj_Tag,
15503 Right_Opnd =>
15504 New_Occurrence_Of
15505 (Node (First_Elmt (Access_Disp_Table (Full_R_Typ))), Loc));
15506 end if;
15507 end if;
15509 -- if Left is an access object then generate test of the form:
15510 -- * if Right_Type excludes null: Left /= null and then ...
15511 -- * if Right_Type includes null: Left = null or else ...
15513 if Is_Access_Type (Orig_Right_Type) then
15514 if Can_Never_Be_Null (Orig_Right_Type) then
15515 Result := Make_And_Then (Loc,
15516 Left_Opnd =>
15517 Make_Op_Ne (Loc,
15518 Left_Opnd => Left,
15519 Right_Opnd => Make_Null (Loc)),
15520 Right_Opnd => Result);
15522 else
15523 Result := Make_Or_Else (Loc,
15524 Left_Opnd =>
15525 Make_Op_Eq (Loc,
15526 Left_Opnd => Left,
15527 Right_Opnd => Make_Null (Loc)),
15528 Right_Opnd => Result);
15529 end if;
15530 end if;
15531 end Tagged_Membership;
15533 ------------------------------
15534 -- Unary_Op_Validity_Checks --
15535 ------------------------------
15537 procedure Unary_Op_Validity_Checks (N : Node_Id) is
15538 begin
15539 if Validity_Checks_On and Validity_Check_Operands then
15540 Ensure_Valid (Right_Opnd (N));
15541 end if;
15542 end Unary_Op_Validity_Checks;
15544 end Exp_Ch4;