PR rtl-optimization/79386
[official-gcc.git] / gcc / ada / checks.adb
blobf0ba9a8ad9e41bab0cd7f067f819e8c228377ab4
1 ------------------------------------------------------------------------------
2 -- --
3 -- GNAT COMPILER COMPONENTS --
4 -- --
5 -- C H E C K S --
6 -- --
7 -- B o d y --
8 -- --
9 -- Copyright (C) 1992-2016, Free Software Foundation, Inc. --
10 -- --
11 -- GNAT is free software; you can redistribute it and/or modify it under --
12 -- terms of the GNU General Public License as published by the Free Soft- --
13 -- ware Foundation; either version 3, or (at your option) any later ver- --
14 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
17 -- for more details. You should have received a copy of the GNU General --
18 -- Public License distributed with GNAT; see file COPYING3. If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license. --
20 -- --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
23 -- --
24 ------------------------------------------------------------------------------
26 with Atree; use Atree;
27 with Casing; use Casing;
28 with Debug; use Debug;
29 with Einfo; use Einfo;
30 with Elists; use Elists;
31 with Eval_Fat; use Eval_Fat;
32 with Exp_Ch11; use Exp_Ch11;
33 with Exp_Ch2; use Exp_Ch2;
34 with Exp_Ch4; use Exp_Ch4;
35 with Exp_Pakd; use Exp_Pakd;
36 with Exp_Util; use Exp_Util;
37 with Expander; use Expander;
38 with Freeze; use Freeze;
39 with Lib; use Lib;
40 with Nlists; use Nlists;
41 with Nmake; use Nmake;
42 with Opt; use Opt;
43 with Output; use Output;
44 with Restrict; use Restrict;
45 with Rident; use Rident;
46 with Rtsfind; use Rtsfind;
47 with Sem; use Sem;
48 with Sem_Aux; use Sem_Aux;
49 with Sem_Ch3; use Sem_Ch3;
50 with Sem_Ch8; use Sem_Ch8;
51 with Sem_Eval; use Sem_Eval;
52 with Sem_Res; use Sem_Res;
53 with Sem_Util; use Sem_Util;
54 with Sem_Warn; use Sem_Warn;
55 with Sinfo; use Sinfo;
56 with Sinput; use Sinput;
57 with Snames; use Snames;
58 with Sprint; use Sprint;
59 with Stand; use Stand;
60 with Stringt; use Stringt;
61 with Targparm; use Targparm;
62 with Tbuild; use Tbuild;
63 with Ttypes; use Ttypes;
64 with Validsw; use Validsw;
66 package body Checks is
68 -- General note: many of these routines are concerned with generating
69 -- checking code to make sure that constraint error is raised at runtime.
70 -- Clearly this code is only needed if the expander is active, since
71 -- otherwise we will not be generating code or going into the runtime
72 -- execution anyway.
74 -- We therefore disconnect most of these checks if the expander is
75 -- inactive. This has the additional benefit that we do not need to
76 -- worry about the tree being messed up by previous errors (since errors
77 -- turn off expansion anyway).
79 -- There are a few exceptions to the above rule. For instance routines
80 -- such as Apply_Scalar_Range_Check that do not insert any code can be
81 -- safely called even when the Expander is inactive (but Errors_Detected
82 -- is 0). The benefit of executing this code when expansion is off, is
83 -- the ability to emit constraint error warning for static expressions
84 -- even when we are not generating code.
86 -- The above is modified in gnatprove mode to ensure that proper check
87 -- flags are always placed, even if expansion is off.
89 -------------------------------------
90 -- Suppression of Redundant Checks --
91 -------------------------------------
93 -- This unit implements a limited circuit for removal of redundant
94 -- checks. The processing is based on a tracing of simple sequential
95 -- flow. For any sequence of statements, we save expressions that are
96 -- marked to be checked, and then if the same expression appears later
97 -- with the same check, then under certain circumstances, the second
98 -- check can be suppressed.
100 -- Basically, we can suppress the check if we know for certain that
101 -- the previous expression has been elaborated (together with its
102 -- check), and we know that the exception frame is the same, and that
103 -- nothing has happened to change the result of the exception.
105 -- Let us examine each of these three conditions in turn to describe
106 -- how we ensure that this condition is met.
108 -- First, we need to know for certain that the previous expression has
109 -- been executed. This is done principally by the mechanism of calling
110 -- Conditional_Statements_Begin at the start of any statement sequence
111 -- and Conditional_Statements_End at the end. The End call causes all
112 -- checks remembered since the Begin call to be discarded. This does
113 -- miss a few cases, notably the case of a nested BEGIN-END block with
114 -- no exception handlers. But the important thing is to be conservative.
115 -- The other protection is that all checks are discarded if a label
116 -- is encountered, since then the assumption of sequential execution
117 -- is violated, and we don't know enough about the flow.
119 -- Second, we need to know that the exception frame is the same. We
120 -- do this by killing all remembered checks when we enter a new frame.
121 -- Again, that's over-conservative, but generally the cases we can help
122 -- with are pretty local anyway (like the body of a loop for example).
124 -- Third, we must be sure to forget any checks which are no longer valid.
125 -- This is done by two mechanisms, first the Kill_Checks_Variable call is
126 -- used to note any changes to local variables. We only attempt to deal
127 -- with checks involving local variables, so we do not need to worry
128 -- about global variables. Second, a call to any non-global procedure
129 -- causes us to abandon all stored checks, since such a all may affect
130 -- the values of any local variables.
132 -- The following define the data structures used to deal with remembering
133 -- checks so that redundant checks can be eliminated as described above.
135 -- Right now, the only expressions that we deal with are of the form of
136 -- simple local objects (either declared locally, or IN parameters) or
137 -- such objects plus/minus a compile time known constant. We can do
138 -- more later on if it seems worthwhile, but this catches many simple
139 -- cases in practice.
141 -- The following record type reflects a single saved check. An entry
142 -- is made in the stack of saved checks if and only if the expression
143 -- has been elaborated with the indicated checks.
145 type Saved_Check is record
146 Killed : Boolean;
147 -- Set True if entry is killed by Kill_Checks
149 Entity : Entity_Id;
150 -- The entity involved in the expression that is checked
152 Offset : Uint;
153 -- A compile time value indicating the result of adding or
154 -- subtracting a compile time value. This value is to be
155 -- added to the value of the Entity. A value of zero is
156 -- used for the case of a simple entity reference.
158 Check_Type : Character;
159 -- This is set to 'R' for a range check (in which case Target_Type
160 -- is set to the target type for the range check) or to 'O' for an
161 -- overflow check (in which case Target_Type is set to Empty).
163 Target_Type : Entity_Id;
164 -- Used only if Do_Range_Check is set. Records the target type for
165 -- the check. We need this, because a check is a duplicate only if
166 -- it has the same target type (or more accurately one with a
167 -- range that is smaller or equal to the stored target type of a
168 -- saved check).
169 end record;
171 -- The following table keeps track of saved checks. Rather than use an
172 -- extensible table, we just use a table of fixed size, and we discard
173 -- any saved checks that do not fit. That's very unlikely to happen and
174 -- this is only an optimization in any case.
176 Saved_Checks : array (Int range 1 .. 200) of Saved_Check;
177 -- Array of saved checks
179 Num_Saved_Checks : Nat := 0;
180 -- Number of saved checks
182 -- The following stack keeps track of statement ranges. It is treated
183 -- as a stack. When Conditional_Statements_Begin is called, an entry
184 -- is pushed onto this stack containing the value of Num_Saved_Checks
185 -- at the time of the call. Then when Conditional_Statements_End is
186 -- called, this value is popped off and used to reset Num_Saved_Checks.
188 -- Note: again, this is a fixed length stack with a size that should
189 -- always be fine. If the value of the stack pointer goes above the
190 -- limit, then we just forget all saved checks.
192 Saved_Checks_Stack : array (Int range 1 .. 100) of Nat;
193 Saved_Checks_TOS : Nat := 0;
195 -----------------------
196 -- Local Subprograms --
197 -----------------------
199 procedure Apply_Arithmetic_Overflow_Strict (N : Node_Id);
200 -- Used to apply arithmetic overflow checks for all cases except operators
201 -- on signed arithmetic types in MINIMIZED/ELIMINATED case (for which we
202 -- call Apply_Arithmetic_Overflow_Minimized_Eliminated below). N can be a
203 -- signed integer arithmetic operator (but not an if or case expression).
204 -- It is also called for types other than signed integers.
206 procedure Apply_Arithmetic_Overflow_Minimized_Eliminated (Op : Node_Id);
207 -- Used to apply arithmetic overflow checks for the case where the overflow
208 -- checking mode is MINIMIZED or ELIMINATED and we have a signed integer
209 -- arithmetic op (which includes the case of if and case expressions). Note
210 -- that Do_Overflow_Check may or may not be set for node Op. In these modes
211 -- we have work to do even if overflow checking is suppressed.
213 procedure Apply_Division_Check
214 (N : Node_Id;
215 Rlo : Uint;
216 Rhi : Uint;
217 ROK : Boolean);
218 -- N is an N_Op_Div, N_Op_Rem, or N_Op_Mod node. This routine applies
219 -- division checks as required if the Do_Division_Check flag is set.
220 -- Rlo and Rhi give the possible range of the right operand, these values
221 -- can be referenced and trusted only if ROK is set True.
223 procedure Apply_Float_Conversion_Check
224 (Ck_Node : Node_Id;
225 Target_Typ : Entity_Id);
226 -- The checks on a conversion from a floating-point type to an integer
227 -- type are delicate. They have to be performed before conversion, they
228 -- have to raise an exception when the operand is a NaN, and rounding must
229 -- be taken into account to determine the safe bounds of the operand.
231 procedure Apply_Selected_Length_Checks
232 (Ck_Node : Node_Id;
233 Target_Typ : Entity_Id;
234 Source_Typ : Entity_Id;
235 Do_Static : Boolean);
236 -- This is the subprogram that does all the work for Apply_Length_Check
237 -- and Apply_Static_Length_Check. Expr, Target_Typ and Source_Typ are as
238 -- described for the above routines. The Do_Static flag indicates that
239 -- only a static check is to be done.
241 procedure Apply_Selected_Range_Checks
242 (Ck_Node : Node_Id;
243 Target_Typ : Entity_Id;
244 Source_Typ : Entity_Id;
245 Do_Static : Boolean);
246 -- This is the subprogram that does all the work for Apply_Range_Check.
247 -- Expr, Target_Typ and Source_Typ are as described for the above
248 -- routine. The Do_Static flag indicates that only a static check is
249 -- to be done.
251 type Check_Type is new Check_Id range Access_Check .. Division_Check;
252 function Check_Needed (Nod : Node_Id; Check : Check_Type) return Boolean;
253 -- This function is used to see if an access or division by zero check is
254 -- needed. The check is to be applied to a single variable appearing in the
255 -- source, and N is the node for the reference. If N is not of this form,
256 -- True is returned with no further processing. If N is of the right form,
257 -- then further processing determines if the given Check is needed.
259 -- The particular circuit is to see if we have the case of a check that is
260 -- not needed because it appears in the right operand of a short circuited
261 -- conditional where the left operand guards the check. For example:
263 -- if Var = 0 or else Q / Var > 12 then
264 -- ...
265 -- end if;
267 -- In this example, the division check is not required. At the same time
268 -- we can issue warnings for suspicious use of non-short-circuited forms,
269 -- such as:
271 -- if Var = 0 or Q / Var > 12 then
272 -- ...
273 -- end if;
275 procedure Find_Check
276 (Expr : Node_Id;
277 Check_Type : Character;
278 Target_Type : Entity_Id;
279 Entry_OK : out Boolean;
280 Check_Num : out Nat;
281 Ent : out Entity_Id;
282 Ofs : out Uint);
283 -- This routine is used by Enable_Range_Check and Enable_Overflow_Check
284 -- to see if a check is of the form for optimization, and if so, to see
285 -- if it has already been performed. Expr is the expression to check,
286 -- and Check_Type is 'R' for a range check, 'O' for an overflow check.
287 -- Target_Type is the target type for a range check, and Empty for an
288 -- overflow check. If the entry is not of the form for optimization,
289 -- then Entry_OK is set to False, and the remaining out parameters
290 -- are undefined. If the entry is OK, then Ent/Ofs are set to the
291 -- entity and offset from the expression. Check_Num is the number of
292 -- a matching saved entry in Saved_Checks, or zero if no such entry
293 -- is located.
295 function Get_Discriminal (E : Entity_Id; Bound : Node_Id) return Node_Id;
296 -- If a discriminal is used in constraining a prival, Return reference
297 -- to the discriminal of the protected body (which renames the parameter
298 -- of the enclosing protected operation). This clumsy transformation is
299 -- needed because privals are created too late and their actual subtypes
300 -- are not available when analysing the bodies of the protected operations.
301 -- This function is called whenever the bound is an entity and the scope
302 -- indicates a protected operation. If the bound is an in-parameter of
303 -- a protected operation that is not a prival, the function returns the
304 -- bound itself.
305 -- To be cleaned up???
307 function Guard_Access
308 (Cond : Node_Id;
309 Loc : Source_Ptr;
310 Ck_Node : Node_Id) return Node_Id;
311 -- In the access type case, guard the test with a test to ensure
312 -- that the access value is non-null, since the checks do not
313 -- not apply to null access values.
315 procedure Install_Static_Check (R_Cno : Node_Id; Loc : Source_Ptr);
316 -- Called by Apply_{Length,Range}_Checks to rewrite the tree with the
317 -- Constraint_Error node.
319 function Is_Signed_Integer_Arithmetic_Op (N : Node_Id) return Boolean;
320 -- Returns True if node N is for an arithmetic operation with signed
321 -- integer operands. This includes unary and binary operators, and also
322 -- if and case expression nodes where the dependent expressions are of
323 -- a signed integer type. These are the kinds of nodes for which special
324 -- handling applies in MINIMIZED or ELIMINATED overflow checking mode.
326 function Range_Or_Validity_Checks_Suppressed
327 (Expr : Node_Id) return Boolean;
328 -- Returns True if either range or validity checks or both are suppressed
329 -- for the type of the given expression, or, if the expression is the name
330 -- of an entity, if these checks are suppressed for the entity.
332 function Selected_Length_Checks
333 (Ck_Node : Node_Id;
334 Target_Typ : Entity_Id;
335 Source_Typ : Entity_Id;
336 Warn_Node : Node_Id) return Check_Result;
337 -- Like Apply_Selected_Length_Checks, except it doesn't modify
338 -- anything, just returns a list of nodes as described in the spec of
339 -- this package for the Range_Check function.
340 -- ??? In fact it does construct the test and insert it into the tree,
341 -- and insert actions in various ways (calling Insert_Action directly
342 -- in particular) so we do not call it in GNATprove mode, contrary to
343 -- Selected_Range_Checks.
345 function Selected_Range_Checks
346 (Ck_Node : Node_Id;
347 Target_Typ : Entity_Id;
348 Source_Typ : Entity_Id;
349 Warn_Node : Node_Id) return Check_Result;
350 -- Like Apply_Selected_Range_Checks, except it doesn't modify anything,
351 -- just returns a list of nodes as described in the spec of this package
352 -- for the Range_Check function.
354 ------------------------------
355 -- Access_Checks_Suppressed --
356 ------------------------------
358 function Access_Checks_Suppressed (E : Entity_Id) return Boolean is
359 begin
360 if Present (E) and then Checks_May_Be_Suppressed (E) then
361 return Is_Check_Suppressed (E, Access_Check);
362 else
363 return Scope_Suppress.Suppress (Access_Check);
364 end if;
365 end Access_Checks_Suppressed;
367 -------------------------------------
368 -- Accessibility_Checks_Suppressed --
369 -------------------------------------
371 function Accessibility_Checks_Suppressed (E : Entity_Id) return Boolean is
372 begin
373 if Present (E) and then Checks_May_Be_Suppressed (E) then
374 return Is_Check_Suppressed (E, Accessibility_Check);
375 else
376 return Scope_Suppress.Suppress (Accessibility_Check);
377 end if;
378 end Accessibility_Checks_Suppressed;
380 -----------------------------
381 -- Activate_Division_Check --
382 -----------------------------
384 procedure Activate_Division_Check (N : Node_Id) is
385 begin
386 Set_Do_Division_Check (N, True);
387 Possible_Local_Raise (N, Standard_Constraint_Error);
388 end Activate_Division_Check;
390 -----------------------------
391 -- Activate_Overflow_Check --
392 -----------------------------
394 procedure Activate_Overflow_Check (N : Node_Id) is
395 Typ : constant Entity_Id := Etype (N);
397 begin
398 -- Floating-point case. If Etype is not set (this can happen when we
399 -- activate a check on a node that has not yet been analyzed), then
400 -- we assume we do not have a floating-point type (as per our spec).
402 if Present (Typ) and then Is_Floating_Point_Type (Typ) then
404 -- Ignore call if we have no automatic overflow checks on the target
405 -- and Check_Float_Overflow mode is not set. These are the cases in
406 -- which we expect to generate infinities and NaN's with no check.
408 if not (Machine_Overflows_On_Target or Check_Float_Overflow) then
409 return;
411 -- Ignore for unary operations ("+", "-", abs) since these can never
412 -- result in overflow for floating-point cases.
414 elsif Nkind (N) in N_Unary_Op then
415 return;
417 -- Otherwise we will set the flag
419 else
420 null;
421 end if;
423 -- Discrete case
425 else
426 -- Nothing to do for Rem/Mod/Plus (overflow not possible, the check
427 -- for zero-divide is a divide check, not an overflow check).
429 if Nkind_In (N, N_Op_Rem, N_Op_Mod, N_Op_Plus) then
430 return;
431 end if;
432 end if;
434 -- Fall through for cases where we do set the flag
436 Set_Do_Overflow_Check (N, True);
437 Possible_Local_Raise (N, Standard_Constraint_Error);
438 end Activate_Overflow_Check;
440 --------------------------
441 -- Activate_Range_Check --
442 --------------------------
444 procedure Activate_Range_Check (N : Node_Id) is
445 begin
446 Set_Do_Range_Check (N, True);
447 Possible_Local_Raise (N, Standard_Constraint_Error);
448 end Activate_Range_Check;
450 ---------------------------------
451 -- Alignment_Checks_Suppressed --
452 ---------------------------------
454 function Alignment_Checks_Suppressed (E : Entity_Id) return Boolean is
455 begin
456 if Present (E) and then Checks_May_Be_Suppressed (E) then
457 return Is_Check_Suppressed (E, Alignment_Check);
458 else
459 return Scope_Suppress.Suppress (Alignment_Check);
460 end if;
461 end Alignment_Checks_Suppressed;
463 ----------------------------------
464 -- Allocation_Checks_Suppressed --
465 ----------------------------------
467 -- Note: at the current time there are no calls to this function, because
468 -- the relevant check is in the run-time, so it is not a check that the
469 -- compiler can suppress anyway, but we still have to recognize the check
470 -- name Allocation_Check since it is part of the standard.
472 function Allocation_Checks_Suppressed (E : Entity_Id) return Boolean is
473 begin
474 if Present (E) and then Checks_May_Be_Suppressed (E) then
475 return Is_Check_Suppressed (E, Allocation_Check);
476 else
477 return Scope_Suppress.Suppress (Allocation_Check);
478 end if;
479 end Allocation_Checks_Suppressed;
481 -------------------------
482 -- Append_Range_Checks --
483 -------------------------
485 procedure Append_Range_Checks
486 (Checks : Check_Result;
487 Stmts : List_Id;
488 Suppress_Typ : Entity_Id;
489 Static_Sloc : Source_Ptr;
490 Flag_Node : Node_Id)
492 Internal_Flag_Node : constant Node_Id := Flag_Node;
493 Internal_Static_Sloc : constant Source_Ptr := Static_Sloc;
495 Checks_On : constant Boolean :=
496 (not Index_Checks_Suppressed (Suppress_Typ))
497 or else (not Range_Checks_Suppressed (Suppress_Typ));
499 begin
500 -- For now we just return if Checks_On is false, however this should
501 -- be enhanced to check for an always True value in the condition
502 -- and to generate a compilation warning???
504 if not Checks_On then
505 return;
506 end if;
508 for J in 1 .. 2 loop
509 exit when No (Checks (J));
511 if Nkind (Checks (J)) = N_Raise_Constraint_Error
512 and then Present (Condition (Checks (J)))
513 then
514 if not Has_Dynamic_Range_Check (Internal_Flag_Node) then
515 Append_To (Stmts, Checks (J));
516 Set_Has_Dynamic_Range_Check (Internal_Flag_Node);
517 end if;
519 else
520 Append_To
521 (Stmts,
522 Make_Raise_Constraint_Error (Internal_Static_Sloc,
523 Reason => CE_Range_Check_Failed));
524 end if;
525 end loop;
526 end Append_Range_Checks;
528 ------------------------
529 -- Apply_Access_Check --
530 ------------------------
532 procedure Apply_Access_Check (N : Node_Id) is
533 P : constant Node_Id := Prefix (N);
535 begin
536 -- We do not need checks if we are not generating code (i.e. the
537 -- expander is not active). This is not just an optimization, there
538 -- are cases (e.g. with pragma Debug) where generating the checks
539 -- can cause real trouble).
541 if not Expander_Active then
542 return;
543 end if;
545 -- No check if short circuiting makes check unnecessary
547 if not Check_Needed (P, Access_Check) then
548 return;
549 end if;
551 -- No check if accessing the Offset_To_Top component of a dispatch
552 -- table. They are safe by construction.
554 if Tagged_Type_Expansion
555 and then Present (Etype (P))
556 and then RTU_Loaded (Ada_Tags)
557 and then RTE_Available (RE_Offset_To_Top_Ptr)
558 and then Etype (P) = RTE (RE_Offset_To_Top_Ptr)
559 then
560 return;
561 end if;
563 -- Otherwise go ahead and install the check
565 Install_Null_Excluding_Check (P);
566 end Apply_Access_Check;
568 -------------------------------
569 -- Apply_Accessibility_Check --
570 -------------------------------
572 procedure Apply_Accessibility_Check
573 (N : Node_Id;
574 Typ : Entity_Id;
575 Insert_Node : Node_Id)
577 Loc : constant Source_Ptr := Sloc (N);
578 Param_Ent : Entity_Id := Param_Entity (N);
579 Param_Level : Node_Id;
580 Type_Level : Node_Id;
582 begin
583 if Ada_Version >= Ada_2012
584 and then not Present (Param_Ent)
585 and then Is_Entity_Name (N)
586 and then Ekind_In (Entity (N), E_Constant, E_Variable)
587 and then Present (Effective_Extra_Accessibility (Entity (N)))
588 then
589 Param_Ent := Entity (N);
590 while Present (Renamed_Object (Param_Ent)) loop
592 -- Renamed_Object must return an Entity_Name here
593 -- because of preceding "Present (E_E_A (...))" test.
595 Param_Ent := Entity (Renamed_Object (Param_Ent));
596 end loop;
597 end if;
599 if Inside_A_Generic then
600 return;
602 -- Only apply the run-time check if the access parameter has an
603 -- associated extra access level parameter and when the level of the
604 -- type is less deep than the level of the access parameter, and
605 -- accessibility checks are not suppressed.
607 elsif Present (Param_Ent)
608 and then Present (Extra_Accessibility (Param_Ent))
609 and then UI_Gt (Object_Access_Level (N),
610 Deepest_Type_Access_Level (Typ))
611 and then not Accessibility_Checks_Suppressed (Param_Ent)
612 and then not Accessibility_Checks_Suppressed (Typ)
613 then
614 Param_Level :=
615 New_Occurrence_Of (Extra_Accessibility (Param_Ent), Loc);
617 Type_Level :=
618 Make_Integer_Literal (Loc, Deepest_Type_Access_Level (Typ));
620 -- Raise Program_Error if the accessibility level of the access
621 -- parameter is deeper than the level of the target access type.
623 Insert_Action (Insert_Node,
624 Make_Raise_Program_Error (Loc,
625 Condition =>
626 Make_Op_Gt (Loc,
627 Left_Opnd => Param_Level,
628 Right_Opnd => Type_Level),
629 Reason => PE_Accessibility_Check_Failed));
631 Analyze_And_Resolve (N);
632 end if;
633 end Apply_Accessibility_Check;
635 --------------------------------
636 -- Apply_Address_Clause_Check --
637 --------------------------------
639 procedure Apply_Address_Clause_Check (E : Entity_Id; N : Node_Id) is
640 pragma Assert (Nkind (N) = N_Freeze_Entity);
642 AC : constant Node_Id := Address_Clause (E);
643 Loc : constant Source_Ptr := Sloc (AC);
644 Typ : constant Entity_Id := Etype (E);
646 Expr : Node_Id;
647 -- Address expression (not necessarily the same as Aexp, for example
648 -- when Aexp is a reference to a constant, in which case Expr gets
649 -- reset to reference the value expression of the constant).
651 begin
652 -- See if alignment check needed. Note that we never need a check if the
653 -- maximum alignment is one, since the check will always succeed.
655 -- Note: we do not check for checks suppressed here, since that check
656 -- was done in Sem_Ch13 when the address clause was processed. We are
657 -- only called if checks were not suppressed. The reason for this is
658 -- that we have to delay the call to Apply_Alignment_Check till freeze
659 -- time (so that all types etc are elaborated), but we have to check
660 -- the status of check suppressing at the point of the address clause.
662 if No (AC)
663 or else not Check_Address_Alignment (AC)
664 or else Maximum_Alignment = 1
665 then
666 return;
667 end if;
669 -- Obtain expression from address clause
671 Expr := Address_Value (Expression (AC));
673 -- See if we know that Expr has an acceptable value at compile time. If
674 -- it hasn't or we don't know, we defer issuing the warning until the
675 -- end of the compilation to take into account back end annotations.
677 if Compile_Time_Known_Value (Expr)
678 and then (Known_Alignment (E) or else Known_Alignment (Typ))
679 then
680 declare
681 AL : Uint := Alignment (Typ);
683 begin
684 -- The object alignment might be more restrictive than the type
685 -- alignment.
687 if Known_Alignment (E) then
688 AL := Alignment (E);
689 end if;
691 if Expr_Value (Expr) mod AL = 0 then
692 return;
693 end if;
694 end;
696 -- If the expression has the form X'Address, then we can find out if the
697 -- object X has an alignment that is compatible with the object E. If it
698 -- hasn't or we don't know, we defer issuing the warning until the end
699 -- of the compilation to take into account back end annotations.
701 elsif Nkind (Expr) = N_Attribute_Reference
702 and then Attribute_Name (Expr) = Name_Address
703 and then
704 Has_Compatible_Alignment (E, Prefix (Expr), False) = Known_Compatible
705 then
706 return;
707 end if;
709 -- Here we do not know if the value is acceptable. Strictly we don't
710 -- have to do anything, since if the alignment is bad, we have an
711 -- erroneous program. However we are allowed to check for erroneous
712 -- conditions and we decide to do this by default if the check is not
713 -- suppressed.
715 -- However, don't do the check if elaboration code is unwanted
717 if Restriction_Active (No_Elaboration_Code) then
718 return;
720 -- Generate a check to raise PE if alignment may be inappropriate
722 else
723 -- If the original expression is a non-static constant, use the name
724 -- of the constant itself rather than duplicating its initialization
725 -- expression, which was extracted above.
727 -- Note: Expr is empty if the address-clause is applied to in-mode
728 -- actuals (allowed by 13.1(22)).
730 if not Present (Expr)
731 or else
732 (Is_Entity_Name (Expression (AC))
733 and then Ekind (Entity (Expression (AC))) = E_Constant
734 and then Nkind (Parent (Entity (Expression (AC)))) =
735 N_Object_Declaration)
736 then
737 Expr := New_Copy_Tree (Expression (AC));
738 else
739 Remove_Side_Effects (Expr);
740 end if;
742 if No (Actions (N)) then
743 Set_Actions (N, New_List);
744 end if;
746 Prepend_To (Actions (N),
747 Make_Raise_Program_Error (Loc,
748 Condition =>
749 Make_Op_Ne (Loc,
750 Left_Opnd =>
751 Make_Op_Mod (Loc,
752 Left_Opnd =>
753 Unchecked_Convert_To
754 (RTE (RE_Integer_Address), Expr),
755 Right_Opnd =>
756 Make_Attribute_Reference (Loc,
757 Prefix => New_Occurrence_Of (E, Loc),
758 Attribute_Name => Name_Alignment)),
759 Right_Opnd => Make_Integer_Literal (Loc, Uint_0)),
760 Reason => PE_Misaligned_Address_Value));
762 Warning_Msg := No_Error_Msg;
763 Analyze (First (Actions (N)), Suppress => All_Checks);
765 -- If the above raise action generated a warning message (for example
766 -- from Warn_On_Non_Local_Exception mode with the active restriction
767 -- No_Exception_Propagation).
769 if Warning_Msg /= No_Error_Msg then
771 -- If the expression has a known at compile time value, then
772 -- once we know the alignment of the type, we can check if the
773 -- exception will be raised or not, and if not, we don't need
774 -- the warning so we will kill the warning later on.
776 if Compile_Time_Known_Value (Expr) then
777 Alignment_Warnings.Append
778 ((E => E, A => Expr_Value (Expr), W => Warning_Msg));
780 -- Add explanation of the warning generated by the check
782 else
783 Error_Msg_N
784 ("\address value may be incompatible with alignment of "
785 & "object?X?", AC);
786 end if;
787 end if;
789 return;
790 end if;
792 exception
794 -- If we have some missing run time component in configurable run time
795 -- mode then just skip the check (it is not required in any case).
797 when RE_Not_Available =>
798 return;
799 end Apply_Address_Clause_Check;
801 -------------------------------------
802 -- Apply_Arithmetic_Overflow_Check --
803 -------------------------------------
805 procedure Apply_Arithmetic_Overflow_Check (N : Node_Id) is
806 begin
807 -- Use old routine in almost all cases (the only case we are treating
808 -- specially is the case of a signed integer arithmetic op with the
809 -- overflow checking mode set to MINIMIZED or ELIMINATED).
811 if Overflow_Check_Mode = Strict
812 or else not Is_Signed_Integer_Arithmetic_Op (N)
813 then
814 Apply_Arithmetic_Overflow_Strict (N);
816 -- Otherwise use the new routine for the case of a signed integer
817 -- arithmetic op, with Do_Overflow_Check set to True, and the checking
818 -- mode is MINIMIZED or ELIMINATED.
820 else
821 Apply_Arithmetic_Overflow_Minimized_Eliminated (N);
822 end if;
823 end Apply_Arithmetic_Overflow_Check;
825 --------------------------------------
826 -- Apply_Arithmetic_Overflow_Strict --
827 --------------------------------------
829 -- This routine is called only if the type is an integer type and an
830 -- arithmetic overflow check may be needed for op (add, subtract, or
831 -- multiply). This check is performed if Backend_Overflow_Checks_On_Target
832 -- is not enabled and Do_Overflow_Check is set. In this case we expand the
833 -- operation into a more complex sequence of tests that ensures that
834 -- overflow is properly caught.
836 -- This is used in CHECKED modes. It is identical to the code for this
837 -- cases before the big overflow earthquake, thus ensuring that in this
838 -- modes we have compatible behavior (and reliability) to what was there
839 -- before. It is also called for types other than signed integers, and if
840 -- the Do_Overflow_Check flag is off.
842 -- Note: we also call this routine if we decide in the MINIMIZED case
843 -- to give up and just generate an overflow check without any fuss.
845 procedure Apply_Arithmetic_Overflow_Strict (N : Node_Id) is
846 Loc : constant Source_Ptr := Sloc (N);
847 Typ : constant Entity_Id := Etype (N);
848 Rtyp : constant Entity_Id := Root_Type (Typ);
850 begin
851 -- Nothing to do if Do_Overflow_Check not set or overflow checks
852 -- suppressed.
854 if not Do_Overflow_Check (N) then
855 return;
856 end if;
858 -- An interesting special case. If the arithmetic operation appears as
859 -- the operand of a type conversion:
861 -- type1 (x op y)
863 -- and all the following conditions apply:
865 -- arithmetic operation is for a signed integer type
866 -- target type type1 is a static integer subtype
867 -- range of x and y are both included in the range of type1
868 -- range of x op y is included in the range of type1
869 -- size of type1 is at least twice the result size of op
871 -- then we don't do an overflow check in any case. Instead, we transform
872 -- the operation so that we end up with:
874 -- type1 (type1 (x) op type1 (y))
876 -- This avoids intermediate overflow before the conversion. It is
877 -- explicitly permitted by RM 3.5.4(24):
879 -- For the execution of a predefined operation of a signed integer
880 -- type, the implementation need not raise Constraint_Error if the
881 -- result is outside the base range of the type, so long as the
882 -- correct result is produced.
884 -- It's hard to imagine that any programmer counts on the exception
885 -- being raised in this case, and in any case it's wrong coding to
886 -- have this expectation, given the RM permission. Furthermore, other
887 -- Ada compilers do allow such out of range results.
889 -- Note that we do this transformation even if overflow checking is
890 -- off, since this is precisely about giving the "right" result and
891 -- avoiding the need for an overflow check.
893 -- Note: this circuit is partially redundant with respect to the similar
894 -- processing in Exp_Ch4.Expand_N_Type_Conversion, but the latter deals
895 -- with cases that do not come through here. We still need the following
896 -- processing even with the Exp_Ch4 code in place, since we want to be
897 -- sure not to generate the arithmetic overflow check in these cases
898 -- (Exp_Ch4 would have a hard time removing them once generated).
900 if Is_Signed_Integer_Type (Typ)
901 and then Nkind (Parent (N)) = N_Type_Conversion
902 then
903 Conversion_Optimization : declare
904 Target_Type : constant Entity_Id :=
905 Base_Type (Entity (Subtype_Mark (Parent (N))));
907 Llo, Lhi : Uint;
908 Rlo, Rhi : Uint;
909 LOK, ROK : Boolean;
911 Vlo : Uint;
912 Vhi : Uint;
913 VOK : Boolean;
915 Tlo : Uint;
916 Thi : Uint;
918 begin
919 if Is_Integer_Type (Target_Type)
920 and then RM_Size (Root_Type (Target_Type)) >= 2 * RM_Size (Rtyp)
921 then
922 Tlo := Expr_Value (Type_Low_Bound (Target_Type));
923 Thi := Expr_Value (Type_High_Bound (Target_Type));
925 Determine_Range
926 (Left_Opnd (N), LOK, Llo, Lhi, Assume_Valid => True);
927 Determine_Range
928 (Right_Opnd (N), ROK, Rlo, Rhi, Assume_Valid => True);
930 if (LOK and ROK)
931 and then Tlo <= Llo and then Lhi <= Thi
932 and then Tlo <= Rlo and then Rhi <= Thi
933 then
934 Determine_Range (N, VOK, Vlo, Vhi, Assume_Valid => True);
936 if VOK and then Tlo <= Vlo and then Vhi <= Thi then
937 Rewrite (Left_Opnd (N),
938 Make_Type_Conversion (Loc,
939 Subtype_Mark => New_Occurrence_Of (Target_Type, Loc),
940 Expression => Relocate_Node (Left_Opnd (N))));
942 Rewrite (Right_Opnd (N),
943 Make_Type_Conversion (Loc,
944 Subtype_Mark => New_Occurrence_Of (Target_Type, Loc),
945 Expression => Relocate_Node (Right_Opnd (N))));
947 -- Rewrite the conversion operand so that the original
948 -- node is retained, in order to avoid the warning for
949 -- redundant conversions in Resolve_Type_Conversion.
951 Rewrite (N, Relocate_Node (N));
953 Set_Etype (N, Target_Type);
955 Analyze_And_Resolve (Left_Opnd (N), Target_Type);
956 Analyze_And_Resolve (Right_Opnd (N), Target_Type);
958 -- Given that the target type is twice the size of the
959 -- source type, overflow is now impossible, so we can
960 -- safely kill the overflow check and return.
962 Set_Do_Overflow_Check (N, False);
963 return;
964 end if;
965 end if;
966 end if;
967 end Conversion_Optimization;
968 end if;
970 -- Now see if an overflow check is required
972 declare
973 Siz : constant Int := UI_To_Int (Esize (Rtyp));
974 Dsiz : constant Int := Siz * 2;
975 Opnod : Node_Id;
976 Ctyp : Entity_Id;
977 Opnd : Node_Id;
978 Cent : RE_Id;
980 begin
981 -- Skip check if back end does overflow checks, or the overflow flag
982 -- is not set anyway, or we are not doing code expansion, or the
983 -- parent node is a type conversion whose operand is an arithmetic
984 -- operation on signed integers on which the expander can promote
985 -- later the operands to type Integer (see Expand_N_Type_Conversion).
987 if Backend_Overflow_Checks_On_Target
988 or else not Do_Overflow_Check (N)
989 or else not Expander_Active
990 or else (Present (Parent (N))
991 and then Nkind (Parent (N)) = N_Type_Conversion
992 and then Integer_Promotion_Possible (Parent (N)))
993 then
994 return;
995 end if;
997 -- Otherwise, generate the full general code for front end overflow
998 -- detection, which works by doing arithmetic in a larger type:
1000 -- x op y
1002 -- is expanded into
1004 -- Typ (Checktyp (x) op Checktyp (y));
1006 -- where Typ is the type of the original expression, and Checktyp is
1007 -- an integer type of sufficient length to hold the largest possible
1008 -- result.
1010 -- If the size of check type exceeds the size of Long_Long_Integer,
1011 -- we use a different approach, expanding to:
1013 -- typ (xxx_With_Ovflo_Check (Integer_64 (x), Integer (y)))
1015 -- where xxx is Add, Multiply or Subtract as appropriate
1017 -- Find check type if one exists
1019 if Dsiz <= Standard_Integer_Size then
1020 Ctyp := Standard_Integer;
1022 elsif Dsiz <= Standard_Long_Long_Integer_Size then
1023 Ctyp := Standard_Long_Long_Integer;
1025 -- No check type exists, use runtime call
1027 else
1028 if Nkind (N) = N_Op_Add then
1029 Cent := RE_Add_With_Ovflo_Check;
1031 elsif Nkind (N) = N_Op_Multiply then
1032 Cent := RE_Multiply_With_Ovflo_Check;
1034 else
1035 pragma Assert (Nkind (N) = N_Op_Subtract);
1036 Cent := RE_Subtract_With_Ovflo_Check;
1037 end if;
1039 Rewrite (N,
1040 OK_Convert_To (Typ,
1041 Make_Function_Call (Loc,
1042 Name => New_Occurrence_Of (RTE (Cent), Loc),
1043 Parameter_Associations => New_List (
1044 OK_Convert_To (RTE (RE_Integer_64), Left_Opnd (N)),
1045 OK_Convert_To (RTE (RE_Integer_64), Right_Opnd (N))))));
1047 Analyze_And_Resolve (N, Typ);
1048 return;
1049 end if;
1051 -- If we fall through, we have the case where we do the arithmetic
1052 -- in the next higher type and get the check by conversion. In these
1053 -- cases Ctyp is set to the type to be used as the check type.
1055 Opnod := Relocate_Node (N);
1057 Opnd := OK_Convert_To (Ctyp, Left_Opnd (Opnod));
1059 Analyze (Opnd);
1060 Set_Etype (Opnd, Ctyp);
1061 Set_Analyzed (Opnd, True);
1062 Set_Left_Opnd (Opnod, Opnd);
1064 Opnd := OK_Convert_To (Ctyp, Right_Opnd (Opnod));
1066 Analyze (Opnd);
1067 Set_Etype (Opnd, Ctyp);
1068 Set_Analyzed (Opnd, True);
1069 Set_Right_Opnd (Opnod, Opnd);
1071 -- The type of the operation changes to the base type of the check
1072 -- type, and we reset the overflow check indication, since clearly no
1073 -- overflow is possible now that we are using a double length type.
1074 -- We also set the Analyzed flag to avoid a recursive attempt to
1075 -- expand the node.
1077 Set_Etype (Opnod, Base_Type (Ctyp));
1078 Set_Do_Overflow_Check (Opnod, False);
1079 Set_Analyzed (Opnod, True);
1081 -- Now build the outer conversion
1083 Opnd := OK_Convert_To (Typ, Opnod);
1084 Analyze (Opnd);
1085 Set_Etype (Opnd, Typ);
1087 -- In the discrete type case, we directly generate the range check
1088 -- for the outer operand. This range check will implement the
1089 -- required overflow check.
1091 if Is_Discrete_Type (Typ) then
1092 Rewrite (N, Opnd);
1093 Generate_Range_Check
1094 (Expression (N), Typ, CE_Overflow_Check_Failed);
1096 -- For other types, we enable overflow checking on the conversion,
1097 -- after setting the node as analyzed to prevent recursive attempts
1098 -- to expand the conversion node.
1100 else
1101 Set_Analyzed (Opnd, True);
1102 Enable_Overflow_Check (Opnd);
1103 Rewrite (N, Opnd);
1104 end if;
1106 exception
1107 when RE_Not_Available =>
1108 return;
1109 end;
1110 end Apply_Arithmetic_Overflow_Strict;
1112 ----------------------------------------------------
1113 -- Apply_Arithmetic_Overflow_Minimized_Eliminated --
1114 ----------------------------------------------------
1116 procedure Apply_Arithmetic_Overflow_Minimized_Eliminated (Op : Node_Id) is
1117 pragma Assert (Is_Signed_Integer_Arithmetic_Op (Op));
1119 Loc : constant Source_Ptr := Sloc (Op);
1120 P : constant Node_Id := Parent (Op);
1122 LLIB : constant Entity_Id := Base_Type (Standard_Long_Long_Integer);
1123 -- Operands and results are of this type when we convert
1125 Result_Type : constant Entity_Id := Etype (Op);
1126 -- Original result type
1128 Check_Mode : constant Overflow_Mode_Type := Overflow_Check_Mode;
1129 pragma Assert (Check_Mode in Minimized_Or_Eliminated);
1131 Lo, Hi : Uint;
1132 -- Ranges of values for result
1134 begin
1135 -- Nothing to do if our parent is one of the following:
1137 -- Another signed integer arithmetic op
1138 -- A membership operation
1139 -- A comparison operation
1141 -- In all these cases, we will process at the higher level (and then
1142 -- this node will be processed during the downwards recursion that
1143 -- is part of the processing in Minimize_Eliminate_Overflows).
1145 if Is_Signed_Integer_Arithmetic_Op (P)
1146 or else Nkind (P) in N_Membership_Test
1147 or else Nkind (P) in N_Op_Compare
1149 -- This is also true for an alternative in a case expression
1151 or else Nkind (P) = N_Case_Expression_Alternative
1153 -- This is also true for a range operand in a membership test
1155 or else (Nkind (P) = N_Range
1156 and then Nkind (Parent (P)) in N_Membership_Test)
1157 then
1158 -- If_Expressions and Case_Expressions are treated as arithmetic
1159 -- ops, but if they appear in an assignment or similar contexts
1160 -- there is no overflow check that starts from that parent node,
1161 -- so apply check now.
1163 if Nkind_In (P, N_If_Expression, N_Case_Expression)
1164 and then not Is_Signed_Integer_Arithmetic_Op (Parent (P))
1165 then
1166 null;
1167 else
1168 return;
1169 end if;
1170 end if;
1172 -- Otherwise, we have a top level arithmetic operation node, and this
1173 -- is where we commence the special processing for MINIMIZED/ELIMINATED
1174 -- modes. This is the case where we tell the machinery not to move into
1175 -- Bignum mode at this top level (of course the top level operation
1176 -- will still be in Bignum mode if either of its operands are of type
1177 -- Bignum).
1179 Minimize_Eliminate_Overflows (Op, Lo, Hi, Top_Level => True);
1181 -- That call may but does not necessarily change the result type of Op.
1182 -- It is the job of this routine to undo such changes, so that at the
1183 -- top level, we have the proper type. This "undoing" is a point at
1184 -- which a final overflow check may be applied.
1186 -- If the result type was not fiddled we are all set. We go to base
1187 -- types here because things may have been rewritten to generate the
1188 -- base type of the operand types.
1190 if Base_Type (Etype (Op)) = Base_Type (Result_Type) then
1191 return;
1193 -- Bignum case
1195 elsif Is_RTE (Etype (Op), RE_Bignum) then
1197 -- We need a sequence that looks like:
1199 -- Rnn : Result_Type;
1201 -- declare
1202 -- M : Mark_Id := SS_Mark;
1203 -- begin
1204 -- Rnn := Long_Long_Integer'Base (From_Bignum (Op));
1205 -- SS_Release (M);
1206 -- end;
1208 -- This block is inserted (using Insert_Actions), and then the node
1209 -- is replaced with a reference to Rnn.
1211 -- If our parent is a conversion node then there is no point in
1212 -- generating a conversion to Result_Type. Instead, we let the parent
1213 -- handle this. Note that this special case is not just about
1214 -- optimization. Consider
1216 -- A,B,C : Integer;
1217 -- ...
1218 -- X := Long_Long_Integer'Base (A * (B ** C));
1220 -- Now the product may fit in Long_Long_Integer but not in Integer.
1221 -- In MINIMIZED/ELIMINATED mode, we don't want to introduce an
1222 -- overflow exception for this intermediate value.
1224 declare
1225 Blk : constant Node_Id := Make_Bignum_Block (Loc);
1226 Rnn : constant Entity_Id := Make_Temporary (Loc, 'R', Op);
1227 RHS : Node_Id;
1229 Rtype : Entity_Id;
1231 begin
1232 RHS := Convert_From_Bignum (Op);
1234 if Nkind (P) /= N_Type_Conversion then
1235 Convert_To_And_Rewrite (Result_Type, RHS);
1236 Rtype := Result_Type;
1238 -- Interesting question, do we need a check on that conversion
1239 -- operation. Answer, not if we know the result is in range.
1240 -- At the moment we are not taking advantage of this. To be
1241 -- looked at later ???
1243 else
1244 Rtype := LLIB;
1245 end if;
1247 Insert_Before
1248 (First (Statements (Handled_Statement_Sequence (Blk))),
1249 Make_Assignment_Statement (Loc,
1250 Name => New_Occurrence_Of (Rnn, Loc),
1251 Expression => RHS));
1253 Insert_Actions (Op, New_List (
1254 Make_Object_Declaration (Loc,
1255 Defining_Identifier => Rnn,
1256 Object_Definition => New_Occurrence_Of (Rtype, Loc)),
1257 Blk));
1259 Rewrite (Op, New_Occurrence_Of (Rnn, Loc));
1260 Analyze_And_Resolve (Op);
1261 end;
1263 -- Here we know the result is Long_Long_Integer'Base, or that it has
1264 -- been rewritten because the parent operation is a conversion. See
1265 -- Apply_Arithmetic_Overflow_Strict.Conversion_Optimization.
1267 else
1268 pragma Assert
1269 (Etype (Op) = LLIB or else Nkind (Parent (Op)) = N_Type_Conversion);
1271 -- All we need to do here is to convert the result to the proper
1272 -- result type. As explained above for the Bignum case, we can
1273 -- omit this if our parent is a type conversion.
1275 if Nkind (P) /= N_Type_Conversion then
1276 Convert_To_And_Rewrite (Result_Type, Op);
1277 end if;
1279 Analyze_And_Resolve (Op);
1280 end if;
1281 end Apply_Arithmetic_Overflow_Minimized_Eliminated;
1283 ----------------------------
1284 -- Apply_Constraint_Check --
1285 ----------------------------
1287 procedure Apply_Constraint_Check
1288 (N : Node_Id;
1289 Typ : Entity_Id;
1290 No_Sliding : Boolean := False)
1292 Desig_Typ : Entity_Id;
1294 begin
1295 -- No checks inside a generic (check the instantiations)
1297 if Inside_A_Generic then
1298 return;
1299 end if;
1301 -- Apply required constraint checks
1303 if Is_Scalar_Type (Typ) then
1304 Apply_Scalar_Range_Check (N, Typ);
1306 elsif Is_Array_Type (Typ) then
1308 -- A useful optimization: an aggregate with only an others clause
1309 -- always has the right bounds.
1311 if Nkind (N) = N_Aggregate
1312 and then No (Expressions (N))
1313 and then Nkind
1314 (First (Choices (First (Component_Associations (N)))))
1315 = N_Others_Choice
1316 then
1317 return;
1318 end if;
1320 if Is_Constrained (Typ) then
1321 Apply_Length_Check (N, Typ);
1323 if No_Sliding then
1324 Apply_Range_Check (N, Typ);
1325 end if;
1326 else
1327 Apply_Range_Check (N, Typ);
1328 end if;
1330 elsif (Is_Record_Type (Typ) or else Is_Private_Type (Typ))
1331 and then Has_Discriminants (Base_Type (Typ))
1332 and then Is_Constrained (Typ)
1333 then
1334 Apply_Discriminant_Check (N, Typ);
1336 elsif Is_Access_Type (Typ) then
1338 Desig_Typ := Designated_Type (Typ);
1340 -- No checks necessary if expression statically null
1342 if Known_Null (N) then
1343 if Can_Never_Be_Null (Typ) then
1344 Install_Null_Excluding_Check (N);
1345 end if;
1347 -- No sliding possible on access to arrays
1349 elsif Is_Array_Type (Desig_Typ) then
1350 if Is_Constrained (Desig_Typ) then
1351 Apply_Length_Check (N, Typ);
1352 end if;
1354 Apply_Range_Check (N, Typ);
1356 elsif Has_Discriminants (Base_Type (Desig_Typ))
1357 and then Is_Constrained (Desig_Typ)
1358 then
1359 Apply_Discriminant_Check (N, Typ);
1360 end if;
1362 -- Apply the 2005 Null_Excluding check. Note that we do not apply
1363 -- this check if the constraint node is illegal, as shown by having
1364 -- an error posted. This additional guard prevents cascaded errors
1365 -- and compiler aborts on illegal programs involving Ada 2005 checks.
1367 if Can_Never_Be_Null (Typ)
1368 and then not Can_Never_Be_Null (Etype (N))
1369 and then not Error_Posted (N)
1370 then
1371 Install_Null_Excluding_Check (N);
1372 end if;
1373 end if;
1374 end Apply_Constraint_Check;
1376 ------------------------------
1377 -- Apply_Discriminant_Check --
1378 ------------------------------
1380 procedure Apply_Discriminant_Check
1381 (N : Node_Id;
1382 Typ : Entity_Id;
1383 Lhs : Node_Id := Empty)
1385 Loc : constant Source_Ptr := Sloc (N);
1386 Do_Access : constant Boolean := Is_Access_Type (Typ);
1387 S_Typ : Entity_Id := Etype (N);
1388 Cond : Node_Id;
1389 T_Typ : Entity_Id;
1391 function Denotes_Explicit_Dereference (Obj : Node_Id) return Boolean;
1392 -- A heap object with an indefinite subtype is constrained by its
1393 -- initial value, and assigning to it requires a constraint_check.
1394 -- The target may be an explicit dereference, or a renaming of one.
1396 function Is_Aliased_Unconstrained_Component return Boolean;
1397 -- It is possible for an aliased component to have a nominal
1398 -- unconstrained subtype (through instantiation). If this is a
1399 -- discriminated component assigned in the expansion of an aggregate
1400 -- in an initialization, the check must be suppressed. This unusual
1401 -- situation requires a predicate of its own.
1403 ----------------------------------
1404 -- Denotes_Explicit_Dereference --
1405 ----------------------------------
1407 function Denotes_Explicit_Dereference (Obj : Node_Id) return Boolean is
1408 begin
1409 return
1410 Nkind (Obj) = N_Explicit_Dereference
1411 or else
1412 (Is_Entity_Name (Obj)
1413 and then Present (Renamed_Object (Entity (Obj)))
1414 and then Nkind (Renamed_Object (Entity (Obj))) =
1415 N_Explicit_Dereference);
1416 end Denotes_Explicit_Dereference;
1418 ----------------------------------------
1419 -- Is_Aliased_Unconstrained_Component --
1420 ----------------------------------------
1422 function Is_Aliased_Unconstrained_Component return Boolean is
1423 Comp : Entity_Id;
1424 Pref : Node_Id;
1426 begin
1427 if Nkind (Lhs) /= N_Selected_Component then
1428 return False;
1429 else
1430 Comp := Entity (Selector_Name (Lhs));
1431 Pref := Prefix (Lhs);
1432 end if;
1434 if Ekind (Comp) /= E_Component
1435 or else not Is_Aliased (Comp)
1436 then
1437 return False;
1438 end if;
1440 return not Comes_From_Source (Pref)
1441 and then In_Instance
1442 and then not Is_Constrained (Etype (Comp));
1443 end Is_Aliased_Unconstrained_Component;
1445 -- Start of processing for Apply_Discriminant_Check
1447 begin
1448 if Do_Access then
1449 T_Typ := Designated_Type (Typ);
1450 else
1451 T_Typ := Typ;
1452 end if;
1454 -- Only apply checks when generating code and discriminant checks are
1455 -- not suppressed. In GNATprove mode, we do not apply the checks, but we
1456 -- still analyze the expression to possibly issue errors on SPARK code
1457 -- when a run-time error can be detected at compile time.
1459 if not GNATprove_Mode then
1460 if not Expander_Active
1461 or else Discriminant_Checks_Suppressed (T_Typ)
1462 then
1463 return;
1464 end if;
1465 end if;
1467 -- No discriminant checks necessary for an access when expression is
1468 -- statically Null. This is not only an optimization, it is fundamental
1469 -- because otherwise discriminant checks may be generated in init procs
1470 -- for types containing an access to a not-yet-frozen record, causing a
1471 -- deadly forward reference.
1473 -- Also, if the expression is of an access type whose designated type is
1474 -- incomplete, then the access value must be null and we suppress the
1475 -- check.
1477 if Known_Null (N) then
1478 return;
1480 elsif Is_Access_Type (S_Typ) then
1481 S_Typ := Designated_Type (S_Typ);
1483 if Ekind (S_Typ) = E_Incomplete_Type then
1484 return;
1485 end if;
1486 end if;
1488 -- If an assignment target is present, then we need to generate the
1489 -- actual subtype if the target is a parameter or aliased object with
1490 -- an unconstrained nominal subtype.
1492 -- Ada 2005 (AI-363): For Ada 2005, we limit the building of the actual
1493 -- subtype to the parameter and dereference cases, since other aliased
1494 -- objects are unconstrained (unless the nominal subtype is explicitly
1495 -- constrained).
1497 if Present (Lhs)
1498 and then (Present (Param_Entity (Lhs))
1499 or else (Ada_Version < Ada_2005
1500 and then not Is_Constrained (T_Typ)
1501 and then Is_Aliased_View (Lhs)
1502 and then not Is_Aliased_Unconstrained_Component)
1503 or else (Ada_Version >= Ada_2005
1504 and then not Is_Constrained (T_Typ)
1505 and then Denotes_Explicit_Dereference (Lhs)
1506 and then Nkind (Original_Node (Lhs)) /=
1507 N_Function_Call))
1508 then
1509 T_Typ := Get_Actual_Subtype (Lhs);
1510 end if;
1512 -- Nothing to do if the type is unconstrained (this is the case where
1513 -- the actual subtype in the RM sense of N is unconstrained and no check
1514 -- is required).
1516 if not Is_Constrained (T_Typ) then
1517 return;
1519 -- Ada 2005: nothing to do if the type is one for which there is a
1520 -- partial view that is constrained.
1522 elsif Ada_Version >= Ada_2005
1523 and then Object_Type_Has_Constrained_Partial_View
1524 (Typ => Base_Type (T_Typ),
1525 Scop => Current_Scope)
1526 then
1527 return;
1528 end if;
1530 -- Nothing to do if the type is an Unchecked_Union
1532 if Is_Unchecked_Union (Base_Type (T_Typ)) then
1533 return;
1534 end if;
1536 -- Suppress checks if the subtypes are the same. The check must be
1537 -- preserved in an assignment to a formal, because the constraint is
1538 -- given by the actual.
1540 if Nkind (Original_Node (N)) /= N_Allocator
1541 and then (No (Lhs)
1542 or else not Is_Entity_Name (Lhs)
1543 or else No (Param_Entity (Lhs)))
1544 then
1545 if (Etype (N) = Typ
1546 or else (Do_Access and then Designated_Type (Typ) = S_Typ))
1547 and then not Is_Aliased_View (Lhs)
1548 then
1549 return;
1550 end if;
1552 -- We can also eliminate checks on allocators with a subtype mark that
1553 -- coincides with the context type. The context type may be a subtype
1554 -- without a constraint (common case, a generic actual).
1556 elsif Nkind (Original_Node (N)) = N_Allocator
1557 and then Is_Entity_Name (Expression (Original_Node (N)))
1558 then
1559 declare
1560 Alloc_Typ : constant Entity_Id :=
1561 Entity (Expression (Original_Node (N)));
1563 begin
1564 if Alloc_Typ = T_Typ
1565 or else (Nkind (Parent (T_Typ)) = N_Subtype_Declaration
1566 and then Is_Entity_Name (
1567 Subtype_Indication (Parent (T_Typ)))
1568 and then Alloc_Typ = Base_Type (T_Typ))
1570 then
1571 return;
1572 end if;
1573 end;
1574 end if;
1576 -- See if we have a case where the types are both constrained, and all
1577 -- the constraints are constants. In this case, we can do the check
1578 -- successfully at compile time.
1580 -- We skip this check for the case where the node is rewritten as
1581 -- an allocator, because it already carries the context subtype,
1582 -- and extracting the discriminants from the aggregate is messy.
1584 if Is_Constrained (S_Typ)
1585 and then Nkind (Original_Node (N)) /= N_Allocator
1586 then
1587 declare
1588 DconT : Elmt_Id;
1589 Discr : Entity_Id;
1590 DconS : Elmt_Id;
1591 ItemS : Node_Id;
1592 ItemT : Node_Id;
1594 begin
1595 -- S_Typ may not have discriminants in the case where it is a
1596 -- private type completed by a default discriminated type. In that
1597 -- case, we need to get the constraints from the underlying type.
1598 -- If the underlying type is unconstrained (i.e. has no default
1599 -- discriminants) no check is needed.
1601 if Has_Discriminants (S_Typ) then
1602 Discr := First_Discriminant (S_Typ);
1603 DconS := First_Elmt (Discriminant_Constraint (S_Typ));
1605 else
1606 Discr := First_Discriminant (Underlying_Type (S_Typ));
1607 DconS :=
1608 First_Elmt
1609 (Discriminant_Constraint (Underlying_Type (S_Typ)));
1611 if No (DconS) then
1612 return;
1613 end if;
1615 -- A further optimization: if T_Typ is derived from S_Typ
1616 -- without imposing a constraint, no check is needed.
1618 if Nkind (Original_Node (Parent (T_Typ))) =
1619 N_Full_Type_Declaration
1620 then
1621 declare
1622 Type_Def : constant Node_Id :=
1623 Type_Definition (Original_Node (Parent (T_Typ)));
1624 begin
1625 if Nkind (Type_Def) = N_Derived_Type_Definition
1626 and then Is_Entity_Name (Subtype_Indication (Type_Def))
1627 and then Entity (Subtype_Indication (Type_Def)) = S_Typ
1628 then
1629 return;
1630 end if;
1631 end;
1632 end if;
1633 end if;
1635 -- Constraint may appear in full view of type
1637 if Ekind (T_Typ) = E_Private_Subtype
1638 and then Present (Full_View (T_Typ))
1639 then
1640 DconT :=
1641 First_Elmt (Discriminant_Constraint (Full_View (T_Typ)));
1642 else
1643 DconT :=
1644 First_Elmt (Discriminant_Constraint (T_Typ));
1645 end if;
1647 while Present (Discr) loop
1648 ItemS := Node (DconS);
1649 ItemT := Node (DconT);
1651 -- For a discriminated component type constrained by the
1652 -- current instance of an enclosing type, there is no
1653 -- applicable discriminant check.
1655 if Nkind (ItemT) = N_Attribute_Reference
1656 and then Is_Access_Type (Etype (ItemT))
1657 and then Is_Entity_Name (Prefix (ItemT))
1658 and then Is_Type (Entity (Prefix (ItemT)))
1659 then
1660 return;
1661 end if;
1663 -- If the expressions for the discriminants are identical
1664 -- and it is side-effect free (for now just an entity),
1665 -- this may be a shared constraint, e.g. from a subtype
1666 -- without a constraint introduced as a generic actual.
1667 -- Examine other discriminants if any.
1669 if ItemS = ItemT
1670 and then Is_Entity_Name (ItemS)
1671 then
1672 null;
1674 elsif not Is_OK_Static_Expression (ItemS)
1675 or else not Is_OK_Static_Expression (ItemT)
1676 then
1677 exit;
1679 elsif Expr_Value (ItemS) /= Expr_Value (ItemT) then
1680 if Do_Access then -- needs run-time check.
1681 exit;
1682 else
1683 Apply_Compile_Time_Constraint_Error
1684 (N, "incorrect value for discriminant&??",
1685 CE_Discriminant_Check_Failed, Ent => Discr);
1686 return;
1687 end if;
1688 end if;
1690 Next_Elmt (DconS);
1691 Next_Elmt (DconT);
1692 Next_Discriminant (Discr);
1693 end loop;
1695 if No (Discr) then
1696 return;
1697 end if;
1698 end;
1699 end if;
1701 -- In GNATprove mode, we do not apply the checks
1703 if GNATprove_Mode then
1704 return;
1705 end if;
1707 -- Here we need a discriminant check. First build the expression
1708 -- for the comparisons of the discriminants:
1710 -- (n.disc1 /= typ.disc1) or else
1711 -- (n.disc2 /= typ.disc2) or else
1712 -- ...
1713 -- (n.discn /= typ.discn)
1715 Cond := Build_Discriminant_Checks (N, T_Typ);
1717 -- If Lhs is set and is a parameter, then the condition is guarded by:
1718 -- lhs'constrained and then (condition built above)
1720 if Present (Param_Entity (Lhs)) then
1721 Cond :=
1722 Make_And_Then (Loc,
1723 Left_Opnd =>
1724 Make_Attribute_Reference (Loc,
1725 Prefix => New_Occurrence_Of (Param_Entity (Lhs), Loc),
1726 Attribute_Name => Name_Constrained),
1727 Right_Opnd => Cond);
1728 end if;
1730 if Do_Access then
1731 Cond := Guard_Access (Cond, Loc, N);
1732 end if;
1734 Insert_Action (N,
1735 Make_Raise_Constraint_Error (Loc,
1736 Condition => Cond,
1737 Reason => CE_Discriminant_Check_Failed));
1738 end Apply_Discriminant_Check;
1740 -------------------------
1741 -- Apply_Divide_Checks --
1742 -------------------------
1744 procedure Apply_Divide_Checks (N : Node_Id) is
1745 Loc : constant Source_Ptr := Sloc (N);
1746 Typ : constant Entity_Id := Etype (N);
1747 Left : constant Node_Id := Left_Opnd (N);
1748 Right : constant Node_Id := Right_Opnd (N);
1750 Mode : constant Overflow_Mode_Type := Overflow_Check_Mode;
1751 -- Current overflow checking mode
1753 LLB : Uint;
1754 Llo : Uint;
1755 Lhi : Uint;
1756 LOK : Boolean;
1757 Rlo : Uint;
1758 Rhi : Uint;
1759 ROK : Boolean;
1761 pragma Warnings (Off, Lhi);
1762 -- Don't actually use this value
1764 begin
1765 -- If we are operating in MINIMIZED or ELIMINATED mode, and we are
1766 -- operating on signed integer types, then the only thing this routine
1767 -- does is to call Apply_Arithmetic_Overflow_Minimized_Eliminated. That
1768 -- procedure will (possibly later on during recursive downward calls),
1769 -- ensure that any needed overflow/division checks are properly applied.
1771 if Mode in Minimized_Or_Eliminated
1772 and then Is_Signed_Integer_Type (Typ)
1773 then
1774 Apply_Arithmetic_Overflow_Minimized_Eliminated (N);
1775 return;
1776 end if;
1778 -- Proceed here in SUPPRESSED or CHECKED modes
1780 if Expander_Active
1781 and then not Backend_Divide_Checks_On_Target
1782 and then Check_Needed (Right, Division_Check)
1783 then
1784 Determine_Range (Right, ROK, Rlo, Rhi, Assume_Valid => True);
1786 -- Deal with division check
1788 if Do_Division_Check (N)
1789 and then not Division_Checks_Suppressed (Typ)
1790 then
1791 Apply_Division_Check (N, Rlo, Rhi, ROK);
1792 end if;
1794 -- Deal with overflow check
1796 if Do_Overflow_Check (N)
1797 and then not Overflow_Checks_Suppressed (Etype (N))
1798 then
1799 Set_Do_Overflow_Check (N, False);
1801 -- Test for extremely annoying case of xxx'First divided by -1
1802 -- for division of signed integer types (only overflow case).
1804 if Nkind (N) = N_Op_Divide
1805 and then Is_Signed_Integer_Type (Typ)
1806 then
1807 Determine_Range (Left, LOK, Llo, Lhi, Assume_Valid => True);
1808 LLB := Expr_Value (Type_Low_Bound (Base_Type (Typ)));
1810 if ((not ROK) or else (Rlo <= (-1) and then (-1) <= Rhi))
1811 and then
1812 ((not LOK) or else (Llo = LLB))
1813 then
1814 Insert_Action (N,
1815 Make_Raise_Constraint_Error (Loc,
1816 Condition =>
1817 Make_And_Then (Loc,
1818 Left_Opnd =>
1819 Make_Op_Eq (Loc,
1820 Left_Opnd =>
1821 Duplicate_Subexpr_Move_Checks (Left),
1822 Right_Opnd => Make_Integer_Literal (Loc, LLB)),
1824 Right_Opnd =>
1825 Make_Op_Eq (Loc,
1826 Left_Opnd => Duplicate_Subexpr (Right),
1827 Right_Opnd => Make_Integer_Literal (Loc, -1))),
1829 Reason => CE_Overflow_Check_Failed));
1830 end if;
1831 end if;
1832 end if;
1833 end if;
1834 end Apply_Divide_Checks;
1836 --------------------------
1837 -- Apply_Division_Check --
1838 --------------------------
1840 procedure Apply_Division_Check
1841 (N : Node_Id;
1842 Rlo : Uint;
1843 Rhi : Uint;
1844 ROK : Boolean)
1846 pragma Assert (Do_Division_Check (N));
1848 Loc : constant Source_Ptr := Sloc (N);
1849 Right : constant Node_Id := Right_Opnd (N);
1851 begin
1852 if Expander_Active
1853 and then not Backend_Divide_Checks_On_Target
1854 and then Check_Needed (Right, Division_Check)
1855 then
1856 -- See if division by zero possible, and if so generate test. This
1857 -- part of the test is not controlled by the -gnato switch, since
1858 -- it is a Division_Check and not an Overflow_Check.
1860 if Do_Division_Check (N) then
1861 Set_Do_Division_Check (N, False);
1863 if (not ROK) or else (Rlo <= 0 and then 0 <= Rhi) then
1864 Insert_Action (N,
1865 Make_Raise_Constraint_Error (Loc,
1866 Condition =>
1867 Make_Op_Eq (Loc,
1868 Left_Opnd => Duplicate_Subexpr_Move_Checks (Right),
1869 Right_Opnd => Make_Integer_Literal (Loc, 0)),
1870 Reason => CE_Divide_By_Zero));
1871 end if;
1872 end if;
1873 end if;
1874 end Apply_Division_Check;
1876 ----------------------------------
1877 -- Apply_Float_Conversion_Check --
1878 ----------------------------------
1880 -- Let F and I be the source and target types of the conversion. The RM
1881 -- specifies that a floating-point value X is rounded to the nearest
1882 -- integer, with halfway cases being rounded away from zero. The rounded
1883 -- value of X is checked against I'Range.
1885 -- The catch in the above paragraph is that there is no good way to know
1886 -- whether the round-to-integer operation resulted in overflow. A remedy is
1887 -- to perform a range check in the floating-point domain instead, however:
1889 -- (1) The bounds may not be known at compile time
1890 -- (2) The check must take into account rounding or truncation.
1891 -- (3) The range of type I may not be exactly representable in F.
1892 -- (4) For the rounding case, The end-points I'First - 0.5 and
1893 -- I'Last + 0.5 may or may not be in range, depending on the
1894 -- sign of I'First and I'Last.
1895 -- (5) X may be a NaN, which will fail any comparison
1897 -- The following steps correctly convert X with rounding:
1899 -- (1) If either I'First or I'Last is not known at compile time, use
1900 -- I'Base instead of I in the next three steps and perform a
1901 -- regular range check against I'Range after conversion.
1902 -- (2) If I'First - 0.5 is representable in F then let Lo be that
1903 -- value and define Lo_OK as (I'First > 0). Otherwise, let Lo be
1904 -- F'Machine (I'First) and let Lo_OK be (Lo >= I'First).
1905 -- In other words, take one of the closest floating-point numbers
1906 -- (which is an integer value) to I'First, and see if it is in
1907 -- range or not.
1908 -- (3) If I'Last + 0.5 is representable in F then let Hi be that value
1909 -- and define Hi_OK as (I'Last < 0). Otherwise, let Hi be
1910 -- F'Machine (I'Last) and let Hi_OK be (Hi <= I'Last).
1911 -- (4) Raise CE when (Lo_OK and X < Lo) or (not Lo_OK and X <= Lo)
1912 -- or (Hi_OK and X > Hi) or (not Hi_OK and X >= Hi)
1914 -- For the truncating case, replace steps (2) and (3) as follows:
1915 -- (2) If I'First > 0, then let Lo be F'Pred (I'First) and let Lo_OK
1916 -- be False. Otherwise, let Lo be F'Succ (I'First - 1) and let
1917 -- Lo_OK be True.
1918 -- (3) If I'Last < 0, then let Hi be F'Succ (I'Last) and let Hi_OK
1919 -- be False. Otherwise let Hi be F'Pred (I'Last + 1) and let
1920 -- Hi_OK be True.
1922 procedure Apply_Float_Conversion_Check
1923 (Ck_Node : Node_Id;
1924 Target_Typ : Entity_Id)
1926 LB : constant Node_Id := Type_Low_Bound (Target_Typ);
1927 HB : constant Node_Id := Type_High_Bound (Target_Typ);
1928 Loc : constant Source_Ptr := Sloc (Ck_Node);
1929 Expr_Type : constant Entity_Id := Base_Type (Etype (Ck_Node));
1930 Target_Base : constant Entity_Id :=
1931 Implementation_Base_Type (Target_Typ);
1933 Par : constant Node_Id := Parent (Ck_Node);
1934 pragma Assert (Nkind (Par) = N_Type_Conversion);
1935 -- Parent of check node, must be a type conversion
1937 Truncate : constant Boolean := Float_Truncate (Par);
1938 Max_Bound : constant Uint :=
1939 UI_Expon
1940 (Machine_Radix_Value (Expr_Type),
1941 Machine_Mantissa_Value (Expr_Type) - 1) - 1;
1943 -- Largest bound, so bound plus or minus half is a machine number of F
1945 Ifirst, Ilast : Uint;
1946 -- Bounds of integer type
1948 Lo, Hi : Ureal;
1949 -- Bounds to check in floating-point domain
1951 Lo_OK, Hi_OK : Boolean;
1952 -- True iff Lo resp. Hi belongs to I'Range
1954 Lo_Chk, Hi_Chk : Node_Id;
1955 -- Expressions that are False iff check fails
1957 Reason : RT_Exception_Code;
1959 begin
1960 -- We do not need checks if we are not generating code (i.e. the full
1961 -- expander is not active). In SPARK mode, we specifically don't want
1962 -- the frontend to expand these checks, which are dealt with directly
1963 -- in the formal verification backend.
1965 if not Expander_Active then
1966 return;
1967 end if;
1969 if not Compile_Time_Known_Value (LB)
1970 or not Compile_Time_Known_Value (HB)
1971 then
1972 declare
1973 -- First check that the value falls in the range of the base type,
1974 -- to prevent overflow during conversion and then perform a
1975 -- regular range check against the (dynamic) bounds.
1977 pragma Assert (Target_Base /= Target_Typ);
1979 Temp : constant Entity_Id := Make_Temporary (Loc, 'T', Par);
1981 begin
1982 Apply_Float_Conversion_Check (Ck_Node, Target_Base);
1983 Set_Etype (Temp, Target_Base);
1985 Insert_Action (Parent (Par),
1986 Make_Object_Declaration (Loc,
1987 Defining_Identifier => Temp,
1988 Object_Definition => New_Occurrence_Of (Target_Typ, Loc),
1989 Expression => New_Copy_Tree (Par)),
1990 Suppress => All_Checks);
1992 Insert_Action (Par,
1993 Make_Raise_Constraint_Error (Loc,
1994 Condition =>
1995 Make_Not_In (Loc,
1996 Left_Opnd => New_Occurrence_Of (Temp, Loc),
1997 Right_Opnd => New_Occurrence_Of (Target_Typ, Loc)),
1998 Reason => CE_Range_Check_Failed));
1999 Rewrite (Par, New_Occurrence_Of (Temp, Loc));
2001 return;
2002 end;
2003 end if;
2005 -- Get the (static) bounds of the target type
2007 Ifirst := Expr_Value (LB);
2008 Ilast := Expr_Value (HB);
2010 -- A simple optimization: if the expression is a universal literal,
2011 -- we can do the comparison with the bounds and the conversion to
2012 -- an integer type statically. The range checks are unchanged.
2014 if Nkind (Ck_Node) = N_Real_Literal
2015 and then Etype (Ck_Node) = Universal_Real
2016 and then Is_Integer_Type (Target_Typ)
2017 and then Nkind (Parent (Ck_Node)) = N_Type_Conversion
2018 then
2019 declare
2020 Int_Val : constant Uint := UR_To_Uint (Realval (Ck_Node));
2022 begin
2023 if Int_Val <= Ilast and then Int_Val >= Ifirst then
2025 -- Conversion is safe
2027 Rewrite (Parent (Ck_Node),
2028 Make_Integer_Literal (Loc, UI_To_Int (Int_Val)));
2029 Analyze_And_Resolve (Parent (Ck_Node), Target_Typ);
2030 return;
2031 end if;
2032 end;
2033 end if;
2035 -- Check against lower bound
2037 if Truncate and then Ifirst > 0 then
2038 Lo := Pred (Expr_Type, UR_From_Uint (Ifirst));
2039 Lo_OK := False;
2041 elsif Truncate then
2042 Lo := Succ (Expr_Type, UR_From_Uint (Ifirst - 1));
2043 Lo_OK := True;
2045 elsif abs (Ifirst) < Max_Bound then
2046 Lo := UR_From_Uint (Ifirst) - Ureal_Half;
2047 Lo_OK := (Ifirst > 0);
2049 else
2050 Lo := Machine (Expr_Type, UR_From_Uint (Ifirst), Round_Even, Ck_Node);
2051 Lo_OK := (Lo >= UR_From_Uint (Ifirst));
2052 end if;
2054 if Lo_OK then
2056 -- Lo_Chk := (X >= Lo)
2058 Lo_Chk := Make_Op_Ge (Loc,
2059 Left_Opnd => Duplicate_Subexpr_No_Checks (Ck_Node),
2060 Right_Opnd => Make_Real_Literal (Loc, Lo));
2062 else
2063 -- Lo_Chk := (X > Lo)
2065 Lo_Chk := Make_Op_Gt (Loc,
2066 Left_Opnd => Duplicate_Subexpr_No_Checks (Ck_Node),
2067 Right_Opnd => Make_Real_Literal (Loc, Lo));
2068 end if;
2070 -- Check against higher bound
2072 if Truncate and then Ilast < 0 then
2073 Hi := Succ (Expr_Type, UR_From_Uint (Ilast));
2074 Hi_OK := False;
2076 elsif Truncate then
2077 Hi := Pred (Expr_Type, UR_From_Uint (Ilast + 1));
2078 Hi_OK := True;
2080 elsif abs (Ilast) < Max_Bound then
2081 Hi := UR_From_Uint (Ilast) + Ureal_Half;
2082 Hi_OK := (Ilast < 0);
2083 else
2084 Hi := Machine (Expr_Type, UR_From_Uint (Ilast), Round_Even, Ck_Node);
2085 Hi_OK := (Hi <= UR_From_Uint (Ilast));
2086 end if;
2088 if Hi_OK then
2090 -- Hi_Chk := (X <= Hi)
2092 Hi_Chk := Make_Op_Le (Loc,
2093 Left_Opnd => Duplicate_Subexpr_No_Checks (Ck_Node),
2094 Right_Opnd => Make_Real_Literal (Loc, Hi));
2096 else
2097 -- Hi_Chk := (X < Hi)
2099 Hi_Chk := Make_Op_Lt (Loc,
2100 Left_Opnd => Duplicate_Subexpr_No_Checks (Ck_Node),
2101 Right_Opnd => Make_Real_Literal (Loc, Hi));
2102 end if;
2104 -- If the bounds of the target type are the same as those of the base
2105 -- type, the check is an overflow check as a range check is not
2106 -- performed in these cases.
2108 if Expr_Value (Type_Low_Bound (Target_Base)) = Ifirst
2109 and then Expr_Value (Type_High_Bound (Target_Base)) = Ilast
2110 then
2111 Reason := CE_Overflow_Check_Failed;
2112 else
2113 Reason := CE_Range_Check_Failed;
2114 end if;
2116 -- Raise CE if either conditions does not hold
2118 Insert_Action (Ck_Node,
2119 Make_Raise_Constraint_Error (Loc,
2120 Condition => Make_Op_Not (Loc, Make_And_Then (Loc, Lo_Chk, Hi_Chk)),
2121 Reason => Reason));
2122 end Apply_Float_Conversion_Check;
2124 ------------------------
2125 -- Apply_Length_Check --
2126 ------------------------
2128 procedure Apply_Length_Check
2129 (Ck_Node : Node_Id;
2130 Target_Typ : Entity_Id;
2131 Source_Typ : Entity_Id := Empty)
2133 begin
2134 Apply_Selected_Length_Checks
2135 (Ck_Node, Target_Typ, Source_Typ, Do_Static => False);
2136 end Apply_Length_Check;
2138 -------------------------------------
2139 -- Apply_Parameter_Aliasing_Checks --
2140 -------------------------------------
2142 procedure Apply_Parameter_Aliasing_Checks
2143 (Call : Node_Id;
2144 Subp : Entity_Id)
2146 Loc : constant Source_Ptr := Sloc (Call);
2148 function May_Cause_Aliasing
2149 (Formal_1 : Entity_Id;
2150 Formal_2 : Entity_Id) return Boolean;
2151 -- Determine whether two formal parameters can alias each other
2152 -- depending on their modes.
2154 function Original_Actual (N : Node_Id) return Node_Id;
2155 -- The expander may replace an actual with a temporary for the sake of
2156 -- side effect removal. The temporary may hide a potential aliasing as
2157 -- it does not share the address of the actual. This routine attempts
2158 -- to retrieve the original actual.
2160 procedure Overlap_Check
2161 (Actual_1 : Node_Id;
2162 Actual_2 : Node_Id;
2163 Formal_1 : Entity_Id;
2164 Formal_2 : Entity_Id;
2165 Check : in out Node_Id);
2166 -- Create a check to determine whether Actual_1 overlaps with Actual_2.
2167 -- If detailed exception messages are enabled, the check is augmented to
2168 -- provide information about the names of the corresponding formals. See
2169 -- the body for details. Actual_1 and Actual_2 denote the two actuals to
2170 -- be tested. Formal_1 and Formal_2 denote the corresponding formals.
2171 -- Check contains all and-ed simple tests generated so far or remains
2172 -- unchanged in the case of detailed exception messaged.
2174 ------------------------
2175 -- May_Cause_Aliasing --
2176 ------------------------
2178 function May_Cause_Aliasing
2179 (Formal_1 : Entity_Id;
2180 Formal_2 : Entity_Id) return Boolean
2182 begin
2183 -- The following combination cannot lead to aliasing
2185 -- Formal 1 Formal 2
2186 -- IN IN
2188 if Ekind (Formal_1) = E_In_Parameter
2189 and then
2190 Ekind (Formal_2) = E_In_Parameter
2191 then
2192 return False;
2194 -- The following combinations may lead to aliasing
2196 -- Formal 1 Formal 2
2197 -- IN OUT
2198 -- IN IN OUT
2199 -- OUT IN
2200 -- OUT IN OUT
2201 -- OUT OUT
2203 else
2204 return True;
2205 end if;
2206 end May_Cause_Aliasing;
2208 ---------------------
2209 -- Original_Actual --
2210 ---------------------
2212 function Original_Actual (N : Node_Id) return Node_Id is
2213 begin
2214 if Nkind (N) = N_Type_Conversion then
2215 return Expression (N);
2217 -- The expander created a temporary to capture the result of a type
2218 -- conversion where the expression is the real actual.
2220 elsif Nkind (N) = N_Identifier
2221 and then Present (Original_Node (N))
2222 and then Nkind (Original_Node (N)) = N_Type_Conversion
2223 then
2224 return Expression (Original_Node (N));
2225 end if;
2227 return N;
2228 end Original_Actual;
2230 -------------------
2231 -- Overlap_Check --
2232 -------------------
2234 procedure Overlap_Check
2235 (Actual_1 : Node_Id;
2236 Actual_2 : Node_Id;
2237 Formal_1 : Entity_Id;
2238 Formal_2 : Entity_Id;
2239 Check : in out Node_Id)
2241 Cond : Node_Id;
2242 ID_Casing : constant Casing_Type :=
2243 Identifier_Casing (Source_Index (Current_Sem_Unit));
2245 begin
2246 -- Generate:
2247 -- Actual_1'Overlaps_Storage (Actual_2)
2249 Cond :=
2250 Make_Attribute_Reference (Loc,
2251 Prefix => New_Copy_Tree (Original_Actual (Actual_1)),
2252 Attribute_Name => Name_Overlaps_Storage,
2253 Expressions =>
2254 New_List (New_Copy_Tree (Original_Actual (Actual_2))));
2256 -- Generate the following check when detailed exception messages are
2257 -- enabled:
2259 -- if Actual_1'Overlaps_Storage (Actual_2) then
2260 -- raise Program_Error with <detailed message>;
2261 -- end if;
2263 if Exception_Extra_Info then
2264 Start_String;
2266 -- Do not generate location information for internal calls
2268 if Comes_From_Source (Call) then
2269 Store_String_Chars (Build_Location_String (Loc));
2270 Store_String_Char (' ');
2271 end if;
2273 Store_String_Chars ("aliased parameters, actuals for """);
2275 Get_Name_String (Chars (Formal_1));
2276 Set_Casing (ID_Casing);
2277 Store_String_Chars (Name_Buffer (1 .. Name_Len));
2279 Store_String_Chars (""" and """);
2281 Get_Name_String (Chars (Formal_2));
2282 Set_Casing (ID_Casing);
2283 Store_String_Chars (Name_Buffer (1 .. Name_Len));
2285 Store_String_Chars (""" overlap");
2287 Insert_Action (Call,
2288 Make_If_Statement (Loc,
2289 Condition => Cond,
2290 Then_Statements => New_List (
2291 Make_Raise_Statement (Loc,
2292 Name =>
2293 New_Occurrence_Of (Standard_Program_Error, Loc),
2294 Expression => Make_String_Literal (Loc, End_String)))));
2296 -- Create a sequence of overlapping checks by and-ing them all
2297 -- together.
2299 else
2300 if No (Check) then
2301 Check := Cond;
2302 else
2303 Check :=
2304 Make_And_Then (Loc,
2305 Left_Opnd => Check,
2306 Right_Opnd => Cond);
2307 end if;
2308 end if;
2309 end Overlap_Check;
2311 -- Local variables
2313 Actual_1 : Node_Id;
2314 Actual_2 : Node_Id;
2315 Check : Node_Id;
2316 Formal_1 : Entity_Id;
2317 Formal_2 : Entity_Id;
2318 Orig_Act_1 : Node_Id;
2319 Orig_Act_2 : Node_Id;
2321 -- Start of processing for Apply_Parameter_Aliasing_Checks
2323 begin
2324 Check := Empty;
2326 Actual_1 := First_Actual (Call);
2327 Formal_1 := First_Formal (Subp);
2328 while Present (Actual_1) and then Present (Formal_1) loop
2329 Orig_Act_1 := Original_Actual (Actual_1);
2331 -- Ensure that the actual is an object that is not passed by value.
2332 -- Elementary types are always passed by value, therefore actuals of
2333 -- such types cannot lead to aliasing. An aggregate is an object in
2334 -- Ada 2012, but an actual that is an aggregate cannot overlap with
2335 -- another actual. A type that is By_Reference (such as an array of
2336 -- controlled types) is not subject to the check because any update
2337 -- will be done in place and a subsequent read will always see the
2338 -- correct value, see RM 6.2 (12/3).
2340 if Nkind (Orig_Act_1) = N_Aggregate
2341 or else (Nkind (Orig_Act_1) = N_Qualified_Expression
2342 and then Nkind (Expression (Orig_Act_1)) = N_Aggregate)
2343 then
2344 null;
2346 elsif Is_Object_Reference (Orig_Act_1)
2347 and then not Is_Elementary_Type (Etype (Orig_Act_1))
2348 and then not Is_By_Reference_Type (Etype (Orig_Act_1))
2349 then
2350 Actual_2 := Next_Actual (Actual_1);
2351 Formal_2 := Next_Formal (Formal_1);
2352 while Present (Actual_2) and then Present (Formal_2) loop
2353 Orig_Act_2 := Original_Actual (Actual_2);
2355 -- The other actual we are testing against must also denote
2356 -- a non pass-by-value object. Generate the check only when
2357 -- the mode of the two formals may lead to aliasing.
2359 if Is_Object_Reference (Orig_Act_2)
2360 and then not Is_Elementary_Type (Etype (Orig_Act_2))
2361 and then May_Cause_Aliasing (Formal_1, Formal_2)
2362 then
2363 Remove_Side_Effects (Actual_1);
2364 Remove_Side_Effects (Actual_2);
2366 Overlap_Check
2367 (Actual_1 => Actual_1,
2368 Actual_2 => Actual_2,
2369 Formal_1 => Formal_1,
2370 Formal_2 => Formal_2,
2371 Check => Check);
2372 end if;
2374 Next_Actual (Actual_2);
2375 Next_Formal (Formal_2);
2376 end loop;
2377 end if;
2379 Next_Actual (Actual_1);
2380 Next_Formal (Formal_1);
2381 end loop;
2383 -- Place a simple check right before the call
2385 if Present (Check) and then not Exception_Extra_Info then
2386 Insert_Action (Call,
2387 Make_Raise_Program_Error (Loc,
2388 Condition => Check,
2389 Reason => PE_Aliased_Parameters));
2390 end if;
2391 end Apply_Parameter_Aliasing_Checks;
2393 -------------------------------------
2394 -- Apply_Parameter_Validity_Checks --
2395 -------------------------------------
2397 procedure Apply_Parameter_Validity_Checks (Subp : Entity_Id) is
2398 Subp_Decl : Node_Id;
2400 procedure Add_Validity_Check
2401 (Formal : Entity_Id;
2402 Prag_Nam : Name_Id;
2403 For_Result : Boolean := False);
2404 -- Add a single 'Valid[_Scalar] check which verifies the initialization
2405 -- of Formal. Prag_Nam denotes the pre or post condition pragma name.
2406 -- Set flag For_Result when to verify the result of a function.
2408 ------------------------
2409 -- Add_Validity_Check --
2410 ------------------------
2412 procedure Add_Validity_Check
2413 (Formal : Entity_Id;
2414 Prag_Nam : Name_Id;
2415 For_Result : Boolean := False)
2417 procedure Build_Pre_Post_Condition (Expr : Node_Id);
2418 -- Create a pre/postcondition pragma that tests expression Expr
2420 ------------------------------
2421 -- Build_Pre_Post_Condition --
2422 ------------------------------
2424 procedure Build_Pre_Post_Condition (Expr : Node_Id) is
2425 Loc : constant Source_Ptr := Sloc (Subp);
2426 Decls : List_Id;
2427 Prag : Node_Id;
2429 begin
2430 Prag :=
2431 Make_Pragma (Loc,
2432 Chars => Prag_Nam,
2433 Pragma_Argument_Associations => New_List (
2434 Make_Pragma_Argument_Association (Loc,
2435 Chars => Name_Check,
2436 Expression => Expr)));
2438 -- Add a message unless exception messages are suppressed
2440 if not Exception_Locations_Suppressed then
2441 Append_To (Pragma_Argument_Associations (Prag),
2442 Make_Pragma_Argument_Association (Loc,
2443 Chars => Name_Message,
2444 Expression =>
2445 Make_String_Literal (Loc,
2446 Strval => "failed "
2447 & Get_Name_String (Prag_Nam)
2448 & " from "
2449 & Build_Location_String (Loc))));
2450 end if;
2452 -- Insert the pragma in the tree
2454 if Nkind (Parent (Subp_Decl)) = N_Compilation_Unit then
2455 Add_Global_Declaration (Prag);
2456 Analyze (Prag);
2458 -- PPC pragmas associated with subprogram bodies must be inserted
2459 -- in the declarative part of the body.
2461 elsif Nkind (Subp_Decl) = N_Subprogram_Body then
2462 Decls := Declarations (Subp_Decl);
2464 if No (Decls) then
2465 Decls := New_List;
2466 Set_Declarations (Subp_Decl, Decls);
2467 end if;
2469 Prepend_To (Decls, Prag);
2470 Analyze (Prag);
2472 -- For subprogram declarations insert the PPC pragma right after
2473 -- the declarative node.
2475 else
2476 Insert_After_And_Analyze (Subp_Decl, Prag);
2477 end if;
2478 end Build_Pre_Post_Condition;
2480 -- Local variables
2482 Loc : constant Source_Ptr := Sloc (Subp);
2483 Typ : constant Entity_Id := Etype (Formal);
2484 Check : Node_Id;
2485 Nam : Name_Id;
2487 -- Start of processing for Add_Validity_Check
2489 begin
2490 -- For scalars, generate 'Valid test
2492 if Is_Scalar_Type (Typ) then
2493 Nam := Name_Valid;
2495 -- For any non-scalar with scalar parts, generate 'Valid_Scalars test
2497 elsif Scalar_Part_Present (Typ) then
2498 Nam := Name_Valid_Scalars;
2500 -- No test needed for other cases (no scalars to test)
2502 else
2503 return;
2504 end if;
2506 -- Step 1: Create the expression to verify the validity of the
2507 -- context.
2509 Check := New_Occurrence_Of (Formal, Loc);
2511 -- When processing a function result, use 'Result. Generate
2512 -- Context'Result
2514 if For_Result then
2515 Check :=
2516 Make_Attribute_Reference (Loc,
2517 Prefix => Check,
2518 Attribute_Name => Name_Result);
2519 end if;
2521 -- Generate:
2522 -- Context['Result]'Valid[_Scalars]
2524 Check :=
2525 Make_Attribute_Reference (Loc,
2526 Prefix => Check,
2527 Attribute_Name => Nam);
2529 -- Step 2: Create a pre or post condition pragma
2531 Build_Pre_Post_Condition (Check);
2532 end Add_Validity_Check;
2534 -- Local variables
2536 Formal : Entity_Id;
2537 Subp_Spec : Node_Id;
2539 -- Start of processing for Apply_Parameter_Validity_Checks
2541 begin
2542 -- Extract the subprogram specification and declaration nodes
2544 Subp_Spec := Parent (Subp);
2546 if Nkind (Subp_Spec) = N_Defining_Program_Unit_Name then
2547 Subp_Spec := Parent (Subp_Spec);
2548 end if;
2550 Subp_Decl := Parent (Subp_Spec);
2552 if not Comes_From_Source (Subp)
2554 -- Do not process formal subprograms because the corresponding actual
2555 -- will receive the proper checks when the instance is analyzed.
2557 or else Is_Formal_Subprogram (Subp)
2559 -- Do not process imported subprograms since pre and postconditions
2560 -- are never verified on routines coming from a different language.
2562 or else Is_Imported (Subp)
2563 or else Is_Intrinsic_Subprogram (Subp)
2565 -- The PPC pragmas generated by this routine do not correspond to
2566 -- source aspects, therefore they cannot be applied to abstract
2567 -- subprograms.
2569 or else Nkind (Subp_Decl) = N_Abstract_Subprogram_Declaration
2571 -- Do not consider subprogram renaminds because the renamed entity
2572 -- already has the proper PPC pragmas.
2574 or else Nkind (Subp_Decl) = N_Subprogram_Renaming_Declaration
2576 -- Do not process null procedures because there is no benefit of
2577 -- adding the checks to a no action routine.
2579 or else (Nkind (Subp_Spec) = N_Procedure_Specification
2580 and then Null_Present (Subp_Spec))
2581 then
2582 return;
2583 end if;
2585 -- Inspect all the formals applying aliasing and scalar initialization
2586 -- checks where applicable.
2588 Formal := First_Formal (Subp);
2589 while Present (Formal) loop
2591 -- Generate the following scalar initialization checks for each
2592 -- formal parameter:
2594 -- mode IN - Pre => Formal'Valid[_Scalars]
2595 -- mode IN OUT - Pre, Post => Formal'Valid[_Scalars]
2596 -- mode OUT - Post => Formal'Valid[_Scalars]
2598 if Check_Validity_Of_Parameters then
2599 if Ekind_In (Formal, E_In_Parameter, E_In_Out_Parameter) then
2600 Add_Validity_Check (Formal, Name_Precondition, False);
2601 end if;
2603 if Ekind_In (Formal, E_In_Out_Parameter, E_Out_Parameter) then
2604 Add_Validity_Check (Formal, Name_Postcondition, False);
2605 end if;
2606 end if;
2608 Next_Formal (Formal);
2609 end loop;
2611 -- Generate following scalar initialization check for function result:
2613 -- Post => Subp'Result'Valid[_Scalars]
2615 if Check_Validity_Of_Parameters and then Ekind (Subp) = E_Function then
2616 Add_Validity_Check (Subp, Name_Postcondition, True);
2617 end if;
2618 end Apply_Parameter_Validity_Checks;
2620 ---------------------------
2621 -- Apply_Predicate_Check --
2622 ---------------------------
2624 procedure Apply_Predicate_Check
2625 (N : Node_Id;
2626 Typ : Entity_Id;
2627 Fun : Entity_Id := Empty)
2629 S : Entity_Id;
2631 begin
2632 if Predicate_Checks_Suppressed (Empty) then
2633 return;
2635 elsif Predicates_Ignored (Typ) then
2636 return;
2638 elsif Present (Predicate_Function (Typ)) then
2639 S := Current_Scope;
2640 while Present (S) and then not Is_Subprogram (S) loop
2641 S := Scope (S);
2642 end loop;
2644 -- A predicate check does not apply within internally generated
2645 -- subprograms, such as TSS functions.
2647 if Within_Internal_Subprogram then
2648 return;
2650 -- If the check appears within the predicate function itself, it
2651 -- means that the user specified a check whose formal is the
2652 -- predicated subtype itself, rather than some covering type. This
2653 -- is likely to be a common error, and thus deserves a warning.
2655 elsif Present (S) and then S = Predicate_Function (Typ) then
2656 Error_Msg_NE
2657 ("predicate check includes a call to& that requires a "
2658 & "predicate check??", Parent (N), Fun);
2659 Error_Msg_N
2660 ("\this will result in infinite recursion??", Parent (N));
2662 if Is_First_Subtype (Typ) then
2663 Error_Msg_NE
2664 ("\use an explicit subtype of& to carry the predicate",
2665 Parent (N), Typ);
2666 end if;
2668 Insert_Action (N,
2669 Make_Raise_Storage_Error (Sloc (N),
2670 Reason => SE_Infinite_Recursion));
2672 -- Here for normal case of predicate active
2674 else
2675 -- If the type has a static predicate and the expression is known
2676 -- at compile time, see if the expression satisfies the predicate.
2678 Check_Expression_Against_Static_Predicate (N, Typ);
2680 if not Expander_Active then
2681 return;
2682 end if;
2684 -- For an entity of the type, generate a call to the predicate
2685 -- function, unless its type is an actual subtype, which is not
2686 -- visible outside of the enclosing subprogram.
2688 if Is_Entity_Name (N)
2689 and then not Is_Actual_Subtype (Typ)
2690 then
2691 Insert_Action (N,
2692 Make_Predicate_Check
2693 (Typ, New_Occurrence_Of (Entity (N), Sloc (N))));
2695 -- If the expression is not an entity it may have side effects,
2696 -- and the following call will create an object declaration for
2697 -- it. We disable checks during its analysis, to prevent an
2698 -- infinite recursion.
2700 else
2701 Insert_Action (N,
2702 Make_Predicate_Check
2703 (Typ, Duplicate_Subexpr (N)), Suppress => All_Checks);
2704 end if;
2705 end if;
2706 end if;
2707 end Apply_Predicate_Check;
2709 -----------------------
2710 -- Apply_Range_Check --
2711 -----------------------
2713 procedure Apply_Range_Check
2714 (Ck_Node : Node_Id;
2715 Target_Typ : Entity_Id;
2716 Source_Typ : Entity_Id := Empty)
2718 begin
2719 Apply_Selected_Range_Checks
2720 (Ck_Node, Target_Typ, Source_Typ, Do_Static => False);
2721 end Apply_Range_Check;
2723 ------------------------------
2724 -- Apply_Scalar_Range_Check --
2725 ------------------------------
2727 -- Note that Apply_Scalar_Range_Check never turns the Do_Range_Check flag
2728 -- off if it is already set on.
2730 procedure Apply_Scalar_Range_Check
2731 (Expr : Node_Id;
2732 Target_Typ : Entity_Id;
2733 Source_Typ : Entity_Id := Empty;
2734 Fixed_Int : Boolean := False)
2736 Parnt : constant Node_Id := Parent (Expr);
2737 S_Typ : Entity_Id;
2738 Arr : Node_Id := Empty; -- initialize to prevent warning
2739 Arr_Typ : Entity_Id := Empty; -- initialize to prevent warning
2740 OK : Boolean;
2742 Is_Subscr_Ref : Boolean;
2743 -- Set true if Expr is a subscript
2745 Is_Unconstrained_Subscr_Ref : Boolean;
2746 -- Set true if Expr is a subscript of an unconstrained array. In this
2747 -- case we do not attempt to do an analysis of the value against the
2748 -- range of the subscript, since we don't know the actual subtype.
2750 Int_Real : Boolean;
2751 -- Set to True if Expr should be regarded as a real value even though
2752 -- the type of Expr might be discrete.
2754 procedure Bad_Value (Warn : Boolean := False);
2755 -- Procedure called if value is determined to be out of range. Warn is
2756 -- True to force a warning instead of an error, even when SPARK_Mode is
2757 -- On.
2759 ---------------
2760 -- Bad_Value --
2761 ---------------
2763 procedure Bad_Value (Warn : Boolean := False) is
2764 begin
2765 Apply_Compile_Time_Constraint_Error
2766 (Expr, "value not in range of}??", CE_Range_Check_Failed,
2767 Ent => Target_Typ,
2768 Typ => Target_Typ,
2769 Warn => Warn);
2770 end Bad_Value;
2772 -- Start of processing for Apply_Scalar_Range_Check
2774 begin
2775 -- Return if check obviously not needed
2778 -- Not needed inside generic
2780 Inside_A_Generic
2782 -- Not needed if previous error
2784 or else Target_Typ = Any_Type
2785 or else Nkind (Expr) = N_Error
2787 -- Not needed for non-scalar type
2789 or else not Is_Scalar_Type (Target_Typ)
2791 -- Not needed if we know node raises CE already
2793 or else Raises_Constraint_Error (Expr)
2794 then
2795 return;
2796 end if;
2798 -- Now, see if checks are suppressed
2800 Is_Subscr_Ref :=
2801 Is_List_Member (Expr) and then Nkind (Parnt) = N_Indexed_Component;
2803 if Is_Subscr_Ref then
2804 Arr := Prefix (Parnt);
2805 Arr_Typ := Get_Actual_Subtype_If_Available (Arr);
2807 if Is_Access_Type (Arr_Typ) then
2808 Arr_Typ := Designated_Type (Arr_Typ);
2809 end if;
2810 end if;
2812 if not Do_Range_Check (Expr) then
2814 -- Subscript reference. Check for Index_Checks suppressed
2816 if Is_Subscr_Ref then
2818 -- Check array type and its base type
2820 if Index_Checks_Suppressed (Arr_Typ)
2821 or else Index_Checks_Suppressed (Base_Type (Arr_Typ))
2822 then
2823 return;
2825 -- Check array itself if it is an entity name
2827 elsif Is_Entity_Name (Arr)
2828 and then Index_Checks_Suppressed (Entity (Arr))
2829 then
2830 return;
2832 -- Check expression itself if it is an entity name
2834 elsif Is_Entity_Name (Expr)
2835 and then Index_Checks_Suppressed (Entity (Expr))
2836 then
2837 return;
2838 end if;
2840 -- All other cases, check for Range_Checks suppressed
2842 else
2843 -- Check target type and its base type
2845 if Range_Checks_Suppressed (Target_Typ)
2846 or else Range_Checks_Suppressed (Base_Type (Target_Typ))
2847 then
2848 return;
2850 -- Check expression itself if it is an entity name
2852 elsif Is_Entity_Name (Expr)
2853 and then Range_Checks_Suppressed (Entity (Expr))
2854 then
2855 return;
2857 -- If Expr is part of an assignment statement, then check left
2858 -- side of assignment if it is an entity name.
2860 elsif Nkind (Parnt) = N_Assignment_Statement
2861 and then Is_Entity_Name (Name (Parnt))
2862 and then Range_Checks_Suppressed (Entity (Name (Parnt)))
2863 then
2864 return;
2865 end if;
2866 end if;
2867 end if;
2869 -- Do not set range checks if they are killed
2871 if Nkind (Expr) = N_Unchecked_Type_Conversion
2872 and then Kill_Range_Check (Expr)
2873 then
2874 return;
2875 end if;
2877 -- Do not set range checks for any values from System.Scalar_Values
2878 -- since the whole idea of such values is to avoid checking them.
2880 if Is_Entity_Name (Expr)
2881 and then Is_RTU (Scope (Entity (Expr)), System_Scalar_Values)
2882 then
2883 return;
2884 end if;
2886 -- Now see if we need a check
2888 if No (Source_Typ) then
2889 S_Typ := Etype (Expr);
2890 else
2891 S_Typ := Source_Typ;
2892 end if;
2894 if not Is_Scalar_Type (S_Typ) or else S_Typ = Any_Type then
2895 return;
2896 end if;
2898 Is_Unconstrained_Subscr_Ref :=
2899 Is_Subscr_Ref and then not Is_Constrained (Arr_Typ);
2901 -- Special checks for floating-point type
2903 if Is_Floating_Point_Type (S_Typ) then
2905 -- Always do a range check if the source type includes infinities and
2906 -- the target type does not include infinities. We do not do this if
2907 -- range checks are killed.
2908 -- If the expression is a literal and the bounds of the type are
2909 -- static constants it may be possible to optimize the check.
2911 if Has_Infinities (S_Typ)
2912 and then not Has_Infinities (Target_Typ)
2913 then
2914 -- If the expression is a literal and the bounds of the type are
2915 -- static constants it may be possible to optimize the check.
2917 if Nkind (Expr) = N_Real_Literal then
2918 declare
2919 Tlo : constant Node_Id := Type_Low_Bound (Target_Typ);
2920 Thi : constant Node_Id := Type_High_Bound (Target_Typ);
2922 begin
2923 if Compile_Time_Known_Value (Tlo)
2924 and then Compile_Time_Known_Value (Thi)
2925 and then Expr_Value_R (Expr) >= Expr_Value_R (Tlo)
2926 and then Expr_Value_R (Expr) <= Expr_Value_R (Thi)
2927 then
2928 return;
2929 else
2930 Enable_Range_Check (Expr);
2931 end if;
2932 end;
2934 else
2935 Enable_Range_Check (Expr);
2936 end if;
2937 end if;
2938 end if;
2940 -- Return if we know expression is definitely in the range of the target
2941 -- type as determined by Determine_Range. Right now we only do this for
2942 -- discrete types, and not fixed-point or floating-point types.
2944 -- The additional less-precise tests below catch these cases
2946 -- Note: skip this if we are given a source_typ, since the point of
2947 -- supplying a Source_Typ is to stop us looking at the expression.
2948 -- We could sharpen this test to be out parameters only ???
2950 if Is_Discrete_Type (Target_Typ)
2951 and then Is_Discrete_Type (Etype (Expr))
2952 and then not Is_Unconstrained_Subscr_Ref
2953 and then No (Source_Typ)
2954 then
2955 declare
2956 Tlo : constant Node_Id := Type_Low_Bound (Target_Typ);
2957 Thi : constant Node_Id := Type_High_Bound (Target_Typ);
2958 Lo : Uint;
2959 Hi : Uint;
2961 begin
2962 if Compile_Time_Known_Value (Tlo)
2963 and then Compile_Time_Known_Value (Thi)
2964 then
2965 declare
2966 Lov : constant Uint := Expr_Value (Tlo);
2967 Hiv : constant Uint := Expr_Value (Thi);
2969 begin
2970 -- If range is null, we for sure have a constraint error
2971 -- (we don't even need to look at the value involved,
2972 -- since all possible values will raise CE).
2974 if Lov > Hiv then
2976 -- When SPARK_Mode is On, force a warning instead of
2977 -- an error in that case, as this likely corresponds
2978 -- to deactivated code.
2980 Bad_Value (Warn => SPARK_Mode = On);
2982 -- In GNATprove mode, we enable the range check so that
2983 -- GNATprove will issue a message if it cannot be proved.
2985 if GNATprove_Mode then
2986 Enable_Range_Check (Expr);
2987 end if;
2989 return;
2990 end if;
2992 -- Otherwise determine range of value
2994 Determine_Range (Expr, OK, Lo, Hi, Assume_Valid => True);
2996 if OK then
2998 -- If definitely in range, all OK
3000 if Lo >= Lov and then Hi <= Hiv then
3001 return;
3003 -- If definitely not in range, warn
3005 elsif Lov > Hi or else Hiv < Lo then
3006 Bad_Value;
3007 return;
3009 -- Otherwise we don't know
3011 else
3012 null;
3013 end if;
3014 end if;
3015 end;
3016 end if;
3017 end;
3018 end if;
3020 Int_Real :=
3021 Is_Floating_Point_Type (S_Typ)
3022 or else (Is_Fixed_Point_Type (S_Typ) and then not Fixed_Int);
3024 -- Check if we can determine at compile time whether Expr is in the
3025 -- range of the target type. Note that if S_Typ is within the bounds
3026 -- of Target_Typ then this must be the case. This check is meaningful
3027 -- only if this is not a conversion between integer and real types.
3029 if not Is_Unconstrained_Subscr_Ref
3030 and then Is_Discrete_Type (S_Typ) = Is_Discrete_Type (Target_Typ)
3031 and then
3032 (In_Subrange_Of (S_Typ, Target_Typ, Fixed_Int)
3034 -- Also check if the expression itself is in the range of the
3035 -- target type if it is a known at compile time value. We skip
3036 -- this test if S_Typ is set since for OUT and IN OUT parameters
3037 -- the Expr itself is not relevant to the checking.
3039 or else
3040 (No (Source_Typ)
3041 and then Is_In_Range (Expr, Target_Typ,
3042 Assume_Valid => True,
3043 Fixed_Int => Fixed_Int,
3044 Int_Real => Int_Real)))
3045 then
3046 return;
3048 elsif Is_Out_Of_Range (Expr, Target_Typ,
3049 Assume_Valid => True,
3050 Fixed_Int => Fixed_Int,
3051 Int_Real => Int_Real)
3052 then
3053 Bad_Value;
3054 return;
3056 -- Floating-point case
3057 -- In the floating-point case, we only do range checks if the type is
3058 -- constrained. We definitely do NOT want range checks for unconstrained
3059 -- types, since we want to have infinities, except when
3060 -- Check_Float_Overflow is set.
3062 elsif Is_Floating_Point_Type (S_Typ) then
3063 if Is_Constrained (S_Typ) or else Check_Float_Overflow then
3064 Enable_Range_Check (Expr);
3065 end if;
3067 -- For all other cases we enable a range check unconditionally
3069 else
3070 Enable_Range_Check (Expr);
3071 return;
3072 end if;
3073 end Apply_Scalar_Range_Check;
3075 ----------------------------------
3076 -- Apply_Selected_Length_Checks --
3077 ----------------------------------
3079 procedure Apply_Selected_Length_Checks
3080 (Ck_Node : Node_Id;
3081 Target_Typ : Entity_Id;
3082 Source_Typ : Entity_Id;
3083 Do_Static : Boolean)
3085 Cond : Node_Id;
3086 R_Result : Check_Result;
3087 R_Cno : Node_Id;
3089 Loc : constant Source_Ptr := Sloc (Ck_Node);
3090 Checks_On : constant Boolean :=
3091 (not Index_Checks_Suppressed (Target_Typ))
3092 or else (not Length_Checks_Suppressed (Target_Typ));
3094 begin
3095 -- Only apply checks when generating code
3097 -- Note: this means that we lose some useful warnings if the expander
3098 -- is not active.
3100 if not Expander_Active then
3101 return;
3102 end if;
3104 R_Result :=
3105 Selected_Length_Checks (Ck_Node, Target_Typ, Source_Typ, Empty);
3107 for J in 1 .. 2 loop
3108 R_Cno := R_Result (J);
3109 exit when No (R_Cno);
3111 -- A length check may mention an Itype which is attached to a
3112 -- subsequent node. At the top level in a package this can cause
3113 -- an order-of-elaboration problem, so we make sure that the itype
3114 -- is referenced now.
3116 if Ekind (Current_Scope) = E_Package
3117 and then Is_Compilation_Unit (Current_Scope)
3118 then
3119 Ensure_Defined (Target_Typ, Ck_Node);
3121 if Present (Source_Typ) then
3122 Ensure_Defined (Source_Typ, Ck_Node);
3124 elsif Is_Itype (Etype (Ck_Node)) then
3125 Ensure_Defined (Etype (Ck_Node), Ck_Node);
3126 end if;
3127 end if;
3129 -- If the item is a conditional raise of constraint error, then have
3130 -- a look at what check is being performed and ???
3132 if Nkind (R_Cno) = N_Raise_Constraint_Error
3133 and then Present (Condition (R_Cno))
3134 then
3135 Cond := Condition (R_Cno);
3137 -- Case where node does not now have a dynamic check
3139 if not Has_Dynamic_Length_Check (Ck_Node) then
3141 -- If checks are on, just insert the check
3143 if Checks_On then
3144 Insert_Action (Ck_Node, R_Cno);
3146 if not Do_Static then
3147 Set_Has_Dynamic_Length_Check (Ck_Node);
3148 end if;
3150 -- If checks are off, then analyze the length check after
3151 -- temporarily attaching it to the tree in case the relevant
3152 -- condition can be evaluated at compile time. We still want a
3153 -- compile time warning in this case.
3155 else
3156 Set_Parent (R_Cno, Ck_Node);
3157 Analyze (R_Cno);
3158 end if;
3159 end if;
3161 -- Output a warning if the condition is known to be True
3163 if Is_Entity_Name (Cond)
3164 and then Entity (Cond) = Standard_True
3165 then
3166 Apply_Compile_Time_Constraint_Error
3167 (Ck_Node, "wrong length for array of}??",
3168 CE_Length_Check_Failed,
3169 Ent => Target_Typ,
3170 Typ => Target_Typ);
3172 -- If we were only doing a static check, or if checks are not
3173 -- on, then we want to delete the check, since it is not needed.
3174 -- We do this by replacing the if statement by a null statement
3176 elsif Do_Static or else not Checks_On then
3177 Remove_Warning_Messages (R_Cno);
3178 Rewrite (R_Cno, Make_Null_Statement (Loc));
3179 end if;
3181 else
3182 Install_Static_Check (R_Cno, Loc);
3183 end if;
3184 end loop;
3185 end Apply_Selected_Length_Checks;
3187 ---------------------------------
3188 -- Apply_Selected_Range_Checks --
3189 ---------------------------------
3191 procedure Apply_Selected_Range_Checks
3192 (Ck_Node : Node_Id;
3193 Target_Typ : Entity_Id;
3194 Source_Typ : Entity_Id;
3195 Do_Static : Boolean)
3197 Loc : constant Source_Ptr := Sloc (Ck_Node);
3198 Checks_On : constant Boolean :=
3199 not Index_Checks_Suppressed (Target_Typ)
3200 or else
3201 not Range_Checks_Suppressed (Target_Typ);
3203 Cond : Node_Id;
3204 R_Cno : Node_Id;
3205 R_Result : Check_Result;
3207 begin
3208 -- Only apply checks when generating code. In GNATprove mode, we do not
3209 -- apply the checks, but we still call Selected_Range_Checks to possibly
3210 -- issue errors on SPARK code when a run-time error can be detected at
3211 -- compile time.
3213 if not GNATprove_Mode then
3214 if not Expander_Active or not Checks_On then
3215 return;
3216 end if;
3217 end if;
3219 R_Result :=
3220 Selected_Range_Checks (Ck_Node, Target_Typ, Source_Typ, Empty);
3222 if GNATprove_Mode then
3223 return;
3224 end if;
3226 for J in 1 .. 2 loop
3227 R_Cno := R_Result (J);
3228 exit when No (R_Cno);
3230 -- The range check requires runtime evaluation. Depending on what its
3231 -- triggering condition is, the check may be converted into a compile
3232 -- time constraint check.
3234 if Nkind (R_Cno) = N_Raise_Constraint_Error
3235 and then Present (Condition (R_Cno))
3236 then
3237 Cond := Condition (R_Cno);
3239 -- Insert the range check before the related context. Note that
3240 -- this action analyses the triggering condition.
3242 Insert_Action (Ck_Node, R_Cno);
3244 -- This old code doesn't make sense, why is the context flagged as
3245 -- requiring dynamic range checks now in the middle of generating
3246 -- them ???
3248 if not Do_Static then
3249 Set_Has_Dynamic_Range_Check (Ck_Node);
3250 end if;
3252 -- The triggering condition evaluates to True, the range check
3253 -- can be converted into a compile time constraint check.
3255 if Is_Entity_Name (Cond)
3256 and then Entity (Cond) = Standard_True
3257 then
3258 -- Since an N_Range is technically not an expression, we have
3259 -- to set one of the bounds to C_E and then just flag the
3260 -- N_Range. The warning message will point to the lower bound
3261 -- and complain about a range, which seems OK.
3263 if Nkind (Ck_Node) = N_Range then
3264 Apply_Compile_Time_Constraint_Error
3265 (Low_Bound (Ck_Node),
3266 "static range out of bounds of}??",
3267 CE_Range_Check_Failed,
3268 Ent => Target_Typ,
3269 Typ => Target_Typ);
3271 Set_Raises_Constraint_Error (Ck_Node);
3273 else
3274 Apply_Compile_Time_Constraint_Error
3275 (Ck_Node,
3276 "static value out of range of}??",
3277 CE_Range_Check_Failed,
3278 Ent => Target_Typ,
3279 Typ => Target_Typ);
3280 end if;
3282 -- If we were only doing a static check, or if checks are not
3283 -- on, then we want to delete the check, since it is not needed.
3284 -- We do this by replacing the if statement by a null statement
3286 elsif Do_Static then
3287 Remove_Warning_Messages (R_Cno);
3288 Rewrite (R_Cno, Make_Null_Statement (Loc));
3289 end if;
3291 -- The range check raises Constraint_Error explicitly
3293 else
3294 Install_Static_Check (R_Cno, Loc);
3295 end if;
3296 end loop;
3297 end Apply_Selected_Range_Checks;
3299 -------------------------------
3300 -- Apply_Static_Length_Check --
3301 -------------------------------
3303 procedure Apply_Static_Length_Check
3304 (Expr : Node_Id;
3305 Target_Typ : Entity_Id;
3306 Source_Typ : Entity_Id := Empty)
3308 begin
3309 Apply_Selected_Length_Checks
3310 (Expr, Target_Typ, Source_Typ, Do_Static => True);
3311 end Apply_Static_Length_Check;
3313 -------------------------------------
3314 -- Apply_Subscript_Validity_Checks --
3315 -------------------------------------
3317 procedure Apply_Subscript_Validity_Checks (Expr : Node_Id) is
3318 Sub : Node_Id;
3320 begin
3321 pragma Assert (Nkind (Expr) = N_Indexed_Component);
3323 -- Loop through subscripts
3325 Sub := First (Expressions (Expr));
3326 while Present (Sub) loop
3328 -- Check one subscript. Note that we do not worry about enumeration
3329 -- type with holes, since we will convert the value to a Pos value
3330 -- for the subscript, and that convert will do the necessary validity
3331 -- check.
3333 Ensure_Valid (Sub, Holes_OK => True);
3335 -- Move to next subscript
3337 Sub := Next (Sub);
3338 end loop;
3339 end Apply_Subscript_Validity_Checks;
3341 ----------------------------------
3342 -- Apply_Type_Conversion_Checks --
3343 ----------------------------------
3345 procedure Apply_Type_Conversion_Checks (N : Node_Id) is
3346 Target_Type : constant Entity_Id := Etype (N);
3347 Target_Base : constant Entity_Id := Base_Type (Target_Type);
3348 Expr : constant Node_Id := Expression (N);
3350 Expr_Type : constant Entity_Id := Underlying_Type (Etype (Expr));
3351 -- Note: if Etype (Expr) is a private type without discriminants, its
3352 -- full view might have discriminants with defaults, so we need the
3353 -- full view here to retrieve the constraints.
3355 begin
3356 if Inside_A_Generic then
3357 return;
3359 -- Skip these checks if serious errors detected, there are some nasty
3360 -- situations of incomplete trees that blow things up.
3362 elsif Serious_Errors_Detected > 0 then
3363 return;
3365 -- Never generate discriminant checks for Unchecked_Union types
3367 elsif Present (Expr_Type)
3368 and then Is_Unchecked_Union (Expr_Type)
3369 then
3370 return;
3372 -- Scalar type conversions of the form Target_Type (Expr) require a
3373 -- range check if we cannot be sure that Expr is in the base type of
3374 -- Target_Typ and also that Expr is in the range of Target_Typ. These
3375 -- are not quite the same condition from an implementation point of
3376 -- view, but clearly the second includes the first.
3378 elsif Is_Scalar_Type (Target_Type) then
3379 declare
3380 Conv_OK : constant Boolean := Conversion_OK (N);
3381 -- If the Conversion_OK flag on the type conversion is set and no
3382 -- floating-point type is involved in the type conversion then
3383 -- fixed-point values must be read as integral values.
3385 Float_To_Int : constant Boolean :=
3386 Is_Floating_Point_Type (Expr_Type)
3387 and then Is_Integer_Type (Target_Type);
3389 begin
3390 if not Overflow_Checks_Suppressed (Target_Base)
3391 and then not Overflow_Checks_Suppressed (Target_Type)
3392 and then not
3393 In_Subrange_Of (Expr_Type, Target_Base, Fixed_Int => Conv_OK)
3394 and then not Float_To_Int
3395 then
3396 -- A small optimization: the attribute 'Pos applied to an
3397 -- enumeration type has a known range, even though its type is
3398 -- Universal_Integer. So in numeric conversions it is usually
3399 -- within range of the target integer type. Use the static
3400 -- bounds of the base types to check. Disable this optimization
3401 -- in case of a generic formal discrete type, because we don't
3402 -- necessarily know the upper bound yet.
3404 if Nkind (Expr) = N_Attribute_Reference
3405 and then Attribute_Name (Expr) = Name_Pos
3406 and then Is_Enumeration_Type (Etype (Prefix (Expr)))
3407 and then not Is_Generic_Type (Etype (Prefix (Expr)))
3408 and then Is_Integer_Type (Target_Type)
3409 then
3410 declare
3411 Enum_T : constant Entity_Id :=
3412 Root_Type (Etype (Prefix (Expr)));
3413 Int_T : constant Entity_Id := Base_Type (Target_Type);
3414 Last_I : constant Uint :=
3415 Intval (High_Bound (Scalar_Range (Int_T)));
3416 Last_E : Uint;
3418 begin
3419 -- Character types have no explicit literals, so we use
3420 -- the known number of characters in the type.
3422 if Root_Type (Enum_T) = Standard_Character then
3423 Last_E := UI_From_Int (255);
3425 elsif Enum_T = Standard_Wide_Character
3426 or else Enum_T = Standard_Wide_Wide_Character
3427 then
3428 Last_E := UI_From_Int (65535);
3430 else
3431 Last_E :=
3432 Enumeration_Pos
3433 (Entity (High_Bound (Scalar_Range (Enum_T))));
3434 end if;
3436 if Last_E <= Last_I then
3437 null;
3439 else
3440 Activate_Overflow_Check (N);
3441 end if;
3442 end;
3444 else
3445 Activate_Overflow_Check (N);
3446 end if;
3447 end if;
3449 if not Range_Checks_Suppressed (Target_Type)
3450 and then not Range_Checks_Suppressed (Expr_Type)
3451 then
3452 if Float_To_Int then
3453 Apply_Float_Conversion_Check (Expr, Target_Type);
3454 else
3455 Apply_Scalar_Range_Check
3456 (Expr, Target_Type, Fixed_Int => Conv_OK);
3458 -- If the target type has predicates, we need to indicate
3459 -- the need for a check, even if Determine_Range finds that
3460 -- the value is within bounds. This may be the case e.g for
3461 -- a division with a constant denominator.
3463 if Has_Predicates (Target_Type) then
3464 Enable_Range_Check (Expr);
3465 end if;
3466 end if;
3467 end if;
3468 end;
3470 elsif Comes_From_Source (N)
3471 and then not Discriminant_Checks_Suppressed (Target_Type)
3472 and then Is_Record_Type (Target_Type)
3473 and then Is_Derived_Type (Target_Type)
3474 and then not Is_Tagged_Type (Target_Type)
3475 and then not Is_Constrained (Target_Type)
3476 and then Present (Stored_Constraint (Target_Type))
3477 then
3478 -- An unconstrained derived type may have inherited discriminant.
3479 -- Build an actual discriminant constraint list using the stored
3480 -- constraint, to verify that the expression of the parent type
3481 -- satisfies the constraints imposed by the (unconstrained) derived
3482 -- type. This applies to value conversions, not to view conversions
3483 -- of tagged types.
3485 declare
3486 Loc : constant Source_Ptr := Sloc (N);
3487 Cond : Node_Id;
3488 Constraint : Elmt_Id;
3489 Discr_Value : Node_Id;
3490 Discr : Entity_Id;
3492 New_Constraints : constant Elist_Id := New_Elmt_List;
3493 Old_Constraints : constant Elist_Id :=
3494 Discriminant_Constraint (Expr_Type);
3496 begin
3497 Constraint := First_Elmt (Stored_Constraint (Target_Type));
3498 while Present (Constraint) loop
3499 Discr_Value := Node (Constraint);
3501 if Is_Entity_Name (Discr_Value)
3502 and then Ekind (Entity (Discr_Value)) = E_Discriminant
3503 then
3504 Discr := Corresponding_Discriminant (Entity (Discr_Value));
3506 if Present (Discr)
3507 and then Scope (Discr) = Base_Type (Expr_Type)
3508 then
3509 -- Parent is constrained by new discriminant. Obtain
3510 -- Value of original discriminant in expression. If the
3511 -- new discriminant has been used to constrain more than
3512 -- one of the stored discriminants, this will provide the
3513 -- required consistency check.
3515 Append_Elmt
3516 (Make_Selected_Component (Loc,
3517 Prefix =>
3518 Duplicate_Subexpr_No_Checks
3519 (Expr, Name_Req => True),
3520 Selector_Name =>
3521 Make_Identifier (Loc, Chars (Discr))),
3522 New_Constraints);
3524 else
3525 -- Discriminant of more remote ancestor ???
3527 return;
3528 end if;
3530 -- Derived type definition has an explicit value for this
3531 -- stored discriminant.
3533 else
3534 Append_Elmt
3535 (Duplicate_Subexpr_No_Checks (Discr_Value),
3536 New_Constraints);
3537 end if;
3539 Next_Elmt (Constraint);
3540 end loop;
3542 -- Use the unconstrained expression type to retrieve the
3543 -- discriminants of the parent, and apply momentarily the
3544 -- discriminant constraint synthesized above.
3546 Set_Discriminant_Constraint (Expr_Type, New_Constraints);
3547 Cond := Build_Discriminant_Checks (Expr, Expr_Type);
3548 Set_Discriminant_Constraint (Expr_Type, Old_Constraints);
3550 Insert_Action (N,
3551 Make_Raise_Constraint_Error (Loc,
3552 Condition => Cond,
3553 Reason => CE_Discriminant_Check_Failed));
3554 end;
3556 -- For arrays, checks are set now, but conversions are applied during
3557 -- expansion, to take into accounts changes of representation. The
3558 -- checks become range checks on the base type or length checks on the
3559 -- subtype, depending on whether the target type is unconstrained or
3560 -- constrained. Note that the range check is put on the expression of a
3561 -- type conversion, while the length check is put on the type conversion
3562 -- itself.
3564 elsif Is_Array_Type (Target_Type) then
3565 if Is_Constrained (Target_Type) then
3566 Set_Do_Length_Check (N);
3567 else
3568 Set_Do_Range_Check (Expr);
3569 end if;
3570 end if;
3571 end Apply_Type_Conversion_Checks;
3573 ----------------------------------------------
3574 -- Apply_Universal_Integer_Attribute_Checks --
3575 ----------------------------------------------
3577 procedure Apply_Universal_Integer_Attribute_Checks (N : Node_Id) is
3578 Loc : constant Source_Ptr := Sloc (N);
3579 Typ : constant Entity_Id := Etype (N);
3581 begin
3582 if Inside_A_Generic then
3583 return;
3585 -- Nothing to do if checks are suppressed
3587 elsif Range_Checks_Suppressed (Typ)
3588 and then Overflow_Checks_Suppressed (Typ)
3589 then
3590 return;
3592 -- Nothing to do if the attribute does not come from source. The
3593 -- internal attributes we generate of this type do not need checks,
3594 -- and furthermore the attempt to check them causes some circular
3595 -- elaboration orders when dealing with packed types.
3597 elsif not Comes_From_Source (N) then
3598 return;
3600 -- If the prefix is a selected component that depends on a discriminant
3601 -- the check may improperly expose a discriminant instead of using
3602 -- the bounds of the object itself. Set the type of the attribute to
3603 -- the base type of the context, so that a check will be imposed when
3604 -- needed (e.g. if the node appears as an index).
3606 elsif Nkind (Prefix (N)) = N_Selected_Component
3607 and then Ekind (Typ) = E_Signed_Integer_Subtype
3608 and then Depends_On_Discriminant (Scalar_Range (Typ))
3609 then
3610 Set_Etype (N, Base_Type (Typ));
3612 -- Otherwise, replace the attribute node with a type conversion node
3613 -- whose expression is the attribute, retyped to universal integer, and
3614 -- whose subtype mark is the target type. The call to analyze this
3615 -- conversion will set range and overflow checks as required for proper
3616 -- detection of an out of range value.
3618 else
3619 Set_Etype (N, Universal_Integer);
3620 Set_Analyzed (N, True);
3622 Rewrite (N,
3623 Make_Type_Conversion (Loc,
3624 Subtype_Mark => New_Occurrence_Of (Typ, Loc),
3625 Expression => Relocate_Node (N)));
3627 Analyze_And_Resolve (N, Typ);
3628 return;
3629 end if;
3630 end Apply_Universal_Integer_Attribute_Checks;
3632 -------------------------------------
3633 -- Atomic_Synchronization_Disabled --
3634 -------------------------------------
3636 -- Note: internally Disable/Enable_Atomic_Synchronization is implemented
3637 -- using a bogus check called Atomic_Synchronization. This is to make it
3638 -- more convenient to get exactly the same semantics as [Un]Suppress.
3640 function Atomic_Synchronization_Disabled (E : Entity_Id) return Boolean is
3641 begin
3642 -- If debug flag d.e is set, always return False, i.e. all atomic sync
3643 -- looks enabled, since it is never disabled.
3645 if Debug_Flag_Dot_E then
3646 return False;
3648 -- If debug flag d.d is set then always return True, i.e. all atomic
3649 -- sync looks disabled, since it always tests True.
3651 elsif Debug_Flag_Dot_D then
3652 return True;
3654 -- If entity present, then check result for that entity
3656 elsif Present (E) and then Checks_May_Be_Suppressed (E) then
3657 return Is_Check_Suppressed (E, Atomic_Synchronization);
3659 -- Otherwise result depends on current scope setting
3661 else
3662 return Scope_Suppress.Suppress (Atomic_Synchronization);
3663 end if;
3664 end Atomic_Synchronization_Disabled;
3666 -------------------------------
3667 -- Build_Discriminant_Checks --
3668 -------------------------------
3670 function Build_Discriminant_Checks
3671 (N : Node_Id;
3672 T_Typ : Entity_Id) return Node_Id
3674 Loc : constant Source_Ptr := Sloc (N);
3675 Cond : Node_Id;
3676 Disc : Elmt_Id;
3677 Disc_Ent : Entity_Id;
3678 Dref : Node_Id;
3679 Dval : Node_Id;
3681 function Aggregate_Discriminant_Val (Disc : Entity_Id) return Node_Id;
3683 ----------------------------------
3684 -- Aggregate_Discriminant_Value --
3685 ----------------------------------
3687 function Aggregate_Discriminant_Val (Disc : Entity_Id) return Node_Id is
3688 Assoc : Node_Id;
3690 begin
3691 -- The aggregate has been normalized with named associations. We use
3692 -- the Chars field to locate the discriminant to take into account
3693 -- discriminants in derived types, which carry the same name as those
3694 -- in the parent.
3696 Assoc := First (Component_Associations (N));
3697 while Present (Assoc) loop
3698 if Chars (First (Choices (Assoc))) = Chars (Disc) then
3699 return Expression (Assoc);
3700 else
3701 Next (Assoc);
3702 end if;
3703 end loop;
3705 -- Discriminant must have been found in the loop above
3707 raise Program_Error;
3708 end Aggregate_Discriminant_Val;
3710 -- Start of processing for Build_Discriminant_Checks
3712 begin
3713 -- Loop through discriminants evolving the condition
3715 Cond := Empty;
3716 Disc := First_Elmt (Discriminant_Constraint (T_Typ));
3718 -- For a fully private type, use the discriminants of the parent type
3720 if Is_Private_Type (T_Typ)
3721 and then No (Full_View (T_Typ))
3722 then
3723 Disc_Ent := First_Discriminant (Etype (Base_Type (T_Typ)));
3724 else
3725 Disc_Ent := First_Discriminant (T_Typ);
3726 end if;
3728 while Present (Disc) loop
3729 Dval := Node (Disc);
3731 if Nkind (Dval) = N_Identifier
3732 and then Ekind (Entity (Dval)) = E_Discriminant
3733 then
3734 Dval := New_Occurrence_Of (Discriminal (Entity (Dval)), Loc);
3735 else
3736 Dval := Duplicate_Subexpr_No_Checks (Dval);
3737 end if;
3739 -- If we have an Unchecked_Union node, we can infer the discriminants
3740 -- of the node.
3742 if Is_Unchecked_Union (Base_Type (T_Typ)) then
3743 Dref := New_Copy (
3744 Get_Discriminant_Value (
3745 First_Discriminant (T_Typ),
3746 T_Typ,
3747 Stored_Constraint (T_Typ)));
3749 elsif Nkind (N) = N_Aggregate then
3750 Dref :=
3751 Duplicate_Subexpr_No_Checks
3752 (Aggregate_Discriminant_Val (Disc_Ent));
3754 else
3755 Dref :=
3756 Make_Selected_Component (Loc,
3757 Prefix =>
3758 Duplicate_Subexpr_No_Checks (N, Name_Req => True),
3759 Selector_Name => Make_Identifier (Loc, Chars (Disc_Ent)));
3761 Set_Is_In_Discriminant_Check (Dref);
3762 end if;
3764 Evolve_Or_Else (Cond,
3765 Make_Op_Ne (Loc,
3766 Left_Opnd => Dref,
3767 Right_Opnd => Dval));
3769 Next_Elmt (Disc);
3770 Next_Discriminant (Disc_Ent);
3771 end loop;
3773 return Cond;
3774 end Build_Discriminant_Checks;
3776 ------------------
3777 -- Check_Needed --
3778 ------------------
3780 function Check_Needed (Nod : Node_Id; Check : Check_Type) return Boolean is
3781 N : Node_Id;
3782 P : Node_Id;
3783 K : Node_Kind;
3784 L : Node_Id;
3785 R : Node_Id;
3787 function Left_Expression (Op : Node_Id) return Node_Id;
3788 -- Return the relevant expression from the left operand of the given
3789 -- short circuit form: this is LO itself, except if LO is a qualified
3790 -- expression, a type conversion, or an expression with actions, in
3791 -- which case this is Left_Expression (Expression (LO)).
3793 ---------------------
3794 -- Left_Expression --
3795 ---------------------
3797 function Left_Expression (Op : Node_Id) return Node_Id is
3798 LE : Node_Id := Left_Opnd (Op);
3799 begin
3800 while Nkind_In (LE, N_Qualified_Expression,
3801 N_Type_Conversion,
3802 N_Expression_With_Actions)
3803 loop
3804 LE := Expression (LE);
3805 end loop;
3807 return LE;
3808 end Left_Expression;
3810 -- Start of processing for Check_Needed
3812 begin
3813 -- Always check if not simple entity
3815 if Nkind (Nod) not in N_Has_Entity
3816 or else not Comes_From_Source (Nod)
3817 then
3818 return True;
3819 end if;
3821 -- Look up tree for short circuit
3823 N := Nod;
3824 loop
3825 P := Parent (N);
3826 K := Nkind (P);
3828 -- Done if out of subexpression (note that we allow generated stuff
3829 -- such as itype declarations in this context, to keep the loop going
3830 -- since we may well have generated such stuff in complex situations.
3831 -- Also done if no parent (probably an error condition, but no point
3832 -- in behaving nasty if we find it).
3834 if No (P)
3835 or else (K not in N_Subexpr and then Comes_From_Source (P))
3836 then
3837 return True;
3839 -- Or/Or Else case, where test is part of the right operand, or is
3840 -- part of one of the actions associated with the right operand, and
3841 -- the left operand is an equality test.
3843 elsif K = N_Op_Or then
3844 exit when N = Right_Opnd (P)
3845 and then Nkind (Left_Expression (P)) = N_Op_Eq;
3847 elsif K = N_Or_Else then
3848 exit when (N = Right_Opnd (P)
3849 or else
3850 (Is_List_Member (N)
3851 and then List_Containing (N) = Actions (P)))
3852 and then Nkind (Left_Expression (P)) = N_Op_Eq;
3854 -- Similar test for the And/And then case, where the left operand
3855 -- is an inequality test.
3857 elsif K = N_Op_And then
3858 exit when N = Right_Opnd (P)
3859 and then Nkind (Left_Expression (P)) = N_Op_Ne;
3861 elsif K = N_And_Then then
3862 exit when (N = Right_Opnd (P)
3863 or else
3864 (Is_List_Member (N)
3865 and then List_Containing (N) = Actions (P)))
3866 and then Nkind (Left_Expression (P)) = N_Op_Ne;
3867 end if;
3869 N := P;
3870 end loop;
3872 -- If we fall through the loop, then we have a conditional with an
3873 -- appropriate test as its left operand, so look further.
3875 L := Left_Expression (P);
3877 -- L is an "=" or "/=" operator: extract its operands
3879 R := Right_Opnd (L);
3880 L := Left_Opnd (L);
3882 -- Left operand of test must match original variable
3884 if Nkind (L) not in N_Has_Entity or else Entity (L) /= Entity (Nod) then
3885 return True;
3886 end if;
3888 -- Right operand of test must be key value (zero or null)
3890 case Check is
3891 when Access_Check =>
3892 if not Known_Null (R) then
3893 return True;
3894 end if;
3896 when Division_Check =>
3897 if not Compile_Time_Known_Value (R)
3898 or else Expr_Value (R) /= Uint_0
3899 then
3900 return True;
3901 end if;
3903 when others =>
3904 raise Program_Error;
3905 end case;
3907 -- Here we have the optimizable case, warn if not short-circuited
3909 if K = N_Op_And or else K = N_Op_Or then
3910 Error_Msg_Warn := SPARK_Mode /= On;
3912 case Check is
3913 when Access_Check =>
3914 if GNATprove_Mode then
3915 Error_Msg_N
3916 ("Constraint_Error might have been raised (access check)",
3917 Parent (Nod));
3918 else
3919 Error_Msg_N
3920 ("Constraint_Error may be raised (access check)??",
3921 Parent (Nod));
3922 end if;
3924 when Division_Check =>
3925 if GNATprove_Mode then
3926 Error_Msg_N
3927 ("Constraint_Error might have been raised (zero divide)",
3928 Parent (Nod));
3929 else
3930 Error_Msg_N
3931 ("Constraint_Error may be raised (zero divide)??",
3932 Parent (Nod));
3933 end if;
3935 when others =>
3936 raise Program_Error;
3937 end case;
3939 if K = N_Op_And then
3940 Error_Msg_N -- CODEFIX
3941 ("use `AND THEN` instead of AND??", P);
3942 else
3943 Error_Msg_N -- CODEFIX
3944 ("use `OR ELSE` instead of OR??", P);
3945 end if;
3947 -- If not short-circuited, we need the check
3949 return True;
3951 -- If short-circuited, we can omit the check
3953 else
3954 return False;
3955 end if;
3956 end Check_Needed;
3958 -----------------------------------
3959 -- Check_Valid_Lvalue_Subscripts --
3960 -----------------------------------
3962 procedure Check_Valid_Lvalue_Subscripts (Expr : Node_Id) is
3963 begin
3964 -- Skip this if range checks are suppressed
3966 if Range_Checks_Suppressed (Etype (Expr)) then
3967 return;
3969 -- Only do this check for expressions that come from source. We assume
3970 -- that expander generated assignments explicitly include any necessary
3971 -- checks. Note that this is not just an optimization, it avoids
3972 -- infinite recursions.
3974 elsif not Comes_From_Source (Expr) then
3975 return;
3977 -- For a selected component, check the prefix
3979 elsif Nkind (Expr) = N_Selected_Component then
3980 Check_Valid_Lvalue_Subscripts (Prefix (Expr));
3981 return;
3983 -- Case of indexed component
3985 elsif Nkind (Expr) = N_Indexed_Component then
3986 Apply_Subscript_Validity_Checks (Expr);
3988 -- Prefix may itself be or contain an indexed component, and these
3989 -- subscripts need checking as well.
3991 Check_Valid_Lvalue_Subscripts (Prefix (Expr));
3992 end if;
3993 end Check_Valid_Lvalue_Subscripts;
3995 ----------------------------------
3996 -- Null_Exclusion_Static_Checks --
3997 ----------------------------------
3999 procedure Null_Exclusion_Static_Checks (N : Node_Id) is
4000 Error_Node : Node_Id;
4001 Expr : Node_Id;
4002 Has_Null : constant Boolean := Has_Null_Exclusion (N);
4003 K : constant Node_Kind := Nkind (N);
4004 Typ : Entity_Id;
4006 begin
4007 pragma Assert
4008 (Nkind_In (K, N_Component_Declaration,
4009 N_Discriminant_Specification,
4010 N_Function_Specification,
4011 N_Object_Declaration,
4012 N_Parameter_Specification));
4014 if K = N_Function_Specification then
4015 Typ := Etype (Defining_Entity (N));
4016 else
4017 Typ := Etype (Defining_Identifier (N));
4018 end if;
4020 case K is
4021 when N_Component_Declaration =>
4022 if Present (Access_Definition (Component_Definition (N))) then
4023 Error_Node := Component_Definition (N);
4024 else
4025 Error_Node := Subtype_Indication (Component_Definition (N));
4026 end if;
4028 when N_Discriminant_Specification =>
4029 Error_Node := Discriminant_Type (N);
4031 when N_Function_Specification =>
4032 Error_Node := Result_Definition (N);
4034 when N_Object_Declaration =>
4035 Error_Node := Object_Definition (N);
4037 when N_Parameter_Specification =>
4038 Error_Node := Parameter_Type (N);
4040 when others =>
4041 raise Program_Error;
4042 end case;
4044 if Has_Null then
4046 -- Enforce legality rule 3.10 (13): A null exclusion can only be
4047 -- applied to an access [sub]type.
4049 if not Is_Access_Type (Typ) then
4050 Error_Msg_N
4051 ("`NOT NULL` allowed only for an access type", Error_Node);
4053 -- Enforce legality rule RM 3.10(14/1): A null exclusion can only
4054 -- be applied to a [sub]type that does not exclude null already.
4056 elsif Can_Never_Be_Null (Typ)
4057 and then Comes_From_Source (Typ)
4058 then
4059 Error_Msg_NE
4060 ("`NOT NULL` not allowed (& already excludes null)",
4061 Error_Node, Typ);
4062 end if;
4063 end if;
4065 -- Check that null-excluding objects are always initialized, except for
4066 -- deferred constants, for which the expression will appear in the full
4067 -- declaration.
4069 if K = N_Object_Declaration
4070 and then No (Expression (N))
4071 and then not Constant_Present (N)
4072 and then not No_Initialization (N)
4073 then
4074 -- Add an expression that assigns null. This node is needed by
4075 -- Apply_Compile_Time_Constraint_Error, which will replace this with
4076 -- a Constraint_Error node.
4078 Set_Expression (N, Make_Null (Sloc (N)));
4079 Set_Etype (Expression (N), Etype (Defining_Identifier (N)));
4081 Apply_Compile_Time_Constraint_Error
4082 (N => Expression (N),
4083 Msg =>
4084 "(Ada 2005) null-excluding objects must be initialized??",
4085 Reason => CE_Null_Not_Allowed);
4086 end if;
4088 -- Check that a null-excluding component, formal or object is not being
4089 -- assigned a null value. Otherwise generate a warning message and
4090 -- replace Expression (N) by an N_Constraint_Error node.
4092 if K /= N_Function_Specification then
4093 Expr := Expression (N);
4095 if Present (Expr) and then Known_Null (Expr) then
4096 case K is
4097 when N_Component_Declaration
4098 | N_Discriminant_Specification
4100 Apply_Compile_Time_Constraint_Error
4101 (N => Expr,
4102 Msg =>
4103 "(Ada 2005) null not allowed in null-excluding "
4104 & "components??",
4105 Reason => CE_Null_Not_Allowed);
4107 when N_Object_Declaration =>
4108 Apply_Compile_Time_Constraint_Error
4109 (N => Expr,
4110 Msg =>
4111 "(Ada 2005) null not allowed in null-excluding "
4112 & "objects??",
4113 Reason => CE_Null_Not_Allowed);
4115 when N_Parameter_Specification =>
4116 Apply_Compile_Time_Constraint_Error
4117 (N => Expr,
4118 Msg =>
4119 "(Ada 2005) null not allowed in null-excluding "
4120 & "formals??",
4121 Reason => CE_Null_Not_Allowed);
4123 when others =>
4124 null;
4125 end case;
4126 end if;
4127 end if;
4128 end Null_Exclusion_Static_Checks;
4130 ----------------------------------
4131 -- Conditional_Statements_Begin --
4132 ----------------------------------
4134 procedure Conditional_Statements_Begin is
4135 begin
4136 Saved_Checks_TOS := Saved_Checks_TOS + 1;
4138 -- If stack overflows, kill all checks, that way we know to simply reset
4139 -- the number of saved checks to zero on return. This should never occur
4140 -- in practice.
4142 if Saved_Checks_TOS > Saved_Checks_Stack'Last then
4143 Kill_All_Checks;
4145 -- In the normal case, we just make a new stack entry saving the current
4146 -- number of saved checks for a later restore.
4148 else
4149 Saved_Checks_Stack (Saved_Checks_TOS) := Num_Saved_Checks;
4151 if Debug_Flag_CC then
4152 w ("Conditional_Statements_Begin: Num_Saved_Checks = ",
4153 Num_Saved_Checks);
4154 end if;
4155 end if;
4156 end Conditional_Statements_Begin;
4158 --------------------------------
4159 -- Conditional_Statements_End --
4160 --------------------------------
4162 procedure Conditional_Statements_End is
4163 begin
4164 pragma Assert (Saved_Checks_TOS > 0);
4166 -- If the saved checks stack overflowed, then we killed all checks, so
4167 -- setting the number of saved checks back to zero is correct. This
4168 -- should never occur in practice.
4170 if Saved_Checks_TOS > Saved_Checks_Stack'Last then
4171 Num_Saved_Checks := 0;
4173 -- In the normal case, restore the number of saved checks from the top
4174 -- stack entry.
4176 else
4177 Num_Saved_Checks := Saved_Checks_Stack (Saved_Checks_TOS);
4179 if Debug_Flag_CC then
4180 w ("Conditional_Statements_End: Num_Saved_Checks = ",
4181 Num_Saved_Checks);
4182 end if;
4183 end if;
4185 Saved_Checks_TOS := Saved_Checks_TOS - 1;
4186 end Conditional_Statements_End;
4188 -------------------------
4189 -- Convert_From_Bignum --
4190 -------------------------
4192 function Convert_From_Bignum (N : Node_Id) return Node_Id is
4193 Loc : constant Source_Ptr := Sloc (N);
4195 begin
4196 pragma Assert (Is_RTE (Etype (N), RE_Bignum));
4198 -- Construct call From Bignum
4200 return
4201 Make_Function_Call (Loc,
4202 Name =>
4203 New_Occurrence_Of (RTE (RE_From_Bignum), Loc),
4204 Parameter_Associations => New_List (Relocate_Node (N)));
4205 end Convert_From_Bignum;
4207 -----------------------
4208 -- Convert_To_Bignum --
4209 -----------------------
4211 function Convert_To_Bignum (N : Node_Id) return Node_Id is
4212 Loc : constant Source_Ptr := Sloc (N);
4214 begin
4215 -- Nothing to do if Bignum already except call Relocate_Node
4217 if Is_RTE (Etype (N), RE_Bignum) then
4218 return Relocate_Node (N);
4220 -- Otherwise construct call to To_Bignum, converting the operand to the
4221 -- required Long_Long_Integer form.
4223 else
4224 pragma Assert (Is_Signed_Integer_Type (Etype (N)));
4225 return
4226 Make_Function_Call (Loc,
4227 Name =>
4228 New_Occurrence_Of (RTE (RE_To_Bignum), Loc),
4229 Parameter_Associations => New_List (
4230 Convert_To (Standard_Long_Long_Integer, Relocate_Node (N))));
4231 end if;
4232 end Convert_To_Bignum;
4234 ---------------------
4235 -- Determine_Range --
4236 ---------------------
4238 Cache_Size : constant := 2 ** 10;
4239 type Cache_Index is range 0 .. Cache_Size - 1;
4240 -- Determine size of below cache (power of 2 is more efficient)
4242 Determine_Range_Cache_N : array (Cache_Index) of Node_Id;
4243 Determine_Range_Cache_V : array (Cache_Index) of Boolean;
4244 Determine_Range_Cache_Lo : array (Cache_Index) of Uint;
4245 Determine_Range_Cache_Hi : array (Cache_Index) of Uint;
4246 Determine_Range_Cache_Lo_R : array (Cache_Index) of Ureal;
4247 Determine_Range_Cache_Hi_R : array (Cache_Index) of Ureal;
4248 -- The above arrays are used to implement a small direct cache for
4249 -- Determine_Range and Determine_Range_R calls. Because of the way these
4250 -- subprograms recursively traces subexpressions, and because overflow
4251 -- checking calls the routine on the way up the tree, a quadratic behavior
4252 -- can otherwise be encountered in large expressions. The cache entry for
4253 -- node N is stored in the (N mod Cache_Size) entry, and can be validated
4254 -- by checking the actual node value stored there. The Range_Cache_V array
4255 -- records the setting of Assume_Valid for the cache entry.
4257 procedure Determine_Range
4258 (N : Node_Id;
4259 OK : out Boolean;
4260 Lo : out Uint;
4261 Hi : out Uint;
4262 Assume_Valid : Boolean := False)
4264 Typ : Entity_Id := Etype (N);
4265 -- Type to use, may get reset to base type for possibly invalid entity
4267 Lo_Left : Uint;
4268 Hi_Left : Uint;
4269 -- Lo and Hi bounds of left operand
4271 Lo_Right : Uint;
4272 Hi_Right : Uint;
4273 -- Lo and Hi bounds of right (or only) operand
4275 Bound : Node_Id;
4276 -- Temp variable used to hold a bound node
4278 Hbound : Uint;
4279 -- High bound of base type of expression
4281 Lor : Uint;
4282 Hir : Uint;
4283 -- Refined values for low and high bounds, after tightening
4285 OK1 : Boolean;
4286 -- Used in lower level calls to indicate if call succeeded
4288 Cindex : Cache_Index;
4289 -- Used to search cache
4291 Btyp : Entity_Id;
4292 -- Base type
4294 function OK_Operands return Boolean;
4295 -- Used for binary operators. Determines the ranges of the left and
4296 -- right operands, and if they are both OK, returns True, and puts
4297 -- the results in Lo_Right, Hi_Right, Lo_Left, Hi_Left.
4299 -----------------
4300 -- OK_Operands --
4301 -----------------
4303 function OK_Operands return Boolean is
4304 begin
4305 Determine_Range
4306 (Left_Opnd (N), OK1, Lo_Left, Hi_Left, Assume_Valid);
4308 if not OK1 then
4309 return False;
4310 end if;
4312 Determine_Range
4313 (Right_Opnd (N), OK1, Lo_Right, Hi_Right, Assume_Valid);
4314 return OK1;
4315 end OK_Operands;
4317 -- Start of processing for Determine_Range
4319 begin
4320 -- Prevent junk warnings by initializing range variables
4322 Lo := No_Uint;
4323 Hi := No_Uint;
4324 Lor := No_Uint;
4325 Hir := No_Uint;
4327 -- For temporary constants internally generated to remove side effects
4328 -- we must use the corresponding expression to determine the range of
4329 -- the expression. But note that the expander can also generate
4330 -- constants in other cases, including deferred constants.
4332 if Is_Entity_Name (N)
4333 and then Nkind (Parent (Entity (N))) = N_Object_Declaration
4334 and then Ekind (Entity (N)) = E_Constant
4335 and then Is_Internal_Name (Chars (Entity (N)))
4336 then
4337 if Present (Expression (Parent (Entity (N)))) then
4338 Determine_Range
4339 (Expression (Parent (Entity (N))), OK, Lo, Hi, Assume_Valid);
4341 elsif Present (Full_View (Entity (N))) then
4342 Determine_Range
4343 (Expression (Parent (Full_View (Entity (N)))),
4344 OK, Lo, Hi, Assume_Valid);
4346 else
4347 OK := False;
4348 end if;
4349 return;
4350 end if;
4352 -- If type is not defined, we can't determine its range
4354 if No (Typ)
4356 -- We don't deal with anything except discrete types
4358 or else not Is_Discrete_Type (Typ)
4360 -- Ignore type for which an error has been posted, since range in
4361 -- this case may well be a bogosity deriving from the error. Also
4362 -- ignore if error posted on the reference node.
4364 or else Error_Posted (N) or else Error_Posted (Typ)
4365 then
4366 OK := False;
4367 return;
4368 end if;
4370 -- For all other cases, we can determine the range
4372 OK := True;
4374 -- If value is compile time known, then the possible range is the one
4375 -- value that we know this expression definitely has.
4377 if Compile_Time_Known_Value (N) then
4378 Lo := Expr_Value (N);
4379 Hi := Lo;
4380 return;
4381 end if;
4383 -- Return if already in the cache
4385 Cindex := Cache_Index (N mod Cache_Size);
4387 if Determine_Range_Cache_N (Cindex) = N
4388 and then
4389 Determine_Range_Cache_V (Cindex) = Assume_Valid
4390 then
4391 Lo := Determine_Range_Cache_Lo (Cindex);
4392 Hi := Determine_Range_Cache_Hi (Cindex);
4393 return;
4394 end if;
4396 -- Otherwise, start by finding the bounds of the type of the expression,
4397 -- the value cannot be outside this range (if it is, then we have an
4398 -- overflow situation, which is a separate check, we are talking here
4399 -- only about the expression value).
4401 -- First a check, never try to find the bounds of a generic type, since
4402 -- these bounds are always junk values, and it is only valid to look at
4403 -- the bounds in an instance.
4405 if Is_Generic_Type (Typ) then
4406 OK := False;
4407 return;
4408 end if;
4410 -- First step, change to use base type unless we know the value is valid
4412 if (Is_Entity_Name (N) and then Is_Known_Valid (Entity (N)))
4413 or else Assume_No_Invalid_Values
4414 or else Assume_Valid
4415 then
4416 null;
4417 else
4418 Typ := Underlying_Type (Base_Type (Typ));
4419 end if;
4421 -- Retrieve the base type. Handle the case where the base type is a
4422 -- private enumeration type.
4424 Btyp := Base_Type (Typ);
4426 if Is_Private_Type (Btyp) and then Present (Full_View (Btyp)) then
4427 Btyp := Full_View (Btyp);
4428 end if;
4430 -- We use the actual bound unless it is dynamic, in which case use the
4431 -- corresponding base type bound if possible. If we can't get a bound
4432 -- then we figure we can't determine the range (a peculiar case, that
4433 -- perhaps cannot happen, but there is no point in bombing in this
4434 -- optimization circuit.
4436 -- First the low bound
4438 Bound := Type_Low_Bound (Typ);
4440 if Compile_Time_Known_Value (Bound) then
4441 Lo := Expr_Value (Bound);
4443 elsif Compile_Time_Known_Value (Type_Low_Bound (Btyp)) then
4444 Lo := Expr_Value (Type_Low_Bound (Btyp));
4446 else
4447 OK := False;
4448 return;
4449 end if;
4451 -- Now the high bound
4453 Bound := Type_High_Bound (Typ);
4455 -- We need the high bound of the base type later on, and this should
4456 -- always be compile time known. Again, it is not clear that this
4457 -- can ever be false, but no point in bombing.
4459 if Compile_Time_Known_Value (Type_High_Bound (Btyp)) then
4460 Hbound := Expr_Value (Type_High_Bound (Btyp));
4461 Hi := Hbound;
4463 else
4464 OK := False;
4465 return;
4466 end if;
4468 -- If we have a static subtype, then that may have a tighter bound so
4469 -- use the upper bound of the subtype instead in this case.
4471 if Compile_Time_Known_Value (Bound) then
4472 Hi := Expr_Value (Bound);
4473 end if;
4475 -- We may be able to refine this value in certain situations. If any
4476 -- refinement is possible, then Lor and Hir are set to possibly tighter
4477 -- bounds, and OK1 is set to True.
4479 case Nkind (N) is
4481 -- For unary plus, result is limited by range of operand
4483 when N_Op_Plus =>
4484 Determine_Range
4485 (Right_Opnd (N), OK1, Lor, Hir, Assume_Valid);
4487 -- For unary minus, determine range of operand, and negate it
4489 when N_Op_Minus =>
4490 Determine_Range
4491 (Right_Opnd (N), OK1, Lo_Right, Hi_Right, Assume_Valid);
4493 if OK1 then
4494 Lor := -Hi_Right;
4495 Hir := -Lo_Right;
4496 end if;
4498 -- For binary addition, get range of each operand and do the
4499 -- addition to get the result range.
4501 when N_Op_Add =>
4502 if OK_Operands then
4503 Lor := Lo_Left + Lo_Right;
4504 Hir := Hi_Left + Hi_Right;
4505 end if;
4507 -- Division is tricky. The only case we consider is where the right
4508 -- operand is a positive constant, and in this case we simply divide
4509 -- the bounds of the left operand
4511 when N_Op_Divide =>
4512 if OK_Operands then
4513 if Lo_Right = Hi_Right
4514 and then Lo_Right > 0
4515 then
4516 Lor := Lo_Left / Lo_Right;
4517 Hir := Hi_Left / Lo_Right;
4518 else
4519 OK1 := False;
4520 end if;
4521 end if;
4523 -- For binary subtraction, get range of each operand and do the worst
4524 -- case subtraction to get the result range.
4526 when N_Op_Subtract =>
4527 if OK_Operands then
4528 Lor := Lo_Left - Hi_Right;
4529 Hir := Hi_Left - Lo_Right;
4530 end if;
4532 -- For MOD, if right operand is a positive constant, then result must
4533 -- be in the allowable range of mod results.
4535 when N_Op_Mod =>
4536 if OK_Operands then
4537 if Lo_Right = Hi_Right
4538 and then Lo_Right /= 0
4539 then
4540 if Lo_Right > 0 then
4541 Lor := Uint_0;
4542 Hir := Lo_Right - 1;
4544 else -- Lo_Right < 0
4545 Lor := Lo_Right + 1;
4546 Hir := Uint_0;
4547 end if;
4549 else
4550 OK1 := False;
4551 end if;
4552 end if;
4554 -- For REM, if right operand is a positive constant, then result must
4555 -- be in the allowable range of mod results.
4557 when N_Op_Rem =>
4558 if OK_Operands then
4559 if Lo_Right = Hi_Right and then Lo_Right /= 0 then
4560 declare
4561 Dval : constant Uint := (abs Lo_Right) - 1;
4563 begin
4564 -- The sign of the result depends on the sign of the
4565 -- dividend (but not on the sign of the divisor, hence
4566 -- the abs operation above).
4568 if Lo_Left < 0 then
4569 Lor := -Dval;
4570 else
4571 Lor := Uint_0;
4572 end if;
4574 if Hi_Left < 0 then
4575 Hir := Uint_0;
4576 else
4577 Hir := Dval;
4578 end if;
4579 end;
4581 else
4582 OK1 := False;
4583 end if;
4584 end if;
4586 -- Attribute reference cases
4588 when N_Attribute_Reference =>
4589 case Attribute_Name (N) is
4591 -- For Pos/Val attributes, we can refine the range using the
4592 -- possible range of values of the attribute expression.
4594 when Name_Pos
4595 | Name_Val
4597 Determine_Range
4598 (First (Expressions (N)), OK1, Lor, Hir, Assume_Valid);
4600 -- For Length attribute, use the bounds of the corresponding
4601 -- index type to refine the range.
4603 when Name_Length =>
4604 declare
4605 Atyp : Entity_Id := Etype (Prefix (N));
4606 Inum : Nat;
4607 Indx : Node_Id;
4609 LL, LU : Uint;
4610 UL, UU : Uint;
4612 begin
4613 if Is_Access_Type (Atyp) then
4614 Atyp := Designated_Type (Atyp);
4615 end if;
4617 -- For string literal, we know exact value
4619 if Ekind (Atyp) = E_String_Literal_Subtype then
4620 OK := True;
4621 Lo := String_Literal_Length (Atyp);
4622 Hi := String_Literal_Length (Atyp);
4623 return;
4624 end if;
4626 -- Otherwise check for expression given
4628 if No (Expressions (N)) then
4629 Inum := 1;
4630 else
4631 Inum :=
4632 UI_To_Int (Expr_Value (First (Expressions (N))));
4633 end if;
4635 Indx := First_Index (Atyp);
4636 for J in 2 .. Inum loop
4637 Indx := Next_Index (Indx);
4638 end loop;
4640 -- If the index type is a formal type or derived from
4641 -- one, the bounds are not static.
4643 if Is_Generic_Type (Root_Type (Etype (Indx))) then
4644 OK := False;
4645 return;
4646 end if;
4648 Determine_Range
4649 (Type_Low_Bound (Etype (Indx)), OK1, LL, LU,
4650 Assume_Valid);
4652 if OK1 then
4653 Determine_Range
4654 (Type_High_Bound (Etype (Indx)), OK1, UL, UU,
4655 Assume_Valid);
4657 if OK1 then
4659 -- The maximum value for Length is the biggest
4660 -- possible gap between the values of the bounds.
4661 -- But of course, this value cannot be negative.
4663 Hir := UI_Max (Uint_0, UU - LL + 1);
4665 -- For constrained arrays, the minimum value for
4666 -- Length is taken from the actual value of the
4667 -- bounds, since the index will be exactly of this
4668 -- subtype.
4670 if Is_Constrained (Atyp) then
4671 Lor := UI_Max (Uint_0, UL - LU + 1);
4673 -- For an unconstrained array, the minimum value
4674 -- for length is always zero.
4676 else
4677 Lor := Uint_0;
4678 end if;
4679 end if;
4680 end if;
4681 end;
4683 -- No special handling for other attributes
4684 -- Probably more opportunities exist here???
4686 when others =>
4687 OK1 := False;
4689 end case;
4691 -- For type conversion from one discrete type to another, we can
4692 -- refine the range using the converted value.
4694 when N_Type_Conversion =>
4695 Determine_Range (Expression (N), OK1, Lor, Hir, Assume_Valid);
4697 -- Nothing special to do for all other expression kinds
4699 when others =>
4700 OK1 := False;
4701 Lor := No_Uint;
4702 Hir := No_Uint;
4703 end case;
4705 -- At this stage, if OK1 is true, then we know that the actual result of
4706 -- the computed expression is in the range Lor .. Hir. We can use this
4707 -- to restrict the possible range of results.
4709 if OK1 then
4711 -- If the refined value of the low bound is greater than the type
4712 -- low bound, then reset it to the more restrictive value. However,
4713 -- we do NOT do this for the case of a modular type where the
4714 -- possible upper bound on the value is above the base type high
4715 -- bound, because that means the result could wrap.
4717 if Lor > Lo
4718 and then not (Is_Modular_Integer_Type (Typ) and then Hir > Hbound)
4719 then
4720 Lo := Lor;
4721 end if;
4723 -- Similarly, if the refined value of the high bound is less than the
4724 -- value so far, then reset it to the more restrictive value. Again,
4725 -- we do not do this if the refined low bound is negative for a
4726 -- modular type, since this would wrap.
4728 if Hir < Hi
4729 and then not (Is_Modular_Integer_Type (Typ) and then Lor < Uint_0)
4730 then
4731 Hi := Hir;
4732 end if;
4733 end if;
4735 -- Set cache entry for future call and we are all done
4737 Determine_Range_Cache_N (Cindex) := N;
4738 Determine_Range_Cache_V (Cindex) := Assume_Valid;
4739 Determine_Range_Cache_Lo (Cindex) := Lo;
4740 Determine_Range_Cache_Hi (Cindex) := Hi;
4741 return;
4743 -- If any exception occurs, it means that we have some bug in the compiler,
4744 -- possibly triggered by a previous error, or by some unforeseen peculiar
4745 -- occurrence. However, this is only an optimization attempt, so there is
4746 -- really no point in crashing the compiler. Instead we just decide, too
4747 -- bad, we can't figure out a range in this case after all.
4749 exception
4750 when others =>
4752 -- Debug flag K disables this behavior (useful for debugging)
4754 if Debug_Flag_K then
4755 raise;
4756 else
4757 OK := False;
4758 Lo := No_Uint;
4759 Hi := No_Uint;
4760 return;
4761 end if;
4762 end Determine_Range;
4764 -----------------------
4765 -- Determine_Range_R --
4766 -----------------------
4768 procedure Determine_Range_R
4769 (N : Node_Id;
4770 OK : out Boolean;
4771 Lo : out Ureal;
4772 Hi : out Ureal;
4773 Assume_Valid : Boolean := False)
4775 Typ : Entity_Id := Etype (N);
4776 -- Type to use, may get reset to base type for possibly invalid entity
4778 Lo_Left : Ureal;
4779 Hi_Left : Ureal;
4780 -- Lo and Hi bounds of left operand
4782 Lo_Right : Ureal;
4783 Hi_Right : Ureal;
4784 -- Lo and Hi bounds of right (or only) operand
4786 Bound : Node_Id;
4787 -- Temp variable used to hold a bound node
4789 Hbound : Ureal;
4790 -- High bound of base type of expression
4792 Lor : Ureal;
4793 Hir : Ureal;
4794 -- Refined values for low and high bounds, after tightening
4796 OK1 : Boolean;
4797 -- Used in lower level calls to indicate if call succeeded
4799 Cindex : Cache_Index;
4800 -- Used to search cache
4802 Btyp : Entity_Id;
4803 -- Base type
4805 function OK_Operands return Boolean;
4806 -- Used for binary operators. Determines the ranges of the left and
4807 -- right operands, and if they are both OK, returns True, and puts
4808 -- the results in Lo_Right, Hi_Right, Lo_Left, Hi_Left.
4810 function Round_Machine (B : Ureal) return Ureal;
4811 -- B is a real bound. Round it using mode Round_Even.
4813 -----------------
4814 -- OK_Operands --
4815 -----------------
4817 function OK_Operands return Boolean is
4818 begin
4819 Determine_Range_R
4820 (Left_Opnd (N), OK1, Lo_Left, Hi_Left, Assume_Valid);
4822 if not OK1 then
4823 return False;
4824 end if;
4826 Determine_Range_R
4827 (Right_Opnd (N), OK1, Lo_Right, Hi_Right, Assume_Valid);
4828 return OK1;
4829 end OK_Operands;
4831 -------------------
4832 -- Round_Machine --
4833 -------------------
4835 function Round_Machine (B : Ureal) return Ureal is
4836 begin
4837 return Machine (Typ, B, Round_Even, N);
4838 end Round_Machine;
4840 -- Start of processing for Determine_Range_R
4842 begin
4843 -- Prevent junk warnings by initializing range variables
4845 Lo := No_Ureal;
4846 Hi := No_Ureal;
4847 Lor := No_Ureal;
4848 Hir := No_Ureal;
4850 -- For temporary constants internally generated to remove side effects
4851 -- we must use the corresponding expression to determine the range of
4852 -- the expression. But note that the expander can also generate
4853 -- constants in other cases, including deferred constants.
4855 if Is_Entity_Name (N)
4856 and then Nkind (Parent (Entity (N))) = N_Object_Declaration
4857 and then Ekind (Entity (N)) = E_Constant
4858 and then Is_Internal_Name (Chars (Entity (N)))
4859 then
4860 if Present (Expression (Parent (Entity (N)))) then
4861 Determine_Range_R
4862 (Expression (Parent (Entity (N))), OK, Lo, Hi, Assume_Valid);
4864 elsif Present (Full_View (Entity (N))) then
4865 Determine_Range_R
4866 (Expression (Parent (Full_View (Entity (N)))),
4867 OK, Lo, Hi, Assume_Valid);
4869 else
4870 OK := False;
4871 end if;
4873 return;
4874 end if;
4876 -- If type is not defined, we can't determine its range
4878 if No (Typ)
4880 -- We don't deal with anything except IEEE floating-point types
4882 or else not Is_Floating_Point_Type (Typ)
4883 or else Float_Rep (Typ) /= IEEE_Binary
4885 -- Ignore type for which an error has been posted, since range in
4886 -- this case may well be a bogosity deriving from the error. Also
4887 -- ignore if error posted on the reference node.
4889 or else Error_Posted (N) or else Error_Posted (Typ)
4890 then
4891 OK := False;
4892 return;
4893 end if;
4895 -- For all other cases, we can determine the range
4897 OK := True;
4899 -- If value is compile time known, then the possible range is the one
4900 -- value that we know this expression definitely has.
4902 if Compile_Time_Known_Value (N) then
4903 Lo := Expr_Value_R (N);
4904 Hi := Lo;
4905 return;
4906 end if;
4908 -- Return if already in the cache
4910 Cindex := Cache_Index (N mod Cache_Size);
4912 if Determine_Range_Cache_N (Cindex) = N
4913 and then
4914 Determine_Range_Cache_V (Cindex) = Assume_Valid
4915 then
4916 Lo := Determine_Range_Cache_Lo_R (Cindex);
4917 Hi := Determine_Range_Cache_Hi_R (Cindex);
4918 return;
4919 end if;
4921 -- Otherwise, start by finding the bounds of the type of the expression,
4922 -- the value cannot be outside this range (if it is, then we have an
4923 -- overflow situation, which is a separate check, we are talking here
4924 -- only about the expression value).
4926 -- First a check, never try to find the bounds of a generic type, since
4927 -- these bounds are always junk values, and it is only valid to look at
4928 -- the bounds in an instance.
4930 if Is_Generic_Type (Typ) then
4931 OK := False;
4932 return;
4933 end if;
4935 -- First step, change to use base type unless we know the value is valid
4937 if (Is_Entity_Name (N) and then Is_Known_Valid (Entity (N)))
4938 or else Assume_No_Invalid_Values
4939 or else Assume_Valid
4940 then
4941 null;
4942 else
4943 Typ := Underlying_Type (Base_Type (Typ));
4944 end if;
4946 -- Retrieve the base type. Handle the case where the base type is a
4947 -- private type.
4949 Btyp := Base_Type (Typ);
4951 if Is_Private_Type (Btyp) and then Present (Full_View (Btyp)) then
4952 Btyp := Full_View (Btyp);
4953 end if;
4955 -- We use the actual bound unless it is dynamic, in which case use the
4956 -- corresponding base type bound if possible. If we can't get a bound
4957 -- then we figure we can't determine the range (a peculiar case, that
4958 -- perhaps cannot happen, but there is no point in bombing in this
4959 -- optimization circuit).
4961 -- First the low bound
4963 Bound := Type_Low_Bound (Typ);
4965 if Compile_Time_Known_Value (Bound) then
4966 Lo := Expr_Value_R (Bound);
4968 elsif Compile_Time_Known_Value (Type_Low_Bound (Btyp)) then
4969 Lo := Expr_Value_R (Type_Low_Bound (Btyp));
4971 else
4972 OK := False;
4973 return;
4974 end if;
4976 -- Now the high bound
4978 Bound := Type_High_Bound (Typ);
4980 -- We need the high bound of the base type later on, and this should
4981 -- always be compile time known. Again, it is not clear that this
4982 -- can ever be false, but no point in bombing.
4984 if Compile_Time_Known_Value (Type_High_Bound (Btyp)) then
4985 Hbound := Expr_Value_R (Type_High_Bound (Btyp));
4986 Hi := Hbound;
4988 else
4989 OK := False;
4990 return;
4991 end if;
4993 -- If we have a static subtype, then that may have a tighter bound so
4994 -- use the upper bound of the subtype instead in this case.
4996 if Compile_Time_Known_Value (Bound) then
4997 Hi := Expr_Value_R (Bound);
4998 end if;
5000 -- We may be able to refine this value in certain situations. If any
5001 -- refinement is possible, then Lor and Hir are set to possibly tighter
5002 -- bounds, and OK1 is set to True.
5004 case Nkind (N) is
5006 -- For unary plus, result is limited by range of operand
5008 when N_Op_Plus =>
5009 Determine_Range_R
5010 (Right_Opnd (N), OK1, Lor, Hir, Assume_Valid);
5012 -- For unary minus, determine range of operand, and negate it
5014 when N_Op_Minus =>
5015 Determine_Range_R
5016 (Right_Opnd (N), OK1, Lo_Right, Hi_Right, Assume_Valid);
5018 if OK1 then
5019 Lor := -Hi_Right;
5020 Hir := -Lo_Right;
5021 end if;
5023 -- For binary addition, get range of each operand and do the
5024 -- addition to get the result range.
5026 when N_Op_Add =>
5027 if OK_Operands then
5028 Lor := Round_Machine (Lo_Left + Lo_Right);
5029 Hir := Round_Machine (Hi_Left + Hi_Right);
5030 end if;
5032 -- For binary subtraction, get range of each operand and do the worst
5033 -- case subtraction to get the result range.
5035 when N_Op_Subtract =>
5036 if OK_Operands then
5037 Lor := Round_Machine (Lo_Left - Hi_Right);
5038 Hir := Round_Machine (Hi_Left - Lo_Right);
5039 end if;
5041 -- For multiplication, get range of each operand and do the
5042 -- four multiplications to get the result range.
5044 when N_Op_Multiply =>
5045 if OK_Operands then
5046 declare
5047 M1 : constant Ureal := Round_Machine (Lo_Left * Lo_Right);
5048 M2 : constant Ureal := Round_Machine (Lo_Left * Hi_Right);
5049 M3 : constant Ureal := Round_Machine (Hi_Left * Lo_Right);
5050 M4 : constant Ureal := Round_Machine (Hi_Left * Hi_Right);
5051 begin
5052 Lor := UR_Min (UR_Min (M1, M2), UR_Min (M3, M4));
5053 Hir := UR_Max (UR_Max (M1, M2), UR_Max (M3, M4));
5054 end;
5055 end if;
5057 -- For division, consider separately the cases where the right
5058 -- operand is positive or negative. Otherwise, the right operand
5059 -- can be arbitrarily close to zero, so the result is likely to
5060 -- be unbounded in one direction, do not attempt to compute it.
5062 when N_Op_Divide =>
5063 if OK_Operands then
5065 -- Right operand is positive
5067 if Lo_Right > Ureal_0 then
5069 -- If the low bound of the left operand is negative, obtain
5070 -- the overall low bound by dividing it by the smallest
5071 -- value of the right operand, and otherwise by the largest
5072 -- value of the right operand.
5074 if Lo_Left < Ureal_0 then
5075 Lor := Round_Machine (Lo_Left / Lo_Right);
5076 else
5077 Lor := Round_Machine (Lo_Left / Hi_Right);
5078 end if;
5080 -- If the high bound of the left operand is negative, obtain
5081 -- the overall high bound by dividing it by the largest
5082 -- value of the right operand, and otherwise by the
5083 -- smallest value of the right operand.
5085 if Hi_Left < Ureal_0 then
5086 Hir := Round_Machine (Hi_Left / Hi_Right);
5087 else
5088 Hir := Round_Machine (Hi_Left / Lo_Right);
5089 end if;
5091 -- Right operand is negative
5093 elsif Hi_Right < Ureal_0 then
5095 -- If the low bound of the left operand is negative, obtain
5096 -- the overall low bound by dividing it by the largest
5097 -- value of the right operand, and otherwise by the smallest
5098 -- value of the right operand.
5100 if Lo_Left < Ureal_0 then
5101 Lor := Round_Machine (Lo_Left / Hi_Right);
5102 else
5103 Lor := Round_Machine (Lo_Left / Lo_Right);
5104 end if;
5106 -- If the high bound of the left operand is negative, obtain
5107 -- the overall high bound by dividing it by the smallest
5108 -- value of the right operand, and otherwise by the
5109 -- largest value of the right operand.
5111 if Hi_Left < Ureal_0 then
5112 Hir := Round_Machine (Hi_Left / Lo_Right);
5113 else
5114 Hir := Round_Machine (Hi_Left / Hi_Right);
5115 end if;
5117 else
5118 OK1 := False;
5119 end if;
5120 end if;
5122 -- For type conversion from one floating-point type to another, we
5123 -- can refine the range using the converted value.
5125 when N_Type_Conversion =>
5126 Determine_Range_R (Expression (N), OK1, Lor, Hir, Assume_Valid);
5128 -- Nothing special to do for all other expression kinds
5130 when others =>
5131 OK1 := False;
5132 Lor := No_Ureal;
5133 Hir := No_Ureal;
5134 end case;
5136 -- At this stage, if OK1 is true, then we know that the actual result of
5137 -- the computed expression is in the range Lor .. Hir. We can use this
5138 -- to restrict the possible range of results.
5140 if OK1 then
5142 -- If the refined value of the low bound is greater than the type
5143 -- low bound, then reset it to the more restrictive value.
5145 if Lor > Lo then
5146 Lo := Lor;
5147 end if;
5149 -- Similarly, if the refined value of the high bound is less than the
5150 -- value so far, then reset it to the more restrictive value.
5152 if Hir < Hi then
5153 Hi := Hir;
5154 end if;
5155 end if;
5157 -- Set cache entry for future call and we are all done
5159 Determine_Range_Cache_N (Cindex) := N;
5160 Determine_Range_Cache_V (Cindex) := Assume_Valid;
5161 Determine_Range_Cache_Lo_R (Cindex) := Lo;
5162 Determine_Range_Cache_Hi_R (Cindex) := Hi;
5163 return;
5165 -- If any exception occurs, it means that we have some bug in the compiler,
5166 -- possibly triggered by a previous error, or by some unforeseen peculiar
5167 -- occurrence. However, this is only an optimization attempt, so there is
5168 -- really no point in crashing the compiler. Instead we just decide, too
5169 -- bad, we can't figure out a range in this case after all.
5171 exception
5172 when others =>
5174 -- Debug flag K disables this behavior (useful for debugging)
5176 if Debug_Flag_K then
5177 raise;
5178 else
5179 OK := False;
5180 Lo := No_Ureal;
5181 Hi := No_Ureal;
5182 return;
5183 end if;
5184 end Determine_Range_R;
5186 ------------------------------------
5187 -- Discriminant_Checks_Suppressed --
5188 ------------------------------------
5190 function Discriminant_Checks_Suppressed (E : Entity_Id) return Boolean is
5191 begin
5192 if Present (E) then
5193 if Is_Unchecked_Union (E) then
5194 return True;
5195 elsif Checks_May_Be_Suppressed (E) then
5196 return Is_Check_Suppressed (E, Discriminant_Check);
5197 end if;
5198 end if;
5200 return Scope_Suppress.Suppress (Discriminant_Check);
5201 end Discriminant_Checks_Suppressed;
5203 --------------------------------
5204 -- Division_Checks_Suppressed --
5205 --------------------------------
5207 function Division_Checks_Suppressed (E : Entity_Id) return Boolean is
5208 begin
5209 if Present (E) and then Checks_May_Be_Suppressed (E) then
5210 return Is_Check_Suppressed (E, Division_Check);
5211 else
5212 return Scope_Suppress.Suppress (Division_Check);
5213 end if;
5214 end Division_Checks_Suppressed;
5216 --------------------------------------
5217 -- Duplicated_Tag_Checks_Suppressed --
5218 --------------------------------------
5220 function Duplicated_Tag_Checks_Suppressed (E : Entity_Id) return Boolean is
5221 begin
5222 if Present (E) and then Checks_May_Be_Suppressed (E) then
5223 return Is_Check_Suppressed (E, Duplicated_Tag_Check);
5224 else
5225 return Scope_Suppress.Suppress (Duplicated_Tag_Check);
5226 end if;
5227 end Duplicated_Tag_Checks_Suppressed;
5229 -----------------------------------
5230 -- Elaboration_Checks_Suppressed --
5231 -----------------------------------
5233 function Elaboration_Checks_Suppressed (E : Entity_Id) return Boolean is
5234 begin
5235 -- The complication in this routine is that if we are in the dynamic
5236 -- model of elaboration, we also check All_Checks, since All_Checks
5237 -- does not set Elaboration_Check explicitly.
5239 if Present (E) then
5240 if Kill_Elaboration_Checks (E) then
5241 return True;
5243 elsif Checks_May_Be_Suppressed (E) then
5244 if Is_Check_Suppressed (E, Elaboration_Check) then
5245 return True;
5246 elsif Dynamic_Elaboration_Checks then
5247 return Is_Check_Suppressed (E, All_Checks);
5248 else
5249 return False;
5250 end if;
5251 end if;
5252 end if;
5254 if Scope_Suppress.Suppress (Elaboration_Check) then
5255 return True;
5256 elsif Dynamic_Elaboration_Checks then
5257 return Scope_Suppress.Suppress (All_Checks);
5258 else
5259 return False;
5260 end if;
5261 end Elaboration_Checks_Suppressed;
5263 ---------------------------
5264 -- Enable_Overflow_Check --
5265 ---------------------------
5267 procedure Enable_Overflow_Check (N : Node_Id) is
5268 Typ : constant Entity_Id := Base_Type (Etype (N));
5269 Mode : constant Overflow_Mode_Type := Overflow_Check_Mode;
5270 Chk : Nat;
5271 OK : Boolean;
5272 Ent : Entity_Id;
5273 Ofs : Uint;
5274 Lo : Uint;
5275 Hi : Uint;
5277 Do_Ovflow_Check : Boolean;
5279 begin
5280 if Debug_Flag_CC then
5281 w ("Enable_Overflow_Check for node ", Int (N));
5282 Write_Str (" Source location = ");
5283 wl (Sloc (N));
5284 pg (Union_Id (N));
5285 end if;
5287 -- No check if overflow checks suppressed for type of node
5289 if Overflow_Checks_Suppressed (Etype (N)) then
5290 return;
5292 -- Nothing to do for unsigned integer types, which do not overflow
5294 elsif Is_Modular_Integer_Type (Typ) then
5295 return;
5296 end if;
5298 -- This is the point at which processing for STRICT mode diverges
5299 -- from processing for MINIMIZED/ELIMINATED modes. This divergence is
5300 -- probably more extreme that it needs to be, but what is going on here
5301 -- is that when we introduced MINIMIZED/ELIMINATED modes, we wanted
5302 -- to leave the processing for STRICT mode untouched. There were
5303 -- two reasons for this. First it avoided any incompatible change of
5304 -- behavior. Second, it guaranteed that STRICT mode continued to be
5305 -- legacy reliable.
5307 -- The big difference is that in STRICT mode there is a fair amount of
5308 -- circuitry to try to avoid setting the Do_Overflow_Check flag if we
5309 -- know that no check is needed. We skip all that in the two new modes,
5310 -- since really overflow checking happens over a whole subtree, and we
5311 -- do the corresponding optimizations later on when applying the checks.
5313 if Mode in Minimized_Or_Eliminated then
5314 if not (Overflow_Checks_Suppressed (Etype (N)))
5315 and then not (Is_Entity_Name (N)
5316 and then Overflow_Checks_Suppressed (Entity (N)))
5317 then
5318 Activate_Overflow_Check (N);
5319 end if;
5321 if Debug_Flag_CC then
5322 w ("Minimized/Eliminated mode");
5323 end if;
5325 return;
5326 end if;
5328 -- Remainder of processing is for STRICT case, and is unchanged from
5329 -- earlier versions preceding the addition of MINIMIZED/ELIMINATED.
5331 -- Nothing to do if the range of the result is known OK. We skip this
5332 -- for conversions, since the caller already did the check, and in any
5333 -- case the condition for deleting the check for a type conversion is
5334 -- different.
5336 if Nkind (N) /= N_Type_Conversion then
5337 Determine_Range (N, OK, Lo, Hi, Assume_Valid => True);
5339 -- Note in the test below that we assume that the range is not OK
5340 -- if a bound of the range is equal to that of the type. That's not
5341 -- quite accurate but we do this for the following reasons:
5343 -- a) The way that Determine_Range works, it will typically report
5344 -- the bounds of the value as being equal to the bounds of the
5345 -- type, because it either can't tell anything more precise, or
5346 -- does not think it is worth the effort to be more precise.
5348 -- b) It is very unusual to have a situation in which this would
5349 -- generate an unnecessary overflow check (an example would be
5350 -- a subtype with a range 0 .. Integer'Last - 1 to which the
5351 -- literal value one is added).
5353 -- c) The alternative is a lot of special casing in this routine
5354 -- which would partially duplicate Determine_Range processing.
5356 if OK then
5357 Do_Ovflow_Check := True;
5359 -- Note that the following checks are quite deliberately > and <
5360 -- rather than >= and <= as explained above.
5362 if Lo > Expr_Value (Type_Low_Bound (Typ))
5363 and then
5364 Hi < Expr_Value (Type_High_Bound (Typ))
5365 then
5366 Do_Ovflow_Check := False;
5368 -- Despite the comments above, it is worth dealing specially with
5369 -- division specially. The only case where integer division can
5370 -- overflow is (largest negative number) / (-1). So we will do
5371 -- an extra range analysis to see if this is possible.
5373 elsif Nkind (N) = N_Op_Divide then
5374 Determine_Range
5375 (Left_Opnd (N), OK, Lo, Hi, Assume_Valid => True);
5377 if OK and then Lo > Expr_Value (Type_Low_Bound (Typ)) then
5378 Do_Ovflow_Check := False;
5380 else
5381 Determine_Range
5382 (Right_Opnd (N), OK, Lo, Hi, Assume_Valid => True);
5384 if OK and then (Lo > Uint_Minus_1
5385 or else
5386 Hi < Uint_Minus_1)
5387 then
5388 Do_Ovflow_Check := False;
5389 end if;
5390 end if;
5391 end if;
5393 -- If no overflow check required, we are done
5395 if not Do_Ovflow_Check then
5396 if Debug_Flag_CC then
5397 w ("No overflow check required");
5398 end if;
5400 return;
5401 end if;
5402 end if;
5403 end if;
5405 -- If not in optimizing mode, set flag and we are done. We are also done
5406 -- (and just set the flag) if the type is not a discrete type, since it
5407 -- is not worth the effort to eliminate checks for other than discrete
5408 -- types. In addition, we take this same path if we have stored the
5409 -- maximum number of checks possible already (a very unlikely situation,
5410 -- but we do not want to blow up).
5412 if Optimization_Level = 0
5413 or else not Is_Discrete_Type (Etype (N))
5414 or else Num_Saved_Checks = Saved_Checks'Last
5415 then
5416 Activate_Overflow_Check (N);
5418 if Debug_Flag_CC then
5419 w ("Optimization off");
5420 end if;
5422 return;
5423 end if;
5425 -- Otherwise evaluate and check the expression
5427 Find_Check
5428 (Expr => N,
5429 Check_Type => 'O',
5430 Target_Type => Empty,
5431 Entry_OK => OK,
5432 Check_Num => Chk,
5433 Ent => Ent,
5434 Ofs => Ofs);
5436 if Debug_Flag_CC then
5437 w ("Called Find_Check");
5438 w (" OK = ", OK);
5440 if OK then
5441 w (" Check_Num = ", Chk);
5442 w (" Ent = ", Int (Ent));
5443 Write_Str (" Ofs = ");
5444 pid (Ofs);
5445 end if;
5446 end if;
5448 -- If check is not of form to optimize, then set flag and we are done
5450 if not OK then
5451 Activate_Overflow_Check (N);
5452 return;
5453 end if;
5455 -- If check is already performed, then return without setting flag
5457 if Chk /= 0 then
5458 if Debug_Flag_CC then
5459 w ("Check suppressed!");
5460 end if;
5462 return;
5463 end if;
5465 -- Here we will make a new entry for the new check
5467 Activate_Overflow_Check (N);
5468 Num_Saved_Checks := Num_Saved_Checks + 1;
5469 Saved_Checks (Num_Saved_Checks) :=
5470 (Killed => False,
5471 Entity => Ent,
5472 Offset => Ofs,
5473 Check_Type => 'O',
5474 Target_Type => Empty);
5476 if Debug_Flag_CC then
5477 w ("Make new entry, check number = ", Num_Saved_Checks);
5478 w (" Entity = ", Int (Ent));
5479 Write_Str (" Offset = ");
5480 pid (Ofs);
5481 w (" Check_Type = O");
5482 w (" Target_Type = Empty");
5483 end if;
5485 -- If we get an exception, then something went wrong, probably because of
5486 -- an error in the structure of the tree due to an incorrect program. Or
5487 -- it may be a bug in the optimization circuit. In either case the safest
5488 -- thing is simply to set the check flag unconditionally.
5490 exception
5491 when others =>
5492 Activate_Overflow_Check (N);
5494 if Debug_Flag_CC then
5495 w (" exception occurred, overflow flag set");
5496 end if;
5498 return;
5499 end Enable_Overflow_Check;
5501 ------------------------
5502 -- Enable_Range_Check --
5503 ------------------------
5505 procedure Enable_Range_Check (N : Node_Id) is
5506 Chk : Nat;
5507 OK : Boolean;
5508 Ent : Entity_Id;
5509 Ofs : Uint;
5510 Ttyp : Entity_Id;
5511 P : Node_Id;
5513 begin
5514 -- Return if unchecked type conversion with range check killed. In this
5515 -- case we never set the flag (that's what Kill_Range_Check is about).
5517 if Nkind (N) = N_Unchecked_Type_Conversion
5518 and then Kill_Range_Check (N)
5519 then
5520 return;
5521 end if;
5523 -- Do not set range check flag if parent is assignment statement or
5524 -- object declaration with Suppress_Assignment_Checks flag set
5526 if Nkind_In (Parent (N), N_Assignment_Statement, N_Object_Declaration)
5527 and then Suppress_Assignment_Checks (Parent (N))
5528 then
5529 return;
5530 end if;
5532 -- Check for various cases where we should suppress the range check
5534 -- No check if range checks suppressed for type of node
5536 if Present (Etype (N)) and then Range_Checks_Suppressed (Etype (N)) then
5537 return;
5539 -- No check if node is an entity name, and range checks are suppressed
5540 -- for this entity, or for the type of this entity.
5542 elsif Is_Entity_Name (N)
5543 and then (Range_Checks_Suppressed (Entity (N))
5544 or else Range_Checks_Suppressed (Etype (Entity (N))))
5545 then
5546 return;
5548 -- No checks if index of array, and index checks are suppressed for
5549 -- the array object or the type of the array.
5551 elsif Nkind (Parent (N)) = N_Indexed_Component then
5552 declare
5553 Pref : constant Node_Id := Prefix (Parent (N));
5554 begin
5555 if Is_Entity_Name (Pref)
5556 and then Index_Checks_Suppressed (Entity (Pref))
5557 then
5558 return;
5559 elsif Index_Checks_Suppressed (Etype (Pref)) then
5560 return;
5561 end if;
5562 end;
5563 end if;
5565 -- Debug trace output
5567 if Debug_Flag_CC then
5568 w ("Enable_Range_Check for node ", Int (N));
5569 Write_Str (" Source location = ");
5570 wl (Sloc (N));
5571 pg (Union_Id (N));
5572 end if;
5574 -- If not in optimizing mode, set flag and we are done. We are also done
5575 -- (and just set the flag) if the type is not a discrete type, since it
5576 -- is not worth the effort to eliminate checks for other than discrete
5577 -- types. In addition, we take this same path if we have stored the
5578 -- maximum number of checks possible already (a very unlikely situation,
5579 -- but we do not want to blow up).
5581 if Optimization_Level = 0
5582 or else No (Etype (N))
5583 or else not Is_Discrete_Type (Etype (N))
5584 or else Num_Saved_Checks = Saved_Checks'Last
5585 then
5586 Activate_Range_Check (N);
5588 if Debug_Flag_CC then
5589 w ("Optimization off");
5590 end if;
5592 return;
5593 end if;
5595 -- Otherwise find out the target type
5597 P := Parent (N);
5599 -- For assignment, use left side subtype
5601 if Nkind (P) = N_Assignment_Statement
5602 and then Expression (P) = N
5603 then
5604 Ttyp := Etype (Name (P));
5606 -- For indexed component, use subscript subtype
5608 elsif Nkind (P) = N_Indexed_Component then
5609 declare
5610 Atyp : Entity_Id;
5611 Indx : Node_Id;
5612 Subs : Node_Id;
5614 begin
5615 Atyp := Etype (Prefix (P));
5617 if Is_Access_Type (Atyp) then
5618 Atyp := Designated_Type (Atyp);
5620 -- If the prefix is an access to an unconstrained array,
5621 -- perform check unconditionally: it depends on the bounds of
5622 -- an object and we cannot currently recognize whether the test
5623 -- may be redundant.
5625 if not Is_Constrained (Atyp) then
5626 Activate_Range_Check (N);
5627 return;
5628 end if;
5630 -- Ditto if prefix is simply an unconstrained array. We used
5631 -- to think this case was OK, if the prefix was not an explicit
5632 -- dereference, but we have now seen a case where this is not
5633 -- true, so it is safer to just suppress the optimization in this
5634 -- case. The back end is getting better at eliminating redundant
5635 -- checks in any case, so the loss won't be important.
5637 elsif Is_Array_Type (Atyp)
5638 and then not Is_Constrained (Atyp)
5639 then
5640 Activate_Range_Check (N);
5641 return;
5642 end if;
5644 Indx := First_Index (Atyp);
5645 Subs := First (Expressions (P));
5646 loop
5647 if Subs = N then
5648 Ttyp := Etype (Indx);
5649 exit;
5650 end if;
5652 Next_Index (Indx);
5653 Next (Subs);
5654 end loop;
5655 end;
5657 -- For now, ignore all other cases, they are not so interesting
5659 else
5660 if Debug_Flag_CC then
5661 w (" target type not found, flag set");
5662 end if;
5664 Activate_Range_Check (N);
5665 return;
5666 end if;
5668 -- Evaluate and check the expression
5670 Find_Check
5671 (Expr => N,
5672 Check_Type => 'R',
5673 Target_Type => Ttyp,
5674 Entry_OK => OK,
5675 Check_Num => Chk,
5676 Ent => Ent,
5677 Ofs => Ofs);
5679 if Debug_Flag_CC then
5680 w ("Called Find_Check");
5681 w ("Target_Typ = ", Int (Ttyp));
5682 w (" OK = ", OK);
5684 if OK then
5685 w (" Check_Num = ", Chk);
5686 w (" Ent = ", Int (Ent));
5687 Write_Str (" Ofs = ");
5688 pid (Ofs);
5689 end if;
5690 end if;
5692 -- If check is not of form to optimize, then set flag and we are done
5694 if not OK then
5695 if Debug_Flag_CC then
5696 w (" expression not of optimizable type, flag set");
5697 end if;
5699 Activate_Range_Check (N);
5700 return;
5701 end if;
5703 -- If check is already performed, then return without setting flag
5705 if Chk /= 0 then
5706 if Debug_Flag_CC then
5707 w ("Check suppressed!");
5708 end if;
5710 return;
5711 end if;
5713 -- Here we will make a new entry for the new check
5715 Activate_Range_Check (N);
5716 Num_Saved_Checks := Num_Saved_Checks + 1;
5717 Saved_Checks (Num_Saved_Checks) :=
5718 (Killed => False,
5719 Entity => Ent,
5720 Offset => Ofs,
5721 Check_Type => 'R',
5722 Target_Type => Ttyp);
5724 if Debug_Flag_CC then
5725 w ("Make new entry, check number = ", Num_Saved_Checks);
5726 w (" Entity = ", Int (Ent));
5727 Write_Str (" Offset = ");
5728 pid (Ofs);
5729 w (" Check_Type = R");
5730 w (" Target_Type = ", Int (Ttyp));
5731 pg (Union_Id (Ttyp));
5732 end if;
5734 -- If we get an exception, then something went wrong, probably because of
5735 -- an error in the structure of the tree due to an incorrect program. Or
5736 -- it may be a bug in the optimization circuit. In either case the safest
5737 -- thing is simply to set the check flag unconditionally.
5739 exception
5740 when others =>
5741 Activate_Range_Check (N);
5743 if Debug_Flag_CC then
5744 w (" exception occurred, range flag set");
5745 end if;
5747 return;
5748 end Enable_Range_Check;
5750 ------------------
5751 -- Ensure_Valid --
5752 ------------------
5754 procedure Ensure_Valid
5755 (Expr : Node_Id;
5756 Holes_OK : Boolean := False;
5757 Related_Id : Entity_Id := Empty;
5758 Is_Low_Bound : Boolean := False;
5759 Is_High_Bound : Boolean := False)
5761 Typ : constant Entity_Id := Etype (Expr);
5763 begin
5764 -- Ignore call if we are not doing any validity checking
5766 if not Validity_Checks_On then
5767 return;
5769 -- Ignore call if range or validity checks suppressed on entity or type
5771 elsif Range_Or_Validity_Checks_Suppressed (Expr) then
5772 return;
5774 -- No check required if expression is from the expander, we assume the
5775 -- expander will generate whatever checks are needed. Note that this is
5776 -- not just an optimization, it avoids infinite recursions.
5778 -- Unchecked conversions must be checked, unless they are initialized
5779 -- scalar values, as in a component assignment in an init proc.
5781 -- In addition, we force a check if Force_Validity_Checks is set
5783 elsif not Comes_From_Source (Expr)
5784 and then not Force_Validity_Checks
5785 and then (Nkind (Expr) /= N_Unchecked_Type_Conversion
5786 or else Kill_Range_Check (Expr))
5787 then
5788 return;
5790 -- No check required if expression is known to have valid value
5792 elsif Expr_Known_Valid (Expr) then
5793 return;
5795 -- No check needed within a generated predicate function. Validity
5796 -- of input value will have been checked earlier.
5798 elsif Ekind (Current_Scope) = E_Function
5799 and then Is_Predicate_Function (Current_Scope)
5800 then
5801 return;
5803 -- Ignore case of enumeration with holes where the flag is set not to
5804 -- worry about holes, since no special validity check is needed
5806 elsif Is_Enumeration_Type (Typ)
5807 and then Has_Non_Standard_Rep (Typ)
5808 and then Holes_OK
5809 then
5810 return;
5812 -- No check required on the left-hand side of an assignment
5814 elsif Nkind (Parent (Expr)) = N_Assignment_Statement
5815 and then Expr = Name (Parent (Expr))
5816 then
5817 return;
5819 -- No check on a universal real constant. The context will eventually
5820 -- convert it to a machine number for some target type, or report an
5821 -- illegality.
5823 elsif Nkind (Expr) = N_Real_Literal
5824 and then Etype (Expr) = Universal_Real
5825 then
5826 return;
5828 -- If the expression denotes a component of a packed boolean array,
5829 -- no possible check applies. We ignore the old ACATS chestnuts that
5830 -- involve Boolean range True..True.
5832 -- Note: validity checks are generated for expressions that yield a
5833 -- scalar type, when it is possible to create a value that is outside of
5834 -- the type. If this is a one-bit boolean no such value exists. This is
5835 -- an optimization, and it also prevents compiler blowing up during the
5836 -- elaboration of improperly expanded packed array references.
5838 elsif Nkind (Expr) = N_Indexed_Component
5839 and then Is_Bit_Packed_Array (Etype (Prefix (Expr)))
5840 and then Root_Type (Etype (Expr)) = Standard_Boolean
5841 then
5842 return;
5844 -- For an expression with actions, we want to insert the validity check
5845 -- on the final Expression.
5847 elsif Nkind (Expr) = N_Expression_With_Actions then
5848 Ensure_Valid (Expression (Expr));
5849 return;
5851 -- An annoying special case. If this is an out parameter of a scalar
5852 -- type, then the value is not going to be accessed, therefore it is
5853 -- inappropriate to do any validity check at the call site.
5855 else
5856 -- Only need to worry about scalar types
5858 if Is_Scalar_Type (Typ) then
5859 declare
5860 P : Node_Id;
5861 N : Node_Id;
5862 E : Entity_Id;
5863 F : Entity_Id;
5864 A : Node_Id;
5865 L : List_Id;
5867 begin
5868 -- Find actual argument (which may be a parameter association)
5869 -- and the parent of the actual argument (the call statement)
5871 N := Expr;
5872 P := Parent (Expr);
5874 if Nkind (P) = N_Parameter_Association then
5875 N := P;
5876 P := Parent (N);
5877 end if;
5879 -- Only need to worry if we are argument of a procedure call
5880 -- since functions don't have out parameters. If this is an
5881 -- indirect or dispatching call, get signature from the
5882 -- subprogram type.
5884 if Nkind (P) = N_Procedure_Call_Statement then
5885 L := Parameter_Associations (P);
5887 if Is_Entity_Name (Name (P)) then
5888 E := Entity (Name (P));
5889 else
5890 pragma Assert (Nkind (Name (P)) = N_Explicit_Dereference);
5891 E := Etype (Name (P));
5892 end if;
5894 -- Only need to worry if there are indeed actuals, and if
5895 -- this could be a procedure call, otherwise we cannot get a
5896 -- match (either we are not an argument, or the mode of the
5897 -- formal is not OUT). This test also filters out the
5898 -- generic case.
5900 if Is_Non_Empty_List (L) and then Is_Subprogram (E) then
5902 -- This is the loop through parameters, looking for an
5903 -- OUT parameter for which we are the argument.
5905 F := First_Formal (E);
5906 A := First (L);
5907 while Present (F) loop
5908 if Ekind (F) = E_Out_Parameter and then A = N then
5909 return;
5910 end if;
5912 Next_Formal (F);
5913 Next (A);
5914 end loop;
5915 end if;
5916 end if;
5917 end;
5918 end if;
5919 end if;
5921 -- If this is a boolean expression, only its elementary operands need
5922 -- checking: if they are valid, a boolean or short-circuit operation
5923 -- with them will be valid as well.
5925 if Base_Type (Typ) = Standard_Boolean
5926 and then
5927 (Nkind (Expr) in N_Op or else Nkind (Expr) in N_Short_Circuit)
5928 then
5929 return;
5930 end if;
5932 -- If we fall through, a validity check is required
5934 Insert_Valid_Check (Expr, Related_Id, Is_Low_Bound, Is_High_Bound);
5936 if Is_Entity_Name (Expr)
5937 and then Safe_To_Capture_Value (Expr, Entity (Expr))
5938 then
5939 Set_Is_Known_Valid (Entity (Expr));
5940 end if;
5941 end Ensure_Valid;
5943 ----------------------
5944 -- Expr_Known_Valid --
5945 ----------------------
5947 function Expr_Known_Valid (Expr : Node_Id) return Boolean is
5948 Typ : constant Entity_Id := Etype (Expr);
5950 begin
5951 -- Non-scalar types are always considered valid, since they never give
5952 -- rise to the issues of erroneous or bounded error behavior that are
5953 -- the concern. In formal reference manual terms the notion of validity
5954 -- only applies to scalar types. Note that even when packed arrays are
5955 -- represented using modular types, they are still arrays semantically,
5956 -- so they are also always valid (in particular, the unused bits can be
5957 -- random rubbish without affecting the validity of the array value).
5959 if not Is_Scalar_Type (Typ) or else Is_Packed_Array_Impl_Type (Typ) then
5960 return True;
5962 -- If no validity checking, then everything is considered valid
5964 elsif not Validity_Checks_On then
5965 return True;
5967 -- Floating-point types are considered valid unless floating-point
5968 -- validity checks have been specifically turned on.
5970 elsif Is_Floating_Point_Type (Typ)
5971 and then not Validity_Check_Floating_Point
5972 then
5973 return True;
5975 -- If the expression is the value of an object that is known to be
5976 -- valid, then clearly the expression value itself is valid.
5978 elsif Is_Entity_Name (Expr)
5979 and then Is_Known_Valid (Entity (Expr))
5981 -- Exclude volatile variables
5983 and then not Treat_As_Volatile (Entity (Expr))
5984 then
5985 return True;
5987 -- References to discriminants are always considered valid. The value
5988 -- of a discriminant gets checked when the object is built. Within the
5989 -- record, we consider it valid, and it is important to do so, since
5990 -- otherwise we can try to generate bogus validity checks which
5991 -- reference discriminants out of scope. Discriminants of concurrent
5992 -- types are excluded for the same reason.
5994 elsif Is_Entity_Name (Expr)
5995 and then Denotes_Discriminant (Expr, Check_Concurrent => True)
5996 then
5997 return True;
5999 -- If the type is one for which all values are known valid, then we are
6000 -- sure that the value is valid except in the slightly odd case where
6001 -- the expression is a reference to a variable whose size has been
6002 -- explicitly set to a value greater than the object size.
6004 elsif Is_Known_Valid (Typ) then
6005 if Is_Entity_Name (Expr)
6006 and then Ekind (Entity (Expr)) = E_Variable
6007 and then Esize (Entity (Expr)) > Esize (Typ)
6008 then
6009 return False;
6010 else
6011 return True;
6012 end if;
6014 -- Integer and character literals always have valid values, where
6015 -- appropriate these will be range checked in any case.
6017 elsif Nkind_In (Expr, N_Integer_Literal, N_Character_Literal) then
6018 return True;
6020 -- If we have a type conversion or a qualification of a known valid
6021 -- value, then the result will always be valid.
6023 elsif Nkind_In (Expr, N_Type_Conversion, N_Qualified_Expression) then
6024 return Expr_Known_Valid (Expression (Expr));
6026 -- Case of expression is a non-floating-point operator. In this case we
6027 -- can assume the result is valid the generated code for the operator
6028 -- will include whatever checks are needed (e.g. range checks) to ensure
6029 -- validity. This assumption does not hold for the floating-point case,
6030 -- since floating-point operators can generate Infinite or NaN results
6031 -- which are considered invalid.
6033 -- Historical note: in older versions, the exemption of floating-point
6034 -- types from this assumption was done only in cases where the parent
6035 -- was an assignment, function call or parameter association. Presumably
6036 -- the idea was that in other contexts, the result would be checked
6037 -- elsewhere, but this list of cases was missing tests (at least the
6038 -- N_Object_Declaration case, as shown by a reported missing validity
6039 -- check), and it is not clear why function calls but not procedure
6040 -- calls were tested for. It really seems more accurate and much
6041 -- safer to recognize that expressions which are the result of a
6042 -- floating-point operator can never be assumed to be valid.
6044 elsif Nkind (Expr) in N_Op and then not Is_Floating_Point_Type (Typ) then
6045 return True;
6047 -- The result of a membership test is always valid, since it is true or
6048 -- false, there are no other possibilities.
6050 elsif Nkind (Expr) in N_Membership_Test then
6051 return True;
6053 -- For all other cases, we do not know the expression is valid
6055 else
6056 return False;
6057 end if;
6058 end Expr_Known_Valid;
6060 ----------------
6061 -- Find_Check --
6062 ----------------
6064 procedure Find_Check
6065 (Expr : Node_Id;
6066 Check_Type : Character;
6067 Target_Type : Entity_Id;
6068 Entry_OK : out Boolean;
6069 Check_Num : out Nat;
6070 Ent : out Entity_Id;
6071 Ofs : out Uint)
6073 function Within_Range_Of
6074 (Target_Type : Entity_Id;
6075 Check_Type : Entity_Id) return Boolean;
6076 -- Given a requirement for checking a range against Target_Type, and
6077 -- and a range Check_Type against which a check has already been made,
6078 -- determines if the check against check type is sufficient to ensure
6079 -- that no check against Target_Type is required.
6081 ---------------------
6082 -- Within_Range_Of --
6083 ---------------------
6085 function Within_Range_Of
6086 (Target_Type : Entity_Id;
6087 Check_Type : Entity_Id) return Boolean
6089 begin
6090 if Target_Type = Check_Type then
6091 return True;
6093 else
6094 declare
6095 Tlo : constant Node_Id := Type_Low_Bound (Target_Type);
6096 Thi : constant Node_Id := Type_High_Bound (Target_Type);
6097 Clo : constant Node_Id := Type_Low_Bound (Check_Type);
6098 Chi : constant Node_Id := Type_High_Bound (Check_Type);
6100 begin
6101 if (Tlo = Clo
6102 or else (Compile_Time_Known_Value (Tlo)
6103 and then
6104 Compile_Time_Known_Value (Clo)
6105 and then
6106 Expr_Value (Clo) >= Expr_Value (Tlo)))
6107 and then
6108 (Thi = Chi
6109 or else (Compile_Time_Known_Value (Thi)
6110 and then
6111 Compile_Time_Known_Value (Chi)
6112 and then
6113 Expr_Value (Chi) <= Expr_Value (Clo)))
6114 then
6115 return True;
6116 else
6117 return False;
6118 end if;
6119 end;
6120 end if;
6121 end Within_Range_Of;
6123 -- Start of processing for Find_Check
6125 begin
6126 -- Establish default, in case no entry is found
6128 Check_Num := 0;
6130 -- Case of expression is simple entity reference
6132 if Is_Entity_Name (Expr) then
6133 Ent := Entity (Expr);
6134 Ofs := Uint_0;
6136 -- Case of expression is entity + known constant
6138 elsif Nkind (Expr) = N_Op_Add
6139 and then Compile_Time_Known_Value (Right_Opnd (Expr))
6140 and then Is_Entity_Name (Left_Opnd (Expr))
6141 then
6142 Ent := Entity (Left_Opnd (Expr));
6143 Ofs := Expr_Value (Right_Opnd (Expr));
6145 -- Case of expression is entity - known constant
6147 elsif Nkind (Expr) = N_Op_Subtract
6148 and then Compile_Time_Known_Value (Right_Opnd (Expr))
6149 and then Is_Entity_Name (Left_Opnd (Expr))
6150 then
6151 Ent := Entity (Left_Opnd (Expr));
6152 Ofs := UI_Negate (Expr_Value (Right_Opnd (Expr)));
6154 -- Any other expression is not of the right form
6156 else
6157 Ent := Empty;
6158 Ofs := Uint_0;
6159 Entry_OK := False;
6160 return;
6161 end if;
6163 -- Come here with expression of appropriate form, check if entity is an
6164 -- appropriate one for our purposes.
6166 if (Ekind (Ent) = E_Variable
6167 or else Is_Constant_Object (Ent))
6168 and then not Is_Library_Level_Entity (Ent)
6169 then
6170 Entry_OK := True;
6171 else
6172 Entry_OK := False;
6173 return;
6174 end if;
6176 -- See if there is matching check already
6178 for J in reverse 1 .. Num_Saved_Checks loop
6179 declare
6180 SC : Saved_Check renames Saved_Checks (J);
6181 begin
6182 if SC.Killed = False
6183 and then SC.Entity = Ent
6184 and then SC.Offset = Ofs
6185 and then SC.Check_Type = Check_Type
6186 and then Within_Range_Of (Target_Type, SC.Target_Type)
6187 then
6188 Check_Num := J;
6189 return;
6190 end if;
6191 end;
6192 end loop;
6194 -- If we fall through entry was not found
6196 return;
6197 end Find_Check;
6199 ---------------------------------
6200 -- Generate_Discriminant_Check --
6201 ---------------------------------
6203 -- Note: the code for this procedure is derived from the
6204 -- Emit_Discriminant_Check Routine in trans.c.
6206 procedure Generate_Discriminant_Check (N : Node_Id) is
6207 Loc : constant Source_Ptr := Sloc (N);
6208 Pref : constant Node_Id := Prefix (N);
6209 Sel : constant Node_Id := Selector_Name (N);
6211 Orig_Comp : constant Entity_Id :=
6212 Original_Record_Component (Entity (Sel));
6213 -- The original component to be checked
6215 Discr_Fct : constant Entity_Id :=
6216 Discriminant_Checking_Func (Orig_Comp);
6217 -- The discriminant checking function
6219 Discr : Entity_Id;
6220 -- One discriminant to be checked in the type
6222 Real_Discr : Entity_Id;
6223 -- Actual discriminant in the call
6225 Pref_Type : Entity_Id;
6226 -- Type of relevant prefix (ignoring private/access stuff)
6228 Args : List_Id;
6229 -- List of arguments for function call
6231 Formal : Entity_Id;
6232 -- Keep track of the formal corresponding to the actual we build for
6233 -- each discriminant, in order to be able to perform the necessary type
6234 -- conversions.
6236 Scomp : Node_Id;
6237 -- Selected component reference for checking function argument
6239 begin
6240 Pref_Type := Etype (Pref);
6242 -- Force evaluation of the prefix, so that it does not get evaluated
6243 -- twice (once for the check, once for the actual reference). Such a
6244 -- double evaluation is always a potential source of inefficiency, and
6245 -- is functionally incorrect in the volatile case, or when the prefix
6246 -- may have side effects. A nonvolatile entity or a component of a
6247 -- nonvolatile entity requires no evaluation.
6249 if Is_Entity_Name (Pref) then
6250 if Treat_As_Volatile (Entity (Pref)) then
6251 Force_Evaluation (Pref, Name_Req => True);
6252 end if;
6254 elsif Treat_As_Volatile (Etype (Pref)) then
6255 Force_Evaluation (Pref, Name_Req => True);
6257 elsif Nkind (Pref) = N_Selected_Component
6258 and then Is_Entity_Name (Prefix (Pref))
6259 then
6260 null;
6262 else
6263 Force_Evaluation (Pref, Name_Req => True);
6264 end if;
6266 -- For a tagged type, use the scope of the original component to
6267 -- obtain the type, because ???
6269 if Is_Tagged_Type (Scope (Orig_Comp)) then
6270 Pref_Type := Scope (Orig_Comp);
6272 -- For an untagged derived type, use the discriminants of the parent
6273 -- which have been renamed in the derivation, possibly by a one-to-many
6274 -- discriminant constraint. For untagged type, initially get the Etype
6275 -- of the prefix
6277 else
6278 if Is_Derived_Type (Pref_Type)
6279 and then Number_Discriminants (Pref_Type) /=
6280 Number_Discriminants (Etype (Base_Type (Pref_Type)))
6281 then
6282 Pref_Type := Etype (Base_Type (Pref_Type));
6283 end if;
6284 end if;
6286 -- We definitely should have a checking function, This routine should
6287 -- not be called if no discriminant checking function is present.
6289 pragma Assert (Present (Discr_Fct));
6291 -- Create the list of the actual parameters for the call. This list
6292 -- is the list of the discriminant fields of the record expression to
6293 -- be discriminant checked.
6295 Args := New_List;
6296 Formal := First_Formal (Discr_Fct);
6297 Discr := First_Discriminant (Pref_Type);
6298 while Present (Discr) loop
6300 -- If we have a corresponding discriminant field, and a parent
6301 -- subtype is present, then we want to use the corresponding
6302 -- discriminant since this is the one with the useful value.
6304 if Present (Corresponding_Discriminant (Discr))
6305 and then Ekind (Pref_Type) = E_Record_Type
6306 and then Present (Parent_Subtype (Pref_Type))
6307 then
6308 Real_Discr := Corresponding_Discriminant (Discr);
6309 else
6310 Real_Discr := Discr;
6311 end if;
6313 -- Construct the reference to the discriminant
6315 Scomp :=
6316 Make_Selected_Component (Loc,
6317 Prefix =>
6318 Unchecked_Convert_To (Pref_Type,
6319 Duplicate_Subexpr (Pref)),
6320 Selector_Name => New_Occurrence_Of (Real_Discr, Loc));
6322 -- Manually analyze and resolve this selected component. We really
6323 -- want it just as it appears above, and do not want the expander
6324 -- playing discriminal games etc with this reference. Then we append
6325 -- the argument to the list we are gathering.
6327 Set_Etype (Scomp, Etype (Real_Discr));
6328 Set_Analyzed (Scomp, True);
6329 Append_To (Args, Convert_To (Etype (Formal), Scomp));
6331 Next_Formal_With_Extras (Formal);
6332 Next_Discriminant (Discr);
6333 end loop;
6335 -- Now build and insert the call
6337 Insert_Action (N,
6338 Make_Raise_Constraint_Error (Loc,
6339 Condition =>
6340 Make_Function_Call (Loc,
6341 Name => New_Occurrence_Of (Discr_Fct, Loc),
6342 Parameter_Associations => Args),
6343 Reason => CE_Discriminant_Check_Failed));
6344 end Generate_Discriminant_Check;
6346 ---------------------------
6347 -- Generate_Index_Checks --
6348 ---------------------------
6350 procedure Generate_Index_Checks (N : Node_Id) is
6352 function Entity_Of_Prefix return Entity_Id;
6353 -- Returns the entity of the prefix of N (or Empty if not found)
6355 ----------------------
6356 -- Entity_Of_Prefix --
6357 ----------------------
6359 function Entity_Of_Prefix return Entity_Id is
6360 P : Node_Id;
6362 begin
6363 P := Prefix (N);
6364 while not Is_Entity_Name (P) loop
6365 if not Nkind_In (P, N_Selected_Component,
6366 N_Indexed_Component)
6367 then
6368 return Empty;
6369 end if;
6371 P := Prefix (P);
6372 end loop;
6374 return Entity (P);
6375 end Entity_Of_Prefix;
6377 -- Local variables
6379 Loc : constant Source_Ptr := Sloc (N);
6380 A : constant Node_Id := Prefix (N);
6381 A_Ent : constant Entity_Id := Entity_Of_Prefix;
6382 Sub : Node_Id;
6384 -- Start of processing for Generate_Index_Checks
6386 begin
6387 -- Ignore call if the prefix is not an array since we have a serious
6388 -- error in the sources. Ignore it also if index checks are suppressed
6389 -- for array object or type.
6391 if not Is_Array_Type (Etype (A))
6392 or else (Present (A_Ent) and then Index_Checks_Suppressed (A_Ent))
6393 or else Index_Checks_Suppressed (Etype (A))
6394 then
6395 return;
6397 -- The indexed component we are dealing with contains 'Loop_Entry in its
6398 -- prefix. This case arises when analysis has determined that constructs
6399 -- such as
6401 -- Prefix'Loop_Entry (Expr)
6402 -- Prefix'Loop_Entry (Expr1, Expr2, ... ExprN)
6404 -- require rewriting for error detection purposes. A side effect of this
6405 -- action is the generation of index checks that mention 'Loop_Entry.
6406 -- Delay the generation of the check until 'Loop_Entry has been properly
6407 -- expanded. This is done in Expand_Loop_Entry_Attributes.
6409 elsif Nkind (Prefix (N)) = N_Attribute_Reference
6410 and then Attribute_Name (Prefix (N)) = Name_Loop_Entry
6411 then
6412 return;
6413 end if;
6415 -- Generate a raise of constraint error with the appropriate reason and
6416 -- a condition of the form:
6418 -- Base_Type (Sub) not in Array'Range (Subscript)
6420 -- Note that the reason we generate the conversion to the base type here
6421 -- is that we definitely want the range check to take place, even if it
6422 -- looks like the subtype is OK. Optimization considerations that allow
6423 -- us to omit the check have already been taken into account in the
6424 -- setting of the Do_Range_Check flag earlier on.
6426 Sub := First (Expressions (N));
6428 -- Handle string literals
6430 if Ekind (Etype (A)) = E_String_Literal_Subtype then
6431 if Do_Range_Check (Sub) then
6432 Set_Do_Range_Check (Sub, False);
6434 -- For string literals we obtain the bounds of the string from the
6435 -- associated subtype.
6437 Insert_Action (N,
6438 Make_Raise_Constraint_Error (Loc,
6439 Condition =>
6440 Make_Not_In (Loc,
6441 Left_Opnd =>
6442 Convert_To (Base_Type (Etype (Sub)),
6443 Duplicate_Subexpr_Move_Checks (Sub)),
6444 Right_Opnd =>
6445 Make_Attribute_Reference (Loc,
6446 Prefix => New_Occurrence_Of (Etype (A), Loc),
6447 Attribute_Name => Name_Range)),
6448 Reason => CE_Index_Check_Failed));
6449 end if;
6451 -- General case
6453 else
6454 declare
6455 A_Idx : Node_Id := Empty;
6456 A_Range : Node_Id;
6457 Ind : Nat;
6458 Num : List_Id;
6459 Range_N : Node_Id;
6461 begin
6462 A_Idx := First_Index (Etype (A));
6463 Ind := 1;
6464 while Present (Sub) loop
6465 if Do_Range_Check (Sub) then
6466 Set_Do_Range_Check (Sub, False);
6468 -- Force evaluation except for the case of a simple name of
6469 -- a nonvolatile entity.
6471 if not Is_Entity_Name (Sub)
6472 or else Treat_As_Volatile (Entity (Sub))
6473 then
6474 Force_Evaluation (Sub);
6475 end if;
6477 if Nkind (A_Idx) = N_Range then
6478 A_Range := A_Idx;
6480 elsif Nkind (A_Idx) = N_Identifier
6481 or else Nkind (A_Idx) = N_Expanded_Name
6482 then
6483 A_Range := Scalar_Range (Entity (A_Idx));
6485 else pragma Assert (Nkind (A_Idx) = N_Subtype_Indication);
6486 A_Range := Range_Expression (Constraint (A_Idx));
6487 end if;
6489 -- For array objects with constant bounds we can generate
6490 -- the index check using the bounds of the type of the index
6492 if Present (A_Ent)
6493 and then Ekind (A_Ent) = E_Variable
6494 and then Is_Constant_Bound (Low_Bound (A_Range))
6495 and then Is_Constant_Bound (High_Bound (A_Range))
6496 then
6497 Range_N :=
6498 Make_Attribute_Reference (Loc,
6499 Prefix =>
6500 New_Occurrence_Of (Etype (A_Idx), Loc),
6501 Attribute_Name => Name_Range);
6503 -- For arrays with non-constant bounds we cannot generate
6504 -- the index check using the bounds of the type of the index
6505 -- since it may reference discriminants of some enclosing
6506 -- type. We obtain the bounds directly from the prefix
6507 -- object.
6509 else
6510 if Ind = 1 then
6511 Num := No_List;
6512 else
6513 Num := New_List (Make_Integer_Literal (Loc, Ind));
6514 end if;
6516 Range_N :=
6517 Make_Attribute_Reference (Loc,
6518 Prefix =>
6519 Duplicate_Subexpr_Move_Checks (A, Name_Req => True),
6520 Attribute_Name => Name_Range,
6521 Expressions => Num);
6522 end if;
6524 Insert_Action (N,
6525 Make_Raise_Constraint_Error (Loc,
6526 Condition =>
6527 Make_Not_In (Loc,
6528 Left_Opnd =>
6529 Convert_To (Base_Type (Etype (Sub)),
6530 Duplicate_Subexpr_Move_Checks (Sub)),
6531 Right_Opnd => Range_N),
6532 Reason => CE_Index_Check_Failed));
6533 end if;
6535 A_Idx := Next_Index (A_Idx);
6536 Ind := Ind + 1;
6537 Next (Sub);
6538 end loop;
6539 end;
6540 end if;
6541 end Generate_Index_Checks;
6543 --------------------------
6544 -- Generate_Range_Check --
6545 --------------------------
6547 procedure Generate_Range_Check
6548 (N : Node_Id;
6549 Target_Type : Entity_Id;
6550 Reason : RT_Exception_Code)
6552 Loc : constant Source_Ptr := Sloc (N);
6553 Source_Type : constant Entity_Id := Etype (N);
6554 Source_Base_Type : constant Entity_Id := Base_Type (Source_Type);
6555 Target_Base_Type : constant Entity_Id := Base_Type (Target_Type);
6557 procedure Convert_And_Check_Range;
6558 -- Convert the conversion operand to the target base type and save in
6559 -- a temporary. Then check the converted value against the range of the
6560 -- target subtype.
6562 -----------------------------
6563 -- Convert_And_Check_Range --
6564 -----------------------------
6566 procedure Convert_And_Check_Range is
6567 Tnn : constant Entity_Id := Make_Temporary (Loc, 'T', N);
6569 begin
6570 -- We make a temporary to hold the value of the converted value
6571 -- (converted to the base type), and then do the test against this
6572 -- temporary. The conversion itself is replaced by an occurrence of
6573 -- Tnn and followed by the explicit range check. Note that checks
6574 -- are suppressed for this code, since we don't want a recursive
6575 -- range check popping up.
6577 -- Tnn : constant Target_Base_Type := Target_Base_Type (N);
6578 -- [constraint_error when Tnn not in Target_Type]
6580 Insert_Actions (N, New_List (
6581 Make_Object_Declaration (Loc,
6582 Defining_Identifier => Tnn,
6583 Object_Definition => New_Occurrence_Of (Target_Base_Type, Loc),
6584 Constant_Present => True,
6585 Expression =>
6586 Make_Type_Conversion (Loc,
6587 Subtype_Mark => New_Occurrence_Of (Target_Base_Type, Loc),
6588 Expression => Duplicate_Subexpr (N))),
6590 Make_Raise_Constraint_Error (Loc,
6591 Condition =>
6592 Make_Not_In (Loc,
6593 Left_Opnd => New_Occurrence_Of (Tnn, Loc),
6594 Right_Opnd => New_Occurrence_Of (Target_Type, Loc)),
6595 Reason => Reason)),
6596 Suppress => All_Checks);
6598 Rewrite (N, New_Occurrence_Of (Tnn, Loc));
6600 -- Set the type of N, because the declaration for Tnn might not
6601 -- be analyzed yet, as is the case if N appears within a record
6602 -- declaration, as a discriminant constraint or expression.
6604 Set_Etype (N, Target_Base_Type);
6605 end Convert_And_Check_Range;
6607 -- Start of processing for Generate_Range_Check
6609 begin
6610 -- First special case, if the source type is already within the range
6611 -- of the target type, then no check is needed (probably we should have
6612 -- stopped Do_Range_Check from being set in the first place, but better
6613 -- late than never in preventing junk code and junk flag settings.
6615 if In_Subrange_Of (Source_Type, Target_Type)
6617 -- We do NOT apply this if the source node is a literal, since in this
6618 -- case the literal has already been labeled as having the subtype of
6619 -- the target.
6621 and then not
6622 (Nkind_In (N, N_Integer_Literal, N_Real_Literal, N_Character_Literal)
6623 or else
6624 (Is_Entity_Name (N)
6625 and then Ekind (Entity (N)) = E_Enumeration_Literal))
6626 then
6627 Set_Do_Range_Check (N, False);
6628 return;
6629 end if;
6631 -- Here a check is needed. If the expander is not active, or if we are
6632 -- in GNATProve mode, then simply set the Do_Range_Check flag and we
6633 -- are done. In both these cases, we just want to see the range check
6634 -- flag set, we do not want to generate the explicit range check code.
6636 if GNATprove_Mode or else not Expander_Active then
6637 Set_Do_Range_Check (N, True);
6638 return;
6639 end if;
6641 -- Here we will generate an explicit range check, so we don't want to
6642 -- set the Do_Range check flag, since the range check is taken care of
6643 -- by the code we will generate.
6645 Set_Do_Range_Check (N, False);
6647 -- Force evaluation of the node, so that it does not get evaluated twice
6648 -- (once for the check, once for the actual reference). Such a double
6649 -- evaluation is always a potential source of inefficiency, and is
6650 -- functionally incorrect in the volatile case.
6652 if not Is_Entity_Name (N) or else Treat_As_Volatile (Entity (N)) then
6653 Force_Evaluation (N);
6654 end if;
6656 -- The easiest case is when Source_Base_Type and Target_Base_Type are
6657 -- the same since in this case we can simply do a direct check of the
6658 -- value of N against the bounds of Target_Type.
6660 -- [constraint_error when N not in Target_Type]
6662 -- Note: this is by far the most common case, for example all cases of
6663 -- checks on the RHS of assignments are in this category, but not all
6664 -- cases are like this. Notably conversions can involve two types.
6666 if Source_Base_Type = Target_Base_Type then
6668 -- Insert the explicit range check. Note that we suppress checks for
6669 -- this code, since we don't want a recursive range check popping up.
6671 Insert_Action (N,
6672 Make_Raise_Constraint_Error (Loc,
6673 Condition =>
6674 Make_Not_In (Loc,
6675 Left_Opnd => Duplicate_Subexpr (N),
6676 Right_Opnd => New_Occurrence_Of (Target_Type, Loc)),
6677 Reason => Reason),
6678 Suppress => All_Checks);
6680 -- Next test for the case where the target type is within the bounds
6681 -- of the base type of the source type, since in this case we can
6682 -- simply convert these bounds to the base type of T to do the test.
6684 -- [constraint_error when N not in
6685 -- Source_Base_Type (Target_Type'First)
6686 -- ..
6687 -- Source_Base_Type(Target_Type'Last))]
6689 -- The conversions will always work and need no check
6691 -- Unchecked_Convert_To is used instead of Convert_To to handle the case
6692 -- of converting from an enumeration value to an integer type, such as
6693 -- occurs for the case of generating a range check on Enum'Val(Exp)
6694 -- (which used to be handled by gigi). This is OK, since the conversion
6695 -- itself does not require a check.
6697 elsif In_Subrange_Of (Target_Type, Source_Base_Type) then
6699 -- Insert the explicit range check. Note that we suppress checks for
6700 -- this code, since we don't want a recursive range check popping up.
6702 if Is_Discrete_Type (Source_Base_Type)
6703 and then
6704 Is_Discrete_Type (Target_Base_Type)
6705 then
6706 Insert_Action (N,
6707 Make_Raise_Constraint_Error (Loc,
6708 Condition =>
6709 Make_Not_In (Loc,
6710 Left_Opnd => Duplicate_Subexpr (N),
6712 Right_Opnd =>
6713 Make_Range (Loc,
6714 Low_Bound =>
6715 Unchecked_Convert_To (Source_Base_Type,
6716 Make_Attribute_Reference (Loc,
6717 Prefix =>
6718 New_Occurrence_Of (Target_Type, Loc),
6719 Attribute_Name => Name_First)),
6721 High_Bound =>
6722 Unchecked_Convert_To (Source_Base_Type,
6723 Make_Attribute_Reference (Loc,
6724 Prefix =>
6725 New_Occurrence_Of (Target_Type, Loc),
6726 Attribute_Name => Name_Last)))),
6727 Reason => Reason),
6728 Suppress => All_Checks);
6730 -- For conversions involving at least one type that is not discrete,
6731 -- first convert to target type and then generate the range check.
6732 -- This avoids problems with values that are close to a bound of the
6733 -- target type that would fail a range check when done in a larger
6734 -- source type before converting but would pass if converted with
6735 -- rounding and then checked (such as in float-to-float conversions).
6737 else
6738 Convert_And_Check_Range;
6739 end if;
6741 -- Note that at this stage we now that the Target_Base_Type is not in
6742 -- the range of the Source_Base_Type (since even the Target_Type itself
6743 -- is not in this range). It could still be the case that Source_Type is
6744 -- in range of the target base type since we have not checked that case.
6746 -- If that is the case, we can freely convert the source to the target,
6747 -- and then test the target result against the bounds.
6749 elsif In_Subrange_Of (Source_Type, Target_Base_Type) then
6750 Convert_And_Check_Range;
6752 -- At this stage, we know that we have two scalar types, which are
6753 -- directly convertible, and where neither scalar type has a base
6754 -- range that is in the range of the other scalar type.
6756 -- The only way this can happen is with a signed and unsigned type.
6757 -- So test for these two cases:
6759 else
6760 -- Case of the source is unsigned and the target is signed
6762 if Is_Unsigned_Type (Source_Base_Type)
6763 and then not Is_Unsigned_Type (Target_Base_Type)
6764 then
6765 -- If the source is unsigned and the target is signed, then we
6766 -- know that the source is not shorter than the target (otherwise
6767 -- the source base type would be in the target base type range).
6769 -- In other words, the unsigned type is either the same size as
6770 -- the target, or it is larger. It cannot be smaller.
6772 pragma Assert
6773 (Esize (Source_Base_Type) >= Esize (Target_Base_Type));
6775 -- We only need to check the low bound if the low bound of the
6776 -- target type is non-negative. If the low bound of the target
6777 -- type is negative, then we know that we will fit fine.
6779 -- If the high bound of the target type is negative, then we
6780 -- know we have a constraint error, since we can't possibly
6781 -- have a negative source.
6783 -- With these two checks out of the way, we can do the check
6784 -- using the source type safely
6786 -- This is definitely the most annoying case.
6788 -- [constraint_error
6789 -- when (Target_Type'First >= 0
6790 -- and then
6791 -- N < Source_Base_Type (Target_Type'First))
6792 -- or else Target_Type'Last < 0
6793 -- or else N > Source_Base_Type (Target_Type'Last)];
6795 -- We turn off all checks since we know that the conversions
6796 -- will work fine, given the guards for negative values.
6798 Insert_Action (N,
6799 Make_Raise_Constraint_Error (Loc,
6800 Condition =>
6801 Make_Or_Else (Loc,
6802 Make_Or_Else (Loc,
6803 Left_Opnd =>
6804 Make_And_Then (Loc,
6805 Left_Opnd => Make_Op_Ge (Loc,
6806 Left_Opnd =>
6807 Make_Attribute_Reference (Loc,
6808 Prefix =>
6809 New_Occurrence_Of (Target_Type, Loc),
6810 Attribute_Name => Name_First),
6811 Right_Opnd => Make_Integer_Literal (Loc, Uint_0)),
6813 Right_Opnd =>
6814 Make_Op_Lt (Loc,
6815 Left_Opnd => Duplicate_Subexpr (N),
6816 Right_Opnd =>
6817 Convert_To (Source_Base_Type,
6818 Make_Attribute_Reference (Loc,
6819 Prefix =>
6820 New_Occurrence_Of (Target_Type, Loc),
6821 Attribute_Name => Name_First)))),
6823 Right_Opnd =>
6824 Make_Op_Lt (Loc,
6825 Left_Opnd =>
6826 Make_Attribute_Reference (Loc,
6827 Prefix => New_Occurrence_Of (Target_Type, Loc),
6828 Attribute_Name => Name_Last),
6829 Right_Opnd => Make_Integer_Literal (Loc, Uint_0))),
6831 Right_Opnd =>
6832 Make_Op_Gt (Loc,
6833 Left_Opnd => Duplicate_Subexpr (N),
6834 Right_Opnd =>
6835 Convert_To (Source_Base_Type,
6836 Make_Attribute_Reference (Loc,
6837 Prefix => New_Occurrence_Of (Target_Type, Loc),
6838 Attribute_Name => Name_Last)))),
6840 Reason => Reason),
6841 Suppress => All_Checks);
6843 -- Only remaining possibility is that the source is signed and
6844 -- the target is unsigned.
6846 else
6847 pragma Assert (not Is_Unsigned_Type (Source_Base_Type)
6848 and then Is_Unsigned_Type (Target_Base_Type));
6850 -- If the source is signed and the target is unsigned, then we
6851 -- know that the target is not shorter than the source (otherwise
6852 -- the target base type would be in the source base type range).
6854 -- In other words, the unsigned type is either the same size as
6855 -- the target, or it is larger. It cannot be smaller.
6857 -- Clearly we have an error if the source value is negative since
6858 -- no unsigned type can have negative values. If the source type
6859 -- is non-negative, then the check can be done using the target
6860 -- type.
6862 -- Tnn : constant Target_Base_Type (N) := Target_Type;
6864 -- [constraint_error
6865 -- when N < 0 or else Tnn not in Target_Type];
6867 -- We turn off all checks for the conversion of N to the target
6868 -- base type, since we generate the explicit check to ensure that
6869 -- the value is non-negative
6871 declare
6872 Tnn : constant Entity_Id := Make_Temporary (Loc, 'T', N);
6874 begin
6875 Insert_Actions (N, New_List (
6876 Make_Object_Declaration (Loc,
6877 Defining_Identifier => Tnn,
6878 Object_Definition =>
6879 New_Occurrence_Of (Target_Base_Type, Loc),
6880 Constant_Present => True,
6881 Expression =>
6882 Make_Unchecked_Type_Conversion (Loc,
6883 Subtype_Mark =>
6884 New_Occurrence_Of (Target_Base_Type, Loc),
6885 Expression => Duplicate_Subexpr (N))),
6887 Make_Raise_Constraint_Error (Loc,
6888 Condition =>
6889 Make_Or_Else (Loc,
6890 Left_Opnd =>
6891 Make_Op_Lt (Loc,
6892 Left_Opnd => Duplicate_Subexpr (N),
6893 Right_Opnd => Make_Integer_Literal (Loc, Uint_0)),
6895 Right_Opnd =>
6896 Make_Not_In (Loc,
6897 Left_Opnd => New_Occurrence_Of (Tnn, Loc),
6898 Right_Opnd =>
6899 New_Occurrence_Of (Target_Type, Loc))),
6901 Reason => Reason)),
6902 Suppress => All_Checks);
6904 -- Set the Etype explicitly, because Insert_Actions may have
6905 -- placed the declaration in the freeze list for an enclosing
6906 -- construct, and thus it is not analyzed yet.
6908 Set_Etype (Tnn, Target_Base_Type);
6909 Rewrite (N, New_Occurrence_Of (Tnn, Loc));
6910 end;
6911 end if;
6912 end if;
6913 end Generate_Range_Check;
6915 ------------------
6916 -- Get_Check_Id --
6917 ------------------
6919 function Get_Check_Id (N : Name_Id) return Check_Id is
6920 begin
6921 -- For standard check name, we can do a direct computation
6923 if N in First_Check_Name .. Last_Check_Name then
6924 return Check_Id (N - (First_Check_Name - 1));
6926 -- For non-standard names added by pragma Check_Name, search table
6928 else
6929 for J in All_Checks + 1 .. Check_Names.Last loop
6930 if Check_Names.Table (J) = N then
6931 return J;
6932 end if;
6933 end loop;
6934 end if;
6936 -- No matching name found
6938 return No_Check_Id;
6939 end Get_Check_Id;
6941 ---------------------
6942 -- Get_Discriminal --
6943 ---------------------
6945 function Get_Discriminal (E : Entity_Id; Bound : Node_Id) return Node_Id is
6946 Loc : constant Source_Ptr := Sloc (E);
6947 D : Entity_Id;
6948 Sc : Entity_Id;
6950 begin
6951 -- The bound can be a bona fide parameter of a protected operation,
6952 -- rather than a prival encoded as an in-parameter.
6954 if No (Discriminal_Link (Entity (Bound))) then
6955 return Bound;
6956 end if;
6958 -- Climb the scope stack looking for an enclosing protected type. If
6959 -- we run out of scopes, return the bound itself.
6961 Sc := Scope (E);
6962 while Present (Sc) loop
6963 if Sc = Standard_Standard then
6964 return Bound;
6965 elsif Ekind (Sc) = E_Protected_Type then
6966 exit;
6967 end if;
6969 Sc := Scope (Sc);
6970 end loop;
6972 D := First_Discriminant (Sc);
6973 while Present (D) loop
6974 if Chars (D) = Chars (Bound) then
6975 return New_Occurrence_Of (Discriminal (D), Loc);
6976 end if;
6978 Next_Discriminant (D);
6979 end loop;
6981 return Bound;
6982 end Get_Discriminal;
6984 ----------------------
6985 -- Get_Range_Checks --
6986 ----------------------
6988 function Get_Range_Checks
6989 (Ck_Node : Node_Id;
6990 Target_Typ : Entity_Id;
6991 Source_Typ : Entity_Id := Empty;
6992 Warn_Node : Node_Id := Empty) return Check_Result
6994 begin
6995 return
6996 Selected_Range_Checks (Ck_Node, Target_Typ, Source_Typ, Warn_Node);
6997 end Get_Range_Checks;
6999 ------------------
7000 -- Guard_Access --
7001 ------------------
7003 function Guard_Access
7004 (Cond : Node_Id;
7005 Loc : Source_Ptr;
7006 Ck_Node : Node_Id) return Node_Id
7008 begin
7009 if Nkind (Cond) = N_Or_Else then
7010 Set_Paren_Count (Cond, 1);
7011 end if;
7013 if Nkind (Ck_Node) = N_Allocator then
7014 return Cond;
7016 else
7017 return
7018 Make_And_Then (Loc,
7019 Left_Opnd =>
7020 Make_Op_Ne (Loc,
7021 Left_Opnd => Duplicate_Subexpr_No_Checks (Ck_Node),
7022 Right_Opnd => Make_Null (Loc)),
7023 Right_Opnd => Cond);
7024 end if;
7025 end Guard_Access;
7027 -----------------------------
7028 -- Index_Checks_Suppressed --
7029 -----------------------------
7031 function Index_Checks_Suppressed (E : Entity_Id) return Boolean is
7032 begin
7033 if Present (E) and then Checks_May_Be_Suppressed (E) then
7034 return Is_Check_Suppressed (E, Index_Check);
7035 else
7036 return Scope_Suppress.Suppress (Index_Check);
7037 end if;
7038 end Index_Checks_Suppressed;
7040 ----------------
7041 -- Initialize --
7042 ----------------
7044 procedure Initialize is
7045 begin
7046 for J in Determine_Range_Cache_N'Range loop
7047 Determine_Range_Cache_N (J) := Empty;
7048 end loop;
7050 Check_Names.Init;
7052 for J in Int range 1 .. All_Checks loop
7053 Check_Names.Append (Name_Id (Int (First_Check_Name) + J - 1));
7054 end loop;
7055 end Initialize;
7057 -------------------------
7058 -- Insert_Range_Checks --
7059 -------------------------
7061 procedure Insert_Range_Checks
7062 (Checks : Check_Result;
7063 Node : Node_Id;
7064 Suppress_Typ : Entity_Id;
7065 Static_Sloc : Source_Ptr := No_Location;
7066 Flag_Node : Node_Id := Empty;
7067 Do_Before : Boolean := False)
7069 Internal_Flag_Node : Node_Id := Flag_Node;
7070 Internal_Static_Sloc : Source_Ptr := Static_Sloc;
7072 Check_Node : Node_Id;
7073 Checks_On : constant Boolean :=
7074 (not Index_Checks_Suppressed (Suppress_Typ))
7075 or else (not Range_Checks_Suppressed (Suppress_Typ));
7077 begin
7078 -- For now we just return if Checks_On is false, however this should be
7079 -- enhanced to check for an always True value in the condition and to
7080 -- generate a compilation warning???
7082 if not Expander_Active or not Checks_On then
7083 return;
7084 end if;
7086 if Static_Sloc = No_Location then
7087 Internal_Static_Sloc := Sloc (Node);
7088 end if;
7090 if No (Flag_Node) then
7091 Internal_Flag_Node := Node;
7092 end if;
7094 for J in 1 .. 2 loop
7095 exit when No (Checks (J));
7097 if Nkind (Checks (J)) = N_Raise_Constraint_Error
7098 and then Present (Condition (Checks (J)))
7099 then
7100 if not Has_Dynamic_Range_Check (Internal_Flag_Node) then
7101 Check_Node := Checks (J);
7102 Mark_Rewrite_Insertion (Check_Node);
7104 if Do_Before then
7105 Insert_Before_And_Analyze (Node, Check_Node);
7106 else
7107 Insert_After_And_Analyze (Node, Check_Node);
7108 end if;
7110 Set_Has_Dynamic_Range_Check (Internal_Flag_Node);
7111 end if;
7113 else
7114 Check_Node :=
7115 Make_Raise_Constraint_Error (Internal_Static_Sloc,
7116 Reason => CE_Range_Check_Failed);
7117 Mark_Rewrite_Insertion (Check_Node);
7119 if Do_Before then
7120 Insert_Before_And_Analyze (Node, Check_Node);
7121 else
7122 Insert_After_And_Analyze (Node, Check_Node);
7123 end if;
7124 end if;
7125 end loop;
7126 end Insert_Range_Checks;
7128 ------------------------
7129 -- Insert_Valid_Check --
7130 ------------------------
7132 procedure Insert_Valid_Check
7133 (Expr : Node_Id;
7134 Related_Id : Entity_Id := Empty;
7135 Is_Low_Bound : Boolean := False;
7136 Is_High_Bound : Boolean := False)
7138 Loc : constant Source_Ptr := Sloc (Expr);
7139 Typ : constant Entity_Id := Etype (Expr);
7140 Exp : Node_Id;
7142 begin
7143 -- Do not insert if checks off, or if not checking validity or if
7144 -- expression is known to be valid.
7146 if not Validity_Checks_On
7147 or else Range_Or_Validity_Checks_Suppressed (Expr)
7148 or else Expr_Known_Valid (Expr)
7149 then
7150 return;
7151 end if;
7153 -- Do not insert checks within a predicate function. This will arise
7154 -- if the current unit and the predicate function are being compiled
7155 -- with validity checks enabled.
7157 if Present (Predicate_Function (Typ))
7158 and then Current_Scope = Predicate_Function (Typ)
7159 then
7160 return;
7161 end if;
7163 -- If the expression is a packed component of a modular type of the
7164 -- right size, the data is always valid.
7166 if Nkind (Expr) = N_Selected_Component
7167 and then Present (Component_Clause (Entity (Selector_Name (Expr))))
7168 and then Is_Modular_Integer_Type (Typ)
7169 and then Modulus (Typ) = 2 ** Esize (Entity (Selector_Name (Expr)))
7170 then
7171 return;
7172 end if;
7174 -- If we have a checked conversion, then validity check applies to
7175 -- the expression inside the conversion, not the result, since if
7176 -- the expression inside is valid, then so is the conversion result.
7178 Exp := Expr;
7179 while Nkind (Exp) = N_Type_Conversion loop
7180 Exp := Expression (Exp);
7181 end loop;
7183 -- We are about to insert the validity check for Exp. We save and
7184 -- reset the Do_Range_Check flag over this validity check, and then
7185 -- put it back for the final original reference (Exp may be rewritten).
7187 declare
7188 DRC : constant Boolean := Do_Range_Check (Exp);
7189 PV : Node_Id;
7190 CE : Node_Id;
7192 begin
7193 Set_Do_Range_Check (Exp, False);
7195 -- Force evaluation to avoid multiple reads for atomic/volatile
7197 -- Note: we set Name_Req to False. We used to set it to True, with
7198 -- the thinking that a name is required as the prefix of the 'Valid
7199 -- call, but in fact the check that the prefix of an attribute is
7200 -- a name is in the parser, and we just don't require it here.
7201 -- Moreover, when we set Name_Req to True, that interfered with the
7202 -- checking for Volatile, since we couldn't just capture the value.
7204 if Is_Entity_Name (Exp)
7205 and then Is_Volatile (Entity (Exp))
7206 then
7207 -- Same reasoning as above for setting Name_Req to False
7209 Force_Evaluation (Exp, Name_Req => False);
7210 end if;
7212 -- Build the prefix for the 'Valid call. If the expression denotes
7213 -- a name, use a renaming to alias it, otherwise use a constant to
7214 -- capture the value of the expression.
7216 -- Temp : ... renames Expr; -- reference to a name
7217 -- Temp : constant ... := Expr; -- all other cases
7219 PV :=
7220 Duplicate_Subexpr_No_Checks
7221 (Exp => Exp,
7222 Name_Req => False,
7223 Renaming_Req => Is_Name_Reference (Exp),
7224 Related_Id => Related_Id,
7225 Is_Low_Bound => Is_Low_Bound,
7226 Is_High_Bound => Is_High_Bound);
7228 -- A rather specialized test. If PV is an analyzed expression which
7229 -- is an indexed component of a packed array that has not been
7230 -- properly expanded, turn off its Analyzed flag to make sure it
7231 -- gets properly reexpanded. If the prefix is an access value,
7232 -- the dereference will be added later.
7234 -- The reason this arises is that Duplicate_Subexpr_No_Checks did
7235 -- an analyze with the old parent pointer. This may point e.g. to
7236 -- a subprogram call, which deactivates this expansion.
7238 if Analyzed (PV)
7239 and then Nkind (PV) = N_Indexed_Component
7240 and then Is_Array_Type (Etype (Prefix (PV)))
7241 and then Present (Packed_Array_Impl_Type (Etype (Prefix (PV))))
7242 then
7243 Set_Analyzed (PV, False);
7244 end if;
7246 -- Build the raise CE node to check for validity. We build a type
7247 -- qualification for the prefix, since it may not be of the form of
7248 -- a name, and we don't care in this context!
7250 CE :=
7251 Make_Raise_Constraint_Error (Loc,
7252 Condition =>
7253 Make_Op_Not (Loc,
7254 Right_Opnd =>
7255 Make_Attribute_Reference (Loc,
7256 Prefix => PV,
7257 Attribute_Name => Name_Valid)),
7258 Reason => CE_Invalid_Data);
7260 -- Insert the validity check. Note that we do this with validity
7261 -- checks turned off, to avoid recursion, we do not want validity
7262 -- checks on the validity checking code itself.
7264 Insert_Action (Expr, CE, Suppress => Validity_Check);
7266 -- If the expression is a reference to an element of a bit-packed
7267 -- array, then it is rewritten as a renaming declaration. If the
7268 -- expression is an actual in a call, it has not been expanded,
7269 -- waiting for the proper point at which to do it. The same happens
7270 -- with renamings, so that we have to force the expansion now. This
7271 -- non-local complication is due to code in exp_ch2,adb, exp_ch4.adb
7272 -- and exp_ch6.adb.
7274 if Is_Entity_Name (Exp)
7275 and then Nkind (Parent (Entity (Exp))) =
7276 N_Object_Renaming_Declaration
7277 then
7278 declare
7279 Old_Exp : constant Node_Id := Name (Parent (Entity (Exp)));
7280 begin
7281 if Nkind (Old_Exp) = N_Indexed_Component
7282 and then Is_Bit_Packed_Array (Etype (Prefix (Old_Exp)))
7283 then
7284 Expand_Packed_Element_Reference (Old_Exp);
7285 end if;
7286 end;
7287 end if;
7289 -- Put back the Do_Range_Check flag on the resulting (possibly
7290 -- rewritten) expression.
7292 -- Note: it might be thought that a validity check is not required
7293 -- when a range check is present, but that's not the case, because
7294 -- the back end is allowed to assume for the range check that the
7295 -- operand is within its declared range (an assumption that validity
7296 -- checking is all about NOT assuming).
7298 -- Note: no need to worry about Possible_Local_Raise here, it will
7299 -- already have been called if original node has Do_Range_Check set.
7301 Set_Do_Range_Check (Exp, DRC);
7302 end;
7303 end Insert_Valid_Check;
7305 -------------------------------------
7306 -- Is_Signed_Integer_Arithmetic_Op --
7307 -------------------------------------
7309 function Is_Signed_Integer_Arithmetic_Op (N : Node_Id) return Boolean is
7310 begin
7311 case Nkind (N) is
7312 when N_Op_Abs
7313 | N_Op_Add
7314 | N_Op_Divide
7315 | N_Op_Expon
7316 | N_Op_Minus
7317 | N_Op_Mod
7318 | N_Op_Multiply
7319 | N_Op_Plus
7320 | N_Op_Rem
7321 | N_Op_Subtract
7323 return Is_Signed_Integer_Type (Etype (N));
7325 when N_Case_Expression
7326 | N_If_Expression
7328 return Is_Signed_Integer_Type (Etype (N));
7330 when others =>
7331 return False;
7332 end case;
7333 end Is_Signed_Integer_Arithmetic_Op;
7335 ----------------------------------
7336 -- Install_Null_Excluding_Check --
7337 ----------------------------------
7339 procedure Install_Null_Excluding_Check (N : Node_Id) is
7340 Loc : constant Source_Ptr := Sloc (Parent (N));
7341 Typ : constant Entity_Id := Etype (N);
7343 function Safe_To_Capture_In_Parameter_Value return Boolean;
7344 -- Determines if it is safe to capture Known_Non_Null status for an
7345 -- the entity referenced by node N. The caller ensures that N is indeed
7346 -- an entity name. It is safe to capture the non-null status for an IN
7347 -- parameter when the reference occurs within a declaration that is sure
7348 -- to be executed as part of the declarative region.
7350 procedure Mark_Non_Null;
7351 -- After installation of check, if the node in question is an entity
7352 -- name, then mark this entity as non-null if possible.
7354 function Safe_To_Capture_In_Parameter_Value return Boolean is
7355 E : constant Entity_Id := Entity (N);
7356 S : constant Entity_Id := Current_Scope;
7357 S_Par : Node_Id;
7359 begin
7360 if Ekind (E) /= E_In_Parameter then
7361 return False;
7362 end if;
7364 -- Two initial context checks. We must be inside a subprogram body
7365 -- with declarations and reference must not appear in nested scopes.
7367 if (Ekind (S) /= E_Function and then Ekind (S) /= E_Procedure)
7368 or else Scope (E) /= S
7369 then
7370 return False;
7371 end if;
7373 S_Par := Parent (Parent (S));
7375 if Nkind (S_Par) /= N_Subprogram_Body
7376 or else No (Declarations (S_Par))
7377 then
7378 return False;
7379 end if;
7381 declare
7382 N_Decl : Node_Id;
7383 P : Node_Id;
7385 begin
7386 -- Retrieve the declaration node of N (if any). Note that N
7387 -- may be a part of a complex initialization expression.
7389 P := Parent (N);
7390 N_Decl := Empty;
7391 while Present (P) loop
7393 -- If we have a short circuit form, and we are within the right
7394 -- hand expression, we return false, since the right hand side
7395 -- is not guaranteed to be elaborated.
7397 if Nkind (P) in N_Short_Circuit
7398 and then N = Right_Opnd (P)
7399 then
7400 return False;
7401 end if;
7403 -- Similarly, if we are in an if expression and not part of the
7404 -- condition, then we return False, since neither the THEN or
7405 -- ELSE dependent expressions will always be elaborated.
7407 if Nkind (P) = N_If_Expression
7408 and then N /= First (Expressions (P))
7409 then
7410 return False;
7411 end if;
7413 -- If within a case expression, and not part of the expression,
7414 -- then return False, since a particular dependent expression
7415 -- may not always be elaborated
7417 if Nkind (P) = N_Case_Expression
7418 and then N /= Expression (P)
7419 then
7420 return False;
7421 end if;
7423 -- While traversing the parent chain, if node N belongs to a
7424 -- statement, then it may never appear in a declarative region.
7426 if Nkind (P) in N_Statement_Other_Than_Procedure_Call
7427 or else Nkind (P) = N_Procedure_Call_Statement
7428 then
7429 return False;
7430 end if;
7432 -- If we are at a declaration, record it and exit
7434 if Nkind (P) in N_Declaration
7435 and then Nkind (P) not in N_Subprogram_Specification
7436 then
7437 N_Decl := P;
7438 exit;
7439 end if;
7441 P := Parent (P);
7442 end loop;
7444 if No (N_Decl) then
7445 return False;
7446 end if;
7448 return List_Containing (N_Decl) = Declarations (S_Par);
7449 end;
7450 end Safe_To_Capture_In_Parameter_Value;
7452 -------------------
7453 -- Mark_Non_Null --
7454 -------------------
7456 procedure Mark_Non_Null is
7457 begin
7458 -- Only case of interest is if node N is an entity name
7460 if Is_Entity_Name (N) then
7462 -- For sure, we want to clear an indication that this is known to
7463 -- be null, since if we get past this check, it definitely is not.
7465 Set_Is_Known_Null (Entity (N), False);
7467 -- We can mark the entity as known to be non-null if either it is
7468 -- safe to capture the value, or in the case of an IN parameter,
7469 -- which is a constant, if the check we just installed is in the
7470 -- declarative region of the subprogram body. In this latter case,
7471 -- a check is decisive for the rest of the body if the expression
7472 -- is sure to be elaborated, since we know we have to elaborate
7473 -- all declarations before executing the body.
7475 -- Couldn't this always be part of Safe_To_Capture_Value ???
7477 if Safe_To_Capture_Value (N, Entity (N))
7478 or else Safe_To_Capture_In_Parameter_Value
7479 then
7480 Set_Is_Known_Non_Null (Entity (N));
7481 end if;
7482 end if;
7483 end Mark_Non_Null;
7485 -- Start of processing for Install_Null_Excluding_Check
7487 begin
7488 pragma Assert (Is_Access_Type (Typ));
7490 -- No check inside a generic, check will be emitted in instance
7492 if Inside_A_Generic then
7493 return;
7494 end if;
7496 -- No check needed if known to be non-null
7498 if Known_Non_Null (N) then
7499 return;
7500 end if;
7502 -- If known to be null, here is where we generate a compile time check
7504 if Known_Null (N) then
7506 -- Avoid generating warning message inside init procs. In SPARK mode
7507 -- we can go ahead and call Apply_Compile_Time_Constraint_Error
7508 -- since it will be turned into an error in any case.
7510 if (not Inside_Init_Proc or else SPARK_Mode = On)
7512 -- Do not emit the warning within a conditional expression,
7513 -- where the expression might not be evaluated, and the warning
7514 -- appear as extraneous noise.
7516 and then not Within_Case_Or_If_Expression (N)
7517 then
7518 Apply_Compile_Time_Constraint_Error
7519 (N, "null value not allowed here??", CE_Access_Check_Failed);
7521 -- Remaining cases, where we silently insert the raise
7523 else
7524 Insert_Action (N,
7525 Make_Raise_Constraint_Error (Loc,
7526 Reason => CE_Access_Check_Failed));
7527 end if;
7529 Mark_Non_Null;
7530 return;
7531 end if;
7533 -- If entity is never assigned, for sure a warning is appropriate
7535 if Is_Entity_Name (N) then
7536 Check_Unset_Reference (N);
7537 end if;
7539 -- No check needed if checks are suppressed on the range. Note that we
7540 -- don't set Is_Known_Non_Null in this case (we could legitimately do
7541 -- so, since the program is erroneous, but we don't like to casually
7542 -- propagate such conclusions from erroneosity).
7544 if Access_Checks_Suppressed (Typ) then
7545 return;
7546 end if;
7548 -- No check needed for access to concurrent record types generated by
7549 -- the expander. This is not just an optimization (though it does indeed
7550 -- remove junk checks). It also avoids generation of junk warnings.
7552 if Nkind (N) in N_Has_Chars
7553 and then Chars (N) = Name_uObject
7554 and then Is_Concurrent_Record_Type
7555 (Directly_Designated_Type (Etype (N)))
7556 then
7557 return;
7558 end if;
7560 -- No check needed in interface thunks since the runtime check is
7561 -- already performed at the caller side.
7563 if Is_Thunk (Current_Scope) then
7564 return;
7565 end if;
7567 -- No check needed for the Get_Current_Excep.all.all idiom generated by
7568 -- the expander within exception handlers, since we know that the value
7569 -- can never be null.
7571 -- Is this really the right way to do this? Normally we generate such
7572 -- code in the expander with checks off, and that's how we suppress this
7573 -- kind of junk check ???
7575 if Nkind (N) = N_Function_Call
7576 and then Nkind (Name (N)) = N_Explicit_Dereference
7577 and then Nkind (Prefix (Name (N))) = N_Identifier
7578 and then Is_RTE (Entity (Prefix (Name (N))), RE_Get_Current_Excep)
7579 then
7580 return;
7581 end if;
7583 -- Otherwise install access check
7585 Insert_Action (N,
7586 Make_Raise_Constraint_Error (Loc,
7587 Condition =>
7588 Make_Op_Eq (Loc,
7589 Left_Opnd => Duplicate_Subexpr_Move_Checks (N),
7590 Right_Opnd => Make_Null (Loc)),
7591 Reason => CE_Access_Check_Failed));
7593 Mark_Non_Null;
7594 end Install_Null_Excluding_Check;
7596 --------------------------
7597 -- Install_Static_Check --
7598 --------------------------
7600 procedure Install_Static_Check (R_Cno : Node_Id; Loc : Source_Ptr) is
7601 Stat : constant Boolean := Is_OK_Static_Expression (R_Cno);
7602 Typ : constant Entity_Id := Etype (R_Cno);
7604 begin
7605 Rewrite (R_Cno,
7606 Make_Raise_Constraint_Error (Loc,
7607 Reason => CE_Range_Check_Failed));
7608 Set_Analyzed (R_Cno);
7609 Set_Etype (R_Cno, Typ);
7610 Set_Raises_Constraint_Error (R_Cno);
7611 Set_Is_Static_Expression (R_Cno, Stat);
7613 -- Now deal with possible local raise handling
7615 Possible_Local_Raise (R_Cno, Standard_Constraint_Error);
7616 end Install_Static_Check;
7618 -------------------------
7619 -- Is_Check_Suppressed --
7620 -------------------------
7622 function Is_Check_Suppressed (E : Entity_Id; C : Check_Id) return Boolean is
7623 Ptr : Suppress_Stack_Entry_Ptr;
7625 begin
7626 -- First search the local entity suppress stack. We search this from the
7627 -- top of the stack down so that we get the innermost entry that applies
7628 -- to this case if there are nested entries.
7630 Ptr := Local_Suppress_Stack_Top;
7631 while Ptr /= null loop
7632 if (Ptr.Entity = Empty or else Ptr.Entity = E)
7633 and then (Ptr.Check = All_Checks or else Ptr.Check = C)
7634 then
7635 return Ptr.Suppress;
7636 end if;
7638 Ptr := Ptr.Prev;
7639 end loop;
7641 -- Now search the global entity suppress table for a matching entry.
7642 -- We also search this from the top down so that if there are multiple
7643 -- pragmas for the same entity, the last one applies (not clear what
7644 -- or whether the RM specifies this handling, but it seems reasonable).
7646 Ptr := Global_Suppress_Stack_Top;
7647 while Ptr /= null loop
7648 if (Ptr.Entity = Empty or else Ptr.Entity = E)
7649 and then (Ptr.Check = All_Checks or else Ptr.Check = C)
7650 then
7651 return Ptr.Suppress;
7652 end if;
7654 Ptr := Ptr.Prev;
7655 end loop;
7657 -- If we did not find a matching entry, then use the normal scope
7658 -- suppress value after all (actually this will be the global setting
7659 -- since it clearly was not overridden at any point). For a predefined
7660 -- check, we test the specific flag. For a user defined check, we check
7661 -- the All_Checks flag. The Overflow flag requires special handling to
7662 -- deal with the General vs Assertion case
7664 if C = Overflow_Check then
7665 return Overflow_Checks_Suppressed (Empty);
7666 elsif C in Predefined_Check_Id then
7667 return Scope_Suppress.Suppress (C);
7668 else
7669 return Scope_Suppress.Suppress (All_Checks);
7670 end if;
7671 end Is_Check_Suppressed;
7673 ---------------------
7674 -- Kill_All_Checks --
7675 ---------------------
7677 procedure Kill_All_Checks is
7678 begin
7679 if Debug_Flag_CC then
7680 w ("Kill_All_Checks");
7681 end if;
7683 -- We reset the number of saved checks to zero, and also modify all
7684 -- stack entries for statement ranges to indicate that the number of
7685 -- checks at each level is now zero.
7687 Num_Saved_Checks := 0;
7689 -- Note: the Int'Min here avoids any possibility of J being out of
7690 -- range when called from e.g. Conditional_Statements_Begin.
7692 for J in 1 .. Int'Min (Saved_Checks_TOS, Saved_Checks_Stack'Last) loop
7693 Saved_Checks_Stack (J) := 0;
7694 end loop;
7695 end Kill_All_Checks;
7697 -----------------
7698 -- Kill_Checks --
7699 -----------------
7701 procedure Kill_Checks (V : Entity_Id) is
7702 begin
7703 if Debug_Flag_CC then
7704 w ("Kill_Checks for entity", Int (V));
7705 end if;
7707 for J in 1 .. Num_Saved_Checks loop
7708 if Saved_Checks (J).Entity = V then
7709 if Debug_Flag_CC then
7710 w (" Checks killed for saved check ", J);
7711 end if;
7713 Saved_Checks (J).Killed := True;
7714 end if;
7715 end loop;
7716 end Kill_Checks;
7718 ------------------------------
7719 -- Length_Checks_Suppressed --
7720 ------------------------------
7722 function Length_Checks_Suppressed (E : Entity_Id) return Boolean is
7723 begin
7724 if Present (E) and then Checks_May_Be_Suppressed (E) then
7725 return Is_Check_Suppressed (E, Length_Check);
7726 else
7727 return Scope_Suppress.Suppress (Length_Check);
7728 end if;
7729 end Length_Checks_Suppressed;
7731 -----------------------
7732 -- Make_Bignum_Block --
7733 -----------------------
7735 function Make_Bignum_Block (Loc : Source_Ptr) return Node_Id is
7736 M : constant Entity_Id := Make_Defining_Identifier (Loc, Name_uM);
7737 begin
7738 return
7739 Make_Block_Statement (Loc,
7740 Declarations =>
7741 New_List (Build_SS_Mark_Call (Loc, M)),
7742 Handled_Statement_Sequence =>
7743 Make_Handled_Sequence_Of_Statements (Loc,
7744 Statements => New_List (Build_SS_Release_Call (Loc, M))));
7745 end Make_Bignum_Block;
7747 ----------------------------------
7748 -- Minimize_Eliminate_Overflows --
7749 ----------------------------------
7751 -- This is a recursive routine that is called at the top of an expression
7752 -- tree to properly process overflow checking for a whole subtree by making
7753 -- recursive calls to process operands. This processing may involve the use
7754 -- of bignum or long long integer arithmetic, which will change the types
7755 -- of operands and results. That's why we can't do this bottom up (since
7756 -- it would interfere with semantic analysis).
7758 -- What happens is that if MINIMIZED/ELIMINATED mode is in effect then
7759 -- the operator expansion routines, as well as the expansion routines for
7760 -- if/case expression, do nothing (for the moment) except call the routine
7761 -- to apply the overflow check (Apply_Arithmetic_Overflow_Check). That
7762 -- routine does nothing for non top-level nodes, so at the point where the
7763 -- call is made for the top level node, the entire expression subtree has
7764 -- not been expanded, or processed for overflow. All that has to happen as
7765 -- a result of the top level call to this routine.
7767 -- As noted above, the overflow processing works by making recursive calls
7768 -- for the operands, and figuring out what to do, based on the processing
7769 -- of these operands (e.g. if a bignum operand appears, the parent op has
7770 -- to be done in bignum mode), and the determined ranges of the operands.
7772 -- After possible rewriting of a constituent subexpression node, a call is
7773 -- made to either reexpand the node (if nothing has changed) or reanalyze
7774 -- the node (if it has been modified by the overflow check processing). The
7775 -- Analyzed_Flag is set to False before the reexpand/reanalyze. To avoid
7776 -- a recursive call into the whole overflow apparatus, an important rule
7777 -- for this call is that the overflow handling mode must be temporarily set
7778 -- to STRICT.
7780 procedure Minimize_Eliminate_Overflows
7781 (N : Node_Id;
7782 Lo : out Uint;
7783 Hi : out Uint;
7784 Top_Level : Boolean)
7786 Rtyp : constant Entity_Id := Etype (N);
7787 pragma Assert (Is_Signed_Integer_Type (Rtyp));
7788 -- Result type, must be a signed integer type
7790 Check_Mode : constant Overflow_Mode_Type := Overflow_Check_Mode;
7791 pragma Assert (Check_Mode in Minimized_Or_Eliminated);
7793 Loc : constant Source_Ptr := Sloc (N);
7795 Rlo, Rhi : Uint;
7796 -- Ranges of values for right operand (operator case)
7798 Llo, Lhi : Uint;
7799 -- Ranges of values for left operand (operator case)
7801 LLIB : constant Entity_Id := Base_Type (Standard_Long_Long_Integer);
7802 -- Operands and results are of this type when we convert
7804 LLLo : constant Uint := Intval (Type_Low_Bound (LLIB));
7805 LLHi : constant Uint := Intval (Type_High_Bound (LLIB));
7806 -- Bounds of Long_Long_Integer
7808 Binary : constant Boolean := Nkind (N) in N_Binary_Op;
7809 -- Indicates binary operator case
7811 OK : Boolean;
7812 -- Used in call to Determine_Range
7814 Bignum_Operands : Boolean;
7815 -- Set True if one or more operands is already of type Bignum, meaning
7816 -- that for sure (regardless of Top_Level setting) we are committed to
7817 -- doing the operation in Bignum mode (or in the case of a case or if
7818 -- expression, converting all the dependent expressions to Bignum).
7820 Long_Long_Integer_Operands : Boolean;
7821 -- Set True if one or more operands is already of type Long_Long_Integer
7822 -- which means that if the result is known to be in the result type
7823 -- range, then we must convert such operands back to the result type.
7825 procedure Reanalyze (Typ : Entity_Id; Suppress : Boolean := False);
7826 -- This is called when we have modified the node and we therefore need
7827 -- to reanalyze it. It is important that we reset the mode to STRICT for
7828 -- this reanalysis, since if we leave it in MINIMIZED or ELIMINATED mode
7829 -- we would reenter this routine recursively which would not be good.
7830 -- The argument Suppress is set True if we also want to suppress
7831 -- overflow checking for the reexpansion (this is set when we know
7832 -- overflow is not possible). Typ is the type for the reanalysis.
7834 procedure Reexpand (Suppress : Boolean := False);
7835 -- This is like Reanalyze, but does not do the Analyze step, it only
7836 -- does a reexpansion. We do this reexpansion in STRICT mode, so that
7837 -- instead of reentering the MINIMIZED/ELIMINATED mode processing, we
7838 -- follow the normal expansion path (e.g. converting A**4 to A**2**2).
7839 -- Note that skipping reanalysis is not just an optimization, testing
7840 -- has showed up several complex cases in which reanalyzing an already
7841 -- analyzed node causes incorrect behavior.
7843 function In_Result_Range return Boolean;
7844 -- Returns True iff Lo .. Hi are within range of the result type
7846 procedure Max (A : in out Uint; B : Uint);
7847 -- If A is No_Uint, sets A to B, else to UI_Max (A, B)
7849 procedure Min (A : in out Uint; B : Uint);
7850 -- If A is No_Uint, sets A to B, else to UI_Min (A, B)
7852 ---------------------
7853 -- In_Result_Range --
7854 ---------------------
7856 function In_Result_Range return Boolean is
7857 begin
7858 if Lo = No_Uint or else Hi = No_Uint then
7859 return False;
7861 elsif Is_OK_Static_Subtype (Etype (N)) then
7862 return Lo >= Expr_Value (Type_Low_Bound (Rtyp))
7863 and then
7864 Hi <= Expr_Value (Type_High_Bound (Rtyp));
7866 else
7867 return Lo >= Expr_Value (Type_Low_Bound (Base_Type (Rtyp)))
7868 and then
7869 Hi <= Expr_Value (Type_High_Bound (Base_Type (Rtyp)));
7870 end if;
7871 end In_Result_Range;
7873 ---------
7874 -- Max --
7875 ---------
7877 procedure Max (A : in out Uint; B : Uint) is
7878 begin
7879 if A = No_Uint or else B > A then
7880 A := B;
7881 end if;
7882 end Max;
7884 ---------
7885 -- Min --
7886 ---------
7888 procedure Min (A : in out Uint; B : Uint) is
7889 begin
7890 if A = No_Uint or else B < A then
7891 A := B;
7892 end if;
7893 end Min;
7895 ---------------
7896 -- Reanalyze --
7897 ---------------
7899 procedure Reanalyze (Typ : Entity_Id; Suppress : Boolean := False) is
7900 Svg : constant Overflow_Mode_Type :=
7901 Scope_Suppress.Overflow_Mode_General;
7902 Sva : constant Overflow_Mode_Type :=
7903 Scope_Suppress.Overflow_Mode_Assertions;
7904 Svo : constant Boolean :=
7905 Scope_Suppress.Suppress (Overflow_Check);
7907 begin
7908 Scope_Suppress.Overflow_Mode_General := Strict;
7909 Scope_Suppress.Overflow_Mode_Assertions := Strict;
7911 if Suppress then
7912 Scope_Suppress.Suppress (Overflow_Check) := True;
7913 end if;
7915 Analyze_And_Resolve (N, Typ);
7917 Scope_Suppress.Suppress (Overflow_Check) := Svo;
7918 Scope_Suppress.Overflow_Mode_General := Svg;
7919 Scope_Suppress.Overflow_Mode_Assertions := Sva;
7920 end Reanalyze;
7922 --------------
7923 -- Reexpand --
7924 --------------
7926 procedure Reexpand (Suppress : Boolean := False) is
7927 Svg : constant Overflow_Mode_Type :=
7928 Scope_Suppress.Overflow_Mode_General;
7929 Sva : constant Overflow_Mode_Type :=
7930 Scope_Suppress.Overflow_Mode_Assertions;
7931 Svo : constant Boolean :=
7932 Scope_Suppress.Suppress (Overflow_Check);
7934 begin
7935 Scope_Suppress.Overflow_Mode_General := Strict;
7936 Scope_Suppress.Overflow_Mode_Assertions := Strict;
7937 Set_Analyzed (N, False);
7939 if Suppress then
7940 Scope_Suppress.Suppress (Overflow_Check) := True;
7941 end if;
7943 Expand (N);
7945 Scope_Suppress.Suppress (Overflow_Check) := Svo;
7946 Scope_Suppress.Overflow_Mode_General := Svg;
7947 Scope_Suppress.Overflow_Mode_Assertions := Sva;
7948 end Reexpand;
7950 -- Start of processing for Minimize_Eliminate_Overflows
7952 begin
7953 -- Case where we do not have a signed integer arithmetic operation
7955 if not Is_Signed_Integer_Arithmetic_Op (N) then
7957 -- Use the normal Determine_Range routine to get the range. We
7958 -- don't require operands to be valid, invalid values may result in
7959 -- rubbish results where the result has not been properly checked for
7960 -- overflow, that's fine.
7962 Determine_Range (N, OK, Lo, Hi, Assume_Valid => False);
7964 -- If Determine_Range did not work (can this in fact happen? Not
7965 -- clear but might as well protect), use type bounds.
7967 if not OK then
7968 Lo := Intval (Type_Low_Bound (Base_Type (Etype (N))));
7969 Hi := Intval (Type_High_Bound (Base_Type (Etype (N))));
7970 end if;
7972 -- If we don't have a binary operator, all we have to do is to set
7973 -- the Hi/Lo range, so we are done.
7975 return;
7977 -- Processing for if expression
7979 elsif Nkind (N) = N_If_Expression then
7980 declare
7981 Then_DE : constant Node_Id := Next (First (Expressions (N)));
7982 Else_DE : constant Node_Id := Next (Then_DE);
7984 begin
7985 Bignum_Operands := False;
7987 Minimize_Eliminate_Overflows
7988 (Then_DE, Lo, Hi, Top_Level => False);
7990 if Lo = No_Uint then
7991 Bignum_Operands := True;
7992 end if;
7994 Minimize_Eliminate_Overflows
7995 (Else_DE, Rlo, Rhi, Top_Level => False);
7997 if Rlo = No_Uint then
7998 Bignum_Operands := True;
7999 else
8000 Long_Long_Integer_Operands :=
8001 Etype (Then_DE) = LLIB or else Etype (Else_DE) = LLIB;
8003 Min (Lo, Rlo);
8004 Max (Hi, Rhi);
8005 end if;
8007 -- If at least one of our operands is now Bignum, we must rebuild
8008 -- the if expression to use Bignum operands. We will analyze the
8009 -- rebuilt if expression with overflow checks off, since once we
8010 -- are in bignum mode, we are all done with overflow checks.
8012 if Bignum_Operands then
8013 Rewrite (N,
8014 Make_If_Expression (Loc,
8015 Expressions => New_List (
8016 Remove_Head (Expressions (N)),
8017 Convert_To_Bignum (Then_DE),
8018 Convert_To_Bignum (Else_DE)),
8019 Is_Elsif => Is_Elsif (N)));
8021 Reanalyze (RTE (RE_Bignum), Suppress => True);
8023 -- If we have no Long_Long_Integer operands, then we are in result
8024 -- range, since it means that none of our operands felt the need
8025 -- to worry about overflow (otherwise it would have already been
8026 -- converted to long long integer or bignum). We reexpand to
8027 -- complete the expansion of the if expression (but we do not
8028 -- need to reanalyze).
8030 elsif not Long_Long_Integer_Operands then
8031 Set_Do_Overflow_Check (N, False);
8032 Reexpand;
8034 -- Otherwise convert us to long long integer mode. Note that we
8035 -- don't need any further overflow checking at this level.
8037 else
8038 Convert_To_And_Rewrite (LLIB, Then_DE);
8039 Convert_To_And_Rewrite (LLIB, Else_DE);
8040 Set_Etype (N, LLIB);
8042 -- Now reanalyze with overflow checks off
8044 Set_Do_Overflow_Check (N, False);
8045 Reanalyze (LLIB, Suppress => True);
8046 end if;
8047 end;
8049 return;
8051 -- Here for case expression
8053 elsif Nkind (N) = N_Case_Expression then
8054 Bignum_Operands := False;
8055 Long_Long_Integer_Operands := False;
8057 declare
8058 Alt : Node_Id;
8060 begin
8061 -- Loop through expressions applying recursive call
8063 Alt := First (Alternatives (N));
8064 while Present (Alt) loop
8065 declare
8066 Aexp : constant Node_Id := Expression (Alt);
8068 begin
8069 Minimize_Eliminate_Overflows
8070 (Aexp, Lo, Hi, Top_Level => False);
8072 if Lo = No_Uint then
8073 Bignum_Operands := True;
8074 elsif Etype (Aexp) = LLIB then
8075 Long_Long_Integer_Operands := True;
8076 end if;
8077 end;
8079 Next (Alt);
8080 end loop;
8082 -- If we have no bignum or long long integer operands, it means
8083 -- that none of our dependent expressions could raise overflow.
8084 -- In this case, we simply return with no changes except for
8085 -- resetting the overflow flag, since we are done with overflow
8086 -- checks for this node. We will reexpand to get the needed
8087 -- expansion for the case expression, but we do not need to
8088 -- reanalyze, since nothing has changed.
8090 if not (Bignum_Operands or Long_Long_Integer_Operands) then
8091 Set_Do_Overflow_Check (N, False);
8092 Reexpand (Suppress => True);
8094 -- Otherwise we are going to rebuild the case expression using
8095 -- either bignum or long long integer operands throughout.
8097 else
8098 declare
8099 Rtype : Entity_Id;
8100 New_Alts : List_Id;
8101 New_Exp : Node_Id;
8103 begin
8104 New_Alts := New_List;
8105 Alt := First (Alternatives (N));
8106 while Present (Alt) loop
8107 if Bignum_Operands then
8108 New_Exp := Convert_To_Bignum (Expression (Alt));
8109 Rtype := RTE (RE_Bignum);
8110 else
8111 New_Exp := Convert_To (LLIB, Expression (Alt));
8112 Rtype := LLIB;
8113 end if;
8115 Append_To (New_Alts,
8116 Make_Case_Expression_Alternative (Sloc (Alt),
8117 Actions => No_List,
8118 Discrete_Choices => Discrete_Choices (Alt),
8119 Expression => New_Exp));
8121 Next (Alt);
8122 end loop;
8124 Rewrite (N,
8125 Make_Case_Expression (Loc,
8126 Expression => Expression (N),
8127 Alternatives => New_Alts));
8129 Reanalyze (Rtype, Suppress => True);
8130 end;
8131 end if;
8132 end;
8134 return;
8135 end if;
8137 -- If we have an arithmetic operator we make recursive calls on the
8138 -- operands to get the ranges (and to properly process the subtree
8139 -- that lies below us).
8141 Minimize_Eliminate_Overflows
8142 (Right_Opnd (N), Rlo, Rhi, Top_Level => False);
8144 if Binary then
8145 Minimize_Eliminate_Overflows
8146 (Left_Opnd (N), Llo, Lhi, Top_Level => False);
8147 end if;
8149 -- Record if we have Long_Long_Integer operands
8151 Long_Long_Integer_Operands :=
8152 Etype (Right_Opnd (N)) = LLIB
8153 or else (Binary and then Etype (Left_Opnd (N)) = LLIB);
8155 -- If either operand is a bignum, then result will be a bignum and we
8156 -- don't need to do any range analysis. As previously discussed we could
8157 -- do range analysis in such cases, but it could mean working with giant
8158 -- numbers at compile time for very little gain (the number of cases
8159 -- in which we could slip back from bignum mode is small).
8161 if Rlo = No_Uint or else (Binary and then Llo = No_Uint) then
8162 Lo := No_Uint;
8163 Hi := No_Uint;
8164 Bignum_Operands := True;
8166 -- Otherwise compute result range
8168 else
8169 Bignum_Operands := False;
8171 case Nkind (N) is
8173 -- Absolute value
8175 when N_Op_Abs =>
8176 Lo := Uint_0;
8177 Hi := UI_Max (abs Rlo, abs Rhi);
8179 -- Addition
8181 when N_Op_Add =>
8182 Lo := Llo + Rlo;
8183 Hi := Lhi + Rhi;
8185 -- Division
8187 when N_Op_Divide =>
8189 -- If the right operand can only be zero, set 0..0
8191 if Rlo = 0 and then Rhi = 0 then
8192 Lo := Uint_0;
8193 Hi := Uint_0;
8195 -- Possible bounds of division must come from dividing end
8196 -- values of the input ranges (four possibilities), provided
8197 -- zero is not included in the possible values of the right
8198 -- operand.
8200 -- Otherwise, we just consider two intervals of values for
8201 -- the right operand: the interval of negative values (up to
8202 -- -1) and the interval of positive values (starting at 1).
8203 -- Since division by 1 is the identity, and division by -1
8204 -- is negation, we get all possible bounds of division in that
8205 -- case by considering:
8206 -- - all values from the division of end values of input
8207 -- ranges;
8208 -- - the end values of the left operand;
8209 -- - the negation of the end values of the left operand.
8211 else
8212 declare
8213 Mrk : constant Uintp.Save_Mark := Mark;
8214 -- Mark so we can release the RR and Ev values
8216 Ev1 : Uint;
8217 Ev2 : Uint;
8218 Ev3 : Uint;
8219 Ev4 : Uint;
8221 begin
8222 -- Discard extreme values of zero for the divisor, since
8223 -- they will simply result in an exception in any case.
8225 if Rlo = 0 then
8226 Rlo := Uint_1;
8227 elsif Rhi = 0 then
8228 Rhi := -Uint_1;
8229 end if;
8231 -- Compute possible bounds coming from dividing end
8232 -- values of the input ranges.
8234 Ev1 := Llo / Rlo;
8235 Ev2 := Llo / Rhi;
8236 Ev3 := Lhi / Rlo;
8237 Ev4 := Lhi / Rhi;
8239 Lo := UI_Min (UI_Min (Ev1, Ev2), UI_Min (Ev3, Ev4));
8240 Hi := UI_Max (UI_Max (Ev1, Ev2), UI_Max (Ev3, Ev4));
8242 -- If the right operand can be both negative or positive,
8243 -- include the end values of the left operand in the
8244 -- extreme values, as well as their negation.
8246 if Rlo < 0 and then Rhi > 0 then
8247 Ev1 := Llo;
8248 Ev2 := -Llo;
8249 Ev3 := Lhi;
8250 Ev4 := -Lhi;
8252 Min (Lo,
8253 UI_Min (UI_Min (Ev1, Ev2), UI_Min (Ev3, Ev4)));
8254 Max (Hi,
8255 UI_Max (UI_Max (Ev1, Ev2), UI_Max (Ev3, Ev4)));
8256 end if;
8258 -- Release the RR and Ev values
8260 Release_And_Save (Mrk, Lo, Hi);
8261 end;
8262 end if;
8264 -- Exponentiation
8266 when N_Op_Expon =>
8268 -- Discard negative values for the exponent, since they will
8269 -- simply result in an exception in any case.
8271 if Rhi < 0 then
8272 Rhi := Uint_0;
8273 elsif Rlo < 0 then
8274 Rlo := Uint_0;
8275 end if;
8277 -- Estimate number of bits in result before we go computing
8278 -- giant useless bounds. Basically the number of bits in the
8279 -- result is the number of bits in the base multiplied by the
8280 -- value of the exponent. If this is big enough that the result
8281 -- definitely won't fit in Long_Long_Integer, switch to bignum
8282 -- mode immediately, and avoid computing giant bounds.
8284 -- The comparison here is approximate, but conservative, it
8285 -- only clicks on cases that are sure to exceed the bounds.
8287 if Num_Bits (UI_Max (abs Llo, abs Lhi)) * Rhi + 1 > 100 then
8288 Lo := No_Uint;
8289 Hi := No_Uint;
8291 -- If right operand is zero then result is 1
8293 elsif Rhi = 0 then
8294 Lo := Uint_1;
8295 Hi := Uint_1;
8297 else
8298 -- High bound comes either from exponentiation of largest
8299 -- positive value to largest exponent value, or from
8300 -- the exponentiation of most negative value to an
8301 -- even exponent.
8303 declare
8304 Hi1, Hi2 : Uint;
8306 begin
8307 if Lhi > 0 then
8308 Hi1 := Lhi ** Rhi;
8309 else
8310 Hi1 := Uint_0;
8311 end if;
8313 if Llo < 0 then
8314 if Rhi mod 2 = 0 then
8315 Hi2 := Llo ** Rhi;
8316 else
8317 Hi2 := Llo ** (Rhi - 1);
8318 end if;
8319 else
8320 Hi2 := Uint_0;
8321 end if;
8323 Hi := UI_Max (Hi1, Hi2);
8324 end;
8326 -- Result can only be negative if base can be negative
8328 if Llo < 0 then
8329 if Rhi mod 2 = 0 then
8330 Lo := Llo ** (Rhi - 1);
8331 else
8332 Lo := Llo ** Rhi;
8333 end if;
8335 -- Otherwise low bound is minimum ** minimum
8337 else
8338 Lo := Llo ** Rlo;
8339 end if;
8340 end if;
8342 -- Negation
8344 when N_Op_Minus =>
8345 Lo := -Rhi;
8346 Hi := -Rlo;
8348 -- Mod
8350 when N_Op_Mod =>
8351 declare
8352 Maxabs : constant Uint := UI_Max (abs Rlo, abs Rhi) - 1;
8353 -- This is the maximum absolute value of the result
8355 begin
8356 Lo := Uint_0;
8357 Hi := Uint_0;
8359 -- The result depends only on the sign and magnitude of
8360 -- the right operand, it does not depend on the sign or
8361 -- magnitude of the left operand.
8363 if Rlo < 0 then
8364 Lo := -Maxabs;
8365 end if;
8367 if Rhi > 0 then
8368 Hi := Maxabs;
8369 end if;
8370 end;
8372 -- Multiplication
8374 when N_Op_Multiply =>
8376 -- Possible bounds of multiplication must come from multiplying
8377 -- end values of the input ranges (four possibilities).
8379 declare
8380 Mrk : constant Uintp.Save_Mark := Mark;
8381 -- Mark so we can release the Ev values
8383 Ev1 : constant Uint := Llo * Rlo;
8384 Ev2 : constant Uint := Llo * Rhi;
8385 Ev3 : constant Uint := Lhi * Rlo;
8386 Ev4 : constant Uint := Lhi * Rhi;
8388 begin
8389 Lo := UI_Min (UI_Min (Ev1, Ev2), UI_Min (Ev3, Ev4));
8390 Hi := UI_Max (UI_Max (Ev1, Ev2), UI_Max (Ev3, Ev4));
8392 -- Release the Ev values
8394 Release_And_Save (Mrk, Lo, Hi);
8395 end;
8397 -- Plus operator (affirmation)
8399 when N_Op_Plus =>
8400 Lo := Rlo;
8401 Hi := Rhi;
8403 -- Remainder
8405 when N_Op_Rem =>
8406 declare
8407 Maxabs : constant Uint := UI_Max (abs Rlo, abs Rhi) - 1;
8408 -- This is the maximum absolute value of the result. Note
8409 -- that the result range does not depend on the sign of the
8410 -- right operand.
8412 begin
8413 Lo := Uint_0;
8414 Hi := Uint_0;
8416 -- Case of left operand negative, which results in a range
8417 -- of -Maxabs .. 0 for those negative values. If there are
8418 -- no negative values then Lo value of result is always 0.
8420 if Llo < 0 then
8421 Lo := -Maxabs;
8422 end if;
8424 -- Case of left operand positive
8426 if Lhi > 0 then
8427 Hi := Maxabs;
8428 end if;
8429 end;
8431 -- Subtract
8433 when N_Op_Subtract =>
8434 Lo := Llo - Rhi;
8435 Hi := Lhi - Rlo;
8437 -- Nothing else should be possible
8439 when others =>
8440 raise Program_Error;
8441 end case;
8442 end if;
8444 -- Here for the case where we have not rewritten anything (no bignum
8445 -- operands or long long integer operands), and we know the result.
8446 -- If we know we are in the result range, and we do not have Bignum
8447 -- operands or Long_Long_Integer operands, we can just reexpand with
8448 -- overflow checks turned off (since we know we cannot have overflow).
8449 -- As always the reexpansion is required to complete expansion of the
8450 -- operator, but we do not need to reanalyze, and we prevent recursion
8451 -- by suppressing the check.
8453 if not (Bignum_Operands or Long_Long_Integer_Operands)
8454 and then In_Result_Range
8455 then
8456 Set_Do_Overflow_Check (N, False);
8457 Reexpand (Suppress => True);
8458 return;
8460 -- Here we know that we are not in the result range, and in the general
8461 -- case we will move into either the Bignum or Long_Long_Integer domain
8462 -- to compute the result. However, there is one exception. If we are
8463 -- at the top level, and we do not have Bignum or Long_Long_Integer
8464 -- operands, we will have to immediately convert the result back to
8465 -- the result type, so there is no point in Bignum/Long_Long_Integer
8466 -- fiddling.
8468 elsif Top_Level
8469 and then not (Bignum_Operands or Long_Long_Integer_Operands)
8471 -- One further refinement. If we are at the top level, but our parent
8472 -- is a type conversion, then go into bignum or long long integer node
8473 -- since the result will be converted to that type directly without
8474 -- going through the result type, and we may avoid an overflow. This
8475 -- is the case for example of Long_Long_Integer (A ** 4), where A is
8476 -- of type Integer, and the result A ** 4 fits in Long_Long_Integer
8477 -- but does not fit in Integer.
8479 and then Nkind (Parent (N)) /= N_Type_Conversion
8480 then
8481 -- Here keep original types, but we need to complete analysis
8483 -- One subtlety. We can't just go ahead and do an analyze operation
8484 -- here because it will cause recursion into the whole MINIMIZED/
8485 -- ELIMINATED overflow processing which is not what we want. Here
8486 -- we are at the top level, and we need a check against the result
8487 -- mode (i.e. we want to use STRICT mode). So do exactly that.
8488 -- Also, we have not modified the node, so this is a case where
8489 -- we need to reexpand, but not reanalyze.
8491 Reexpand;
8492 return;
8494 -- Cases where we do the operation in Bignum mode. This happens either
8495 -- because one of our operands is in Bignum mode already, or because
8496 -- the computed bounds are outside the bounds of Long_Long_Integer,
8497 -- which in some cases can be indicated by Hi and Lo being No_Uint.
8499 -- Note: we could do better here and in some cases switch back from
8500 -- Bignum mode to normal mode, e.g. big mod 2 must be in the range
8501 -- 0 .. 1, but the cases are rare and it is not worth the effort.
8502 -- Failing to do this switching back is only an efficiency issue.
8504 elsif Lo = No_Uint or else Lo < LLLo or else Hi > LLHi then
8506 -- OK, we are definitely outside the range of Long_Long_Integer. The
8507 -- question is whether to move to Bignum mode, or stay in the domain
8508 -- of Long_Long_Integer, signalling that an overflow check is needed.
8510 -- Obviously in MINIMIZED mode we stay with LLI, since we are not in
8511 -- the Bignum business. In ELIMINATED mode, we will normally move
8512 -- into Bignum mode, but there is an exception if neither of our
8513 -- operands is Bignum now, and we are at the top level (Top_Level
8514 -- set True). In this case, there is no point in moving into Bignum
8515 -- mode to prevent overflow if the caller will immediately convert
8516 -- the Bignum value back to LLI with an overflow check. It's more
8517 -- efficient to stay in LLI mode with an overflow check (if needed)
8519 if Check_Mode = Minimized
8520 or else (Top_Level and not Bignum_Operands)
8521 then
8522 if Do_Overflow_Check (N) then
8523 Enable_Overflow_Check (N);
8524 end if;
8526 -- The result now has to be in Long_Long_Integer mode, so adjust
8527 -- the possible range to reflect this. Note these calls also
8528 -- change No_Uint values from the top level case to LLI bounds.
8530 Max (Lo, LLLo);
8531 Min (Hi, LLHi);
8533 -- Otherwise we are in ELIMINATED mode and we switch to Bignum mode
8535 else
8536 pragma Assert (Check_Mode = Eliminated);
8538 declare
8539 Fent : Entity_Id;
8540 Args : List_Id;
8542 begin
8543 case Nkind (N) is
8544 when N_Op_Abs =>
8545 Fent := RTE (RE_Big_Abs);
8547 when N_Op_Add =>
8548 Fent := RTE (RE_Big_Add);
8550 when N_Op_Divide =>
8551 Fent := RTE (RE_Big_Div);
8553 when N_Op_Expon =>
8554 Fent := RTE (RE_Big_Exp);
8556 when N_Op_Minus =>
8557 Fent := RTE (RE_Big_Neg);
8559 when N_Op_Mod =>
8560 Fent := RTE (RE_Big_Mod);
8562 when N_Op_Multiply =>
8563 Fent := RTE (RE_Big_Mul);
8565 when N_Op_Rem =>
8566 Fent := RTE (RE_Big_Rem);
8568 when N_Op_Subtract =>
8569 Fent := RTE (RE_Big_Sub);
8571 -- Anything else is an internal error, this includes the
8572 -- N_Op_Plus case, since how can plus cause the result
8573 -- to be out of range if the operand is in range?
8575 when others =>
8576 raise Program_Error;
8577 end case;
8579 -- Construct argument list for Bignum call, converting our
8580 -- operands to Bignum form if they are not already there.
8582 Args := New_List;
8584 if Binary then
8585 Append_To (Args, Convert_To_Bignum (Left_Opnd (N)));
8586 end if;
8588 Append_To (Args, Convert_To_Bignum (Right_Opnd (N)));
8590 -- Now rewrite the arithmetic operator with a call to the
8591 -- corresponding bignum function.
8593 Rewrite (N,
8594 Make_Function_Call (Loc,
8595 Name => New_Occurrence_Of (Fent, Loc),
8596 Parameter_Associations => Args));
8597 Reanalyze (RTE (RE_Bignum), Suppress => True);
8599 -- Indicate result is Bignum mode
8601 Lo := No_Uint;
8602 Hi := No_Uint;
8603 return;
8604 end;
8605 end if;
8607 -- Otherwise we are in range of Long_Long_Integer, so no overflow
8608 -- check is required, at least not yet.
8610 else
8611 Set_Do_Overflow_Check (N, False);
8612 end if;
8614 -- Here we are not in Bignum territory, but we may have long long
8615 -- integer operands that need special handling. First a special check:
8616 -- If an exponentiation operator exponent is of type Long_Long_Integer,
8617 -- it means we converted it to prevent overflow, but exponentiation
8618 -- requires a Natural right operand, so convert it back to Natural.
8619 -- This conversion may raise an exception which is fine.
8621 if Nkind (N) = N_Op_Expon and then Etype (Right_Opnd (N)) = LLIB then
8622 Convert_To_And_Rewrite (Standard_Natural, Right_Opnd (N));
8623 end if;
8625 -- Here we will do the operation in Long_Long_Integer. We do this even
8626 -- if we know an overflow check is required, better to do this in long
8627 -- long integer mode, since we are less likely to overflow.
8629 -- Convert right or only operand to Long_Long_Integer, except that
8630 -- we do not touch the exponentiation right operand.
8632 if Nkind (N) /= N_Op_Expon then
8633 Convert_To_And_Rewrite (LLIB, Right_Opnd (N));
8634 end if;
8636 -- Convert left operand to Long_Long_Integer for binary case
8638 if Binary then
8639 Convert_To_And_Rewrite (LLIB, Left_Opnd (N));
8640 end if;
8642 -- Reset node to unanalyzed
8644 Set_Analyzed (N, False);
8645 Set_Etype (N, Empty);
8646 Set_Entity (N, Empty);
8648 -- Now analyze this new node. This reanalysis will complete processing
8649 -- for the node. In particular we will complete the expansion of an
8650 -- exponentiation operator (e.g. changing A ** 2 to A * A), and also
8651 -- we will complete any division checks (since we have not changed the
8652 -- setting of the Do_Division_Check flag).
8654 -- We do this reanalysis in STRICT mode to avoid recursion into the
8655 -- MINIMIZED/ELIMINATED handling, since we are now done with that.
8657 declare
8658 SG : constant Overflow_Mode_Type :=
8659 Scope_Suppress.Overflow_Mode_General;
8660 SA : constant Overflow_Mode_Type :=
8661 Scope_Suppress.Overflow_Mode_Assertions;
8663 begin
8664 Scope_Suppress.Overflow_Mode_General := Strict;
8665 Scope_Suppress.Overflow_Mode_Assertions := Strict;
8667 if not Do_Overflow_Check (N) then
8668 Reanalyze (LLIB, Suppress => True);
8669 else
8670 Reanalyze (LLIB);
8671 end if;
8673 Scope_Suppress.Overflow_Mode_General := SG;
8674 Scope_Suppress.Overflow_Mode_Assertions := SA;
8675 end;
8676 end Minimize_Eliminate_Overflows;
8678 -------------------------
8679 -- Overflow_Check_Mode --
8680 -------------------------
8682 function Overflow_Check_Mode return Overflow_Mode_Type is
8683 begin
8684 if In_Assertion_Expr = 0 then
8685 return Scope_Suppress.Overflow_Mode_General;
8686 else
8687 return Scope_Suppress.Overflow_Mode_Assertions;
8688 end if;
8689 end Overflow_Check_Mode;
8691 --------------------------------
8692 -- Overflow_Checks_Suppressed --
8693 --------------------------------
8695 function Overflow_Checks_Suppressed (E : Entity_Id) return Boolean is
8696 begin
8697 if Present (E) and then Checks_May_Be_Suppressed (E) then
8698 return Is_Check_Suppressed (E, Overflow_Check);
8699 else
8700 return Scope_Suppress.Suppress (Overflow_Check);
8701 end if;
8702 end Overflow_Checks_Suppressed;
8704 ---------------------------------
8705 -- Predicate_Checks_Suppressed --
8706 ---------------------------------
8708 function Predicate_Checks_Suppressed (E : Entity_Id) return Boolean is
8709 begin
8710 if Present (E) and then Checks_May_Be_Suppressed (E) then
8711 return Is_Check_Suppressed (E, Predicate_Check);
8712 else
8713 return Scope_Suppress.Suppress (Predicate_Check);
8714 end if;
8715 end Predicate_Checks_Suppressed;
8717 -----------------------------
8718 -- Range_Checks_Suppressed --
8719 -----------------------------
8721 function Range_Checks_Suppressed (E : Entity_Id) return Boolean is
8722 begin
8723 if Present (E) then
8724 if Kill_Range_Checks (E) then
8725 return True;
8727 elsif Checks_May_Be_Suppressed (E) then
8728 return Is_Check_Suppressed (E, Range_Check);
8729 end if;
8730 end if;
8732 return Scope_Suppress.Suppress (Range_Check);
8733 end Range_Checks_Suppressed;
8735 -----------------------------------------
8736 -- Range_Or_Validity_Checks_Suppressed --
8737 -----------------------------------------
8739 -- Note: the coding would be simpler here if we simply made appropriate
8740 -- calls to Range/Validity_Checks_Suppressed, but that would result in
8741 -- duplicated checks which we prefer to avoid.
8743 function Range_Or_Validity_Checks_Suppressed
8744 (Expr : Node_Id) return Boolean
8746 begin
8747 -- Immediate return if scope checks suppressed for either check
8749 if Scope_Suppress.Suppress (Range_Check)
8751 Scope_Suppress.Suppress (Validity_Check)
8752 then
8753 return True;
8754 end if;
8756 -- If no expression, that's odd, decide that checks are suppressed,
8757 -- since we don't want anyone trying to do checks in this case, which
8758 -- is most likely the result of some other error.
8760 if No (Expr) then
8761 return True;
8762 end if;
8764 -- Expression is present, so perform suppress checks on type
8766 declare
8767 Typ : constant Entity_Id := Etype (Expr);
8768 begin
8769 if Checks_May_Be_Suppressed (Typ)
8770 and then (Is_Check_Suppressed (Typ, Range_Check)
8771 or else
8772 Is_Check_Suppressed (Typ, Validity_Check))
8773 then
8774 return True;
8775 end if;
8776 end;
8778 -- If expression is an entity name, perform checks on this entity
8780 if Is_Entity_Name (Expr) then
8781 declare
8782 Ent : constant Entity_Id := Entity (Expr);
8783 begin
8784 if Checks_May_Be_Suppressed (Ent) then
8785 return Is_Check_Suppressed (Ent, Range_Check)
8786 or else Is_Check_Suppressed (Ent, Validity_Check);
8787 end if;
8788 end;
8789 end if;
8791 -- If we fall through, no checks suppressed
8793 return False;
8794 end Range_Or_Validity_Checks_Suppressed;
8796 -------------------
8797 -- Remove_Checks --
8798 -------------------
8800 procedure Remove_Checks (Expr : Node_Id) is
8801 function Process (N : Node_Id) return Traverse_Result;
8802 -- Process a single node during the traversal
8804 procedure Traverse is new Traverse_Proc (Process);
8805 -- The traversal procedure itself
8807 -------------
8808 -- Process --
8809 -------------
8811 function Process (N : Node_Id) return Traverse_Result is
8812 begin
8813 if Nkind (N) not in N_Subexpr then
8814 return Skip;
8815 end if;
8817 Set_Do_Range_Check (N, False);
8819 case Nkind (N) is
8820 when N_And_Then =>
8821 Traverse (Left_Opnd (N));
8822 return Skip;
8824 when N_Attribute_Reference =>
8825 Set_Do_Overflow_Check (N, False);
8827 when N_Function_Call =>
8828 Set_Do_Tag_Check (N, False);
8830 when N_Op =>
8831 Set_Do_Overflow_Check (N, False);
8833 case Nkind (N) is
8834 when N_Op_Divide =>
8835 Set_Do_Division_Check (N, False);
8837 when N_Op_And =>
8838 Set_Do_Length_Check (N, False);
8840 when N_Op_Mod =>
8841 Set_Do_Division_Check (N, False);
8843 when N_Op_Or =>
8844 Set_Do_Length_Check (N, False);
8846 when N_Op_Rem =>
8847 Set_Do_Division_Check (N, False);
8849 when N_Op_Xor =>
8850 Set_Do_Length_Check (N, False);
8852 when others =>
8853 null;
8854 end case;
8856 when N_Or_Else =>
8857 Traverse (Left_Opnd (N));
8858 return Skip;
8860 when N_Selected_Component =>
8861 Set_Do_Discriminant_Check (N, False);
8863 when N_Type_Conversion =>
8864 Set_Do_Length_Check (N, False);
8865 Set_Do_Tag_Check (N, False);
8866 Set_Do_Overflow_Check (N, False);
8868 when others =>
8869 null;
8870 end case;
8872 return OK;
8873 end Process;
8875 -- Start of processing for Remove_Checks
8877 begin
8878 Traverse (Expr);
8879 end Remove_Checks;
8881 ----------------------------
8882 -- Selected_Length_Checks --
8883 ----------------------------
8885 function Selected_Length_Checks
8886 (Ck_Node : Node_Id;
8887 Target_Typ : Entity_Id;
8888 Source_Typ : Entity_Id;
8889 Warn_Node : Node_Id) return Check_Result
8891 Loc : constant Source_Ptr := Sloc (Ck_Node);
8892 S_Typ : Entity_Id;
8893 T_Typ : Entity_Id;
8894 Expr_Actual : Node_Id;
8895 Exptyp : Entity_Id;
8896 Cond : Node_Id := Empty;
8897 Do_Access : Boolean := False;
8898 Wnode : Node_Id := Warn_Node;
8899 Ret_Result : Check_Result := (Empty, Empty);
8900 Num_Checks : Natural := 0;
8902 procedure Add_Check (N : Node_Id);
8903 -- Adds the action given to Ret_Result if N is non-Empty
8905 function Get_E_Length (E : Entity_Id; Indx : Nat) return Node_Id;
8906 function Get_N_Length (N : Node_Id; Indx : Nat) return Node_Id;
8907 -- Comments required ???
8909 function Same_Bounds (L : Node_Id; R : Node_Id) return Boolean;
8910 -- True for equal literals and for nodes that denote the same constant
8911 -- entity, even if its value is not a static constant. This includes the
8912 -- case of a discriminal reference within an init proc. Removes some
8913 -- obviously superfluous checks.
8915 function Length_E_Cond
8916 (Exptyp : Entity_Id;
8917 Typ : Entity_Id;
8918 Indx : Nat) return Node_Id;
8919 -- Returns expression to compute:
8920 -- Typ'Length /= Exptyp'Length
8922 function Length_N_Cond
8923 (Expr : Node_Id;
8924 Typ : Entity_Id;
8925 Indx : Nat) return Node_Id;
8926 -- Returns expression to compute:
8927 -- Typ'Length /= Expr'Length
8929 ---------------
8930 -- Add_Check --
8931 ---------------
8933 procedure Add_Check (N : Node_Id) is
8934 begin
8935 if Present (N) then
8937 -- For now, ignore attempt to place more than two checks ???
8938 -- This is really worrisome, are we really discarding checks ???
8940 if Num_Checks = 2 then
8941 return;
8942 end if;
8944 pragma Assert (Num_Checks <= 1);
8945 Num_Checks := Num_Checks + 1;
8946 Ret_Result (Num_Checks) := N;
8947 end if;
8948 end Add_Check;
8950 ------------------
8951 -- Get_E_Length --
8952 ------------------
8954 function Get_E_Length (E : Entity_Id; Indx : Nat) return Node_Id is
8955 SE : constant Entity_Id := Scope (E);
8956 N : Node_Id;
8957 E1 : Entity_Id := E;
8959 begin
8960 if Ekind (Scope (E)) = E_Record_Type
8961 and then Has_Discriminants (Scope (E))
8962 then
8963 N := Build_Discriminal_Subtype_Of_Component (E);
8965 if Present (N) then
8966 Insert_Action (Ck_Node, N);
8967 E1 := Defining_Identifier (N);
8968 end if;
8969 end if;
8971 if Ekind (E1) = E_String_Literal_Subtype then
8972 return
8973 Make_Integer_Literal (Loc,
8974 Intval => String_Literal_Length (E1));
8976 elsif SE /= Standard_Standard
8977 and then Ekind (Scope (SE)) = E_Protected_Type
8978 and then Has_Discriminants (Scope (SE))
8979 and then Has_Completion (Scope (SE))
8980 and then not Inside_Init_Proc
8981 then
8982 -- If the type whose length is needed is a private component
8983 -- constrained by a discriminant, we must expand the 'Length
8984 -- attribute into an explicit computation, using the discriminal
8985 -- of the current protected operation. This is because the actual
8986 -- type of the prival is constructed after the protected opera-
8987 -- tion has been fully expanded.
8989 declare
8990 Indx_Type : Node_Id;
8991 Lo : Node_Id;
8992 Hi : Node_Id;
8993 Do_Expand : Boolean := False;
8995 begin
8996 Indx_Type := First_Index (E);
8998 for J in 1 .. Indx - 1 loop
8999 Next_Index (Indx_Type);
9000 end loop;
9002 Get_Index_Bounds (Indx_Type, Lo, Hi);
9004 if Nkind (Lo) = N_Identifier
9005 and then Ekind (Entity (Lo)) = E_In_Parameter
9006 then
9007 Lo := Get_Discriminal (E, Lo);
9008 Do_Expand := True;
9009 end if;
9011 if Nkind (Hi) = N_Identifier
9012 and then Ekind (Entity (Hi)) = E_In_Parameter
9013 then
9014 Hi := Get_Discriminal (E, Hi);
9015 Do_Expand := True;
9016 end if;
9018 if Do_Expand then
9019 if not Is_Entity_Name (Lo) then
9020 Lo := Duplicate_Subexpr_No_Checks (Lo);
9021 end if;
9023 if not Is_Entity_Name (Hi) then
9024 Lo := Duplicate_Subexpr_No_Checks (Hi);
9025 end if;
9027 N :=
9028 Make_Op_Add (Loc,
9029 Left_Opnd =>
9030 Make_Op_Subtract (Loc,
9031 Left_Opnd => Hi,
9032 Right_Opnd => Lo),
9034 Right_Opnd => Make_Integer_Literal (Loc, 1));
9035 return N;
9037 else
9038 N :=
9039 Make_Attribute_Reference (Loc,
9040 Attribute_Name => Name_Length,
9041 Prefix =>
9042 New_Occurrence_Of (E1, Loc));
9044 if Indx > 1 then
9045 Set_Expressions (N, New_List (
9046 Make_Integer_Literal (Loc, Indx)));
9047 end if;
9049 return N;
9050 end if;
9051 end;
9053 else
9054 N :=
9055 Make_Attribute_Reference (Loc,
9056 Attribute_Name => Name_Length,
9057 Prefix =>
9058 New_Occurrence_Of (E1, Loc));
9060 if Indx > 1 then
9061 Set_Expressions (N, New_List (
9062 Make_Integer_Literal (Loc, Indx)));
9063 end if;
9065 return N;
9066 end if;
9067 end Get_E_Length;
9069 ------------------
9070 -- Get_N_Length --
9071 ------------------
9073 function Get_N_Length (N : Node_Id; Indx : Nat) return Node_Id is
9074 begin
9075 return
9076 Make_Attribute_Reference (Loc,
9077 Attribute_Name => Name_Length,
9078 Prefix =>
9079 Duplicate_Subexpr_No_Checks (N, Name_Req => True),
9080 Expressions => New_List (
9081 Make_Integer_Literal (Loc, Indx)));
9082 end Get_N_Length;
9084 -------------------
9085 -- Length_E_Cond --
9086 -------------------
9088 function Length_E_Cond
9089 (Exptyp : Entity_Id;
9090 Typ : Entity_Id;
9091 Indx : Nat) return Node_Id
9093 begin
9094 return
9095 Make_Op_Ne (Loc,
9096 Left_Opnd => Get_E_Length (Typ, Indx),
9097 Right_Opnd => Get_E_Length (Exptyp, Indx));
9098 end Length_E_Cond;
9100 -------------------
9101 -- Length_N_Cond --
9102 -------------------
9104 function Length_N_Cond
9105 (Expr : Node_Id;
9106 Typ : Entity_Id;
9107 Indx : Nat) return Node_Id
9109 begin
9110 return
9111 Make_Op_Ne (Loc,
9112 Left_Opnd => Get_E_Length (Typ, Indx),
9113 Right_Opnd => Get_N_Length (Expr, Indx));
9114 end Length_N_Cond;
9116 -----------------
9117 -- Same_Bounds --
9118 -----------------
9120 function Same_Bounds (L : Node_Id; R : Node_Id) return Boolean is
9121 begin
9122 return
9123 (Nkind (L) = N_Integer_Literal
9124 and then Nkind (R) = N_Integer_Literal
9125 and then Intval (L) = Intval (R))
9127 or else
9128 (Is_Entity_Name (L)
9129 and then Ekind (Entity (L)) = E_Constant
9130 and then ((Is_Entity_Name (R)
9131 and then Entity (L) = Entity (R))
9132 or else
9133 (Nkind (R) = N_Type_Conversion
9134 and then Is_Entity_Name (Expression (R))
9135 and then Entity (L) = Entity (Expression (R)))))
9137 or else
9138 (Is_Entity_Name (R)
9139 and then Ekind (Entity (R)) = E_Constant
9140 and then Nkind (L) = N_Type_Conversion
9141 and then Is_Entity_Name (Expression (L))
9142 and then Entity (R) = Entity (Expression (L)))
9144 or else
9145 (Is_Entity_Name (L)
9146 and then Is_Entity_Name (R)
9147 and then Entity (L) = Entity (R)
9148 and then Ekind (Entity (L)) = E_In_Parameter
9149 and then Inside_Init_Proc);
9150 end Same_Bounds;
9152 -- Start of processing for Selected_Length_Checks
9154 begin
9155 -- Checks will be applied only when generating code
9157 if not Expander_Active then
9158 return Ret_Result;
9159 end if;
9161 if Target_Typ = Any_Type
9162 or else Target_Typ = Any_Composite
9163 or else Raises_Constraint_Error (Ck_Node)
9164 then
9165 return Ret_Result;
9166 end if;
9168 if No (Wnode) then
9169 Wnode := Ck_Node;
9170 end if;
9172 T_Typ := Target_Typ;
9174 if No (Source_Typ) then
9175 S_Typ := Etype (Ck_Node);
9176 else
9177 S_Typ := Source_Typ;
9178 end if;
9180 if S_Typ = Any_Type or else S_Typ = Any_Composite then
9181 return Ret_Result;
9182 end if;
9184 if Is_Access_Type (T_Typ) and then Is_Access_Type (S_Typ) then
9185 S_Typ := Designated_Type (S_Typ);
9186 T_Typ := Designated_Type (T_Typ);
9187 Do_Access := True;
9189 -- A simple optimization for the null case
9191 if Known_Null (Ck_Node) then
9192 return Ret_Result;
9193 end if;
9194 end if;
9196 if Is_Array_Type (T_Typ) and then Is_Array_Type (S_Typ) then
9197 if Is_Constrained (T_Typ) then
9199 -- The checking code to be generated will freeze the corresponding
9200 -- array type. However, we must freeze the type now, so that the
9201 -- freeze node does not appear within the generated if expression,
9202 -- but ahead of it.
9204 Freeze_Before (Ck_Node, T_Typ);
9206 Expr_Actual := Get_Referenced_Object (Ck_Node);
9207 Exptyp := Get_Actual_Subtype (Ck_Node);
9209 if Is_Access_Type (Exptyp) then
9210 Exptyp := Designated_Type (Exptyp);
9211 end if;
9213 -- String_Literal case. This needs to be handled specially be-
9214 -- cause no index types are available for string literals. The
9215 -- condition is simply:
9217 -- T_Typ'Length = string-literal-length
9219 if Nkind (Expr_Actual) = N_String_Literal
9220 and then Ekind (Etype (Expr_Actual)) = E_String_Literal_Subtype
9221 then
9222 Cond :=
9223 Make_Op_Ne (Loc,
9224 Left_Opnd => Get_E_Length (T_Typ, 1),
9225 Right_Opnd =>
9226 Make_Integer_Literal (Loc,
9227 Intval =>
9228 String_Literal_Length (Etype (Expr_Actual))));
9230 -- General array case. Here we have a usable actual subtype for
9231 -- the expression, and the condition is built from the two types
9232 -- (Do_Length):
9234 -- T_Typ'Length /= Exptyp'Length or else
9235 -- T_Typ'Length (2) /= Exptyp'Length (2) or else
9236 -- T_Typ'Length (3) /= Exptyp'Length (3) or else
9237 -- ...
9239 elsif Is_Constrained (Exptyp) then
9240 declare
9241 Ndims : constant Nat := Number_Dimensions (T_Typ);
9243 L_Index : Node_Id;
9244 R_Index : Node_Id;
9245 L_Low : Node_Id;
9246 L_High : Node_Id;
9247 R_Low : Node_Id;
9248 R_High : Node_Id;
9249 L_Length : Uint;
9250 R_Length : Uint;
9251 Ref_Node : Node_Id;
9253 begin
9254 -- At the library level, we need to ensure that the type of
9255 -- the object is elaborated before the check itself is
9256 -- emitted. This is only done if the object is in the
9257 -- current compilation unit, otherwise the type is frozen
9258 -- and elaborated in its unit.
9260 if Is_Itype (Exptyp)
9261 and then
9262 Ekind (Cunit_Entity (Current_Sem_Unit)) = E_Package
9263 and then
9264 not In_Package_Body (Cunit_Entity (Current_Sem_Unit))
9265 and then In_Open_Scopes (Scope (Exptyp))
9266 then
9267 Ref_Node := Make_Itype_Reference (Sloc (Ck_Node));
9268 Set_Itype (Ref_Node, Exptyp);
9269 Insert_Action (Ck_Node, Ref_Node);
9270 end if;
9272 L_Index := First_Index (T_Typ);
9273 R_Index := First_Index (Exptyp);
9275 for Indx in 1 .. Ndims loop
9276 if not (Nkind (L_Index) = N_Raise_Constraint_Error
9277 or else
9278 Nkind (R_Index) = N_Raise_Constraint_Error)
9279 then
9280 Get_Index_Bounds (L_Index, L_Low, L_High);
9281 Get_Index_Bounds (R_Index, R_Low, R_High);
9283 -- Deal with compile time length check. Note that we
9284 -- skip this in the access case, because the access
9285 -- value may be null, so we cannot know statically.
9287 if not Do_Access
9288 and then Compile_Time_Known_Value (L_Low)
9289 and then Compile_Time_Known_Value (L_High)
9290 and then Compile_Time_Known_Value (R_Low)
9291 and then Compile_Time_Known_Value (R_High)
9292 then
9293 if Expr_Value (L_High) >= Expr_Value (L_Low) then
9294 L_Length := Expr_Value (L_High) -
9295 Expr_Value (L_Low) + 1;
9296 else
9297 L_Length := UI_From_Int (0);
9298 end if;
9300 if Expr_Value (R_High) >= Expr_Value (R_Low) then
9301 R_Length := Expr_Value (R_High) -
9302 Expr_Value (R_Low) + 1;
9303 else
9304 R_Length := UI_From_Int (0);
9305 end if;
9307 if L_Length > R_Length then
9308 Add_Check
9309 (Compile_Time_Constraint_Error
9310 (Wnode, "too few elements for}??", T_Typ));
9312 elsif L_Length < R_Length then
9313 Add_Check
9314 (Compile_Time_Constraint_Error
9315 (Wnode, "too many elements for}??", T_Typ));
9316 end if;
9318 -- The comparison for an individual index subtype
9319 -- is omitted if the corresponding index subtypes
9320 -- statically match, since the result is known to
9321 -- be true. Note that this test is worth while even
9322 -- though we do static evaluation, because non-static
9323 -- subtypes can statically match.
9325 elsif not
9326 Subtypes_Statically_Match
9327 (Etype (L_Index), Etype (R_Index))
9329 and then not
9330 (Same_Bounds (L_Low, R_Low)
9331 and then Same_Bounds (L_High, R_High))
9332 then
9333 Evolve_Or_Else
9334 (Cond, Length_E_Cond (Exptyp, T_Typ, Indx));
9335 end if;
9337 Next (L_Index);
9338 Next (R_Index);
9339 end if;
9340 end loop;
9341 end;
9343 -- Handle cases where we do not get a usable actual subtype that
9344 -- is constrained. This happens for example in the function call
9345 -- and explicit dereference cases. In these cases, we have to get
9346 -- the length or range from the expression itself, making sure we
9347 -- do not evaluate it more than once.
9349 -- Here Ck_Node is the original expression, or more properly the
9350 -- result of applying Duplicate_Expr to the original tree, forcing
9351 -- the result to be a name.
9353 else
9354 declare
9355 Ndims : constant Nat := Number_Dimensions (T_Typ);
9357 begin
9358 -- Build the condition for the explicit dereference case
9360 for Indx in 1 .. Ndims loop
9361 Evolve_Or_Else
9362 (Cond, Length_N_Cond (Ck_Node, T_Typ, Indx));
9363 end loop;
9364 end;
9365 end if;
9366 end if;
9367 end if;
9369 -- Construct the test and insert into the tree
9371 if Present (Cond) then
9372 if Do_Access then
9373 Cond := Guard_Access (Cond, Loc, Ck_Node);
9374 end if;
9376 Add_Check
9377 (Make_Raise_Constraint_Error (Loc,
9378 Condition => Cond,
9379 Reason => CE_Length_Check_Failed));
9380 end if;
9382 return Ret_Result;
9383 end Selected_Length_Checks;
9385 ---------------------------
9386 -- Selected_Range_Checks --
9387 ---------------------------
9389 function Selected_Range_Checks
9390 (Ck_Node : Node_Id;
9391 Target_Typ : Entity_Id;
9392 Source_Typ : Entity_Id;
9393 Warn_Node : Node_Id) return Check_Result
9395 Loc : constant Source_Ptr := Sloc (Ck_Node);
9396 S_Typ : Entity_Id;
9397 T_Typ : Entity_Id;
9398 Expr_Actual : Node_Id;
9399 Exptyp : Entity_Id;
9400 Cond : Node_Id := Empty;
9401 Do_Access : Boolean := False;
9402 Wnode : Node_Id := Warn_Node;
9403 Ret_Result : Check_Result := (Empty, Empty);
9404 Num_Checks : Integer := 0;
9406 procedure Add_Check (N : Node_Id);
9407 -- Adds the action given to Ret_Result if N is non-Empty
9409 function Discrete_Range_Cond
9410 (Expr : Node_Id;
9411 Typ : Entity_Id) return Node_Id;
9412 -- Returns expression to compute:
9413 -- Low_Bound (Expr) < Typ'First
9414 -- or else
9415 -- High_Bound (Expr) > Typ'Last
9417 function Discrete_Expr_Cond
9418 (Expr : Node_Id;
9419 Typ : Entity_Id) return Node_Id;
9420 -- Returns expression to compute:
9421 -- Expr < Typ'First
9422 -- or else
9423 -- Expr > Typ'Last
9425 function Get_E_First_Or_Last
9426 (Loc : Source_Ptr;
9427 E : Entity_Id;
9428 Indx : Nat;
9429 Nam : Name_Id) return Node_Id;
9430 -- Returns an attribute reference
9431 -- E'First or E'Last
9432 -- with a source location of Loc.
9434 -- Nam is Name_First or Name_Last, according to which attribute is
9435 -- desired. If Indx is non-zero, it is passed as a literal in the
9436 -- Expressions of the attribute reference (identifying the desired
9437 -- array dimension).
9439 function Get_N_First (N : Node_Id; Indx : Nat) return Node_Id;
9440 function Get_N_Last (N : Node_Id; Indx : Nat) return Node_Id;
9441 -- Returns expression to compute:
9442 -- N'First or N'Last using Duplicate_Subexpr_No_Checks
9444 function Range_E_Cond
9445 (Exptyp : Entity_Id;
9446 Typ : Entity_Id;
9447 Indx : Nat)
9448 return Node_Id;
9449 -- Returns expression to compute:
9450 -- Exptyp'First < Typ'First or else Exptyp'Last > Typ'Last
9452 function Range_Equal_E_Cond
9453 (Exptyp : Entity_Id;
9454 Typ : Entity_Id;
9455 Indx : Nat) return Node_Id;
9456 -- Returns expression to compute:
9457 -- Exptyp'First /= Typ'First or else Exptyp'Last /= Typ'Last
9459 function Range_N_Cond
9460 (Expr : Node_Id;
9461 Typ : Entity_Id;
9462 Indx : Nat) return Node_Id;
9463 -- Return expression to compute:
9464 -- Expr'First < Typ'First or else Expr'Last > Typ'Last
9466 ---------------
9467 -- Add_Check --
9468 ---------------
9470 procedure Add_Check (N : Node_Id) is
9471 begin
9472 if Present (N) then
9474 -- For now, ignore attempt to place more than 2 checks ???
9476 if Num_Checks = 2 then
9477 return;
9478 end if;
9480 pragma Assert (Num_Checks <= 1);
9481 Num_Checks := Num_Checks + 1;
9482 Ret_Result (Num_Checks) := N;
9483 end if;
9484 end Add_Check;
9486 -------------------------
9487 -- Discrete_Expr_Cond --
9488 -------------------------
9490 function Discrete_Expr_Cond
9491 (Expr : Node_Id;
9492 Typ : Entity_Id) return Node_Id
9494 begin
9495 return
9496 Make_Or_Else (Loc,
9497 Left_Opnd =>
9498 Make_Op_Lt (Loc,
9499 Left_Opnd =>
9500 Convert_To (Base_Type (Typ),
9501 Duplicate_Subexpr_No_Checks (Expr)),
9502 Right_Opnd =>
9503 Convert_To (Base_Type (Typ),
9504 Get_E_First_Or_Last (Loc, Typ, 0, Name_First))),
9506 Right_Opnd =>
9507 Make_Op_Gt (Loc,
9508 Left_Opnd =>
9509 Convert_To (Base_Type (Typ),
9510 Duplicate_Subexpr_No_Checks (Expr)),
9511 Right_Opnd =>
9512 Convert_To
9513 (Base_Type (Typ),
9514 Get_E_First_Or_Last (Loc, Typ, 0, Name_Last))));
9515 end Discrete_Expr_Cond;
9517 -------------------------
9518 -- Discrete_Range_Cond --
9519 -------------------------
9521 function Discrete_Range_Cond
9522 (Expr : Node_Id;
9523 Typ : Entity_Id) return Node_Id
9525 LB : Node_Id := Low_Bound (Expr);
9526 HB : Node_Id := High_Bound (Expr);
9528 Left_Opnd : Node_Id;
9529 Right_Opnd : Node_Id;
9531 begin
9532 if Nkind (LB) = N_Identifier
9533 and then Ekind (Entity (LB)) = E_Discriminant
9534 then
9535 LB := New_Occurrence_Of (Discriminal (Entity (LB)), Loc);
9536 end if;
9538 Left_Opnd :=
9539 Make_Op_Lt (Loc,
9540 Left_Opnd =>
9541 Convert_To
9542 (Base_Type (Typ), Duplicate_Subexpr_No_Checks (LB)),
9544 Right_Opnd =>
9545 Convert_To
9546 (Base_Type (Typ),
9547 Get_E_First_Or_Last (Loc, Typ, 0, Name_First)));
9549 if Nkind (HB) = N_Identifier
9550 and then Ekind (Entity (HB)) = E_Discriminant
9551 then
9552 HB := New_Occurrence_Of (Discriminal (Entity (HB)), Loc);
9553 end if;
9555 Right_Opnd :=
9556 Make_Op_Gt (Loc,
9557 Left_Opnd =>
9558 Convert_To
9559 (Base_Type (Typ), Duplicate_Subexpr_No_Checks (HB)),
9561 Right_Opnd =>
9562 Convert_To
9563 (Base_Type (Typ),
9564 Get_E_First_Or_Last (Loc, Typ, 0, Name_Last)));
9566 return Make_Or_Else (Loc, Left_Opnd, Right_Opnd);
9567 end Discrete_Range_Cond;
9569 -------------------------
9570 -- Get_E_First_Or_Last --
9571 -------------------------
9573 function Get_E_First_Or_Last
9574 (Loc : Source_Ptr;
9575 E : Entity_Id;
9576 Indx : Nat;
9577 Nam : Name_Id) return Node_Id
9579 Exprs : List_Id;
9580 begin
9581 if Indx > 0 then
9582 Exprs := New_List (Make_Integer_Literal (Loc, UI_From_Int (Indx)));
9583 else
9584 Exprs := No_List;
9585 end if;
9587 return Make_Attribute_Reference (Loc,
9588 Prefix => New_Occurrence_Of (E, Loc),
9589 Attribute_Name => Nam,
9590 Expressions => Exprs);
9591 end Get_E_First_Or_Last;
9593 -----------------
9594 -- Get_N_First --
9595 -----------------
9597 function Get_N_First (N : Node_Id; Indx : Nat) return Node_Id is
9598 begin
9599 return
9600 Make_Attribute_Reference (Loc,
9601 Attribute_Name => Name_First,
9602 Prefix =>
9603 Duplicate_Subexpr_No_Checks (N, Name_Req => True),
9604 Expressions => New_List (
9605 Make_Integer_Literal (Loc, Indx)));
9606 end Get_N_First;
9608 ----------------
9609 -- Get_N_Last --
9610 ----------------
9612 function Get_N_Last (N : Node_Id; Indx : Nat) return Node_Id is
9613 begin
9614 return
9615 Make_Attribute_Reference (Loc,
9616 Attribute_Name => Name_Last,
9617 Prefix =>
9618 Duplicate_Subexpr_No_Checks (N, Name_Req => True),
9619 Expressions => New_List (
9620 Make_Integer_Literal (Loc, Indx)));
9621 end Get_N_Last;
9623 ------------------
9624 -- Range_E_Cond --
9625 ------------------
9627 function Range_E_Cond
9628 (Exptyp : Entity_Id;
9629 Typ : Entity_Id;
9630 Indx : Nat) return Node_Id
9632 begin
9633 return
9634 Make_Or_Else (Loc,
9635 Left_Opnd =>
9636 Make_Op_Lt (Loc,
9637 Left_Opnd =>
9638 Get_E_First_Or_Last (Loc, Exptyp, Indx, Name_First),
9639 Right_Opnd =>
9640 Get_E_First_Or_Last (Loc, Typ, Indx, Name_First)),
9642 Right_Opnd =>
9643 Make_Op_Gt (Loc,
9644 Left_Opnd =>
9645 Get_E_First_Or_Last (Loc, Exptyp, Indx, Name_Last),
9646 Right_Opnd =>
9647 Get_E_First_Or_Last (Loc, Typ, Indx, Name_Last)));
9648 end Range_E_Cond;
9650 ------------------------
9651 -- Range_Equal_E_Cond --
9652 ------------------------
9654 function Range_Equal_E_Cond
9655 (Exptyp : Entity_Id;
9656 Typ : Entity_Id;
9657 Indx : Nat) return Node_Id
9659 begin
9660 return
9661 Make_Or_Else (Loc,
9662 Left_Opnd =>
9663 Make_Op_Ne (Loc,
9664 Left_Opnd =>
9665 Get_E_First_Or_Last (Loc, Exptyp, Indx, Name_First),
9666 Right_Opnd =>
9667 Get_E_First_Or_Last (Loc, Typ, Indx, Name_First)),
9669 Right_Opnd =>
9670 Make_Op_Ne (Loc,
9671 Left_Opnd =>
9672 Get_E_First_Or_Last (Loc, Exptyp, Indx, Name_Last),
9673 Right_Opnd =>
9674 Get_E_First_Or_Last (Loc, Typ, Indx, Name_Last)));
9675 end Range_Equal_E_Cond;
9677 ------------------
9678 -- Range_N_Cond --
9679 ------------------
9681 function Range_N_Cond
9682 (Expr : Node_Id;
9683 Typ : Entity_Id;
9684 Indx : Nat) return Node_Id
9686 begin
9687 return
9688 Make_Or_Else (Loc,
9689 Left_Opnd =>
9690 Make_Op_Lt (Loc,
9691 Left_Opnd =>
9692 Get_N_First (Expr, Indx),
9693 Right_Opnd =>
9694 Get_E_First_Or_Last (Loc, Typ, Indx, Name_First)),
9696 Right_Opnd =>
9697 Make_Op_Gt (Loc,
9698 Left_Opnd =>
9699 Get_N_Last (Expr, Indx),
9700 Right_Opnd =>
9701 Get_E_First_Or_Last (Loc, Typ, Indx, Name_Last)));
9702 end Range_N_Cond;
9704 -- Start of processing for Selected_Range_Checks
9706 begin
9707 -- Checks will be applied only when generating code. In GNATprove mode,
9708 -- we do not apply the checks, but we still call Selected_Range_Checks
9709 -- to possibly issue errors on SPARK code when a run-time error can be
9710 -- detected at compile time.
9712 if not Expander_Active and not GNATprove_Mode then
9713 return Ret_Result;
9714 end if;
9716 if Target_Typ = Any_Type
9717 or else Target_Typ = Any_Composite
9718 or else Raises_Constraint_Error (Ck_Node)
9719 then
9720 return Ret_Result;
9721 end if;
9723 if No (Wnode) then
9724 Wnode := Ck_Node;
9725 end if;
9727 T_Typ := Target_Typ;
9729 if No (Source_Typ) then
9730 S_Typ := Etype (Ck_Node);
9731 else
9732 S_Typ := Source_Typ;
9733 end if;
9735 if S_Typ = Any_Type or else S_Typ = Any_Composite then
9736 return Ret_Result;
9737 end if;
9739 -- The order of evaluating T_Typ before S_Typ seems to be critical
9740 -- because S_Typ can be derived from Etype (Ck_Node), if it's not passed
9741 -- in, and since Node can be an N_Range node, it might be invalid.
9742 -- Should there be an assert check somewhere for taking the Etype of
9743 -- an N_Range node ???
9745 if Is_Access_Type (T_Typ) and then Is_Access_Type (S_Typ) then
9746 S_Typ := Designated_Type (S_Typ);
9747 T_Typ := Designated_Type (T_Typ);
9748 Do_Access := True;
9750 -- A simple optimization for the null case
9752 if Known_Null (Ck_Node) then
9753 return Ret_Result;
9754 end if;
9755 end if;
9757 -- For an N_Range Node, check for a null range and then if not
9758 -- null generate a range check action.
9760 if Nkind (Ck_Node) = N_Range then
9762 -- There's no point in checking a range against itself
9764 if Ck_Node = Scalar_Range (T_Typ) then
9765 return Ret_Result;
9766 end if;
9768 declare
9769 T_LB : constant Node_Id := Type_Low_Bound (T_Typ);
9770 T_HB : constant Node_Id := Type_High_Bound (T_Typ);
9771 Known_T_LB : constant Boolean := Compile_Time_Known_Value (T_LB);
9772 Known_T_HB : constant Boolean := Compile_Time_Known_Value (T_HB);
9774 LB : Node_Id := Low_Bound (Ck_Node);
9775 HB : Node_Id := High_Bound (Ck_Node);
9776 Known_LB : Boolean := False;
9777 Known_HB : Boolean := False;
9779 Null_Range : Boolean;
9780 Out_Of_Range_L : Boolean;
9781 Out_Of_Range_H : Boolean;
9783 begin
9784 -- Compute what is known at compile time
9786 if Known_T_LB and Known_T_HB then
9787 if Compile_Time_Known_Value (LB) then
9788 Known_LB := True;
9790 -- There's no point in checking that a bound is within its
9791 -- own range so pretend that it is known in this case. First
9792 -- deal with low bound.
9794 elsif Ekind (Etype (LB)) = E_Signed_Integer_Subtype
9795 and then Scalar_Range (Etype (LB)) = Scalar_Range (T_Typ)
9796 then
9797 LB := T_LB;
9798 Known_LB := True;
9799 end if;
9801 -- Likewise for the high bound
9803 if Compile_Time_Known_Value (HB) then
9804 Known_HB := True;
9806 elsif Ekind (Etype (HB)) = E_Signed_Integer_Subtype
9807 and then Scalar_Range (Etype (HB)) = Scalar_Range (T_Typ)
9808 then
9809 HB := T_HB;
9810 Known_HB := True;
9811 end if;
9812 end if;
9814 -- Check for case where everything is static and we can do the
9815 -- check at compile time. This is skipped if we have an access
9816 -- type, since the access value may be null.
9818 -- ??? This code can be improved since you only need to know that
9819 -- the two respective bounds (LB & T_LB or HB & T_HB) are known at
9820 -- compile time to emit pertinent messages.
9822 if Known_T_LB and Known_T_HB and Known_LB and Known_HB
9823 and not Do_Access
9824 then
9825 -- Floating-point case
9827 if Is_Floating_Point_Type (S_Typ) then
9828 Null_Range := Expr_Value_R (HB) < Expr_Value_R (LB);
9829 Out_Of_Range_L :=
9830 (Expr_Value_R (LB) < Expr_Value_R (T_LB))
9831 or else
9832 (Expr_Value_R (LB) > Expr_Value_R (T_HB));
9834 Out_Of_Range_H :=
9835 (Expr_Value_R (HB) > Expr_Value_R (T_HB))
9836 or else
9837 (Expr_Value_R (HB) < Expr_Value_R (T_LB));
9839 -- Fixed or discrete type case
9841 else
9842 Null_Range := Expr_Value (HB) < Expr_Value (LB);
9843 Out_Of_Range_L :=
9844 (Expr_Value (LB) < Expr_Value (T_LB))
9845 or else
9846 (Expr_Value (LB) > Expr_Value (T_HB));
9848 Out_Of_Range_H :=
9849 (Expr_Value (HB) > Expr_Value (T_HB))
9850 or else
9851 (Expr_Value (HB) < Expr_Value (T_LB));
9852 end if;
9854 if not Null_Range then
9855 if Out_Of_Range_L then
9856 if No (Warn_Node) then
9857 Add_Check
9858 (Compile_Time_Constraint_Error
9859 (Low_Bound (Ck_Node),
9860 "static value out of range of}??", T_Typ));
9862 else
9863 Add_Check
9864 (Compile_Time_Constraint_Error
9865 (Wnode,
9866 "static range out of bounds of}??", T_Typ));
9867 end if;
9868 end if;
9870 if Out_Of_Range_H then
9871 if No (Warn_Node) then
9872 Add_Check
9873 (Compile_Time_Constraint_Error
9874 (High_Bound (Ck_Node),
9875 "static value out of range of}??", T_Typ));
9877 else
9878 Add_Check
9879 (Compile_Time_Constraint_Error
9880 (Wnode,
9881 "static range out of bounds of}??", T_Typ));
9882 end if;
9883 end if;
9884 end if;
9886 else
9887 declare
9888 LB : Node_Id := Low_Bound (Ck_Node);
9889 HB : Node_Id := High_Bound (Ck_Node);
9891 begin
9892 -- If either bound is a discriminant and we are within the
9893 -- record declaration, it is a use of the discriminant in a
9894 -- constraint of a component, and nothing can be checked
9895 -- here. The check will be emitted within the init proc.
9896 -- Before then, the discriminal has no real meaning.
9897 -- Similarly, if the entity is a discriminal, there is no
9898 -- check to perform yet.
9900 -- The same holds within a discriminated synchronized type,
9901 -- where the discriminant may constrain a component or an
9902 -- entry family.
9904 if Nkind (LB) = N_Identifier
9905 and then Denotes_Discriminant (LB, True)
9906 then
9907 if Current_Scope = Scope (Entity (LB))
9908 or else Is_Concurrent_Type (Current_Scope)
9909 or else Ekind (Entity (LB)) /= E_Discriminant
9910 then
9911 return Ret_Result;
9912 else
9913 LB :=
9914 New_Occurrence_Of (Discriminal (Entity (LB)), Loc);
9915 end if;
9916 end if;
9918 if Nkind (HB) = N_Identifier
9919 and then Denotes_Discriminant (HB, True)
9920 then
9921 if Current_Scope = Scope (Entity (HB))
9922 or else Is_Concurrent_Type (Current_Scope)
9923 or else Ekind (Entity (HB)) /= E_Discriminant
9924 then
9925 return Ret_Result;
9926 else
9927 HB :=
9928 New_Occurrence_Of (Discriminal (Entity (HB)), Loc);
9929 end if;
9930 end if;
9932 Cond := Discrete_Range_Cond (Ck_Node, T_Typ);
9933 Set_Paren_Count (Cond, 1);
9935 Cond :=
9936 Make_And_Then (Loc,
9937 Left_Opnd =>
9938 Make_Op_Ge (Loc,
9939 Left_Opnd =>
9940 Convert_To (Base_Type (Etype (HB)),
9941 Duplicate_Subexpr_No_Checks (HB)),
9942 Right_Opnd =>
9943 Convert_To (Base_Type (Etype (LB)),
9944 Duplicate_Subexpr_No_Checks (LB))),
9945 Right_Opnd => Cond);
9946 end;
9947 end if;
9948 end;
9950 elsif Is_Scalar_Type (S_Typ) then
9952 -- This somewhat duplicates what Apply_Scalar_Range_Check does,
9953 -- except the above simply sets a flag in the node and lets
9954 -- gigi generate the check base on the Etype of the expression.
9955 -- Sometimes, however we want to do a dynamic check against an
9956 -- arbitrary target type, so we do that here.
9958 if Ekind (Base_Type (S_Typ)) /= Ekind (Base_Type (T_Typ)) then
9959 Cond := Discrete_Expr_Cond (Ck_Node, T_Typ);
9961 -- For literals, we can tell if the constraint error will be
9962 -- raised at compile time, so we never need a dynamic check, but
9963 -- if the exception will be raised, then post the usual warning,
9964 -- and replace the literal with a raise constraint error
9965 -- expression. As usual, skip this for access types
9967 elsif Compile_Time_Known_Value (Ck_Node) and then not Do_Access then
9968 declare
9969 LB : constant Node_Id := Type_Low_Bound (T_Typ);
9970 UB : constant Node_Id := Type_High_Bound (T_Typ);
9972 Out_Of_Range : Boolean;
9973 Static_Bounds : constant Boolean :=
9974 Compile_Time_Known_Value (LB)
9975 and Compile_Time_Known_Value (UB);
9977 begin
9978 -- Following range tests should use Sem_Eval routine ???
9980 if Static_Bounds then
9981 if Is_Floating_Point_Type (S_Typ) then
9982 Out_Of_Range :=
9983 (Expr_Value_R (Ck_Node) < Expr_Value_R (LB))
9984 or else
9985 (Expr_Value_R (Ck_Node) > Expr_Value_R (UB));
9987 -- Fixed or discrete type
9989 else
9990 Out_Of_Range :=
9991 Expr_Value (Ck_Node) < Expr_Value (LB)
9992 or else
9993 Expr_Value (Ck_Node) > Expr_Value (UB);
9994 end if;
9996 -- Bounds of the type are static and the literal is out of
9997 -- range so output a warning message.
9999 if Out_Of_Range then
10000 if No (Warn_Node) then
10001 Add_Check
10002 (Compile_Time_Constraint_Error
10003 (Ck_Node,
10004 "static value out of range of}??", T_Typ));
10006 else
10007 Add_Check
10008 (Compile_Time_Constraint_Error
10009 (Wnode,
10010 "static value out of range of}??", T_Typ));
10011 end if;
10012 end if;
10014 else
10015 Cond := Discrete_Expr_Cond (Ck_Node, T_Typ);
10016 end if;
10017 end;
10019 -- Here for the case of a non-static expression, we need a runtime
10020 -- check unless the source type range is guaranteed to be in the
10021 -- range of the target type.
10023 else
10024 if not In_Subrange_Of (S_Typ, T_Typ) then
10025 Cond := Discrete_Expr_Cond (Ck_Node, T_Typ);
10026 end if;
10027 end if;
10028 end if;
10030 if Is_Array_Type (T_Typ) and then Is_Array_Type (S_Typ) then
10031 if Is_Constrained (T_Typ) then
10033 Expr_Actual := Get_Referenced_Object (Ck_Node);
10034 Exptyp := Get_Actual_Subtype (Expr_Actual);
10036 if Is_Access_Type (Exptyp) then
10037 Exptyp := Designated_Type (Exptyp);
10038 end if;
10040 -- String_Literal case. This needs to be handled specially be-
10041 -- cause no index types are available for string literals. The
10042 -- condition is simply:
10044 -- T_Typ'Length = string-literal-length
10046 if Nkind (Expr_Actual) = N_String_Literal then
10047 null;
10049 -- General array case. Here we have a usable actual subtype for
10050 -- the expression, and the condition is built from the two types
10052 -- T_Typ'First < Exptyp'First or else
10053 -- T_Typ'Last > Exptyp'Last or else
10054 -- T_Typ'First(1) < Exptyp'First(1) or else
10055 -- T_Typ'Last(1) > Exptyp'Last(1) or else
10056 -- ...
10058 elsif Is_Constrained (Exptyp) then
10059 declare
10060 Ndims : constant Nat := Number_Dimensions (T_Typ);
10062 L_Index : Node_Id;
10063 R_Index : Node_Id;
10065 begin
10066 L_Index := First_Index (T_Typ);
10067 R_Index := First_Index (Exptyp);
10069 for Indx in 1 .. Ndims loop
10070 if not (Nkind (L_Index) = N_Raise_Constraint_Error
10071 or else
10072 Nkind (R_Index) = N_Raise_Constraint_Error)
10073 then
10074 -- Deal with compile time length check. Note that we
10075 -- skip this in the access case, because the access
10076 -- value may be null, so we cannot know statically.
10078 if not
10079 Subtypes_Statically_Match
10080 (Etype (L_Index), Etype (R_Index))
10081 then
10082 -- If the target type is constrained then we
10083 -- have to check for exact equality of bounds
10084 -- (required for qualified expressions).
10086 if Is_Constrained (T_Typ) then
10087 Evolve_Or_Else
10088 (Cond,
10089 Range_Equal_E_Cond (Exptyp, T_Typ, Indx));
10090 else
10091 Evolve_Or_Else
10092 (Cond, Range_E_Cond (Exptyp, T_Typ, Indx));
10093 end if;
10094 end if;
10096 Next (L_Index);
10097 Next (R_Index);
10098 end if;
10099 end loop;
10100 end;
10102 -- Handle cases where we do not get a usable actual subtype that
10103 -- is constrained. This happens for example in the function call
10104 -- and explicit dereference cases. In these cases, we have to get
10105 -- the length or range from the expression itself, making sure we
10106 -- do not evaluate it more than once.
10108 -- Here Ck_Node is the original expression, or more properly the
10109 -- result of applying Duplicate_Expr to the original tree,
10110 -- forcing the result to be a name.
10112 else
10113 declare
10114 Ndims : constant Nat := Number_Dimensions (T_Typ);
10116 begin
10117 -- Build the condition for the explicit dereference case
10119 for Indx in 1 .. Ndims loop
10120 Evolve_Or_Else
10121 (Cond, Range_N_Cond (Ck_Node, T_Typ, Indx));
10122 end loop;
10123 end;
10124 end if;
10126 else
10127 -- For a conversion to an unconstrained array type, generate an
10128 -- Action to check that the bounds of the source value are within
10129 -- the constraints imposed by the target type (RM 4.6(38)). No
10130 -- check is needed for a conversion to an access to unconstrained
10131 -- array type, as 4.6(24.15/2) requires the designated subtypes
10132 -- of the two access types to statically match.
10134 if Nkind (Parent (Ck_Node)) = N_Type_Conversion
10135 and then not Do_Access
10136 then
10137 declare
10138 Opnd_Index : Node_Id;
10139 Targ_Index : Node_Id;
10140 Opnd_Range : Node_Id;
10142 begin
10143 Opnd_Index := First_Index (Get_Actual_Subtype (Ck_Node));
10144 Targ_Index := First_Index (T_Typ);
10145 while Present (Opnd_Index) loop
10147 -- If the index is a range, use its bounds. If it is an
10148 -- entity (as will be the case if it is a named subtype
10149 -- or an itype created for a slice) retrieve its range.
10151 if Is_Entity_Name (Opnd_Index)
10152 and then Is_Type (Entity (Opnd_Index))
10153 then
10154 Opnd_Range := Scalar_Range (Entity (Opnd_Index));
10155 else
10156 Opnd_Range := Opnd_Index;
10157 end if;
10159 if Nkind (Opnd_Range) = N_Range then
10160 if Is_In_Range
10161 (Low_Bound (Opnd_Range), Etype (Targ_Index),
10162 Assume_Valid => True)
10163 and then
10164 Is_In_Range
10165 (High_Bound (Opnd_Range), Etype (Targ_Index),
10166 Assume_Valid => True)
10167 then
10168 null;
10170 -- If null range, no check needed
10172 elsif
10173 Compile_Time_Known_Value (High_Bound (Opnd_Range))
10174 and then
10175 Compile_Time_Known_Value (Low_Bound (Opnd_Range))
10176 and then
10177 Expr_Value (High_Bound (Opnd_Range)) <
10178 Expr_Value (Low_Bound (Opnd_Range))
10179 then
10180 null;
10182 elsif Is_Out_Of_Range
10183 (Low_Bound (Opnd_Range), Etype (Targ_Index),
10184 Assume_Valid => True)
10185 or else
10186 Is_Out_Of_Range
10187 (High_Bound (Opnd_Range), Etype (Targ_Index),
10188 Assume_Valid => True)
10189 then
10190 Add_Check
10191 (Compile_Time_Constraint_Error
10192 (Wnode, "value out of range of}??", T_Typ));
10194 else
10195 Evolve_Or_Else
10196 (Cond,
10197 Discrete_Range_Cond
10198 (Opnd_Range, Etype (Targ_Index)));
10199 end if;
10200 end if;
10202 Next_Index (Opnd_Index);
10203 Next_Index (Targ_Index);
10204 end loop;
10205 end;
10206 end if;
10207 end if;
10208 end if;
10210 -- Construct the test and insert into the tree
10212 if Present (Cond) then
10213 if Do_Access then
10214 Cond := Guard_Access (Cond, Loc, Ck_Node);
10215 end if;
10217 Add_Check
10218 (Make_Raise_Constraint_Error (Loc,
10219 Condition => Cond,
10220 Reason => CE_Range_Check_Failed));
10221 end if;
10223 return Ret_Result;
10224 end Selected_Range_Checks;
10226 -------------------------------
10227 -- Storage_Checks_Suppressed --
10228 -------------------------------
10230 function Storage_Checks_Suppressed (E : Entity_Id) return Boolean is
10231 begin
10232 if Present (E) and then Checks_May_Be_Suppressed (E) then
10233 return Is_Check_Suppressed (E, Storage_Check);
10234 else
10235 return Scope_Suppress.Suppress (Storage_Check);
10236 end if;
10237 end Storage_Checks_Suppressed;
10239 ---------------------------
10240 -- Tag_Checks_Suppressed --
10241 ---------------------------
10243 function Tag_Checks_Suppressed (E : Entity_Id) return Boolean is
10244 begin
10245 if Present (E)
10246 and then Checks_May_Be_Suppressed (E)
10247 then
10248 return Is_Check_Suppressed (E, Tag_Check);
10249 else
10250 return Scope_Suppress.Suppress (Tag_Check);
10251 end if;
10252 end Tag_Checks_Suppressed;
10254 ---------------------------------------
10255 -- Validate_Alignment_Check_Warnings --
10256 ---------------------------------------
10258 procedure Validate_Alignment_Check_Warnings is
10259 begin
10260 for J in Alignment_Warnings.First .. Alignment_Warnings.Last loop
10261 declare
10262 AWR : Alignment_Warnings_Record
10263 renames Alignment_Warnings.Table (J);
10264 begin
10265 if Known_Alignment (AWR.E)
10266 and then AWR.A mod Alignment (AWR.E) = 0
10267 then
10268 Delete_Warning_And_Continuations (AWR.W);
10269 end if;
10270 end;
10271 end loop;
10272 end Validate_Alignment_Check_Warnings;
10274 --------------------------
10275 -- Validity_Check_Range --
10276 --------------------------
10278 procedure Validity_Check_Range
10279 (N : Node_Id;
10280 Related_Id : Entity_Id := Empty)
10282 begin
10283 if Validity_Checks_On and Validity_Check_Operands then
10284 if Nkind (N) = N_Range then
10285 Ensure_Valid
10286 (Expr => Low_Bound (N),
10287 Related_Id => Related_Id,
10288 Is_Low_Bound => True);
10290 Ensure_Valid
10291 (Expr => High_Bound (N),
10292 Related_Id => Related_Id,
10293 Is_High_Bound => True);
10294 end if;
10295 end if;
10296 end Validity_Check_Range;
10298 --------------------------------
10299 -- Validity_Checks_Suppressed --
10300 --------------------------------
10302 function Validity_Checks_Suppressed (E : Entity_Id) return Boolean is
10303 begin
10304 if Present (E) and then Checks_May_Be_Suppressed (E) then
10305 return Is_Check_Suppressed (E, Validity_Check);
10306 else
10307 return Scope_Suppress.Suppress (Validity_Check);
10308 end if;
10309 end Validity_Checks_Suppressed;
10311 end Checks;