* arm.c (FL_WBUF): Define.
[official-gcc.git] / gcc / ada / checks.adb
blob5255e214f53047b63b09327fc842e1a8b92551bd
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-2005 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 2, 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 COPYING. If not, write --
19 -- to the Free Software Foundation, 59 Temple Place - Suite 330, Boston, --
20 -- MA 02111-1307, USA. --
21 -- --
22 -- GNAT was originally developed by the GNAT team at New York University. --
23 -- Extensive contributions were provided by Ada Core Technologies Inc. --
24 -- --
25 ------------------------------------------------------------------------------
27 with Atree; use Atree;
28 with Debug; use Debug;
29 with Einfo; use Einfo;
30 with Errout; use Errout;
31 with Exp_Ch2; use Exp_Ch2;
32 with Exp_Util; use Exp_Util;
33 with Elists; use Elists;
34 with Eval_Fat; use Eval_Fat;
35 with Freeze; use Freeze;
36 with Lib; use Lib;
37 with Nlists; use Nlists;
38 with Nmake; use Nmake;
39 with Opt; use Opt;
40 with Output; use Output;
41 with Restrict; use Restrict;
42 with Rident; use Rident;
43 with Rtsfind; use Rtsfind;
44 with Sem; use Sem;
45 with Sem_Eval; use Sem_Eval;
46 with Sem_Ch3; use Sem_Ch3;
47 with Sem_Ch8; use Sem_Ch8;
48 with Sem_Res; use Sem_Res;
49 with Sem_Util; use Sem_Util;
50 with Sem_Warn; use Sem_Warn;
51 with Sinfo; use Sinfo;
52 with Sinput; use Sinput;
53 with Snames; use Snames;
54 with Sprint; use Sprint;
55 with Stand; use Stand;
56 with Targparm; use Targparm;
57 with Tbuild; use Tbuild;
58 with Ttypes; use Ttypes;
59 with Urealp; use Urealp;
60 with Validsw; use Validsw;
62 package body Checks is
64 -- General note: many of these routines are concerned with generating
65 -- checking code to make sure that constraint error is raised at runtime.
66 -- Clearly this code is only needed if the expander is active, since
67 -- otherwise we will not be generating code or going into the runtime
68 -- execution anyway.
70 -- We therefore disconnect most of these checks if the expander is
71 -- inactive. This has the additional benefit that we do not need to
72 -- worry about the tree being messed up by previous errors (since errors
73 -- turn off expansion anyway).
75 -- There are a few exceptions to the above rule. For instance routines
76 -- such as Apply_Scalar_Range_Check that do not insert any code can be
77 -- safely called even when the Expander is inactive (but Errors_Detected
78 -- is 0). The benefit of executing this code when expansion is off, is
79 -- the ability to emit constraint error warning for static expressions
80 -- even when we are not generating code.
82 -------------------------------------
83 -- Suppression of Redundant Checks --
84 -------------------------------------
86 -- This unit implements a limited circuit for removal of redundant
87 -- checks. The processing is based on a tracing of simple sequential
88 -- flow. For any sequence of statements, we save expressions that are
89 -- marked to be checked, and then if the same expression appears later
90 -- with the same check, then under certain circumstances, the second
91 -- check can be suppressed.
93 -- Basically, we can suppress the check if we know for certain that
94 -- the previous expression has been elaborated (together with its
95 -- check), and we know that the exception frame is the same, and that
96 -- nothing has happened to change the result of the exception.
98 -- Let us examine each of these three conditions in turn to describe
99 -- how we ensure that this condition is met.
101 -- First, we need to know for certain that the previous expression has
102 -- been executed. This is done principly by the mechanism of calling
103 -- Conditional_Statements_Begin at the start of any statement sequence
104 -- and Conditional_Statements_End at the end. The End call causes all
105 -- checks remembered since the Begin call to be discarded. This does
106 -- miss a few cases, notably the case of a nested BEGIN-END block with
107 -- no exception handlers. But the important thing is to be conservative.
108 -- The other protection is that all checks are discarded if a label
109 -- is encountered, since then the assumption of sequential execution
110 -- is violated, and we don't know enough about the flow.
112 -- Second, we need to know that the exception frame is the same. We
113 -- do this by killing all remembered checks when we enter a new frame.
114 -- Again, that's over-conservative, but generally the cases we can help
115 -- with are pretty local anyway (like the body of a loop for example).
117 -- Third, we must be sure to forget any checks which are no longer valid.
118 -- This is done by two mechanisms, first the Kill_Checks_Variable call is
119 -- used to note any changes to local variables. We only attempt to deal
120 -- with checks involving local variables, so we do not need to worry
121 -- about global variables. Second, a call to any non-global procedure
122 -- causes us to abandon all stored checks, since such a all may affect
123 -- the values of any local variables.
125 -- The following define the data structures used to deal with remembering
126 -- checks so that redundant checks can be eliminated as described above.
128 -- Right now, the only expressions that we deal with are of the form of
129 -- simple local objects (either declared locally, or IN parameters) or
130 -- such objects plus/minus a compile time known constant. We can do
131 -- more later on if it seems worthwhile, but this catches many simple
132 -- cases in practice.
134 -- The following record type reflects a single saved check. An entry
135 -- is made in the stack of saved checks if and only if the expression
136 -- has been elaborated with the indicated checks.
138 type Saved_Check is record
139 Killed : Boolean;
140 -- Set True if entry is killed by Kill_Checks
142 Entity : Entity_Id;
143 -- The entity involved in the expression that is checked
145 Offset : Uint;
146 -- A compile time value indicating the result of adding or
147 -- subtracting a compile time value. This value is to be
148 -- added to the value of the Entity. A value of zero is
149 -- used for the case of a simple entity reference.
151 Check_Type : Character;
152 -- This is set to 'R' for a range check (in which case Target_Type
153 -- is set to the target type for the range check) or to 'O' for an
154 -- overflow check (in which case Target_Type is set to Empty).
156 Target_Type : Entity_Id;
157 -- Used only if Do_Range_Check is set. Records the target type for
158 -- the check. We need this, because a check is a duplicate only if
159 -- it has a the same target type (or more accurately one with a
160 -- range that is smaller or equal to the stored target type of a
161 -- saved check).
162 end record;
164 -- The following table keeps track of saved checks. Rather than use an
165 -- extensible table. We just use a table of fixed size, and we discard
166 -- any saved checks that do not fit. That's very unlikely to happen and
167 -- this is only an optimization in any case.
169 Saved_Checks : array (Int range 1 .. 200) of Saved_Check;
170 -- Array of saved checks
172 Num_Saved_Checks : Nat := 0;
173 -- Number of saved checks
175 -- The following stack keeps track of statement ranges. It is treated
176 -- as a stack. When Conditional_Statements_Begin is called, an entry
177 -- is pushed onto this stack containing the value of Num_Saved_Checks
178 -- at the time of the call. Then when Conditional_Statements_End is
179 -- called, this value is popped off and used to reset Num_Saved_Checks.
181 -- Note: again, this is a fixed length stack with a size that should
182 -- always be fine. If the value of the stack pointer goes above the
183 -- limit, then we just forget all saved checks.
185 Saved_Checks_Stack : array (Int range 1 .. 100) of Nat;
186 Saved_Checks_TOS : Nat := 0;
188 -----------------------
189 -- Local Subprograms --
190 -----------------------
192 procedure Apply_Float_Conversion_Check
193 (Ck_Node : Node_Id;
194 Target_Typ : Entity_Id);
195 -- The checks on a conversion from a floating-point type to an integer
196 -- type are delicate. They have to be performed before conversion, they
197 -- have to raise an exception when the operand is a NaN, and rounding must
198 -- be taken into account to determine the safe bounds of the operand.
200 procedure Apply_Selected_Length_Checks
201 (Ck_Node : Node_Id;
202 Target_Typ : Entity_Id;
203 Source_Typ : Entity_Id;
204 Do_Static : Boolean);
205 -- This is the subprogram that does all the work for Apply_Length_Check
206 -- and Apply_Static_Length_Check. Expr, Target_Typ and Source_Typ are as
207 -- described for the above routines. The Do_Static flag indicates that
208 -- only a static check is to be done.
210 procedure Apply_Selected_Range_Checks
211 (Ck_Node : Node_Id;
212 Target_Typ : Entity_Id;
213 Source_Typ : Entity_Id;
214 Do_Static : Boolean);
215 -- This is the subprogram that does all the work for Apply_Range_Check.
216 -- Expr, Target_Typ and Source_Typ are as described for the above
217 -- routine. The Do_Static flag indicates that only a static check is
218 -- to be done.
220 procedure Find_Check
221 (Expr : Node_Id;
222 Check_Type : Character;
223 Target_Type : Entity_Id;
224 Entry_OK : out Boolean;
225 Check_Num : out Nat;
226 Ent : out Entity_Id;
227 Ofs : out Uint);
228 -- This routine is used by Enable_Range_Check and Enable_Overflow_Check
229 -- to see if a check is of the form for optimization, and if so, to see
230 -- if it has already been performed. Expr is the expression to check,
231 -- and Check_Type is 'R' for a range check, 'O' for an overflow check.
232 -- Target_Type is the target type for a range check, and Empty for an
233 -- overflow check. If the entry is not of the form for optimization,
234 -- then Entry_OK is set to False, and the remaining out parameters
235 -- are undefined. If the entry is OK, then Ent/Ofs are set to the
236 -- entity and offset from the expression. Check_Num is the number of
237 -- a matching saved entry in Saved_Checks, or zero if no such entry
238 -- is located.
240 function Get_Discriminal (E : Entity_Id; Bound : Node_Id) return Node_Id;
241 -- If a discriminal is used in constraining a prival, Return reference
242 -- to the discriminal of the protected body (which renames the parameter
243 -- of the enclosing protected operation). This clumsy transformation is
244 -- needed because privals are created too late and their actual subtypes
245 -- are not available when analysing the bodies of the protected operations.
246 -- To be cleaned up???
248 function Guard_Access
249 (Cond : Node_Id;
250 Loc : Source_Ptr;
251 Ck_Node : Node_Id) return Node_Id;
252 -- In the access type case, guard the test with a test to ensure
253 -- that the access value is non-null, since the checks do not
254 -- not apply to null access values.
256 procedure Install_Null_Excluding_Check (N : Node_Id);
257 -- Determines whether an access node requires a runtime access check and
258 -- if so inserts the appropriate run-time check
260 procedure Install_Static_Check (R_Cno : Node_Id; Loc : Source_Ptr);
261 -- Called by Apply_{Length,Range}_Checks to rewrite the tree with the
262 -- Constraint_Error node.
264 function Selected_Length_Checks
265 (Ck_Node : Node_Id;
266 Target_Typ : Entity_Id;
267 Source_Typ : Entity_Id;
268 Warn_Node : Node_Id) return Check_Result;
269 -- Like Apply_Selected_Length_Checks, except it doesn't modify
270 -- anything, just returns a list of nodes as described in the spec of
271 -- this package for the Range_Check function.
273 function Selected_Range_Checks
274 (Ck_Node : Node_Id;
275 Target_Typ : Entity_Id;
276 Source_Typ : Entity_Id;
277 Warn_Node : Node_Id) return Check_Result;
278 -- Like Apply_Selected_Range_Checks, except it doesn't modify anything,
279 -- just returns a list of nodes as described in the spec of this package
280 -- for the Range_Check function.
282 ------------------------------
283 -- Access_Checks_Suppressed --
284 ------------------------------
286 function Access_Checks_Suppressed (E : Entity_Id) return Boolean is
287 begin
288 if Present (E) and then Checks_May_Be_Suppressed (E) then
289 return Is_Check_Suppressed (E, Access_Check);
290 else
291 return Scope_Suppress (Access_Check);
292 end if;
293 end Access_Checks_Suppressed;
295 -------------------------------------
296 -- Accessibility_Checks_Suppressed --
297 -------------------------------------
299 function Accessibility_Checks_Suppressed (E : Entity_Id) return Boolean is
300 begin
301 if Present (E) and then Checks_May_Be_Suppressed (E) then
302 return Is_Check_Suppressed (E, Accessibility_Check);
303 else
304 return Scope_Suppress (Accessibility_Check);
305 end if;
306 end Accessibility_Checks_Suppressed;
308 -------------------------
309 -- Append_Range_Checks --
310 -------------------------
312 procedure Append_Range_Checks
313 (Checks : Check_Result;
314 Stmts : List_Id;
315 Suppress_Typ : Entity_Id;
316 Static_Sloc : Source_Ptr;
317 Flag_Node : Node_Id)
319 Internal_Flag_Node : constant Node_Id := Flag_Node;
320 Internal_Static_Sloc : constant Source_Ptr := Static_Sloc;
322 Checks_On : constant Boolean :=
323 (not Index_Checks_Suppressed (Suppress_Typ))
324 or else
325 (not Range_Checks_Suppressed (Suppress_Typ));
327 begin
328 -- For now we just return if Checks_On is false, however this should
329 -- be enhanced to check for an always True value in the condition
330 -- and to generate a compilation warning???
332 if not Checks_On then
333 return;
334 end if;
336 for J in 1 .. 2 loop
337 exit when No (Checks (J));
339 if Nkind (Checks (J)) = N_Raise_Constraint_Error
340 and then Present (Condition (Checks (J)))
341 then
342 if not Has_Dynamic_Range_Check (Internal_Flag_Node) then
343 Append_To (Stmts, Checks (J));
344 Set_Has_Dynamic_Range_Check (Internal_Flag_Node);
345 end if;
347 else
348 Append_To
349 (Stmts,
350 Make_Raise_Constraint_Error (Internal_Static_Sloc,
351 Reason => CE_Range_Check_Failed));
352 end if;
353 end loop;
354 end Append_Range_Checks;
356 ------------------------
357 -- Apply_Access_Check --
358 ------------------------
360 procedure Apply_Access_Check (N : Node_Id) is
361 P : constant Node_Id := Prefix (N);
363 begin
364 if Inside_A_Generic then
365 return;
366 end if;
368 if Is_Entity_Name (P) then
369 Check_Unset_Reference (P);
370 end if;
372 -- We do not need access checks if prefix is known to be non-null
374 if Known_Non_Null (P) then
375 return;
377 -- We do not need access checks if they are suppressed on the type
379 elsif Access_Checks_Suppressed (Etype (P)) then
380 return;
382 -- We do not need checks if we are not generating code (i.e. the
383 -- expander is not active). This is not just an optimization, there
384 -- are cases (e.g. with pragma Debug) where generating the checks
385 -- can cause real trouble).
387 elsif not Expander_Active then
388 return;
389 end if;
391 -- Case where P is an entity name
393 if Is_Entity_Name (P) then
394 declare
395 Ent : constant Entity_Id := Entity (P);
397 begin
398 if Access_Checks_Suppressed (Ent) then
399 return;
400 end if;
402 -- Otherwise we are going to generate an access check, and
403 -- are we have done it, the entity will now be known non null
404 -- But we have to check for safe sequential semantics here!
406 if Safe_To_Capture_Value (N, Ent) then
407 Set_Is_Known_Non_Null (Ent);
408 end if;
409 end;
410 end if;
412 -- Access check is required
414 Install_Null_Excluding_Check (P);
415 end Apply_Access_Check;
417 -------------------------------
418 -- Apply_Accessibility_Check --
419 -------------------------------
421 procedure Apply_Accessibility_Check (N : Node_Id; Typ : Entity_Id) is
422 Loc : constant Source_Ptr := Sloc (N);
423 Param_Ent : constant Entity_Id := Param_Entity (N);
424 Param_Level : Node_Id;
425 Type_Level : Node_Id;
427 begin
428 if Inside_A_Generic then
429 return;
431 -- Only apply the run-time check if the access parameter
432 -- has an associated extra access level parameter and
433 -- when the level of the type is less deep than the level
434 -- of the access parameter.
436 elsif Present (Param_Ent)
437 and then Present (Extra_Accessibility (Param_Ent))
438 and then UI_Gt (Object_Access_Level (N),
439 Type_Access_Level (Typ))
440 and then not Accessibility_Checks_Suppressed (Param_Ent)
441 and then not Accessibility_Checks_Suppressed (Typ)
442 then
443 Param_Level :=
444 New_Occurrence_Of (Extra_Accessibility (Param_Ent), Loc);
446 Type_Level :=
447 Make_Integer_Literal (Loc, Type_Access_Level (Typ));
449 -- Raise Program_Error if the accessibility level of the
450 -- the access parameter is deeper than the level of the
451 -- target access type.
453 Insert_Action (N,
454 Make_Raise_Program_Error (Loc,
455 Condition =>
456 Make_Op_Gt (Loc,
457 Left_Opnd => Param_Level,
458 Right_Opnd => Type_Level),
459 Reason => PE_Accessibility_Check_Failed));
461 Analyze_And_Resolve (N);
462 end if;
463 end Apply_Accessibility_Check;
465 ---------------------------
466 -- Apply_Alignment_Check --
467 ---------------------------
469 procedure Apply_Alignment_Check (E : Entity_Id; N : Node_Id) is
470 AC : constant Node_Id := Address_Clause (E);
471 Typ : constant Entity_Id := Etype (E);
472 Expr : Node_Id;
473 Loc : Source_Ptr;
475 Alignment_Required : constant Boolean := Maximum_Alignment > 1;
476 -- Constant to show whether target requires alignment checks
478 begin
479 -- See if check needed. Note that we never need a check if the
480 -- maximum alignment is one, since the check will always succeed
482 if No (AC)
483 or else not Check_Address_Alignment (AC)
484 or else not Alignment_Required
485 then
486 return;
487 end if;
489 Loc := Sloc (AC);
490 Expr := Expression (AC);
492 if Nkind (Expr) = N_Unchecked_Type_Conversion then
493 Expr := Expression (Expr);
495 elsif Nkind (Expr) = N_Function_Call
496 and then Is_Entity_Name (Name (Expr))
497 and then Is_RTE (Entity (Name (Expr)), RE_To_Address)
498 then
499 Expr := First (Parameter_Associations (Expr));
501 if Nkind (Expr) = N_Parameter_Association then
502 Expr := Explicit_Actual_Parameter (Expr);
503 end if;
504 end if;
506 -- Here Expr is the address value. See if we know that the
507 -- value is unacceptable at compile time.
509 if Compile_Time_Known_Value (Expr)
510 and then (Known_Alignment (E) or else Known_Alignment (Typ))
511 then
512 declare
513 AL : Uint := Alignment (Typ);
515 begin
516 -- The object alignment might be more restrictive than the
517 -- type alignment.
519 if Known_Alignment (E) then
520 AL := Alignment (E);
521 end if;
523 if Expr_Value (Expr) mod AL /= 0 then
524 Insert_Action (N,
525 Make_Raise_Program_Error (Loc,
526 Reason => PE_Misaligned_Address_Value));
527 Error_Msg_NE
528 ("?specified address for& not " &
529 "consistent with alignment ('R'M 13.3(27))", Expr, E);
530 end if;
531 end;
533 -- Here we do not know if the value is acceptable, generate
534 -- code to raise PE if alignment is inappropriate.
536 else
537 -- Skip generation of this code if we don't want elab code
539 if not Restriction_Active (No_Elaboration_Code) then
540 Insert_After_And_Analyze (N,
541 Make_Raise_Program_Error (Loc,
542 Condition =>
543 Make_Op_Ne (Loc,
544 Left_Opnd =>
545 Make_Op_Mod (Loc,
546 Left_Opnd =>
547 Unchecked_Convert_To
548 (RTE (RE_Integer_Address),
549 Duplicate_Subexpr_No_Checks (Expr)),
550 Right_Opnd =>
551 Make_Attribute_Reference (Loc,
552 Prefix => New_Occurrence_Of (E, Loc),
553 Attribute_Name => Name_Alignment)),
554 Right_Opnd => Make_Integer_Literal (Loc, Uint_0)),
555 Reason => PE_Misaligned_Address_Value),
556 Suppress => All_Checks);
557 end if;
558 end if;
560 return;
562 exception
563 when RE_Not_Available =>
564 return;
565 end Apply_Alignment_Check;
567 -------------------------------------
568 -- Apply_Arithmetic_Overflow_Check --
569 -------------------------------------
571 -- This routine is called only if the type is an integer type, and
572 -- a software arithmetic overflow check must be performed for op
573 -- (add, subtract, multiply). The check is performed only if
574 -- Software_Overflow_Checking is enabled and Do_Overflow_Check
575 -- is set. In this case we expand the operation into a more complex
576 -- sequence of tests that ensures that overflow is properly caught.
578 procedure Apply_Arithmetic_Overflow_Check (N : Node_Id) is
579 Loc : constant Source_Ptr := Sloc (N);
580 Typ : constant Entity_Id := Etype (N);
581 Rtyp : constant Entity_Id := Root_Type (Typ);
582 Siz : constant Int := UI_To_Int (Esize (Rtyp));
583 Dsiz : constant Int := Siz * 2;
584 Opnod : Node_Id;
585 Ctyp : Entity_Id;
586 Opnd : Node_Id;
587 Cent : RE_Id;
589 begin
590 -- Skip this if overflow checks are done in back end, or the overflow
591 -- flag is not set anyway, or we are not doing code expansion.
593 if Backend_Overflow_Checks_On_Target
594 or else not Do_Overflow_Check (N)
595 or else not Expander_Active
596 then
597 return;
598 end if;
600 -- Otherwise, we generate the full general code for front end overflow
601 -- detection, which works by doing arithmetic in a larger type:
603 -- x op y
605 -- is expanded into
607 -- Typ (Checktyp (x) op Checktyp (y));
609 -- where Typ is the type of the original expression, and Checktyp is
610 -- an integer type of sufficient length to hold the largest possible
611 -- result.
613 -- In the case where check type exceeds the size of Long_Long_Integer,
614 -- we use a different approach, expanding to:
616 -- typ (xxx_With_Ovflo_Check (Integer_64 (x), Integer (y)))
618 -- where xxx is Add, Multiply or Subtract as appropriate
620 -- Find check type if one exists
622 if Dsiz <= Standard_Integer_Size then
623 Ctyp := Standard_Integer;
625 elsif Dsiz <= Standard_Long_Long_Integer_Size then
626 Ctyp := Standard_Long_Long_Integer;
628 -- No check type exists, use runtime call
630 else
631 if Nkind (N) = N_Op_Add then
632 Cent := RE_Add_With_Ovflo_Check;
634 elsif Nkind (N) = N_Op_Multiply then
635 Cent := RE_Multiply_With_Ovflo_Check;
637 else
638 pragma Assert (Nkind (N) = N_Op_Subtract);
639 Cent := RE_Subtract_With_Ovflo_Check;
640 end if;
642 Rewrite (N,
643 OK_Convert_To (Typ,
644 Make_Function_Call (Loc,
645 Name => New_Reference_To (RTE (Cent), Loc),
646 Parameter_Associations => New_List (
647 OK_Convert_To (RTE (RE_Integer_64), Left_Opnd (N)),
648 OK_Convert_To (RTE (RE_Integer_64), Right_Opnd (N))))));
650 Analyze_And_Resolve (N, Typ);
651 return;
652 end if;
654 -- If we fall through, we have the case where we do the arithmetic in
655 -- the next higher type and get the check by conversion. In these cases
656 -- Ctyp is set to the type to be used as the check type.
658 Opnod := Relocate_Node (N);
660 Opnd := OK_Convert_To (Ctyp, Left_Opnd (Opnod));
662 Analyze (Opnd);
663 Set_Etype (Opnd, Ctyp);
664 Set_Analyzed (Opnd, True);
665 Set_Left_Opnd (Opnod, Opnd);
667 Opnd := OK_Convert_To (Ctyp, Right_Opnd (Opnod));
669 Analyze (Opnd);
670 Set_Etype (Opnd, Ctyp);
671 Set_Analyzed (Opnd, True);
672 Set_Right_Opnd (Opnod, Opnd);
674 -- The type of the operation changes to the base type of the check
675 -- type, and we reset the overflow check indication, since clearly
676 -- no overflow is possible now that we are using a double length
677 -- type. We also set the Analyzed flag to avoid a recursive attempt
678 -- to expand the node.
680 Set_Etype (Opnod, Base_Type (Ctyp));
681 Set_Do_Overflow_Check (Opnod, False);
682 Set_Analyzed (Opnod, True);
684 -- Now build the outer conversion
686 Opnd := OK_Convert_To (Typ, Opnod);
687 Analyze (Opnd);
688 Set_Etype (Opnd, Typ);
690 -- In the discrete type case, we directly generate the range check
691 -- for the outer operand. This range check will implement the required
692 -- overflow check.
694 if Is_Discrete_Type (Typ) then
695 Rewrite (N, Opnd);
696 Generate_Range_Check (Expression (N), Typ, CE_Overflow_Check_Failed);
698 -- For other types, we enable overflow checking on the conversion,
699 -- after setting the node as analyzed to prevent recursive attempts
700 -- to expand the conversion node.
702 else
703 Set_Analyzed (Opnd, True);
704 Enable_Overflow_Check (Opnd);
705 Rewrite (N, Opnd);
706 end if;
708 exception
709 when RE_Not_Available =>
710 return;
711 end Apply_Arithmetic_Overflow_Check;
713 ----------------------------
714 -- Apply_Array_Size_Check --
715 ----------------------------
717 -- The situation is as follows. In GNAT 3 (GCC 2.x), the size in bits
718 -- is computed in 32 bits without an overflow check. That's a real
719 -- problem for Ada. So what we do in GNAT 3 is to approximate the
720 -- size of an array by manually multiplying the element size by the
721 -- number of elements, and comparing that against the allowed limits.
723 -- In GNAT 5, the size in byte is still computed in 32 bits without
724 -- an overflow check in the dynamic case, but the size in bits is
725 -- computed in 64 bits. We assume that's good enough, and we do not
726 -- bother to generate any front end test.
728 procedure Apply_Array_Size_Check (N : Node_Id; Typ : Entity_Id) is
729 Loc : constant Source_Ptr := Sloc (N);
730 Ctyp : constant Entity_Id := Component_Type (Typ);
731 Ent : constant Entity_Id := Defining_Identifier (N);
732 Decl : Node_Id;
733 Lo : Node_Id;
734 Hi : Node_Id;
735 Lob : Uint;
736 Hib : Uint;
737 Siz : Uint;
738 Xtyp : Entity_Id;
739 Indx : Node_Id;
740 Sizx : Node_Id;
741 Code : Node_Id;
743 Static : Boolean := True;
744 -- Set false if any index subtye bound is non-static
746 Umark : constant Uintp.Save_Mark := Uintp.Mark;
747 -- We can throw away all the Uint computations here, since they are
748 -- done only to generate boolean test results.
750 Check_Siz : Uint;
751 -- Size to check against
753 function Is_Address_Or_Import (Decl : Node_Id) return Boolean;
754 -- Determines if Decl is an address clause or Import/Interface pragma
755 -- that references the defining identifier of the current declaration.
757 --------------------------
758 -- Is_Address_Or_Import --
759 --------------------------
761 function Is_Address_Or_Import (Decl : Node_Id) return Boolean is
762 begin
763 if Nkind (Decl) = N_At_Clause then
764 return Chars (Identifier (Decl)) = Chars (Ent);
766 elsif Nkind (Decl) = N_Attribute_Definition_Clause then
767 return
768 Chars (Decl) = Name_Address
769 and then
770 Nkind (Name (Decl)) = N_Identifier
771 and then
772 Chars (Name (Decl)) = Chars (Ent);
774 elsif Nkind (Decl) = N_Pragma then
775 if (Chars (Decl) = Name_Import
776 or else
777 Chars (Decl) = Name_Interface)
778 and then Present (Pragma_Argument_Associations (Decl))
779 then
780 declare
781 F : constant Node_Id :=
782 First (Pragma_Argument_Associations (Decl));
784 begin
785 return
786 Present (F)
787 and then
788 Present (Next (F))
789 and then
790 Nkind (Expression (Next (F))) = N_Identifier
791 and then
792 Chars (Expression (Next (F))) = Chars (Ent);
793 end;
795 else
796 return False;
797 end if;
799 else
800 return False;
801 end if;
802 end Is_Address_Or_Import;
804 -- Start of processing for Apply_Array_Size_Check
806 begin
807 -- Do size check on local arrays. We only need this in the GCC 2
808 -- case, since in GCC 3, we expect the back end to properly handle
809 -- things. This routine can be removed when we baseline GNAT 3.
811 if Opt.GCC_Version >= 3 then
812 return;
813 end if;
815 -- No need for a check if not expanding
817 if not Expander_Active then
818 return;
819 end if;
821 -- No need for a check if checks are suppressed
823 if Storage_Checks_Suppressed (Typ) then
824 return;
825 end if;
827 -- It is pointless to insert this check inside an init proc, because
828 -- that's too late, we have already built the object to be the right
829 -- size, and if it's too large, too bad!
831 if Inside_Init_Proc then
832 return;
833 end if;
835 -- Look head for pragma interface/import or address clause applying
836 -- to this entity. If found, we suppress the check entirely. For now
837 -- we only look ahead 20 declarations to stop this becoming too slow
838 -- Note that eventually this whole routine gets moved to gigi.
840 Decl := N;
841 for Ctr in 1 .. 20 loop
842 Next (Decl);
843 exit when No (Decl);
845 if Is_Address_Or_Import (Decl) then
846 return;
847 end if;
848 end loop;
850 -- First step is to calculate the maximum number of elements. For
851 -- this calculation, we use the actual size of the subtype if it is
852 -- static, and if a bound of a subtype is non-static, we go to the
853 -- bound of the base type.
855 Siz := Uint_1;
856 Indx := First_Index (Typ);
857 while Present (Indx) loop
858 Xtyp := Etype (Indx);
859 Lo := Type_Low_Bound (Xtyp);
860 Hi := Type_High_Bound (Xtyp);
862 -- If any bound raises constraint error, we will never get this
863 -- far, so there is no need to generate any kind of check.
865 if Raises_Constraint_Error (Lo)
866 or else
867 Raises_Constraint_Error (Hi)
868 then
869 Uintp.Release (Umark);
870 return;
871 end if;
873 -- Otherwise get bounds values
875 if Is_Static_Expression (Lo) then
876 Lob := Expr_Value (Lo);
877 else
878 Lob := Expr_Value (Type_Low_Bound (Base_Type (Xtyp)));
879 Static := False;
880 end if;
882 if Is_Static_Expression (Hi) then
883 Hib := Expr_Value (Hi);
884 else
885 Hib := Expr_Value (Type_High_Bound (Base_Type (Xtyp)));
886 Static := False;
887 end if;
889 Siz := Siz * UI_Max (Hib - Lob + 1, Uint_0);
890 Next_Index (Indx);
891 end loop;
893 -- Compute the limit against which we want to check. For subprograms,
894 -- where the array will go on the stack, we use 8*2**24, which (in
895 -- bits) is the size of a 16 megabyte array.
897 if Is_Subprogram (Scope (Ent)) then
898 Check_Siz := Uint_2 ** 27;
899 else
900 Check_Siz := Uint_2 ** 31;
901 end if;
903 -- If we have all static bounds and Siz is too large, then we know
904 -- we know we have a storage error right now, so generate message
906 if Static and then Siz >= Check_Siz then
907 Insert_Action (N,
908 Make_Raise_Storage_Error (Loc,
909 Reason => SE_Object_Too_Large));
910 Error_Msg_N ("?Storage_Error will be raised at run-time", N);
911 Uintp.Release (Umark);
912 return;
913 end if;
915 -- Case of component size known at compile time. If the array
916 -- size is definitely in range, then we do not need a check.
918 if Known_Esize (Ctyp)
919 and then Siz * Esize (Ctyp) < Check_Siz
920 then
921 Uintp.Release (Umark);
922 return;
923 end if;
925 -- Here if a dynamic check is required
927 -- What we do is to build an expression for the size of the array,
928 -- which is computed as the 'Size of the array component, times
929 -- the size of each dimension.
931 Uintp.Release (Umark);
933 Sizx :=
934 Make_Attribute_Reference (Loc,
935 Prefix => New_Occurrence_Of (Ctyp, Loc),
936 Attribute_Name => Name_Size);
938 Indx := First_Index (Typ);
939 for J in 1 .. Number_Dimensions (Typ) loop
940 if Sloc (Etype (Indx)) = Sloc (N) then
941 Ensure_Defined (Etype (Indx), N);
942 end if;
944 Sizx :=
945 Make_Op_Multiply (Loc,
946 Left_Opnd => Sizx,
947 Right_Opnd =>
948 Make_Attribute_Reference (Loc,
949 Prefix => New_Occurrence_Of (Typ, Loc),
950 Attribute_Name => Name_Length,
951 Expressions => New_List (
952 Make_Integer_Literal (Loc, J))));
953 Next_Index (Indx);
954 end loop;
956 -- Emit the check
958 Code :=
959 Make_Raise_Storage_Error (Loc,
960 Condition =>
961 Make_Op_Ge (Loc,
962 Left_Opnd => Sizx,
963 Right_Opnd =>
964 Make_Integer_Literal (Loc,
965 Intval => Check_Siz)),
966 Reason => SE_Object_Too_Large);
968 Set_Size_Check_Code (Defining_Identifier (N), Code);
969 Insert_Action (N, Code, Suppress => All_Checks);
970 end Apply_Array_Size_Check;
972 ----------------------------
973 -- Apply_Constraint_Check --
974 ----------------------------
976 procedure Apply_Constraint_Check
977 (N : Node_Id;
978 Typ : Entity_Id;
979 No_Sliding : Boolean := False)
981 Desig_Typ : Entity_Id;
983 begin
984 if Inside_A_Generic then
985 return;
987 elsif Is_Scalar_Type (Typ) then
988 Apply_Scalar_Range_Check (N, Typ);
990 elsif Is_Array_Type (Typ) then
992 -- A useful optimization: an aggregate with only an Others clause
993 -- always has the right bounds.
995 if Nkind (N) = N_Aggregate
996 and then No (Expressions (N))
997 and then Nkind
998 (First (Choices (First (Component_Associations (N)))))
999 = N_Others_Choice
1000 then
1001 return;
1002 end if;
1004 if Is_Constrained (Typ) then
1005 Apply_Length_Check (N, Typ);
1007 if No_Sliding then
1008 Apply_Range_Check (N, Typ);
1009 end if;
1010 else
1011 Apply_Range_Check (N, Typ);
1012 end if;
1014 elsif (Is_Record_Type (Typ)
1015 or else Is_Private_Type (Typ))
1016 and then Has_Discriminants (Base_Type (Typ))
1017 and then Is_Constrained (Typ)
1018 then
1019 Apply_Discriminant_Check (N, Typ);
1021 elsif Is_Access_Type (Typ) then
1023 Desig_Typ := Designated_Type (Typ);
1025 -- No checks necessary if expression statically null
1027 if Nkind (N) = N_Null then
1028 null;
1030 -- No sliding possible on access to arrays
1032 elsif Is_Array_Type (Desig_Typ) then
1033 if Is_Constrained (Desig_Typ) then
1034 Apply_Length_Check (N, Typ);
1035 end if;
1037 Apply_Range_Check (N, Typ);
1039 elsif Has_Discriminants (Base_Type (Desig_Typ))
1040 and then Is_Constrained (Desig_Typ)
1041 then
1042 Apply_Discriminant_Check (N, Typ);
1043 end if;
1045 if Can_Never_Be_Null (Typ)
1046 and then not Can_Never_Be_Null (Etype (N))
1047 then
1048 Install_Null_Excluding_Check (N);
1049 end if;
1050 end if;
1051 end Apply_Constraint_Check;
1053 ------------------------------
1054 -- Apply_Discriminant_Check --
1055 ------------------------------
1057 procedure Apply_Discriminant_Check
1058 (N : Node_Id;
1059 Typ : Entity_Id;
1060 Lhs : Node_Id := Empty)
1062 Loc : constant Source_Ptr := Sloc (N);
1063 Do_Access : constant Boolean := Is_Access_Type (Typ);
1064 S_Typ : Entity_Id := Etype (N);
1065 Cond : Node_Id;
1066 T_Typ : Entity_Id;
1068 function Is_Aliased_Unconstrained_Component return Boolean;
1069 -- It is possible for an aliased component to have a nominal
1070 -- unconstrained subtype (through instantiation). If this is a
1071 -- discriminated component assigned in the expansion of an aggregate
1072 -- in an initialization, the check must be suppressed. This unusual
1073 -- situation requires a predicate of its own (see 7503-008).
1075 ----------------------------------------
1076 -- Is_Aliased_Unconstrained_Component --
1077 ----------------------------------------
1079 function Is_Aliased_Unconstrained_Component return Boolean is
1080 Comp : Entity_Id;
1081 Pref : Node_Id;
1083 begin
1084 if Nkind (Lhs) /= N_Selected_Component then
1085 return False;
1086 else
1087 Comp := Entity (Selector_Name (Lhs));
1088 Pref := Prefix (Lhs);
1089 end if;
1091 if Ekind (Comp) /= E_Component
1092 or else not Is_Aliased (Comp)
1093 then
1094 return False;
1095 end if;
1097 return not Comes_From_Source (Pref)
1098 and then In_Instance
1099 and then not Is_Constrained (Etype (Comp));
1100 end Is_Aliased_Unconstrained_Component;
1102 -- Start of processing for Apply_Discriminant_Check
1104 begin
1105 if Do_Access then
1106 T_Typ := Designated_Type (Typ);
1107 else
1108 T_Typ := Typ;
1109 end if;
1111 -- Nothing to do if discriminant checks are suppressed or else no code
1112 -- is to be generated
1114 if not Expander_Active
1115 or else Discriminant_Checks_Suppressed (T_Typ)
1116 then
1117 return;
1118 end if;
1120 -- No discriminant checks necessary for access when expression
1121 -- is statically Null. This is not only an optimization, this is
1122 -- fundamental because otherwise discriminant checks may be generated
1123 -- in init procs for types containing an access to a non-frozen yet
1124 -- record, causing a deadly forward reference.
1126 -- Also, if the expression is of an access type whose designated
1127 -- type is incomplete, then the access value must be null and
1128 -- we suppress the check.
1130 if Nkind (N) = N_Null then
1131 return;
1133 elsif Is_Access_Type (S_Typ) then
1134 S_Typ := Designated_Type (S_Typ);
1136 if Ekind (S_Typ) = E_Incomplete_Type then
1137 return;
1138 end if;
1139 end if;
1141 -- If an assignment target is present, then we need to generate
1142 -- the actual subtype if the target is a parameter or aliased
1143 -- object with an unconstrained nominal subtype.
1145 if Present (Lhs)
1146 and then (Present (Param_Entity (Lhs))
1147 or else (not Is_Constrained (T_Typ)
1148 and then Is_Aliased_View (Lhs)
1149 and then not Is_Aliased_Unconstrained_Component))
1150 then
1151 T_Typ := Get_Actual_Subtype (Lhs);
1152 end if;
1154 -- Nothing to do if the type is unconstrained (this is the case
1155 -- where the actual subtype in the RM sense of N is unconstrained
1156 -- and no check is required).
1158 if not Is_Constrained (T_Typ) then
1159 return;
1160 end if;
1162 -- Nothing to do if the type is an Unchecked_Union
1164 if Is_Unchecked_Union (Base_Type (T_Typ)) then
1165 return;
1166 end if;
1168 -- Suppress checks if the subtypes are the same.
1169 -- the check must be preserved in an assignment to a formal, because
1170 -- the constraint is given by the actual.
1172 if Nkind (Original_Node (N)) /= N_Allocator
1173 and then (No (Lhs)
1174 or else not Is_Entity_Name (Lhs)
1175 or else No (Param_Entity (Lhs)))
1176 then
1177 if (Etype (N) = Typ
1178 or else (Do_Access and then Designated_Type (Typ) = S_Typ))
1179 and then not Is_Aliased_View (Lhs)
1180 then
1181 return;
1182 end if;
1184 -- We can also eliminate checks on allocators with a subtype mark
1185 -- that coincides with the context type. The context type may be a
1186 -- subtype without a constraint (common case, a generic actual).
1188 elsif Nkind (Original_Node (N)) = N_Allocator
1189 and then Is_Entity_Name (Expression (Original_Node (N)))
1190 then
1191 declare
1192 Alloc_Typ : constant Entity_Id :=
1193 Entity (Expression (Original_Node (N)));
1195 begin
1196 if Alloc_Typ = T_Typ
1197 or else (Nkind (Parent (T_Typ)) = N_Subtype_Declaration
1198 and then Is_Entity_Name (
1199 Subtype_Indication (Parent (T_Typ)))
1200 and then Alloc_Typ = Base_Type (T_Typ))
1202 then
1203 return;
1204 end if;
1205 end;
1206 end if;
1208 -- See if we have a case where the types are both constrained, and
1209 -- all the constraints are constants. In this case, we can do the
1210 -- check successfully at compile time.
1212 -- We skip this check for the case where the node is a rewritten`
1213 -- allocator, because it already carries the context subtype, and
1214 -- extracting the discriminants from the aggregate is messy.
1216 if Is_Constrained (S_Typ)
1217 and then Nkind (Original_Node (N)) /= N_Allocator
1218 then
1219 declare
1220 DconT : Elmt_Id;
1221 Discr : Entity_Id;
1222 DconS : Elmt_Id;
1223 ItemS : Node_Id;
1224 ItemT : Node_Id;
1226 begin
1227 -- S_Typ may not have discriminants in the case where it is a
1228 -- private type completed by a default discriminated type. In
1229 -- that case, we need to get the constraints from the
1230 -- underlying_type. If the underlying type is unconstrained (i.e.
1231 -- has no default discriminants) no check is needed.
1233 if Has_Discriminants (S_Typ) then
1234 Discr := First_Discriminant (S_Typ);
1235 DconS := First_Elmt (Discriminant_Constraint (S_Typ));
1237 else
1238 Discr := First_Discriminant (Underlying_Type (S_Typ));
1239 DconS :=
1240 First_Elmt
1241 (Discriminant_Constraint (Underlying_Type (S_Typ)));
1243 if No (DconS) then
1244 return;
1245 end if;
1247 -- A further optimization: if T_Typ is derived from S_Typ
1248 -- without imposing a constraint, no check is needed.
1250 if Nkind (Original_Node (Parent (T_Typ))) =
1251 N_Full_Type_Declaration
1252 then
1253 declare
1254 Type_Def : constant Node_Id :=
1255 Type_Definition
1256 (Original_Node (Parent (T_Typ)));
1257 begin
1258 if Nkind (Type_Def) = N_Derived_Type_Definition
1259 and then Is_Entity_Name (Subtype_Indication (Type_Def))
1260 and then Entity (Subtype_Indication (Type_Def)) = S_Typ
1261 then
1262 return;
1263 end if;
1264 end;
1265 end if;
1266 end if;
1268 DconT := First_Elmt (Discriminant_Constraint (T_Typ));
1270 while Present (Discr) loop
1271 ItemS := Node (DconS);
1272 ItemT := Node (DconT);
1274 exit when
1275 not Is_OK_Static_Expression (ItemS)
1276 or else
1277 not Is_OK_Static_Expression (ItemT);
1279 if Expr_Value (ItemS) /= Expr_Value (ItemT) then
1280 if Do_Access then -- needs run-time check.
1281 exit;
1282 else
1283 Apply_Compile_Time_Constraint_Error
1284 (N, "incorrect value for discriminant&?",
1285 CE_Discriminant_Check_Failed, Ent => Discr);
1286 return;
1287 end if;
1288 end if;
1290 Next_Elmt (DconS);
1291 Next_Elmt (DconT);
1292 Next_Discriminant (Discr);
1293 end loop;
1295 if No (Discr) then
1296 return;
1297 end if;
1298 end;
1299 end if;
1301 -- Here we need a discriminant check. First build the expression
1302 -- for the comparisons of the discriminants:
1304 -- (n.disc1 /= typ.disc1) or else
1305 -- (n.disc2 /= typ.disc2) or else
1306 -- ...
1307 -- (n.discn /= typ.discn)
1309 Cond := Build_Discriminant_Checks (N, T_Typ);
1311 -- If Lhs is set and is a parameter, then the condition is
1312 -- guarded by: lhs'constrained and then (condition built above)
1314 if Present (Param_Entity (Lhs)) then
1315 Cond :=
1316 Make_And_Then (Loc,
1317 Left_Opnd =>
1318 Make_Attribute_Reference (Loc,
1319 Prefix => New_Occurrence_Of (Param_Entity (Lhs), Loc),
1320 Attribute_Name => Name_Constrained),
1321 Right_Opnd => Cond);
1322 end if;
1324 if Do_Access then
1325 Cond := Guard_Access (Cond, Loc, N);
1326 end if;
1328 Insert_Action (N,
1329 Make_Raise_Constraint_Error (Loc,
1330 Condition => Cond,
1331 Reason => CE_Discriminant_Check_Failed));
1332 end Apply_Discriminant_Check;
1334 ------------------------
1335 -- Apply_Divide_Check --
1336 ------------------------
1338 procedure Apply_Divide_Check (N : Node_Id) is
1339 Loc : constant Source_Ptr := Sloc (N);
1340 Typ : constant Entity_Id := Etype (N);
1341 Left : constant Node_Id := Left_Opnd (N);
1342 Right : constant Node_Id := Right_Opnd (N);
1344 LLB : Uint;
1345 Llo : Uint;
1346 Lhi : Uint;
1347 LOK : Boolean;
1348 Rlo : Uint;
1349 Rhi : Uint;
1350 ROK : Boolean;
1352 begin
1353 if Expander_Active
1354 and not Backend_Divide_Checks_On_Target
1355 then
1356 Determine_Range (Right, ROK, Rlo, Rhi);
1358 -- See if division by zero possible, and if so generate test. This
1359 -- part of the test is not controlled by the -gnato switch.
1361 if Do_Division_Check (N) then
1362 if (not ROK) or else (Rlo <= 0 and then 0 <= Rhi) then
1363 Insert_Action (N,
1364 Make_Raise_Constraint_Error (Loc,
1365 Condition =>
1366 Make_Op_Eq (Loc,
1367 Left_Opnd => Duplicate_Subexpr_Move_Checks (Right),
1368 Right_Opnd => Make_Integer_Literal (Loc, 0)),
1369 Reason => CE_Divide_By_Zero));
1370 end if;
1371 end if;
1373 -- Test for extremely annoying case of xxx'First divided by -1
1375 if Do_Overflow_Check (N) then
1377 if Nkind (N) = N_Op_Divide
1378 and then Is_Signed_Integer_Type (Typ)
1379 then
1380 Determine_Range (Left, LOK, Llo, Lhi);
1381 LLB := Expr_Value (Type_Low_Bound (Base_Type (Typ)));
1383 if ((not ROK) or else (Rlo <= (-1) and then (-1) <= Rhi))
1384 and then
1385 ((not LOK) or else (Llo = LLB))
1386 then
1387 Insert_Action (N,
1388 Make_Raise_Constraint_Error (Loc,
1389 Condition =>
1390 Make_And_Then (Loc,
1392 Make_Op_Eq (Loc,
1393 Left_Opnd =>
1394 Duplicate_Subexpr_Move_Checks (Left),
1395 Right_Opnd => Make_Integer_Literal (Loc, LLB)),
1397 Make_Op_Eq (Loc,
1398 Left_Opnd =>
1399 Duplicate_Subexpr (Right),
1400 Right_Opnd =>
1401 Make_Integer_Literal (Loc, -1))),
1402 Reason => CE_Overflow_Check_Failed));
1403 end if;
1404 end if;
1405 end if;
1406 end if;
1407 end Apply_Divide_Check;
1409 ----------------------------------
1410 -- Apply_Float_Conversion_Check --
1411 ----------------------------------
1413 -- Let F and I be the source and target types of the conversion.
1414 -- The Ada standard specifies that a floating-point value X is rounded
1415 -- to the nearest integer, with halfway cases being rounded away from
1416 -- zero. The rounded value of X is checked against I'Range.
1418 -- The catch in the above paragraph is that there is no good way
1419 -- to know whether the round-to-integer operation resulted in
1420 -- overflow. A remedy is to perform a range check in the floating-point
1421 -- domain instead, however:
1422 -- (1) The bounds may not be known at compile time
1423 -- (2) The check must take into account possible rounding.
1424 -- (3) The range of type I may not be exactly representable in F.
1425 -- (4) The end-points I'First - 0.5 and I'Last + 0.5 may or may
1426 -- not be in range, depending on the sign of I'First and I'Last.
1427 -- (5) X may be a NaN, which will fail any comparison
1429 -- The following steps take care of these issues converting X:
1430 -- (1) If either I'First or I'Last is not known at compile time, use
1431 -- I'Base instead of I in the next three steps and perform a
1432 -- regular range check against I'Range after conversion.
1433 -- (2) If I'First - 0.5 is representable in F then let Lo be that
1434 -- value and define Lo_OK as (I'First > 0). Otherwise, let Lo be
1435 -- F'Machine (T) and let Lo_OK be (Lo >= I'First). In other words,
1436 -- take one of the closest floating-point numbers to T, and see if
1437 -- it is in range or not.
1438 -- (3) If I'Last + 0.5 is representable in F then let Hi be that value
1439 -- and define Hi_OK as (I'Last < 0). Otherwise, let Hi be
1440 -- F'Rounding (T) and let Hi_OK be (Hi <= I'Last).
1441 -- (4) Raise CE when (Lo_OK and X < Lo) or (not Lo_OK and X <= Lo)
1442 -- or (Hi_OK and X > Hi) or (not Hi_OK and X >= Hi)
1444 procedure Apply_Float_Conversion_Check
1445 (Ck_Node : Node_Id;
1446 Target_Typ : Entity_Id)
1448 LB : constant Node_Id := Type_Low_Bound (Target_Typ);
1449 HB : constant Node_Id := Type_High_Bound (Target_Typ);
1450 Loc : constant Source_Ptr := Sloc (Ck_Node);
1451 Expr_Type : constant Entity_Id := Base_Type (Etype (Ck_Node));
1452 Target_Base : constant Entity_Id := Implementation_Base_Type
1453 (Target_Typ);
1454 Max_Bound : constant Uint := UI_Expon
1455 (Machine_Radix (Expr_Type),
1456 Machine_Mantissa (Expr_Type) - 1) - 1;
1457 -- Largest bound, so bound plus or minus half is a machine number of F
1459 Ifirst,
1460 Ilast : Uint; -- Bounds of integer type
1461 Lo, Hi : Ureal; -- Bounds to check in floating-point domain
1462 Lo_OK,
1463 Hi_OK : Boolean; -- True iff Lo resp. Hi belongs to I'Range
1465 Lo_Chk,
1466 Hi_Chk : Node_Id; -- Expressions that are False iff check fails
1468 Reason : RT_Exception_Code;
1470 begin
1471 if not Compile_Time_Known_Value (LB)
1472 or not Compile_Time_Known_Value (HB)
1473 then
1474 declare
1475 -- First check that the value falls in the range of the base
1476 -- type, to prevent overflow during conversion and then
1477 -- perform a regular range check against the (dynamic) bounds.
1479 Par : constant Node_Id := Parent (Ck_Node);
1481 pragma Assert (Target_Base /= Target_Typ);
1482 pragma Assert (Nkind (Par) = N_Type_Conversion);
1484 Temp : constant Entity_Id :=
1485 Make_Defining_Identifier (Loc,
1486 Chars => New_Internal_Name ('T'));
1488 begin
1489 Apply_Float_Conversion_Check (Ck_Node, Target_Base);
1490 Set_Etype (Temp, Target_Base);
1492 Insert_Action (Parent (Par),
1493 Make_Object_Declaration (Loc,
1494 Defining_Identifier => Temp,
1495 Object_Definition => New_Occurrence_Of (Target_Typ, Loc),
1496 Expression => New_Copy_Tree (Par)),
1497 Suppress => All_Checks);
1499 Insert_Action (Par,
1500 Make_Raise_Constraint_Error (Loc,
1501 Condition =>
1502 Make_Not_In (Loc,
1503 Left_Opnd => New_Occurrence_Of (Temp, Loc),
1504 Right_Opnd => New_Occurrence_Of (Target_Typ, Loc)),
1505 Reason => CE_Range_Check_Failed));
1506 Rewrite (Par, New_Occurrence_Of (Temp, Loc));
1508 return;
1509 end;
1510 end if;
1512 -- Get the bounds of the target type
1514 Ifirst := Expr_Value (LB);
1515 Ilast := Expr_Value (HB);
1517 -- Check against lower bound
1519 if abs (Ifirst) < Max_Bound then
1520 Lo := UR_From_Uint (Ifirst) - Ureal_Half;
1521 Lo_OK := (Ifirst > 0);
1522 else
1523 Lo := Machine (Expr_Type, UR_From_Uint (Ifirst), Round_Even, Ck_Node);
1524 Lo_OK := (Lo >= UR_From_Uint (Ifirst));
1525 end if;
1527 if Lo_OK then
1529 -- Lo_Chk := (X >= Lo)
1531 Lo_Chk := Make_Op_Ge (Loc,
1532 Left_Opnd => Duplicate_Subexpr_No_Checks (Ck_Node),
1533 Right_Opnd => Make_Real_Literal (Loc, Lo));
1535 else
1536 -- Lo_Chk := (X > Lo)
1538 Lo_Chk := Make_Op_Gt (Loc,
1539 Left_Opnd => Duplicate_Subexpr_No_Checks (Ck_Node),
1540 Right_Opnd => Make_Real_Literal (Loc, Lo));
1541 end if;
1543 -- Check against higher bound
1545 if abs (Ilast) < Max_Bound then
1546 Hi := UR_From_Uint (Ilast) + Ureal_Half;
1547 Hi_OK := (Ilast < 0);
1548 else
1549 Hi := Machine (Expr_Type, UR_From_Uint (Ilast), Round_Even, Ck_Node);
1550 Hi_OK := (Hi <= UR_From_Uint (Ilast));
1551 end if;
1553 if Hi_OK then
1555 -- Hi_Chk := (X <= Hi)
1557 Hi_Chk := Make_Op_Le (Loc,
1558 Left_Opnd => Duplicate_Subexpr_No_Checks (Ck_Node),
1559 Right_Opnd => Make_Real_Literal (Loc, Hi));
1561 else
1562 -- Hi_Chk := (X < Hi)
1564 Hi_Chk := Make_Op_Lt (Loc,
1565 Left_Opnd => Duplicate_Subexpr_No_Checks (Ck_Node),
1566 Right_Opnd => Make_Real_Literal (Loc, Hi));
1567 end if;
1569 -- If the bounds of the target type are the same as those of the
1570 -- base type, the check is an overflow check as a range check is
1571 -- not performed in these cases.
1573 if Expr_Value (Type_Low_Bound (Target_Base)) = Ifirst
1574 and then Expr_Value (Type_High_Bound (Target_Base)) = Ilast
1575 then
1576 Reason := CE_Overflow_Check_Failed;
1577 else
1578 Reason := CE_Range_Check_Failed;
1579 end if;
1581 -- Raise CE if either conditions does not hold
1583 Insert_Action (Ck_Node,
1584 Make_Raise_Constraint_Error (Loc,
1585 Condition => Make_Op_Not (Loc, Make_Op_And (Loc, Lo_Chk, Hi_Chk)),
1586 Reason => Reason));
1587 end Apply_Float_Conversion_Check;
1589 ------------------------
1590 -- Apply_Length_Check --
1591 ------------------------
1593 procedure Apply_Length_Check
1594 (Ck_Node : Node_Id;
1595 Target_Typ : Entity_Id;
1596 Source_Typ : Entity_Id := Empty)
1598 begin
1599 Apply_Selected_Length_Checks
1600 (Ck_Node, Target_Typ, Source_Typ, Do_Static => False);
1601 end Apply_Length_Check;
1603 -----------------------
1604 -- Apply_Range_Check --
1605 -----------------------
1607 procedure Apply_Range_Check
1608 (Ck_Node : Node_Id;
1609 Target_Typ : Entity_Id;
1610 Source_Typ : Entity_Id := Empty)
1612 begin
1613 Apply_Selected_Range_Checks
1614 (Ck_Node, Target_Typ, Source_Typ, Do_Static => False);
1615 end Apply_Range_Check;
1617 ------------------------------
1618 -- Apply_Scalar_Range_Check --
1619 ------------------------------
1621 -- Note that Apply_Scalar_Range_Check never turns the Do_Range_Check
1622 -- flag off if it is already set on.
1624 procedure Apply_Scalar_Range_Check
1625 (Expr : Node_Id;
1626 Target_Typ : Entity_Id;
1627 Source_Typ : Entity_Id := Empty;
1628 Fixed_Int : Boolean := False)
1630 Parnt : constant Node_Id := Parent (Expr);
1631 S_Typ : Entity_Id;
1632 Arr : Node_Id := Empty; -- initialize to prevent warning
1633 Arr_Typ : Entity_Id := Empty; -- initialize to prevent warning
1634 OK : Boolean;
1636 Is_Subscr_Ref : Boolean;
1637 -- Set true if Expr is a subscript
1639 Is_Unconstrained_Subscr_Ref : Boolean;
1640 -- Set true if Expr is a subscript of an unconstrained array. In this
1641 -- case we do not attempt to do an analysis of the value against the
1642 -- range of the subscript, since we don't know the actual subtype.
1644 Int_Real : Boolean;
1645 -- Set to True if Expr should be regarded as a real value
1646 -- even though the type of Expr might be discrete.
1648 procedure Bad_Value;
1649 -- Procedure called if value is determined to be out of range
1651 ---------------
1652 -- Bad_Value --
1653 ---------------
1655 procedure Bad_Value is
1656 begin
1657 Apply_Compile_Time_Constraint_Error
1658 (Expr, "value not in range of}?", CE_Range_Check_Failed,
1659 Ent => Target_Typ,
1660 Typ => Target_Typ);
1661 end Bad_Value;
1663 -- Start of processing for Apply_Scalar_Range_Check
1665 begin
1666 if Inside_A_Generic then
1667 return;
1669 -- Return if check obviously not needed. Note that we do not check
1670 -- for the expander being inactive, since this routine does not
1671 -- insert any code, but it does generate useful warnings sometimes,
1672 -- which we would like even if we are in semantics only mode.
1674 elsif Target_Typ = Any_Type
1675 or else not Is_Scalar_Type (Target_Typ)
1676 or else Raises_Constraint_Error (Expr)
1677 then
1678 return;
1679 end if;
1681 -- Now, see if checks are suppressed
1683 Is_Subscr_Ref :=
1684 Is_List_Member (Expr) and then Nkind (Parnt) = N_Indexed_Component;
1686 if Is_Subscr_Ref then
1687 Arr := Prefix (Parnt);
1688 Arr_Typ := Get_Actual_Subtype_If_Available (Arr);
1689 end if;
1691 if not Do_Range_Check (Expr) then
1693 -- Subscript reference. Check for Index_Checks suppressed
1695 if Is_Subscr_Ref then
1697 -- Check array type and its base type
1699 if Index_Checks_Suppressed (Arr_Typ)
1700 or else Index_Checks_Suppressed (Base_Type (Arr_Typ))
1701 then
1702 return;
1704 -- Check array itself if it is an entity name
1706 elsif Is_Entity_Name (Arr)
1707 and then Index_Checks_Suppressed (Entity (Arr))
1708 then
1709 return;
1711 -- Check expression itself if it is an entity name
1713 elsif Is_Entity_Name (Expr)
1714 and then Index_Checks_Suppressed (Entity (Expr))
1715 then
1716 return;
1717 end if;
1719 -- All other cases, check for Range_Checks suppressed
1721 else
1722 -- Check target type and its base type
1724 if Range_Checks_Suppressed (Target_Typ)
1725 or else Range_Checks_Suppressed (Base_Type (Target_Typ))
1726 then
1727 return;
1729 -- Check expression itself if it is an entity name
1731 elsif Is_Entity_Name (Expr)
1732 and then Range_Checks_Suppressed (Entity (Expr))
1733 then
1734 return;
1736 -- If Expr is part of an assignment statement, then check
1737 -- left side of assignment if it is an entity name.
1739 elsif Nkind (Parnt) = N_Assignment_Statement
1740 and then Is_Entity_Name (Name (Parnt))
1741 and then Range_Checks_Suppressed (Entity (Name (Parnt)))
1742 then
1743 return;
1744 end if;
1745 end if;
1746 end if;
1748 -- Do not set range checks if they are killed
1750 if Nkind (Expr) = N_Unchecked_Type_Conversion
1751 and then Kill_Range_Check (Expr)
1752 then
1753 return;
1754 end if;
1756 -- Do not set range checks for any values from System.Scalar_Values
1757 -- since the whole idea of such values is to avoid checking them!
1759 if Is_Entity_Name (Expr)
1760 and then Is_RTU (Scope (Entity (Expr)), System_Scalar_Values)
1761 then
1762 return;
1763 end if;
1765 -- Now see if we need a check
1767 if No (Source_Typ) then
1768 S_Typ := Etype (Expr);
1769 else
1770 S_Typ := Source_Typ;
1771 end if;
1773 if not Is_Scalar_Type (S_Typ) or else S_Typ = Any_Type then
1774 return;
1775 end if;
1777 Is_Unconstrained_Subscr_Ref :=
1778 Is_Subscr_Ref and then not Is_Constrained (Arr_Typ);
1780 -- Always do a range check if the source type includes infinities
1781 -- and the target type does not include infinities. We do not do
1782 -- this if range checks are killed.
1784 if Is_Floating_Point_Type (S_Typ)
1785 and then Has_Infinities (S_Typ)
1786 and then not Has_Infinities (Target_Typ)
1787 then
1788 Enable_Range_Check (Expr);
1789 end if;
1791 -- Return if we know expression is definitely in the range of
1792 -- the target type as determined by Determine_Range. Right now
1793 -- we only do this for discrete types, and not fixed-point or
1794 -- floating-point types.
1796 -- The additional less-precise tests below catch these cases
1798 -- Note: skip this if we are given a source_typ, since the point
1799 -- of supplying a Source_Typ is to stop us looking at the expression.
1800 -- could sharpen this test to be out parameters only ???
1802 if Is_Discrete_Type (Target_Typ)
1803 and then Is_Discrete_Type (Etype (Expr))
1804 and then not Is_Unconstrained_Subscr_Ref
1805 and then No (Source_Typ)
1806 then
1807 declare
1808 Tlo : constant Node_Id := Type_Low_Bound (Target_Typ);
1809 Thi : constant Node_Id := Type_High_Bound (Target_Typ);
1810 Lo : Uint;
1811 Hi : Uint;
1813 begin
1814 if Compile_Time_Known_Value (Tlo)
1815 and then Compile_Time_Known_Value (Thi)
1816 then
1817 declare
1818 Lov : constant Uint := Expr_Value (Tlo);
1819 Hiv : constant Uint := Expr_Value (Thi);
1821 begin
1822 -- If range is null, we for sure have a constraint error
1823 -- (we don't even need to look at the value involved,
1824 -- since all possible values will raise CE).
1826 if Lov > Hiv then
1827 Bad_Value;
1828 return;
1829 end if;
1831 -- Otherwise determine range of value
1833 Determine_Range (Expr, OK, Lo, Hi);
1835 if OK then
1837 -- If definitely in range, all OK
1839 if Lo >= Lov and then Hi <= Hiv then
1840 return;
1842 -- If definitely not in range, warn
1844 elsif Lov > Hi or else Hiv < Lo then
1845 Bad_Value;
1846 return;
1848 -- Otherwise we don't know
1850 else
1851 null;
1852 end if;
1853 end if;
1854 end;
1855 end if;
1856 end;
1857 end if;
1859 Int_Real :=
1860 Is_Floating_Point_Type (S_Typ)
1861 or else (Is_Fixed_Point_Type (S_Typ) and then not Fixed_Int);
1863 -- Check if we can determine at compile time whether Expr is in the
1864 -- range of the target type. Note that if S_Typ is within the bounds
1865 -- of Target_Typ then this must be the case. This check is meaningful
1866 -- only if this is not a conversion between integer and real types.
1868 if not Is_Unconstrained_Subscr_Ref
1869 and then
1870 Is_Discrete_Type (S_Typ) = Is_Discrete_Type (Target_Typ)
1871 and then
1872 (In_Subrange_Of (S_Typ, Target_Typ, Fixed_Int)
1873 or else
1874 Is_In_Range (Expr, Target_Typ, Fixed_Int, Int_Real))
1875 then
1876 return;
1878 elsif Is_Out_Of_Range (Expr, Target_Typ, Fixed_Int, Int_Real) then
1879 Bad_Value;
1880 return;
1882 -- In the floating-point case, we only do range checks if the
1883 -- type is constrained. We definitely do NOT want range checks
1884 -- for unconstrained types, since we want to have infinities
1886 elsif Is_Floating_Point_Type (S_Typ) then
1887 if Is_Constrained (S_Typ) then
1888 Enable_Range_Check (Expr);
1889 end if;
1891 -- For all other cases we enable a range check unconditionally
1893 else
1894 Enable_Range_Check (Expr);
1895 return;
1896 end if;
1897 end Apply_Scalar_Range_Check;
1899 ----------------------------------
1900 -- Apply_Selected_Length_Checks --
1901 ----------------------------------
1903 procedure Apply_Selected_Length_Checks
1904 (Ck_Node : Node_Id;
1905 Target_Typ : Entity_Id;
1906 Source_Typ : Entity_Id;
1907 Do_Static : Boolean)
1909 Cond : Node_Id;
1910 R_Result : Check_Result;
1911 R_Cno : Node_Id;
1913 Loc : constant Source_Ptr := Sloc (Ck_Node);
1914 Checks_On : constant Boolean :=
1915 (not Index_Checks_Suppressed (Target_Typ))
1916 or else
1917 (not Length_Checks_Suppressed (Target_Typ));
1919 begin
1920 if not Expander_Active then
1921 return;
1922 end if;
1924 R_Result :=
1925 Selected_Length_Checks (Ck_Node, Target_Typ, Source_Typ, Empty);
1927 for J in 1 .. 2 loop
1928 R_Cno := R_Result (J);
1929 exit when No (R_Cno);
1931 -- A length check may mention an Itype which is attached to a
1932 -- subsequent node. At the top level in a package this can cause
1933 -- an order-of-elaboration problem, so we make sure that the itype
1934 -- is referenced now.
1936 if Ekind (Current_Scope) = E_Package
1937 and then Is_Compilation_Unit (Current_Scope)
1938 then
1939 Ensure_Defined (Target_Typ, Ck_Node);
1941 if Present (Source_Typ) then
1942 Ensure_Defined (Source_Typ, Ck_Node);
1944 elsif Is_Itype (Etype (Ck_Node)) then
1945 Ensure_Defined (Etype (Ck_Node), Ck_Node);
1946 end if;
1947 end if;
1949 -- If the item is a conditional raise of constraint error,
1950 -- then have a look at what check is being performed and
1951 -- ???
1953 if Nkind (R_Cno) = N_Raise_Constraint_Error
1954 and then Present (Condition (R_Cno))
1955 then
1956 Cond := Condition (R_Cno);
1958 if not Has_Dynamic_Length_Check (Ck_Node)
1959 and then Checks_On
1960 then
1961 Insert_Action (Ck_Node, R_Cno);
1963 if not Do_Static then
1964 Set_Has_Dynamic_Length_Check (Ck_Node);
1965 end if;
1966 end if;
1968 -- Output a warning if the condition is known to be True
1970 if Is_Entity_Name (Cond)
1971 and then Entity (Cond) = Standard_True
1972 then
1973 Apply_Compile_Time_Constraint_Error
1974 (Ck_Node, "wrong length for array of}?",
1975 CE_Length_Check_Failed,
1976 Ent => Target_Typ,
1977 Typ => Target_Typ);
1979 -- If we were only doing a static check, or if checks are not
1980 -- on, then we want to delete the check, since it is not needed.
1981 -- We do this by replacing the if statement by a null statement
1983 elsif Do_Static or else not Checks_On then
1984 Rewrite (R_Cno, Make_Null_Statement (Loc));
1985 end if;
1987 else
1988 Install_Static_Check (R_Cno, Loc);
1989 end if;
1991 end loop;
1993 end Apply_Selected_Length_Checks;
1995 ---------------------------------
1996 -- Apply_Selected_Range_Checks --
1997 ---------------------------------
1999 procedure Apply_Selected_Range_Checks
2000 (Ck_Node : Node_Id;
2001 Target_Typ : Entity_Id;
2002 Source_Typ : Entity_Id;
2003 Do_Static : Boolean)
2005 Cond : Node_Id;
2006 R_Result : Check_Result;
2007 R_Cno : Node_Id;
2009 Loc : constant Source_Ptr := Sloc (Ck_Node);
2010 Checks_On : constant Boolean :=
2011 (not Index_Checks_Suppressed (Target_Typ))
2012 or else
2013 (not Range_Checks_Suppressed (Target_Typ));
2015 begin
2016 if not Expander_Active or else not Checks_On then
2017 return;
2018 end if;
2020 R_Result :=
2021 Selected_Range_Checks (Ck_Node, Target_Typ, Source_Typ, Empty);
2023 for J in 1 .. 2 loop
2025 R_Cno := R_Result (J);
2026 exit when No (R_Cno);
2028 -- If the item is a conditional raise of constraint error,
2029 -- then have a look at what check is being performed and
2030 -- ???
2032 if Nkind (R_Cno) = N_Raise_Constraint_Error
2033 and then Present (Condition (R_Cno))
2034 then
2035 Cond := Condition (R_Cno);
2037 if not Has_Dynamic_Range_Check (Ck_Node) then
2038 Insert_Action (Ck_Node, R_Cno);
2040 if not Do_Static then
2041 Set_Has_Dynamic_Range_Check (Ck_Node);
2042 end if;
2043 end if;
2045 -- Output a warning if the condition is known to be True
2047 if Is_Entity_Name (Cond)
2048 and then Entity (Cond) = Standard_True
2049 then
2050 -- Since an N_Range is technically not an expression, we
2051 -- have to set one of the bounds to C_E and then just flag
2052 -- the N_Range. The warning message will point to the
2053 -- lower bound and complain about a range, which seems OK.
2055 if Nkind (Ck_Node) = N_Range then
2056 Apply_Compile_Time_Constraint_Error
2057 (Low_Bound (Ck_Node), "static range out of bounds of}?",
2058 CE_Range_Check_Failed,
2059 Ent => Target_Typ,
2060 Typ => Target_Typ);
2062 Set_Raises_Constraint_Error (Ck_Node);
2064 else
2065 Apply_Compile_Time_Constraint_Error
2066 (Ck_Node, "static value out of range of}?",
2067 CE_Range_Check_Failed,
2068 Ent => Target_Typ,
2069 Typ => Target_Typ);
2070 end if;
2072 -- If we were only doing a static check, or if checks are not
2073 -- on, then we want to delete the check, since it is not needed.
2074 -- We do this by replacing the if statement by a null statement
2076 elsif Do_Static or else not Checks_On then
2077 Rewrite (R_Cno, Make_Null_Statement (Loc));
2078 end if;
2080 else
2081 Install_Static_Check (R_Cno, Loc);
2082 end if;
2083 end loop;
2084 end Apply_Selected_Range_Checks;
2086 -------------------------------
2087 -- Apply_Static_Length_Check --
2088 -------------------------------
2090 procedure Apply_Static_Length_Check
2091 (Expr : Node_Id;
2092 Target_Typ : Entity_Id;
2093 Source_Typ : Entity_Id := Empty)
2095 begin
2096 Apply_Selected_Length_Checks
2097 (Expr, Target_Typ, Source_Typ, Do_Static => True);
2098 end Apply_Static_Length_Check;
2100 -------------------------------------
2101 -- Apply_Subscript_Validity_Checks --
2102 -------------------------------------
2104 procedure Apply_Subscript_Validity_Checks (Expr : Node_Id) is
2105 Sub : Node_Id;
2107 begin
2108 pragma Assert (Nkind (Expr) = N_Indexed_Component);
2110 -- Loop through subscripts
2112 Sub := First (Expressions (Expr));
2113 while Present (Sub) loop
2115 -- Check one subscript. Note that we do not worry about
2116 -- enumeration type with holes, since we will convert the
2117 -- value to a Pos value for the subscript, and that convert
2118 -- will do the necessary validity check.
2120 Ensure_Valid (Sub, Holes_OK => True);
2122 -- Move to next subscript
2124 Sub := Next (Sub);
2125 end loop;
2126 end Apply_Subscript_Validity_Checks;
2128 ----------------------------------
2129 -- Apply_Type_Conversion_Checks --
2130 ----------------------------------
2132 procedure Apply_Type_Conversion_Checks (N : Node_Id) is
2133 Target_Type : constant Entity_Id := Etype (N);
2134 Target_Base : constant Entity_Id := Base_Type (Target_Type);
2135 Expr : constant Node_Id := Expression (N);
2136 Expr_Type : constant Entity_Id := Etype (Expr);
2138 begin
2139 if Inside_A_Generic then
2140 return;
2142 -- Skip these checks if serious errors detected, there are some nasty
2143 -- situations of incomplete trees that blow things up.
2145 elsif Serious_Errors_Detected > 0 then
2146 return;
2148 -- Scalar type conversions of the form Target_Type (Expr) require
2149 -- a range check if we cannot be sure that Expr is in the base type
2150 -- of Target_Typ and also that Expr is in the range of Target_Typ.
2151 -- These are not quite the same condition from an implementation
2152 -- point of view, but clearly the second includes the first.
2154 elsif Is_Scalar_Type (Target_Type) then
2155 declare
2156 Conv_OK : constant Boolean := Conversion_OK (N);
2157 -- If the Conversion_OK flag on the type conversion is set
2158 -- and no floating point type is involved in the type conversion
2159 -- then fixed point values must be read as integral values.
2161 Float_To_Int : constant Boolean :=
2162 Is_Floating_Point_Type (Expr_Type)
2163 and then Is_Integer_Type (Target_Type);
2165 begin
2166 if not Overflow_Checks_Suppressed (Target_Base)
2167 and then not In_Subrange_Of (Expr_Type, Target_Base, Conv_OK)
2168 and then not Float_To_Int
2169 then
2170 Set_Do_Overflow_Check (N);
2171 end if;
2173 if not Range_Checks_Suppressed (Target_Type)
2174 and then not Range_Checks_Suppressed (Expr_Type)
2175 then
2176 if Float_To_Int then
2177 Apply_Float_Conversion_Check (Expr, Target_Type);
2178 else
2179 Apply_Scalar_Range_Check
2180 (Expr, Target_Type, Fixed_Int => Conv_OK);
2181 end if;
2182 end if;
2183 end;
2185 elsif Comes_From_Source (N)
2186 and then Is_Record_Type (Target_Type)
2187 and then Is_Derived_Type (Target_Type)
2188 and then not Is_Tagged_Type (Target_Type)
2189 and then not Is_Constrained (Target_Type)
2190 and then Present (Stored_Constraint (Target_Type))
2191 then
2192 -- An unconstrained derived type may have inherited discriminant
2193 -- Build an actual discriminant constraint list using the stored
2194 -- constraint, to verify that the expression of the parent type
2195 -- satisfies the constraints imposed by the (unconstrained!)
2196 -- derived type. This applies to value conversions, not to view
2197 -- conversions of tagged types.
2199 declare
2200 Loc : constant Source_Ptr := Sloc (N);
2201 Cond : Node_Id;
2202 Constraint : Elmt_Id;
2203 Discr_Value : Node_Id;
2204 Discr : Entity_Id;
2206 New_Constraints : constant Elist_Id := New_Elmt_List;
2207 Old_Constraints : constant Elist_Id :=
2208 Discriminant_Constraint (Expr_Type);
2210 begin
2211 Constraint := First_Elmt (Stored_Constraint (Target_Type));
2213 while Present (Constraint) loop
2214 Discr_Value := Node (Constraint);
2216 if Is_Entity_Name (Discr_Value)
2217 and then Ekind (Entity (Discr_Value)) = E_Discriminant
2218 then
2219 Discr := Corresponding_Discriminant (Entity (Discr_Value));
2221 if Present (Discr)
2222 and then Scope (Discr) = Base_Type (Expr_Type)
2223 then
2224 -- Parent is constrained by new discriminant. Obtain
2225 -- Value of original discriminant in expression. If
2226 -- the new discriminant has been used to constrain more
2227 -- than one of the stored discriminants, this will
2228 -- provide the required consistency check.
2230 Append_Elmt (
2231 Make_Selected_Component (Loc,
2232 Prefix =>
2233 Duplicate_Subexpr_No_Checks
2234 (Expr, Name_Req => True),
2235 Selector_Name =>
2236 Make_Identifier (Loc, Chars (Discr))),
2237 New_Constraints);
2239 else
2240 -- Discriminant of more remote ancestor ???
2242 return;
2243 end if;
2245 -- Derived type definition has an explicit value for
2246 -- this stored discriminant.
2248 else
2249 Append_Elmt
2250 (Duplicate_Subexpr_No_Checks (Discr_Value),
2251 New_Constraints);
2252 end if;
2254 Next_Elmt (Constraint);
2255 end loop;
2257 -- Use the unconstrained expression type to retrieve the
2258 -- discriminants of the parent, and apply momentarily the
2259 -- discriminant constraint synthesized above.
2261 Set_Discriminant_Constraint (Expr_Type, New_Constraints);
2262 Cond := Build_Discriminant_Checks (Expr, Expr_Type);
2263 Set_Discriminant_Constraint (Expr_Type, Old_Constraints);
2265 Insert_Action (N,
2266 Make_Raise_Constraint_Error (Loc,
2267 Condition => Cond,
2268 Reason => CE_Discriminant_Check_Failed));
2269 end;
2271 -- For arrays, conversions are applied during expansion, to take
2272 -- into accounts changes of representation. The checks become range
2273 -- checks on the base type or length checks on the subtype, depending
2274 -- on whether the target type is unconstrained or constrained.
2276 else
2277 null;
2278 end if;
2279 end Apply_Type_Conversion_Checks;
2281 ----------------------------------------------
2282 -- Apply_Universal_Integer_Attribute_Checks --
2283 ----------------------------------------------
2285 procedure Apply_Universal_Integer_Attribute_Checks (N : Node_Id) is
2286 Loc : constant Source_Ptr := Sloc (N);
2287 Typ : constant Entity_Id := Etype (N);
2289 begin
2290 if Inside_A_Generic then
2291 return;
2293 -- Nothing to do if checks are suppressed
2295 elsif Range_Checks_Suppressed (Typ)
2296 and then Overflow_Checks_Suppressed (Typ)
2297 then
2298 return;
2300 -- Nothing to do if the attribute does not come from source. The
2301 -- internal attributes we generate of this type do not need checks,
2302 -- and furthermore the attempt to check them causes some circular
2303 -- elaboration orders when dealing with packed types.
2305 elsif not Comes_From_Source (N) then
2306 return;
2308 -- If the prefix is a selected component that depends on a discriminant
2309 -- the check may improperly expose a discriminant instead of using
2310 -- the bounds of the object itself. Set the type of the attribute to
2311 -- the base type of the context, so that a check will be imposed when
2312 -- needed (e.g. if the node appears as an index).
2314 elsif Nkind (Prefix (N)) = N_Selected_Component
2315 and then Ekind (Typ) = E_Signed_Integer_Subtype
2316 and then Depends_On_Discriminant (Scalar_Range (Typ))
2317 then
2318 Set_Etype (N, Base_Type (Typ));
2320 -- Otherwise, replace the attribute node with a type conversion
2321 -- node whose expression is the attribute, retyped to universal
2322 -- integer, and whose subtype mark is the target type. The call
2323 -- to analyze this conversion will set range and overflow checks
2324 -- as required for proper detection of an out of range value.
2326 else
2327 Set_Etype (N, Universal_Integer);
2328 Set_Analyzed (N, True);
2330 Rewrite (N,
2331 Make_Type_Conversion (Loc,
2332 Subtype_Mark => New_Occurrence_Of (Typ, Loc),
2333 Expression => Relocate_Node (N)));
2335 Analyze_And_Resolve (N, Typ);
2336 return;
2337 end if;
2339 end Apply_Universal_Integer_Attribute_Checks;
2341 -------------------------------
2342 -- Build_Discriminant_Checks --
2343 -------------------------------
2345 function Build_Discriminant_Checks
2346 (N : Node_Id;
2347 T_Typ : Entity_Id) return Node_Id
2349 Loc : constant Source_Ptr := Sloc (N);
2350 Cond : Node_Id;
2351 Disc : Elmt_Id;
2352 Disc_Ent : Entity_Id;
2353 Dref : Node_Id;
2354 Dval : Node_Id;
2356 begin
2357 Cond := Empty;
2358 Disc := First_Elmt (Discriminant_Constraint (T_Typ));
2360 -- For a fully private type, use the discriminants of the parent type
2362 if Is_Private_Type (T_Typ)
2363 and then No (Full_View (T_Typ))
2364 then
2365 Disc_Ent := First_Discriminant (Etype (Base_Type (T_Typ)));
2366 else
2367 Disc_Ent := First_Discriminant (T_Typ);
2368 end if;
2370 while Present (Disc) loop
2371 Dval := Node (Disc);
2373 if Nkind (Dval) = N_Identifier
2374 and then Ekind (Entity (Dval)) = E_Discriminant
2375 then
2376 Dval := New_Occurrence_Of (Discriminal (Entity (Dval)), Loc);
2377 else
2378 Dval := Duplicate_Subexpr_No_Checks (Dval);
2379 end if;
2381 -- If we have an Unchecked_Union node, we can infer the discriminants
2382 -- of the node.
2384 if Is_Unchecked_Union (Base_Type (T_Typ)) then
2385 Dref := New_Copy (
2386 Get_Discriminant_Value (
2387 First_Discriminant (T_Typ),
2388 T_Typ,
2389 Stored_Constraint (T_Typ)));
2391 else
2392 Dref :=
2393 Make_Selected_Component (Loc,
2394 Prefix =>
2395 Duplicate_Subexpr_No_Checks (N, Name_Req => True),
2396 Selector_Name =>
2397 Make_Identifier (Loc, Chars (Disc_Ent)));
2399 Set_Is_In_Discriminant_Check (Dref);
2400 end if;
2402 Evolve_Or_Else (Cond,
2403 Make_Op_Ne (Loc,
2404 Left_Opnd => Dref,
2405 Right_Opnd => Dval));
2407 Next_Elmt (Disc);
2408 Next_Discriminant (Disc_Ent);
2409 end loop;
2411 return Cond;
2412 end Build_Discriminant_Checks;
2414 -----------------------------------
2415 -- Check_Valid_Lvalue_Subscripts --
2416 -----------------------------------
2418 procedure Check_Valid_Lvalue_Subscripts (Expr : Node_Id) is
2419 begin
2420 -- Skip this if range checks are suppressed
2422 if Range_Checks_Suppressed (Etype (Expr)) then
2423 return;
2425 -- Only do this check for expressions that come from source. We
2426 -- assume that expander generated assignments explicitly include
2427 -- any necessary checks. Note that this is not just an optimization,
2428 -- it avoids infinite recursions!
2430 elsif not Comes_From_Source (Expr) then
2431 return;
2433 -- For a selected component, check the prefix
2435 elsif Nkind (Expr) = N_Selected_Component then
2436 Check_Valid_Lvalue_Subscripts (Prefix (Expr));
2437 return;
2439 -- Case of indexed component
2441 elsif Nkind (Expr) = N_Indexed_Component then
2442 Apply_Subscript_Validity_Checks (Expr);
2444 -- Prefix may itself be or contain an indexed component, and
2445 -- these subscripts need checking as well
2447 Check_Valid_Lvalue_Subscripts (Prefix (Expr));
2448 end if;
2449 end Check_Valid_Lvalue_Subscripts;
2451 ----------------------------------
2452 -- Null_Exclusion_Static_Checks --
2453 ----------------------------------
2455 procedure Null_Exclusion_Static_Checks (N : Node_Id) is
2456 K : constant Node_Kind := Nkind (N);
2457 Typ : Entity_Id;
2458 Related_Nod : Node_Id;
2459 Has_Null_Exclusion : Boolean := False;
2461 type Msg_Kind is (Components, Formals, Objects);
2462 Msg_K : Msg_Kind := Objects;
2463 -- Used by local subprograms to generate precise error messages
2465 procedure Check_Must_Be_Access
2466 (Typ : Entity_Id;
2467 Has_Null_Exclusion : Boolean);
2468 -- ??? local subprograms must have comment on spec
2470 procedure Check_Already_Null_Excluding_Type
2471 (Typ : Entity_Id;
2472 Has_Null_Exclusion : Boolean;
2473 Related_Nod : Node_Id);
2474 -- ??? local subprograms must have comment on spec
2476 procedure Check_Must_Be_Initialized
2477 (N : Node_Id;
2478 Related_Nod : Node_Id);
2479 -- ??? local subprograms must have comment on spec
2481 procedure Check_Null_Not_Allowed (N : Node_Id);
2482 -- ??? local subprograms must have comment on spec
2484 -- ??? following bodies lack comments
2486 --------------------------
2487 -- Check_Must_Be_Access --
2488 --------------------------
2490 procedure Check_Must_Be_Access
2491 (Typ : Entity_Id;
2492 Has_Null_Exclusion : Boolean)
2494 begin
2495 if Has_Null_Exclusion
2496 and then not Is_Access_Type (Typ)
2497 then
2498 Error_Msg_N ("(Ada 2005) must be an access type", Related_Nod);
2499 end if;
2500 end Check_Must_Be_Access;
2502 ---------------------------------------
2503 -- Check_Already_Null_Excluding_Type --
2504 ---------------------------------------
2506 procedure Check_Already_Null_Excluding_Type
2507 (Typ : Entity_Id;
2508 Has_Null_Exclusion : Boolean;
2509 Related_Nod : Node_Id)
2511 begin
2512 if Has_Null_Exclusion
2513 and then Can_Never_Be_Null (Typ)
2514 then
2515 Error_Msg_N
2516 ("(Ada 2005) already a null-excluding type", Related_Nod);
2517 end if;
2518 end Check_Already_Null_Excluding_Type;
2520 -------------------------------
2521 -- Check_Must_Be_Initialized --
2522 -------------------------------
2524 procedure Check_Must_Be_Initialized
2525 (N : Node_Id;
2526 Related_Nod : Node_Id)
2528 Expr : constant Node_Id := Expression (N);
2530 begin
2531 pragma Assert (Nkind (N) = N_Component_Declaration
2532 or else Nkind (N) = N_Object_Declaration);
2534 if not Present (Expr) then
2535 case Msg_K is
2536 when Components =>
2537 Error_Msg_N
2538 ("(Ada 2005) null-excluding components must be " &
2539 "initialized", Related_Nod);
2541 when Formals =>
2542 Error_Msg_N
2543 ("(Ada 2005) null-excluding formals must be initialized",
2544 Related_Nod);
2546 when Objects =>
2547 Error_Msg_N
2548 ("(Ada 2005) null-excluding objects must be initialized",
2549 Related_Nod);
2550 end case;
2551 end if;
2552 end Check_Must_Be_Initialized;
2554 ----------------------------
2555 -- Check_Null_Not_Allowed --
2556 ----------------------------
2558 procedure Check_Null_Not_Allowed (N : Node_Id) is
2559 Expr : constant Node_Id := Expression (N);
2561 begin
2562 if Present (Expr)
2563 and then Nkind (Expr) = N_Null
2564 then
2565 case Msg_K is
2566 when Components =>
2567 Apply_Compile_Time_Constraint_Error
2568 (N => Expr,
2569 Msg => "(Ada 2005) NULL not allowed in"
2570 & " null-excluding components?",
2571 Reason => CE_Null_Not_Allowed,
2572 Rep => False);
2574 when Formals =>
2575 Apply_Compile_Time_Constraint_Error
2576 (N => Expr,
2577 Msg => "(Ada 2005) NULL not allowed in"
2578 & " null-excluding formals?",
2579 Reason => CE_Null_Not_Allowed,
2580 Rep => False);
2582 when Objects =>
2583 Apply_Compile_Time_Constraint_Error
2584 (N => Expr,
2585 Msg => "(Ada 2005) NULL not allowed in"
2586 & " null-excluding objects?",
2587 Reason => CE_Null_Not_Allowed,
2588 Rep => False);
2589 end case;
2590 end if;
2591 end Check_Null_Not_Allowed;
2593 -- Start of processing for Null_Exclusion_Static_Checks
2595 begin
2596 pragma Assert (K = N_Component_Declaration
2597 or else K = N_Parameter_Specification
2598 or else K = N_Object_Declaration
2599 or else K = N_Discriminant_Specification
2600 or else K = N_Allocator);
2602 case K is
2603 when N_Component_Declaration =>
2604 Msg_K := Components;
2606 if not Present (Access_Definition (Component_Definition (N))) then
2607 Has_Null_Exclusion := Null_Exclusion_Present
2608 (Component_Definition (N));
2609 Typ := Etype (Subtype_Indication (Component_Definition (N)));
2610 Related_Nod := Subtype_Indication (Component_Definition (N));
2611 Check_Must_Be_Access (Typ, Has_Null_Exclusion);
2612 Check_Already_Null_Excluding_Type
2613 (Typ, Has_Null_Exclusion, Related_Nod);
2614 Check_Must_Be_Initialized (N, Related_Nod);
2615 end if;
2617 Check_Null_Not_Allowed (N);
2619 when N_Parameter_Specification =>
2620 Msg_K := Formals;
2621 Has_Null_Exclusion := Null_Exclusion_Present (N);
2622 Typ := Entity (Parameter_Type (N));
2623 Related_Nod := Parameter_Type (N);
2624 Check_Must_Be_Access (Typ, Has_Null_Exclusion);
2625 Check_Already_Null_Excluding_Type
2626 (Typ, Has_Null_Exclusion, Related_Nod);
2627 Check_Null_Not_Allowed (N);
2629 when N_Object_Declaration =>
2630 Msg_K := Objects;
2631 Has_Null_Exclusion := Null_Exclusion_Present (N);
2632 Typ := Entity (Object_Definition (N));
2633 Related_Nod := Object_Definition (N);
2634 Check_Must_Be_Access (Typ, Has_Null_Exclusion);
2635 Check_Already_Null_Excluding_Type
2636 (Typ, Has_Null_Exclusion, Related_Nod);
2637 Check_Must_Be_Initialized (N, Related_Nod);
2638 Check_Null_Not_Allowed (N);
2640 when N_Discriminant_Specification =>
2641 Msg_K := Components;
2643 if Nkind (Discriminant_Type (N)) /= N_Access_Definition then
2644 Has_Null_Exclusion := Null_Exclusion_Present (N);
2645 Typ := Etype (Defining_Identifier (N));
2646 Related_Nod := Discriminant_Type (N);
2647 Check_Must_Be_Access (Typ, Has_Null_Exclusion);
2648 Check_Already_Null_Excluding_Type
2649 (Typ, Has_Null_Exclusion, Related_Nod);
2650 end if;
2652 Check_Null_Not_Allowed (N);
2654 when N_Allocator =>
2655 Msg_K := Objects;
2656 Has_Null_Exclusion := Null_Exclusion_Present (N);
2657 Typ := Etype (Expression (N));
2659 if Nkind (Expression (N)) = N_Qualified_Expression then
2660 Related_Nod := Subtype_Mark (Expression (N));
2661 else
2662 Related_Nod := Expression (N);
2663 end if;
2665 Check_Must_Be_Access (Typ, Has_Null_Exclusion);
2666 Check_Already_Null_Excluding_Type
2667 (Typ, Has_Null_Exclusion, Related_Nod);
2668 Check_Null_Not_Allowed (N);
2670 when others =>
2671 raise Program_Error;
2672 end case;
2673 end Null_Exclusion_Static_Checks;
2675 ----------------------------------
2676 -- Conditional_Statements_Begin --
2677 ----------------------------------
2679 procedure Conditional_Statements_Begin is
2680 begin
2681 Saved_Checks_TOS := Saved_Checks_TOS + 1;
2683 -- If stack overflows, kill all checks, that way we know to
2684 -- simply reset the number of saved checks to zero on return.
2685 -- This should never occur in practice.
2687 if Saved_Checks_TOS > Saved_Checks_Stack'Last then
2688 Kill_All_Checks;
2690 -- In the normal case, we just make a new stack entry saving
2691 -- the current number of saved checks for a later restore.
2693 else
2694 Saved_Checks_Stack (Saved_Checks_TOS) := Num_Saved_Checks;
2696 if Debug_Flag_CC then
2697 w ("Conditional_Statements_Begin: Num_Saved_Checks = ",
2698 Num_Saved_Checks);
2699 end if;
2700 end if;
2701 end Conditional_Statements_Begin;
2703 --------------------------------
2704 -- Conditional_Statements_End --
2705 --------------------------------
2707 procedure Conditional_Statements_End is
2708 begin
2709 pragma Assert (Saved_Checks_TOS > 0);
2711 -- If the saved checks stack overflowed, then we killed all
2712 -- checks, so setting the number of saved checks back to
2713 -- zero is correct. This should never occur in practice.
2715 if Saved_Checks_TOS > Saved_Checks_Stack'Last then
2716 Num_Saved_Checks := 0;
2718 -- In the normal case, restore the number of saved checks
2719 -- from the top stack entry.
2721 else
2722 Num_Saved_Checks := Saved_Checks_Stack (Saved_Checks_TOS);
2723 if Debug_Flag_CC then
2724 w ("Conditional_Statements_End: Num_Saved_Checks = ",
2725 Num_Saved_Checks);
2726 end if;
2727 end if;
2729 Saved_Checks_TOS := Saved_Checks_TOS - 1;
2730 end Conditional_Statements_End;
2732 ---------------------
2733 -- Determine_Range --
2734 ---------------------
2736 Cache_Size : constant := 2 ** 10;
2737 type Cache_Index is range 0 .. Cache_Size - 1;
2738 -- Determine size of below cache (power of 2 is more efficient!)
2740 Determine_Range_Cache_N : array (Cache_Index) of Node_Id;
2741 Determine_Range_Cache_Lo : array (Cache_Index) of Uint;
2742 Determine_Range_Cache_Hi : array (Cache_Index) of Uint;
2743 -- The above arrays are used to implement a small direct cache
2744 -- for Determine_Range calls. Because of the way Determine_Range
2745 -- recursively traces subexpressions, and because overflow checking
2746 -- calls the routine on the way up the tree, a quadratic behavior
2747 -- can otherwise be encountered in large expressions. The cache
2748 -- entry for node N is stored in the (N mod Cache_Size) entry, and
2749 -- can be validated by checking the actual node value stored there.
2751 procedure Determine_Range
2752 (N : Node_Id;
2753 OK : out Boolean;
2754 Lo : out Uint;
2755 Hi : out Uint)
2757 Typ : constant Entity_Id := Etype (N);
2759 Lo_Left : Uint;
2760 Hi_Left : Uint;
2761 -- Lo and Hi bounds of left operand
2763 Lo_Right : Uint;
2764 Hi_Right : Uint;
2765 -- Lo and Hi bounds of right (or only) operand
2767 Bound : Node_Id;
2768 -- Temp variable used to hold a bound node
2770 Hbound : Uint;
2771 -- High bound of base type of expression
2773 Lor : Uint;
2774 Hir : Uint;
2775 -- Refined values for low and high bounds, after tightening
2777 OK1 : Boolean;
2778 -- Used in lower level calls to indicate if call succeeded
2780 Cindex : Cache_Index;
2781 -- Used to search cache
2783 function OK_Operands return Boolean;
2784 -- Used for binary operators. Determines the ranges of the left and
2785 -- right operands, and if they are both OK, returns True, and puts
2786 -- the results in Lo_Right, Hi_Right, Lo_Left, Hi_Left
2788 -----------------
2789 -- OK_Operands --
2790 -----------------
2792 function OK_Operands return Boolean is
2793 begin
2794 Determine_Range (Left_Opnd (N), OK1, Lo_Left, Hi_Left);
2796 if not OK1 then
2797 return False;
2798 end if;
2800 Determine_Range (Right_Opnd (N), OK1, Lo_Right, Hi_Right);
2801 return OK1;
2802 end OK_Operands;
2804 -- Start of processing for Determine_Range
2806 begin
2807 -- Prevent junk warnings by initializing range variables
2809 Lo := No_Uint;
2810 Hi := No_Uint;
2811 Lor := No_Uint;
2812 Hir := No_Uint;
2814 -- If the type is not discrete, or is undefined, then we can't
2815 -- do anything about determining the range.
2817 if No (Typ) or else not Is_Discrete_Type (Typ)
2818 or else Error_Posted (N)
2819 then
2820 OK := False;
2821 return;
2822 end if;
2824 -- For all other cases, we can determine the range
2826 OK := True;
2828 -- If value is compile time known, then the possible range is the
2829 -- one value that we know this expression definitely has!
2831 if Compile_Time_Known_Value (N) then
2832 Lo := Expr_Value (N);
2833 Hi := Lo;
2834 return;
2835 end if;
2837 -- Return if already in the cache
2839 Cindex := Cache_Index (N mod Cache_Size);
2841 if Determine_Range_Cache_N (Cindex) = N then
2842 Lo := Determine_Range_Cache_Lo (Cindex);
2843 Hi := Determine_Range_Cache_Hi (Cindex);
2844 return;
2845 end if;
2847 -- Otherwise, start by finding the bounds of the type of the
2848 -- expression, the value cannot be outside this range (if it
2849 -- is, then we have an overflow situation, which is a separate
2850 -- check, we are talking here only about the expression value).
2852 -- We use the actual bound unless it is dynamic, in which case
2853 -- use the corresponding base type bound if possible. If we can't
2854 -- get a bound then we figure we can't determine the range (a
2855 -- peculiar case, that perhaps cannot happen, but there is no
2856 -- point in bombing in this optimization circuit.
2858 -- First the low bound
2860 Bound := Type_Low_Bound (Typ);
2862 if Compile_Time_Known_Value (Bound) then
2863 Lo := Expr_Value (Bound);
2865 elsif Compile_Time_Known_Value (Type_Low_Bound (Base_Type (Typ))) then
2866 Lo := Expr_Value (Type_Low_Bound (Base_Type (Typ)));
2868 else
2869 OK := False;
2870 return;
2871 end if;
2873 -- Now the high bound
2875 Bound := Type_High_Bound (Typ);
2877 -- We need the high bound of the base type later on, and this should
2878 -- always be compile time known. Again, it is not clear that this
2879 -- can ever be false, but no point in bombing.
2881 if Compile_Time_Known_Value (Type_High_Bound (Base_Type (Typ))) then
2882 Hbound := Expr_Value (Type_High_Bound (Base_Type (Typ)));
2883 Hi := Hbound;
2885 else
2886 OK := False;
2887 return;
2888 end if;
2890 -- If we have a static subtype, then that may have a tighter bound
2891 -- so use the upper bound of the subtype instead in this case.
2893 if Compile_Time_Known_Value (Bound) then
2894 Hi := Expr_Value (Bound);
2895 end if;
2897 -- We may be able to refine this value in certain situations. If
2898 -- refinement is possible, then Lor and Hir are set to possibly
2899 -- tighter bounds, and OK1 is set to True.
2901 case Nkind (N) is
2903 -- For unary plus, result is limited by range of operand
2905 when N_Op_Plus =>
2906 Determine_Range (Right_Opnd (N), OK1, Lor, Hir);
2908 -- For unary minus, determine range of operand, and negate it
2910 when N_Op_Minus =>
2911 Determine_Range (Right_Opnd (N), OK1, Lo_Right, Hi_Right);
2913 if OK1 then
2914 Lor := -Hi_Right;
2915 Hir := -Lo_Right;
2916 end if;
2918 -- For binary addition, get range of each operand and do the
2919 -- addition to get the result range.
2921 when N_Op_Add =>
2922 if OK_Operands then
2923 Lor := Lo_Left + Lo_Right;
2924 Hir := Hi_Left + Hi_Right;
2925 end if;
2927 -- Division is tricky. The only case we consider is where the
2928 -- right operand is a positive constant, and in this case we
2929 -- simply divide the bounds of the left operand
2931 when N_Op_Divide =>
2932 if OK_Operands then
2933 if Lo_Right = Hi_Right
2934 and then Lo_Right > 0
2935 then
2936 Lor := Lo_Left / Lo_Right;
2937 Hir := Hi_Left / Lo_Right;
2939 else
2940 OK1 := False;
2941 end if;
2942 end if;
2944 -- For binary subtraction, get range of each operand and do
2945 -- the worst case subtraction to get the result range.
2947 when N_Op_Subtract =>
2948 if OK_Operands then
2949 Lor := Lo_Left - Hi_Right;
2950 Hir := Hi_Left - Lo_Right;
2951 end if;
2953 -- For MOD, if right operand is a positive constant, then
2954 -- result must be in the allowable range of mod results.
2956 when N_Op_Mod =>
2957 if OK_Operands then
2958 if Lo_Right = Hi_Right
2959 and then Lo_Right /= 0
2960 then
2961 if Lo_Right > 0 then
2962 Lor := Uint_0;
2963 Hir := Lo_Right - 1;
2965 else -- Lo_Right < 0
2966 Lor := Lo_Right + 1;
2967 Hir := Uint_0;
2968 end if;
2970 else
2971 OK1 := False;
2972 end if;
2973 end if;
2975 -- For REM, if right operand is a positive constant, then
2976 -- result must be in the allowable range of mod results.
2978 when N_Op_Rem =>
2979 if OK_Operands then
2980 if Lo_Right = Hi_Right
2981 and then Lo_Right /= 0
2982 then
2983 declare
2984 Dval : constant Uint := (abs Lo_Right) - 1;
2986 begin
2987 -- The sign of the result depends on the sign of the
2988 -- dividend (but not on the sign of the divisor, hence
2989 -- the abs operation above).
2991 if Lo_Left < 0 then
2992 Lor := -Dval;
2993 else
2994 Lor := Uint_0;
2995 end if;
2997 if Hi_Left < 0 then
2998 Hir := Uint_0;
2999 else
3000 Hir := Dval;
3001 end if;
3002 end;
3004 else
3005 OK1 := False;
3006 end if;
3007 end if;
3009 -- Attribute reference cases
3011 when N_Attribute_Reference =>
3012 case Attribute_Name (N) is
3014 -- For Pos/Val attributes, we can refine the range using the
3015 -- possible range of values of the attribute expression
3017 when Name_Pos | Name_Val =>
3018 Determine_Range (First (Expressions (N)), OK1, Lor, Hir);
3020 -- For Length attribute, use the bounds of the corresponding
3021 -- index type to refine the range.
3023 when Name_Length =>
3024 declare
3025 Atyp : Entity_Id := Etype (Prefix (N));
3026 Inum : Nat;
3027 Indx : Node_Id;
3029 LL, LU : Uint;
3030 UL, UU : Uint;
3032 begin
3033 if Is_Access_Type (Atyp) then
3034 Atyp := Designated_Type (Atyp);
3035 end if;
3037 -- For string literal, we know exact value
3039 if Ekind (Atyp) = E_String_Literal_Subtype then
3040 OK := True;
3041 Lo := String_Literal_Length (Atyp);
3042 Hi := String_Literal_Length (Atyp);
3043 return;
3044 end if;
3046 -- Otherwise check for expression given
3048 if No (Expressions (N)) then
3049 Inum := 1;
3050 else
3051 Inum :=
3052 UI_To_Int (Expr_Value (First (Expressions (N))));
3053 end if;
3055 Indx := First_Index (Atyp);
3056 for J in 2 .. Inum loop
3057 Indx := Next_Index (Indx);
3058 end loop;
3060 Determine_Range
3061 (Type_Low_Bound (Etype (Indx)), OK1, LL, LU);
3063 if OK1 then
3064 Determine_Range
3065 (Type_High_Bound (Etype (Indx)), OK1, UL, UU);
3067 if OK1 then
3069 -- The maximum value for Length is the biggest
3070 -- possible gap between the values of the bounds.
3071 -- But of course, this value cannot be negative.
3073 Hir := UI_Max (Uint_0, UU - LL);
3075 -- For constrained arrays, the minimum value for
3076 -- Length is taken from the actual value of the
3077 -- bounds, since the index will be exactly of
3078 -- this subtype.
3080 if Is_Constrained (Atyp) then
3081 Lor := UI_Max (Uint_0, UL - LU);
3083 -- For an unconstrained array, the minimum value
3084 -- for length is always zero.
3086 else
3087 Lor := Uint_0;
3088 end if;
3089 end if;
3090 end if;
3091 end;
3093 -- No special handling for other attributes
3094 -- Probably more opportunities exist here ???
3096 when others =>
3097 OK1 := False;
3099 end case;
3101 -- For type conversion from one discrete type to another, we
3102 -- can refine the range using the converted value.
3104 when N_Type_Conversion =>
3105 Determine_Range (Expression (N), OK1, Lor, Hir);
3107 -- Nothing special to do for all other expression kinds
3109 when others =>
3110 OK1 := False;
3111 Lor := No_Uint;
3112 Hir := No_Uint;
3113 end case;
3115 -- At this stage, if OK1 is true, then we know that the actual
3116 -- result of the computed expression is in the range Lor .. Hir.
3117 -- We can use this to restrict the possible range of results.
3119 if OK1 then
3121 -- If the refined value of the low bound is greater than the
3122 -- type high bound, then reset it to the more restrictive
3123 -- value. However, we do NOT do this for the case of a modular
3124 -- type where the possible upper bound on the value is above the
3125 -- base type high bound, because that means the result could wrap.
3127 if Lor > Lo
3128 and then not (Is_Modular_Integer_Type (Typ)
3129 and then Hir > Hbound)
3130 then
3131 Lo := Lor;
3132 end if;
3134 -- Similarly, if the refined value of the high bound is less
3135 -- than the value so far, then reset it to the more restrictive
3136 -- value. Again, we do not do this if the refined low bound is
3137 -- negative for a modular type, since this would wrap.
3139 if Hir < Hi
3140 and then not (Is_Modular_Integer_Type (Typ)
3141 and then Lor < Uint_0)
3142 then
3143 Hi := Hir;
3144 end if;
3145 end if;
3147 -- Set cache entry for future call and we are all done
3149 Determine_Range_Cache_N (Cindex) := N;
3150 Determine_Range_Cache_Lo (Cindex) := Lo;
3151 Determine_Range_Cache_Hi (Cindex) := Hi;
3152 return;
3154 -- If any exception occurs, it means that we have some bug in the compiler
3155 -- possibly triggered by a previous error, or by some unforseen peculiar
3156 -- occurrence. However, this is only an optimization attempt, so there is
3157 -- really no point in crashing the compiler. Instead we just decide, too
3158 -- bad, we can't figure out a range in this case after all.
3160 exception
3161 when others =>
3163 -- Debug flag K disables this behavior (useful for debugging)
3165 if Debug_Flag_K then
3166 raise;
3167 else
3168 OK := False;
3169 Lo := No_Uint;
3170 Hi := No_Uint;
3171 return;
3172 end if;
3173 end Determine_Range;
3175 ------------------------------------
3176 -- Discriminant_Checks_Suppressed --
3177 ------------------------------------
3179 function Discriminant_Checks_Suppressed (E : Entity_Id) return Boolean is
3180 begin
3181 if Present (E) then
3182 if Is_Unchecked_Union (E) then
3183 return True;
3184 elsif Checks_May_Be_Suppressed (E) then
3185 return Is_Check_Suppressed (E, Discriminant_Check);
3186 end if;
3187 end if;
3189 return Scope_Suppress (Discriminant_Check);
3190 end Discriminant_Checks_Suppressed;
3192 --------------------------------
3193 -- Division_Checks_Suppressed --
3194 --------------------------------
3196 function Division_Checks_Suppressed (E : Entity_Id) return Boolean is
3197 begin
3198 if Present (E) and then Checks_May_Be_Suppressed (E) then
3199 return Is_Check_Suppressed (E, Division_Check);
3200 else
3201 return Scope_Suppress (Division_Check);
3202 end if;
3203 end Division_Checks_Suppressed;
3205 -----------------------------------
3206 -- Elaboration_Checks_Suppressed --
3207 -----------------------------------
3209 function Elaboration_Checks_Suppressed (E : Entity_Id) return Boolean is
3210 begin
3211 if Present (E) then
3212 if Kill_Elaboration_Checks (E) then
3213 return True;
3214 elsif Checks_May_Be_Suppressed (E) then
3215 return Is_Check_Suppressed (E, Elaboration_Check);
3216 end if;
3217 end if;
3219 return Scope_Suppress (Elaboration_Check);
3220 end Elaboration_Checks_Suppressed;
3222 ---------------------------
3223 -- Enable_Overflow_Check --
3224 ---------------------------
3226 procedure Enable_Overflow_Check (N : Node_Id) is
3227 Typ : constant Entity_Id := Base_Type (Etype (N));
3228 Chk : Nat;
3229 OK : Boolean;
3230 Ent : Entity_Id;
3231 Ofs : Uint;
3232 Lo : Uint;
3233 Hi : Uint;
3235 begin
3236 if Debug_Flag_CC then
3237 w ("Enable_Overflow_Check for node ", Int (N));
3238 Write_Str (" Source location = ");
3239 wl (Sloc (N));
3240 pg (N);
3241 end if;
3243 -- Nothing to do if the range of the result is known OK. We skip
3244 -- this for conversions, since the caller already did the check,
3245 -- and in any case the condition for deleting the check for a
3246 -- type conversion is different in any case.
3248 if Nkind (N) /= N_Type_Conversion then
3249 Determine_Range (N, OK, Lo, Hi);
3251 -- Note in the test below that we assume that if a bound of the
3252 -- range is equal to that of the type. That's not quite accurate
3253 -- but we do this for the following reasons:
3255 -- a) The way that Determine_Range works, it will typically report
3256 -- the bounds of the value as being equal to the bounds of the
3257 -- type, because it either can't tell anything more precise, or
3258 -- does not think it is worth the effort to be more precise.
3260 -- b) It is very unusual to have a situation in which this would
3261 -- generate an unnecessary overflow check (an example would be
3262 -- a subtype with a range 0 .. Integer'Last - 1 to which the
3263 -- literal value one is added.
3265 -- c) The alternative is a lot of special casing in this routine
3266 -- which would partially duplicate Determine_Range processing.
3268 if OK
3269 and then Lo > Expr_Value (Type_Low_Bound (Typ))
3270 and then Hi < Expr_Value (Type_High_Bound (Typ))
3271 then
3272 if Debug_Flag_CC then
3273 w ("No overflow check required");
3274 end if;
3276 return;
3277 end if;
3278 end if;
3280 -- If not in optimizing mode, set flag and we are done. We are also
3281 -- done (and just set the flag) if the type is not a discrete type,
3282 -- since it is not worth the effort to eliminate checks for other
3283 -- than discrete types. In addition, we take this same path if we
3284 -- have stored the maximum number of checks possible already (a
3285 -- very unlikely situation, but we do not want to blow up!)
3287 if Optimization_Level = 0
3288 or else not Is_Discrete_Type (Etype (N))
3289 or else Num_Saved_Checks = Saved_Checks'Last
3290 then
3291 Set_Do_Overflow_Check (N, True);
3293 if Debug_Flag_CC then
3294 w ("Optimization off");
3295 end if;
3297 return;
3298 end if;
3300 -- Otherwise evaluate and check the expression
3302 Find_Check
3303 (Expr => N,
3304 Check_Type => 'O',
3305 Target_Type => Empty,
3306 Entry_OK => OK,
3307 Check_Num => Chk,
3308 Ent => Ent,
3309 Ofs => Ofs);
3311 if Debug_Flag_CC then
3312 w ("Called Find_Check");
3313 w (" OK = ", OK);
3315 if OK then
3316 w (" Check_Num = ", Chk);
3317 w (" Ent = ", Int (Ent));
3318 Write_Str (" Ofs = ");
3319 pid (Ofs);
3320 end if;
3321 end if;
3323 -- If check is not of form to optimize, then set flag and we are done
3325 if not OK then
3326 Set_Do_Overflow_Check (N, True);
3327 return;
3328 end if;
3330 -- If check is already performed, then return without setting flag
3332 if Chk /= 0 then
3333 if Debug_Flag_CC then
3334 w ("Check suppressed!");
3335 end if;
3337 return;
3338 end if;
3340 -- Here we will make a new entry for the new check
3342 Set_Do_Overflow_Check (N, True);
3343 Num_Saved_Checks := Num_Saved_Checks + 1;
3344 Saved_Checks (Num_Saved_Checks) :=
3345 (Killed => False,
3346 Entity => Ent,
3347 Offset => Ofs,
3348 Check_Type => 'O',
3349 Target_Type => Empty);
3351 if Debug_Flag_CC then
3352 w ("Make new entry, check number = ", Num_Saved_Checks);
3353 w (" Entity = ", Int (Ent));
3354 Write_Str (" Offset = ");
3355 pid (Ofs);
3356 w (" Check_Type = O");
3357 w (" Target_Type = Empty");
3358 end if;
3360 -- If we get an exception, then something went wrong, probably because
3361 -- of an error in the structure of the tree due to an incorrect program.
3362 -- Or it may be a bug in the optimization circuit. In either case the
3363 -- safest thing is simply to set the check flag unconditionally.
3365 exception
3366 when others =>
3367 Set_Do_Overflow_Check (N, True);
3369 if Debug_Flag_CC then
3370 w (" exception occurred, overflow flag set");
3371 end if;
3373 return;
3374 end Enable_Overflow_Check;
3376 ------------------------
3377 -- Enable_Range_Check --
3378 ------------------------
3380 procedure Enable_Range_Check (N : Node_Id) is
3381 Chk : Nat;
3382 OK : Boolean;
3383 Ent : Entity_Id;
3384 Ofs : Uint;
3385 Ttyp : Entity_Id;
3386 P : Node_Id;
3388 begin
3389 -- Return if unchecked type conversion with range check killed.
3390 -- In this case we never set the flag (that's what Kill_Range_Check
3391 -- is all about!)
3393 if Nkind (N) = N_Unchecked_Type_Conversion
3394 and then Kill_Range_Check (N)
3395 then
3396 return;
3397 end if;
3399 -- Debug trace output
3401 if Debug_Flag_CC then
3402 w ("Enable_Range_Check for node ", Int (N));
3403 Write_Str (" Source location = ");
3404 wl (Sloc (N));
3405 pg (N);
3406 end if;
3408 -- If not in optimizing mode, set flag and we are done. We are also
3409 -- done (and just set the flag) if the type is not a discrete type,
3410 -- since it is not worth the effort to eliminate checks for other
3411 -- than discrete types. In addition, we take this same path if we
3412 -- have stored the maximum number of checks possible already (a
3413 -- very unlikely situation, but we do not want to blow up!)
3415 if Optimization_Level = 0
3416 or else No (Etype (N))
3417 or else not Is_Discrete_Type (Etype (N))
3418 or else Num_Saved_Checks = Saved_Checks'Last
3419 then
3420 Set_Do_Range_Check (N, True);
3422 if Debug_Flag_CC then
3423 w ("Optimization off");
3424 end if;
3426 return;
3427 end if;
3429 -- Otherwise find out the target type
3431 P := Parent (N);
3433 -- For assignment, use left side subtype
3435 if Nkind (P) = N_Assignment_Statement
3436 and then Expression (P) = N
3437 then
3438 Ttyp := Etype (Name (P));
3440 -- For indexed component, use subscript subtype
3442 elsif Nkind (P) = N_Indexed_Component then
3443 declare
3444 Atyp : Entity_Id;
3445 Indx : Node_Id;
3446 Subs : Node_Id;
3448 begin
3449 Atyp := Etype (Prefix (P));
3451 if Is_Access_Type (Atyp) then
3452 Atyp := Designated_Type (Atyp);
3454 -- If the prefix is an access to an unconstrained array,
3455 -- perform check unconditionally: it depends on the bounds
3456 -- of an object and we cannot currently recognize whether
3457 -- the test may be redundant.
3459 if not Is_Constrained (Atyp) then
3460 Set_Do_Range_Check (N, True);
3461 return;
3462 end if;
3464 -- Ditto if the prefix is an explicit dereference whose
3465 -- designated type is unconstrained.
3467 elsif Nkind (Prefix (P)) = N_Explicit_Dereference
3468 and then not Is_Constrained (Atyp)
3469 then
3470 Set_Do_Range_Check (N, True);
3471 return;
3472 end if;
3474 Indx := First_Index (Atyp);
3475 Subs := First (Expressions (P));
3476 loop
3477 if Subs = N then
3478 Ttyp := Etype (Indx);
3479 exit;
3480 end if;
3482 Next_Index (Indx);
3483 Next (Subs);
3484 end loop;
3485 end;
3487 -- For now, ignore all other cases, they are not so interesting
3489 else
3490 if Debug_Flag_CC then
3491 w (" target type not found, flag set");
3492 end if;
3494 Set_Do_Range_Check (N, True);
3495 return;
3496 end if;
3498 -- Evaluate and check the expression
3500 Find_Check
3501 (Expr => N,
3502 Check_Type => 'R',
3503 Target_Type => Ttyp,
3504 Entry_OK => OK,
3505 Check_Num => Chk,
3506 Ent => Ent,
3507 Ofs => Ofs);
3509 if Debug_Flag_CC then
3510 w ("Called Find_Check");
3511 w ("Target_Typ = ", Int (Ttyp));
3512 w (" OK = ", OK);
3514 if OK then
3515 w (" Check_Num = ", Chk);
3516 w (" Ent = ", Int (Ent));
3517 Write_Str (" Ofs = ");
3518 pid (Ofs);
3519 end if;
3520 end if;
3522 -- If check is not of form to optimize, then set flag and we are done
3524 if not OK then
3525 if Debug_Flag_CC then
3526 w (" expression not of optimizable type, flag set");
3527 end if;
3529 Set_Do_Range_Check (N, True);
3530 return;
3531 end if;
3533 -- If check is already performed, then return without setting flag
3535 if Chk /= 0 then
3536 if Debug_Flag_CC then
3537 w ("Check suppressed!");
3538 end if;
3540 return;
3541 end if;
3543 -- Here we will make a new entry for the new check
3545 Set_Do_Range_Check (N, True);
3546 Num_Saved_Checks := Num_Saved_Checks + 1;
3547 Saved_Checks (Num_Saved_Checks) :=
3548 (Killed => False,
3549 Entity => Ent,
3550 Offset => Ofs,
3551 Check_Type => 'R',
3552 Target_Type => Ttyp);
3554 if Debug_Flag_CC then
3555 w ("Make new entry, check number = ", Num_Saved_Checks);
3556 w (" Entity = ", Int (Ent));
3557 Write_Str (" Offset = ");
3558 pid (Ofs);
3559 w (" Check_Type = R");
3560 w (" Target_Type = ", Int (Ttyp));
3561 pg (Ttyp);
3562 end if;
3564 -- If we get an exception, then something went wrong, probably because
3565 -- of an error in the structure of the tree due to an incorrect program.
3566 -- Or it may be a bug in the optimization circuit. In either case the
3567 -- safest thing is simply to set the check flag unconditionally.
3569 exception
3570 when others =>
3571 Set_Do_Range_Check (N, True);
3573 if Debug_Flag_CC then
3574 w (" exception occurred, range flag set");
3575 end if;
3577 return;
3578 end Enable_Range_Check;
3580 ------------------
3581 -- Ensure_Valid --
3582 ------------------
3584 procedure Ensure_Valid (Expr : Node_Id; Holes_OK : Boolean := False) is
3585 Typ : constant Entity_Id := Etype (Expr);
3587 begin
3588 -- Ignore call if we are not doing any validity checking
3590 if not Validity_Checks_On then
3591 return;
3593 -- Ignore call if range checks suppressed on entity in question
3595 elsif Is_Entity_Name (Expr)
3596 and then Range_Checks_Suppressed (Entity (Expr))
3597 then
3598 return;
3600 -- No check required if expression is from the expander, we assume
3601 -- the expander will generate whatever checks are needed. Note that
3602 -- this is not just an optimization, it avoids infinite recursions!
3604 -- Unchecked conversions must be checked, unless they are initialized
3605 -- scalar values, as in a component assignment in an init proc.
3607 -- In addition, we force a check if Force_Validity_Checks is set
3609 elsif not Comes_From_Source (Expr)
3610 and then not Force_Validity_Checks
3611 and then (Nkind (Expr) /= N_Unchecked_Type_Conversion
3612 or else Kill_Range_Check (Expr))
3613 then
3614 return;
3616 -- No check required if expression is known to have valid value
3618 elsif Expr_Known_Valid (Expr) then
3619 return;
3621 -- No check required if checks off
3623 elsif Range_Checks_Suppressed (Typ) then
3624 return;
3626 -- Ignore case of enumeration with holes where the flag is set not
3627 -- to worry about holes, since no special validity check is needed
3629 elsif Is_Enumeration_Type (Typ)
3630 and then Has_Non_Standard_Rep (Typ)
3631 and then Holes_OK
3632 then
3633 return;
3635 -- No check required on the left-hand side of an assignment
3637 elsif Nkind (Parent (Expr)) = N_Assignment_Statement
3638 and then Expr = Name (Parent (Expr))
3639 then
3640 return;
3642 -- An annoying special case. If this is an out parameter of a scalar
3643 -- type, then the value is not going to be accessed, therefore it is
3644 -- inappropriate to do any validity check at the call site.
3646 else
3647 -- Only need to worry about scalar types
3649 if Is_Scalar_Type (Typ) then
3650 declare
3651 P : Node_Id;
3652 N : Node_Id;
3653 E : Entity_Id;
3654 F : Entity_Id;
3655 A : Node_Id;
3656 L : List_Id;
3658 begin
3659 -- Find actual argument (which may be a parameter association)
3660 -- and the parent of the actual argument (the call statement)
3662 N := Expr;
3663 P := Parent (Expr);
3665 if Nkind (P) = N_Parameter_Association then
3666 N := P;
3667 P := Parent (N);
3668 end if;
3670 -- Only need to worry if we are argument of a procedure
3671 -- call since functions don't have out parameters. If this
3672 -- is an indirect or dispatching call, get signature from
3673 -- the subprogram type.
3675 if Nkind (P) = N_Procedure_Call_Statement then
3676 L := Parameter_Associations (P);
3678 if Is_Entity_Name (Name (P)) then
3679 E := Entity (Name (P));
3680 else
3681 pragma Assert (Nkind (Name (P)) = N_Explicit_Dereference);
3682 E := Etype (Name (P));
3683 end if;
3685 -- Only need to worry if there are indeed actuals, and
3686 -- if this could be a procedure call, otherwise we cannot
3687 -- get a match (either we are not an argument, or the
3688 -- mode of the formal is not OUT). This test also filters
3689 -- out the generic case.
3691 if Is_Non_Empty_List (L)
3692 and then Is_Subprogram (E)
3693 then
3694 -- This is the loop through parameters, looking to
3695 -- see if there is an OUT parameter for which we are
3696 -- the argument.
3698 F := First_Formal (E);
3699 A := First (L);
3701 while Present (F) loop
3702 if Ekind (F) = E_Out_Parameter and then A = N then
3703 return;
3704 end if;
3706 Next_Formal (F);
3707 Next (A);
3708 end loop;
3709 end if;
3710 end if;
3711 end;
3712 end if;
3713 end if;
3715 -- If we fall through, a validity check is required. Note that it would
3716 -- not be good to set Do_Range_Check, even in contexts where this is
3717 -- permissible, since this flag causes checking against the target type,
3718 -- not the source type in contexts such as assignments
3720 Insert_Valid_Check (Expr);
3721 end Ensure_Valid;
3723 ----------------------
3724 -- Expr_Known_Valid --
3725 ----------------------
3727 function Expr_Known_Valid (Expr : Node_Id) return Boolean is
3728 Typ : constant Entity_Id := Etype (Expr);
3730 begin
3731 -- Non-scalar types are always considered valid, since they never
3732 -- give rise to the issues of erroneous or bounded error behavior
3733 -- that are the concern. In formal reference manual terms the
3734 -- notion of validity only applies to scalar types. Note that
3735 -- even when packed arrays are represented using modular types,
3736 -- they are still arrays semantically, so they are also always
3737 -- valid (in particular, the unused bits can be random rubbish
3738 -- without affecting the validity of the array value).
3740 if not Is_Scalar_Type (Typ) or else Is_Packed_Array_Type (Typ) then
3741 return True;
3743 -- If no validity checking, then everything is considered valid
3745 elsif not Validity_Checks_On then
3746 return True;
3748 -- Floating-point types are considered valid unless floating-point
3749 -- validity checks have been specifically turned on.
3751 elsif Is_Floating_Point_Type (Typ)
3752 and then not Validity_Check_Floating_Point
3753 then
3754 return True;
3756 -- If the expression is the value of an object that is known to
3757 -- be valid, then clearly the expression value itself is valid.
3759 elsif Is_Entity_Name (Expr)
3760 and then Is_Known_Valid (Entity (Expr))
3761 then
3762 return True;
3764 -- If the type is one for which all values are known valid, then
3765 -- we are sure that the value is valid except in the slightly odd
3766 -- case where the expression is a reference to a variable whose size
3767 -- has been explicitly set to a value greater than the object size.
3769 elsif Is_Known_Valid (Typ) then
3770 if Is_Entity_Name (Expr)
3771 and then Ekind (Entity (Expr)) = E_Variable
3772 and then Esize (Entity (Expr)) > Esize (Typ)
3773 then
3774 return False;
3775 else
3776 return True;
3777 end if;
3779 -- Integer and character literals always have valid values, where
3780 -- appropriate these will be range checked in any case.
3782 elsif Nkind (Expr) = N_Integer_Literal
3783 or else
3784 Nkind (Expr) = N_Character_Literal
3785 then
3786 return True;
3788 -- If we have a type conversion or a qualification of a known valid
3789 -- value, then the result will always be valid.
3791 elsif Nkind (Expr) = N_Type_Conversion
3792 or else
3793 Nkind (Expr) = N_Qualified_Expression
3794 then
3795 return Expr_Known_Valid (Expression (Expr));
3797 -- The result of any function call or operator is always considered
3798 -- valid, since we assume the necessary checks are done by the call.
3799 -- For operators on floating-point operations, we must also check
3800 -- when the operation is the right-hand side of an assignment, or
3801 -- is an actual in a call.
3803 elsif
3804 Nkind (Expr) in N_Binary_Op or else Nkind (Expr) in N_Unary_Op
3805 then
3806 if Is_Floating_Point_Type (Typ)
3807 and then Validity_Check_Floating_Point
3808 and then
3809 (Nkind (Parent (Expr)) = N_Assignment_Statement
3810 or else Nkind (Parent (Expr)) = N_Function_Call
3811 or else Nkind (Parent (Expr)) = N_Parameter_Association)
3812 then
3813 return False;
3814 else
3815 return True;
3816 end if;
3818 elsif Nkind (Expr) = N_Function_Call then
3819 return True;
3821 -- For all other cases, we do not know the expression is valid
3823 else
3824 return False;
3825 end if;
3826 end Expr_Known_Valid;
3828 ----------------
3829 -- Find_Check --
3830 ----------------
3832 procedure Find_Check
3833 (Expr : Node_Id;
3834 Check_Type : Character;
3835 Target_Type : Entity_Id;
3836 Entry_OK : out Boolean;
3837 Check_Num : out Nat;
3838 Ent : out Entity_Id;
3839 Ofs : out Uint)
3841 function Within_Range_Of
3842 (Target_Type : Entity_Id;
3843 Check_Type : Entity_Id) return Boolean;
3844 -- Given a requirement for checking a range against Target_Type, and
3845 -- and a range Check_Type against which a check has already been made,
3846 -- determines if the check against check type is sufficient to ensure
3847 -- that no check against Target_Type is required.
3849 ---------------------
3850 -- Within_Range_Of --
3851 ---------------------
3853 function Within_Range_Of
3854 (Target_Type : Entity_Id;
3855 Check_Type : Entity_Id) return Boolean
3857 begin
3858 if Target_Type = Check_Type then
3859 return True;
3861 else
3862 declare
3863 Tlo : constant Node_Id := Type_Low_Bound (Target_Type);
3864 Thi : constant Node_Id := Type_High_Bound (Target_Type);
3865 Clo : constant Node_Id := Type_Low_Bound (Check_Type);
3866 Chi : constant Node_Id := Type_High_Bound (Check_Type);
3868 begin
3869 if (Tlo = Clo
3870 or else (Compile_Time_Known_Value (Tlo)
3871 and then
3872 Compile_Time_Known_Value (Clo)
3873 and then
3874 Expr_Value (Clo) >= Expr_Value (Tlo)))
3875 and then
3876 (Thi = Chi
3877 or else (Compile_Time_Known_Value (Thi)
3878 and then
3879 Compile_Time_Known_Value (Chi)
3880 and then
3881 Expr_Value (Chi) <= Expr_Value (Clo)))
3882 then
3883 return True;
3884 else
3885 return False;
3886 end if;
3887 end;
3888 end if;
3889 end Within_Range_Of;
3891 -- Start of processing for Find_Check
3893 begin
3894 -- Establish default, to avoid warnings from GCC
3896 Check_Num := 0;
3898 -- Case of expression is simple entity reference
3900 if Is_Entity_Name (Expr) then
3901 Ent := Entity (Expr);
3902 Ofs := Uint_0;
3904 -- Case of expression is entity + known constant
3906 elsif Nkind (Expr) = N_Op_Add
3907 and then Compile_Time_Known_Value (Right_Opnd (Expr))
3908 and then Is_Entity_Name (Left_Opnd (Expr))
3909 then
3910 Ent := Entity (Left_Opnd (Expr));
3911 Ofs := Expr_Value (Right_Opnd (Expr));
3913 -- Case of expression is entity - known constant
3915 elsif Nkind (Expr) = N_Op_Subtract
3916 and then Compile_Time_Known_Value (Right_Opnd (Expr))
3917 and then Is_Entity_Name (Left_Opnd (Expr))
3918 then
3919 Ent := Entity (Left_Opnd (Expr));
3920 Ofs := UI_Negate (Expr_Value (Right_Opnd (Expr)));
3922 -- Any other expression is not of the right form
3924 else
3925 Ent := Empty;
3926 Ofs := Uint_0;
3927 Entry_OK := False;
3928 return;
3929 end if;
3931 -- Come here with expression of appropriate form, check if
3932 -- entity is an appropriate one for our purposes.
3934 if (Ekind (Ent) = E_Variable
3935 or else
3936 Ekind (Ent) = E_Constant
3937 or else
3938 Ekind (Ent) = E_Loop_Parameter
3939 or else
3940 Ekind (Ent) = E_In_Parameter)
3941 and then not Is_Library_Level_Entity (Ent)
3942 then
3943 Entry_OK := True;
3944 else
3945 Entry_OK := False;
3946 return;
3947 end if;
3949 -- See if there is matching check already
3951 for J in reverse 1 .. Num_Saved_Checks loop
3952 declare
3953 SC : Saved_Check renames Saved_Checks (J);
3955 begin
3956 if SC.Killed = False
3957 and then SC.Entity = Ent
3958 and then SC.Offset = Ofs
3959 and then SC.Check_Type = Check_Type
3960 and then Within_Range_Of (Target_Type, SC.Target_Type)
3961 then
3962 Check_Num := J;
3963 return;
3964 end if;
3965 end;
3966 end loop;
3968 -- If we fall through entry was not found
3970 Check_Num := 0;
3971 return;
3972 end Find_Check;
3974 ---------------------------------
3975 -- Generate_Discriminant_Check --
3976 ---------------------------------
3978 -- Note: the code for this procedure is derived from the
3979 -- emit_discriminant_check routine a-trans.c v1.659.
3981 procedure Generate_Discriminant_Check (N : Node_Id) is
3982 Loc : constant Source_Ptr := Sloc (N);
3983 Pref : constant Node_Id := Prefix (N);
3984 Sel : constant Node_Id := Selector_Name (N);
3986 Orig_Comp : constant Entity_Id :=
3987 Original_Record_Component (Entity (Sel));
3988 -- The original component to be checked
3990 Discr_Fct : constant Entity_Id :=
3991 Discriminant_Checking_Func (Orig_Comp);
3992 -- The discriminant checking function
3994 Discr : Entity_Id;
3995 -- One discriminant to be checked in the type
3997 Real_Discr : Entity_Id;
3998 -- Actual discriminant in the call
4000 Pref_Type : Entity_Id;
4001 -- Type of relevant prefix (ignoring private/access stuff)
4003 Args : List_Id;
4004 -- List of arguments for function call
4006 Formal : Entity_Id;
4007 -- Keep track of the formal corresponding to the actual we build
4008 -- for each discriminant, in order to be able to perform the
4009 -- necessary type conversions.
4011 Scomp : Node_Id;
4012 -- Selected component reference for checking function argument
4014 begin
4015 Pref_Type := Etype (Pref);
4017 -- Force evaluation of the prefix, so that it does not get evaluated
4018 -- twice (once for the check, once for the actual reference). Such a
4019 -- double evaluation is always a potential source of inefficiency,
4020 -- and is functionally incorrect in the volatile case, or when the
4021 -- prefix may have side-effects. An entity or a component of an
4022 -- entity requires no evaluation.
4024 if Is_Entity_Name (Pref) then
4025 if Treat_As_Volatile (Entity (Pref)) then
4026 Force_Evaluation (Pref, Name_Req => True);
4027 end if;
4029 elsif Treat_As_Volatile (Etype (Pref)) then
4030 Force_Evaluation (Pref, Name_Req => True);
4032 elsif Nkind (Pref) = N_Selected_Component
4033 and then Is_Entity_Name (Prefix (Pref))
4034 then
4035 null;
4037 else
4038 Force_Evaluation (Pref, Name_Req => True);
4039 end if;
4041 -- For a tagged type, use the scope of the original component to
4042 -- obtain the type, because ???
4044 if Is_Tagged_Type (Scope (Orig_Comp)) then
4045 Pref_Type := Scope (Orig_Comp);
4047 -- For an untagged derived type, use the discriminants of the
4048 -- parent which have been renamed in the derivation, possibly
4049 -- by a one-to-many discriminant constraint.
4050 -- For non-tagged type, initially get the Etype of the prefix
4052 else
4053 if Is_Derived_Type (Pref_Type)
4054 and then Number_Discriminants (Pref_Type) /=
4055 Number_Discriminants (Etype (Base_Type (Pref_Type)))
4056 then
4057 Pref_Type := Etype (Base_Type (Pref_Type));
4058 end if;
4059 end if;
4061 -- We definitely should have a checking function, This routine should
4062 -- not be called if no discriminant checking function is present.
4064 pragma Assert (Present (Discr_Fct));
4066 -- Create the list of the actual parameters for the call. This list
4067 -- is the list of the discriminant fields of the record expression to
4068 -- be discriminant checked.
4070 Args := New_List;
4071 Formal := First_Formal (Discr_Fct);
4072 Discr := First_Discriminant (Pref_Type);
4073 while Present (Discr) loop
4075 -- If we have a corresponding discriminant field, and a parent
4076 -- subtype is present, then we want to use the corresponding
4077 -- discriminant since this is the one with the useful value.
4079 if Present (Corresponding_Discriminant (Discr))
4080 and then Ekind (Pref_Type) = E_Record_Type
4081 and then Present (Parent_Subtype (Pref_Type))
4082 then
4083 Real_Discr := Corresponding_Discriminant (Discr);
4084 else
4085 Real_Discr := Discr;
4086 end if;
4088 -- Construct the reference to the discriminant
4090 Scomp :=
4091 Make_Selected_Component (Loc,
4092 Prefix =>
4093 Unchecked_Convert_To (Pref_Type,
4094 Duplicate_Subexpr (Pref)),
4095 Selector_Name => New_Occurrence_Of (Real_Discr, Loc));
4097 -- Manually analyze and resolve this selected component. We really
4098 -- want it just as it appears above, and do not want the expander
4099 -- playing discriminal games etc with this reference. Then we
4100 -- append the argument to the list we are gathering.
4102 Set_Etype (Scomp, Etype (Real_Discr));
4103 Set_Analyzed (Scomp, True);
4104 Append_To (Args, Convert_To (Etype (Formal), Scomp));
4106 Next_Formal_With_Extras (Formal);
4107 Next_Discriminant (Discr);
4108 end loop;
4110 -- Now build and insert the call
4112 Insert_Action (N,
4113 Make_Raise_Constraint_Error (Loc,
4114 Condition =>
4115 Make_Function_Call (Loc,
4116 Name => New_Occurrence_Of (Discr_Fct, Loc),
4117 Parameter_Associations => Args),
4118 Reason => CE_Discriminant_Check_Failed));
4119 end Generate_Discriminant_Check;
4121 ---------------------------
4122 -- Generate_Index_Checks --
4123 ---------------------------
4125 procedure Generate_Index_Checks (N : Node_Id) is
4126 Loc : constant Source_Ptr := Sloc (N);
4127 A : constant Node_Id := Prefix (N);
4128 Sub : Node_Id;
4129 Ind : Nat;
4130 Num : List_Id;
4132 begin
4133 Sub := First (Expressions (N));
4134 Ind := 1;
4135 while Present (Sub) loop
4136 if Do_Range_Check (Sub) then
4137 Set_Do_Range_Check (Sub, False);
4139 -- Force evaluation except for the case of a simple name of
4140 -- a non-volatile entity.
4142 if not Is_Entity_Name (Sub)
4143 or else Treat_As_Volatile (Entity (Sub))
4144 then
4145 Force_Evaluation (Sub);
4146 end if;
4148 -- Generate a raise of constraint error with the appropriate
4149 -- reason and a condition of the form:
4151 -- Base_Type(Sub) not in array'range (subscript)
4153 -- Note that the reason we generate the conversion to the
4154 -- base type here is that we definitely want the range check
4155 -- to take place, even if it looks like the subtype is OK.
4156 -- Optimization considerations that allow us to omit the
4157 -- check have already been taken into account in the setting
4158 -- of the Do_Range_Check flag earlier on.
4160 if Ind = 1 then
4161 Num := No_List;
4162 else
4163 Num := New_List (Make_Integer_Literal (Loc, Ind));
4164 end if;
4166 Insert_Action (N,
4167 Make_Raise_Constraint_Error (Loc,
4168 Condition =>
4169 Make_Not_In (Loc,
4170 Left_Opnd =>
4171 Convert_To (Base_Type (Etype (Sub)),
4172 Duplicate_Subexpr_Move_Checks (Sub)),
4173 Right_Opnd =>
4174 Make_Attribute_Reference (Loc,
4175 Prefix => Duplicate_Subexpr_Move_Checks (A),
4176 Attribute_Name => Name_Range,
4177 Expressions => Num)),
4178 Reason => CE_Index_Check_Failed));
4179 end if;
4181 Ind := Ind + 1;
4182 Next (Sub);
4183 end loop;
4184 end Generate_Index_Checks;
4186 --------------------------
4187 -- Generate_Range_Check --
4188 --------------------------
4190 procedure Generate_Range_Check
4191 (N : Node_Id;
4192 Target_Type : Entity_Id;
4193 Reason : RT_Exception_Code)
4195 Loc : constant Source_Ptr := Sloc (N);
4196 Source_Type : constant Entity_Id := Etype (N);
4197 Source_Base_Type : constant Entity_Id := Base_Type (Source_Type);
4198 Target_Base_Type : constant Entity_Id := Base_Type (Target_Type);
4200 begin
4201 -- First special case, if the source type is already within the
4202 -- range of the target type, then no check is needed (probably we
4203 -- should have stopped Do_Range_Check from being set in the first
4204 -- place, but better late than later in preventing junk code!
4206 -- We do NOT apply this if the source node is a literal, since in
4207 -- this case the literal has already been labeled as having the
4208 -- subtype of the target.
4210 if In_Subrange_Of (Source_Type, Target_Type)
4211 and then not
4212 (Nkind (N) = N_Integer_Literal
4213 or else
4214 Nkind (N) = N_Real_Literal
4215 or else
4216 Nkind (N) = N_Character_Literal
4217 or else
4218 (Is_Entity_Name (N)
4219 and then Ekind (Entity (N)) = E_Enumeration_Literal))
4220 then
4221 return;
4222 end if;
4224 -- We need a check, so force evaluation of the node, so that it does
4225 -- not get evaluated twice (once for the check, once for the actual
4226 -- reference). Such a double evaluation is always a potential source
4227 -- of inefficiency, and is functionally incorrect in the volatile case.
4229 if not Is_Entity_Name (N)
4230 or else Treat_As_Volatile (Entity (N))
4231 then
4232 Force_Evaluation (N);
4233 end if;
4235 -- The easiest case is when Source_Base_Type and Target_Base_Type
4236 -- are the same since in this case we can simply do a direct
4237 -- check of the value of N against the bounds of Target_Type.
4239 -- [constraint_error when N not in Target_Type]
4241 -- Note: this is by far the most common case, for example all cases of
4242 -- checks on the RHS of assignments are in this category, but not all
4243 -- cases are like this. Notably conversions can involve two types.
4245 if Source_Base_Type = Target_Base_Type then
4246 Insert_Action (N,
4247 Make_Raise_Constraint_Error (Loc,
4248 Condition =>
4249 Make_Not_In (Loc,
4250 Left_Opnd => Duplicate_Subexpr (N),
4251 Right_Opnd => New_Occurrence_Of (Target_Type, Loc)),
4252 Reason => Reason));
4254 -- Next test for the case where the target type is within the bounds
4255 -- of the base type of the source type, since in this case we can
4256 -- simply convert these bounds to the base type of T to do the test.
4258 -- [constraint_error when N not in
4259 -- Source_Base_Type (Target_Type'First)
4260 -- ..
4261 -- Source_Base_Type(Target_Type'Last))]
4263 -- The conversions will always work and need no check
4265 elsif In_Subrange_Of (Target_Type, Source_Base_Type) then
4266 Insert_Action (N,
4267 Make_Raise_Constraint_Error (Loc,
4268 Condition =>
4269 Make_Not_In (Loc,
4270 Left_Opnd => Duplicate_Subexpr (N),
4272 Right_Opnd =>
4273 Make_Range (Loc,
4274 Low_Bound =>
4275 Convert_To (Source_Base_Type,
4276 Make_Attribute_Reference (Loc,
4277 Prefix =>
4278 New_Occurrence_Of (Target_Type, Loc),
4279 Attribute_Name => Name_First)),
4281 High_Bound =>
4282 Convert_To (Source_Base_Type,
4283 Make_Attribute_Reference (Loc,
4284 Prefix =>
4285 New_Occurrence_Of (Target_Type, Loc),
4286 Attribute_Name => Name_Last)))),
4287 Reason => Reason));
4289 -- Note that at this stage we now that the Target_Base_Type is
4290 -- not in the range of the Source_Base_Type (since even the
4291 -- Target_Type itself is not in this range). It could still be
4292 -- the case that the Source_Type is in range of the target base
4293 -- type, since we have not checked that case.
4295 -- If that is the case, we can freely convert the source to the
4296 -- target, and then test the target result against the bounds.
4298 elsif In_Subrange_Of (Source_Type, Target_Base_Type) then
4300 -- We make a temporary to hold the value of the converted
4301 -- value (converted to the base type), and then we will
4302 -- do the test against this temporary.
4304 -- Tnn : constant Target_Base_Type := Target_Base_Type (N);
4305 -- [constraint_error when Tnn not in Target_Type]
4307 -- Then the conversion itself is replaced by an occurrence of Tnn
4309 declare
4310 Tnn : constant Entity_Id :=
4311 Make_Defining_Identifier (Loc,
4312 Chars => New_Internal_Name ('T'));
4314 begin
4315 Insert_Actions (N, New_List (
4316 Make_Object_Declaration (Loc,
4317 Defining_Identifier => Tnn,
4318 Object_Definition =>
4319 New_Occurrence_Of (Target_Base_Type, Loc),
4320 Constant_Present => True,
4321 Expression =>
4322 Make_Type_Conversion (Loc,
4323 Subtype_Mark => New_Occurrence_Of (Target_Base_Type, Loc),
4324 Expression => Duplicate_Subexpr (N))),
4326 Make_Raise_Constraint_Error (Loc,
4327 Condition =>
4328 Make_Not_In (Loc,
4329 Left_Opnd => New_Occurrence_Of (Tnn, Loc),
4330 Right_Opnd => New_Occurrence_Of (Target_Type, Loc)),
4332 Reason => Reason)));
4334 Rewrite (N, New_Occurrence_Of (Tnn, Loc));
4335 end;
4337 -- At this stage, we know that we have two scalar types, which are
4338 -- directly convertible, and where neither scalar type has a base
4339 -- range that is in the range of the other scalar type.
4341 -- The only way this can happen is with a signed and unsigned type.
4342 -- So test for these two cases:
4344 else
4345 -- Case of the source is unsigned and the target is signed
4347 if Is_Unsigned_Type (Source_Base_Type)
4348 and then not Is_Unsigned_Type (Target_Base_Type)
4349 then
4350 -- If the source is unsigned and the target is signed, then we
4351 -- know that the source is not shorter than the target (otherwise
4352 -- the source base type would be in the target base type range).
4354 -- In other words, the unsigned type is either the same size
4355 -- as the target, or it is larger. It cannot be smaller.
4357 pragma Assert
4358 (Esize (Source_Base_Type) >= Esize (Target_Base_Type));
4360 -- We only need to check the low bound if the low bound of the
4361 -- target type is non-negative. If the low bound of the target
4362 -- type is negative, then we know that we will fit fine.
4364 -- If the high bound of the target type is negative, then we
4365 -- know we have a constraint error, since we can't possibly
4366 -- have a negative source.
4368 -- With these two checks out of the way, we can do the check
4369 -- using the source type safely
4371 -- This is definitely the most annoying case!
4373 -- [constraint_error
4374 -- when (Target_Type'First >= 0
4375 -- and then
4376 -- N < Source_Base_Type (Target_Type'First))
4377 -- or else Target_Type'Last < 0
4378 -- or else N > Source_Base_Type (Target_Type'Last)];
4380 -- We turn off all checks since we know that the conversions
4381 -- will work fine, given the guards for negative values.
4383 Insert_Action (N,
4384 Make_Raise_Constraint_Error (Loc,
4385 Condition =>
4386 Make_Or_Else (Loc,
4387 Make_Or_Else (Loc,
4388 Left_Opnd =>
4389 Make_And_Then (Loc,
4390 Left_Opnd => Make_Op_Ge (Loc,
4391 Left_Opnd =>
4392 Make_Attribute_Reference (Loc,
4393 Prefix =>
4394 New_Occurrence_Of (Target_Type, Loc),
4395 Attribute_Name => Name_First),
4396 Right_Opnd => Make_Integer_Literal (Loc, Uint_0)),
4398 Right_Opnd =>
4399 Make_Op_Lt (Loc,
4400 Left_Opnd => Duplicate_Subexpr (N),
4401 Right_Opnd =>
4402 Convert_To (Source_Base_Type,
4403 Make_Attribute_Reference (Loc,
4404 Prefix =>
4405 New_Occurrence_Of (Target_Type, Loc),
4406 Attribute_Name => Name_First)))),
4408 Right_Opnd =>
4409 Make_Op_Lt (Loc,
4410 Left_Opnd =>
4411 Make_Attribute_Reference (Loc,
4412 Prefix => New_Occurrence_Of (Target_Type, Loc),
4413 Attribute_Name => Name_Last),
4414 Right_Opnd => Make_Integer_Literal (Loc, Uint_0))),
4416 Right_Opnd =>
4417 Make_Op_Gt (Loc,
4418 Left_Opnd => Duplicate_Subexpr (N),
4419 Right_Opnd =>
4420 Convert_To (Source_Base_Type,
4421 Make_Attribute_Reference (Loc,
4422 Prefix => New_Occurrence_Of (Target_Type, Loc),
4423 Attribute_Name => Name_Last)))),
4425 Reason => Reason),
4426 Suppress => All_Checks);
4428 -- Only remaining possibility is that the source is signed and
4429 -- the target is unsigned
4431 else
4432 pragma Assert (not Is_Unsigned_Type (Source_Base_Type)
4433 and then Is_Unsigned_Type (Target_Base_Type));
4435 -- If the source is signed and the target is unsigned, then
4436 -- we know that the target is not shorter than the source
4437 -- (otherwise the target base type would be in the source
4438 -- base type range).
4440 -- In other words, the unsigned type is either the same size
4441 -- as the target, or it is larger. It cannot be smaller.
4443 -- Clearly we have an error if the source value is negative
4444 -- since no unsigned type can have negative values. If the
4445 -- source type is non-negative, then the check can be done
4446 -- using the target type.
4448 -- Tnn : constant Target_Base_Type (N) := Target_Type;
4450 -- [constraint_error
4451 -- when N < 0 or else Tnn not in Target_Type];
4453 -- We turn off all checks for the conversion of N to the
4454 -- target base type, since we generate the explicit check
4455 -- to ensure that the value is non-negative
4457 declare
4458 Tnn : constant Entity_Id :=
4459 Make_Defining_Identifier (Loc,
4460 Chars => New_Internal_Name ('T'));
4462 begin
4463 Insert_Actions (N, New_List (
4464 Make_Object_Declaration (Loc,
4465 Defining_Identifier => Tnn,
4466 Object_Definition =>
4467 New_Occurrence_Of (Target_Base_Type, Loc),
4468 Constant_Present => True,
4469 Expression =>
4470 Make_Type_Conversion (Loc,
4471 Subtype_Mark =>
4472 New_Occurrence_Of (Target_Base_Type, Loc),
4473 Expression => Duplicate_Subexpr (N))),
4475 Make_Raise_Constraint_Error (Loc,
4476 Condition =>
4477 Make_Or_Else (Loc,
4478 Left_Opnd =>
4479 Make_Op_Lt (Loc,
4480 Left_Opnd => Duplicate_Subexpr (N),
4481 Right_Opnd => Make_Integer_Literal (Loc, Uint_0)),
4483 Right_Opnd =>
4484 Make_Not_In (Loc,
4485 Left_Opnd => New_Occurrence_Of (Tnn, Loc),
4486 Right_Opnd =>
4487 New_Occurrence_Of (Target_Type, Loc))),
4489 Reason => Reason)),
4490 Suppress => All_Checks);
4492 -- Set the Etype explicitly, because Insert_Actions may
4493 -- have placed the declaration in the freeze list for an
4494 -- enclosing construct, and thus it is not analyzed yet.
4496 Set_Etype (Tnn, Target_Base_Type);
4497 Rewrite (N, New_Occurrence_Of (Tnn, Loc));
4498 end;
4499 end if;
4500 end if;
4501 end Generate_Range_Check;
4503 ---------------------
4504 -- Get_Discriminal --
4505 ---------------------
4507 function Get_Discriminal (E : Entity_Id; Bound : Node_Id) return Node_Id is
4508 Loc : constant Source_Ptr := Sloc (E);
4509 D : Entity_Id;
4510 Sc : Entity_Id;
4512 begin
4513 -- The entity E is the type of a private component of the protected
4514 -- type, or the type of a renaming of that component within a protected
4515 -- operation of that type.
4517 Sc := Scope (E);
4519 if Ekind (Sc) /= E_Protected_Type then
4520 Sc := Scope (Sc);
4522 if Ekind (Sc) /= E_Protected_Type then
4523 return Bound;
4524 end if;
4525 end if;
4527 D := First_Discriminant (Sc);
4529 while Present (D)
4530 and then Chars (D) /= Chars (Bound)
4531 loop
4532 Next_Discriminant (D);
4533 end loop;
4535 return New_Occurrence_Of (Discriminal (D), Loc);
4536 end Get_Discriminal;
4538 ------------------
4539 -- Guard_Access --
4540 ------------------
4542 function Guard_Access
4543 (Cond : Node_Id;
4544 Loc : Source_Ptr;
4545 Ck_Node : Node_Id) return Node_Id
4547 begin
4548 if Nkind (Cond) = N_Or_Else then
4549 Set_Paren_Count (Cond, 1);
4550 end if;
4552 if Nkind (Ck_Node) = N_Allocator then
4553 return Cond;
4554 else
4555 return
4556 Make_And_Then (Loc,
4557 Left_Opnd =>
4558 Make_Op_Ne (Loc,
4559 Left_Opnd => Duplicate_Subexpr_No_Checks (Ck_Node),
4560 Right_Opnd => Make_Null (Loc)),
4561 Right_Opnd => Cond);
4562 end if;
4563 end Guard_Access;
4565 -----------------------------
4566 -- Index_Checks_Suppressed --
4567 -----------------------------
4569 function Index_Checks_Suppressed (E : Entity_Id) return Boolean is
4570 begin
4571 if Present (E) and then Checks_May_Be_Suppressed (E) then
4572 return Is_Check_Suppressed (E, Index_Check);
4573 else
4574 return Scope_Suppress (Index_Check);
4575 end if;
4576 end Index_Checks_Suppressed;
4578 ----------------
4579 -- Initialize --
4580 ----------------
4582 procedure Initialize is
4583 begin
4584 for J in Determine_Range_Cache_N'Range loop
4585 Determine_Range_Cache_N (J) := Empty;
4586 end loop;
4587 end Initialize;
4589 -------------------------
4590 -- Insert_Range_Checks --
4591 -------------------------
4593 procedure Insert_Range_Checks
4594 (Checks : Check_Result;
4595 Node : Node_Id;
4596 Suppress_Typ : Entity_Id;
4597 Static_Sloc : Source_Ptr := No_Location;
4598 Flag_Node : Node_Id := Empty;
4599 Do_Before : Boolean := False)
4601 Internal_Flag_Node : Node_Id := Flag_Node;
4602 Internal_Static_Sloc : Source_Ptr := Static_Sloc;
4604 Check_Node : Node_Id;
4605 Checks_On : constant Boolean :=
4606 (not Index_Checks_Suppressed (Suppress_Typ))
4607 or else
4608 (not Range_Checks_Suppressed (Suppress_Typ));
4610 begin
4611 -- For now we just return if Checks_On is false, however this should
4612 -- be enhanced to check for an always True value in the condition
4613 -- and to generate a compilation warning???
4615 if not Expander_Active or else not Checks_On then
4616 return;
4617 end if;
4619 if Static_Sloc = No_Location then
4620 Internal_Static_Sloc := Sloc (Node);
4621 end if;
4623 if No (Flag_Node) then
4624 Internal_Flag_Node := Node;
4625 end if;
4627 for J in 1 .. 2 loop
4628 exit when No (Checks (J));
4630 if Nkind (Checks (J)) = N_Raise_Constraint_Error
4631 and then Present (Condition (Checks (J)))
4632 then
4633 if not Has_Dynamic_Range_Check (Internal_Flag_Node) then
4634 Check_Node := Checks (J);
4635 Mark_Rewrite_Insertion (Check_Node);
4637 if Do_Before then
4638 Insert_Before_And_Analyze (Node, Check_Node);
4639 else
4640 Insert_After_And_Analyze (Node, Check_Node);
4641 end if;
4643 Set_Has_Dynamic_Range_Check (Internal_Flag_Node);
4644 end if;
4646 else
4647 Check_Node :=
4648 Make_Raise_Constraint_Error (Internal_Static_Sloc,
4649 Reason => CE_Range_Check_Failed);
4650 Mark_Rewrite_Insertion (Check_Node);
4652 if Do_Before then
4653 Insert_Before_And_Analyze (Node, Check_Node);
4654 else
4655 Insert_After_And_Analyze (Node, Check_Node);
4656 end if;
4657 end if;
4658 end loop;
4659 end Insert_Range_Checks;
4661 ------------------------
4662 -- Insert_Valid_Check --
4663 ------------------------
4665 procedure Insert_Valid_Check (Expr : Node_Id) is
4666 Loc : constant Source_Ptr := Sloc (Expr);
4667 Exp : Node_Id;
4669 begin
4670 -- Do not insert if checks off, or if not checking validity
4672 if Range_Checks_Suppressed (Etype (Expr))
4673 or else (not Validity_Checks_On)
4674 then
4675 return;
4676 end if;
4678 -- If we have a checked conversion, then validity check applies to
4679 -- the expression inside the conversion, not the result, since if
4680 -- the expression inside is valid, then so is the conversion result.
4682 Exp := Expr;
4683 while Nkind (Exp) = N_Type_Conversion loop
4684 Exp := Expression (Exp);
4685 end loop;
4687 -- Insert the validity check. Note that we do this with validity
4688 -- checks turned off, to avoid recursion, we do not want validity
4689 -- checks on the validity checking code itself!
4691 Validity_Checks_On := False;
4692 Insert_Action
4693 (Expr,
4694 Make_Raise_Constraint_Error (Loc,
4695 Condition =>
4696 Make_Op_Not (Loc,
4697 Right_Opnd =>
4698 Make_Attribute_Reference (Loc,
4699 Prefix =>
4700 Duplicate_Subexpr_No_Checks (Exp, Name_Req => True),
4701 Attribute_Name => Name_Valid)),
4702 Reason => CE_Invalid_Data),
4703 Suppress => All_Checks);
4704 Validity_Checks_On := True;
4705 end Insert_Valid_Check;
4707 ----------------------------------
4708 -- Install_Null_Excluding_Check --
4709 ----------------------------------
4711 procedure Install_Null_Excluding_Check (N : Node_Id) is
4712 Loc : constant Source_Ptr := Sloc (N);
4713 Etyp : constant Entity_Id := Etype (N);
4715 begin
4716 pragma Assert (Is_Access_Type (Etyp));
4718 -- Don't need access check if: 1) we are analyzing a generic, 2) it is
4719 -- known to be non-null, or 3) the check was suppressed on the type
4721 if Inside_A_Generic
4722 or else Access_Checks_Suppressed (Etyp)
4723 then
4724 return;
4726 -- Otherwise install access check
4728 else
4729 Insert_Action (N,
4730 Make_Raise_Constraint_Error (Loc,
4731 Condition =>
4732 Make_Op_Eq (Loc,
4733 Left_Opnd => Duplicate_Subexpr_Move_Checks (N),
4734 Right_Opnd => Make_Null (Loc)),
4735 Reason => CE_Access_Check_Failed));
4736 end if;
4737 end Install_Null_Excluding_Check;
4739 --------------------------
4740 -- Install_Static_Check --
4741 --------------------------
4743 procedure Install_Static_Check (R_Cno : Node_Id; Loc : Source_Ptr) is
4744 Stat : constant Boolean := Is_Static_Expression (R_Cno);
4745 Typ : constant Entity_Id := Etype (R_Cno);
4747 begin
4748 Rewrite (R_Cno,
4749 Make_Raise_Constraint_Error (Loc,
4750 Reason => CE_Range_Check_Failed));
4751 Set_Analyzed (R_Cno);
4752 Set_Etype (R_Cno, Typ);
4753 Set_Raises_Constraint_Error (R_Cno);
4754 Set_Is_Static_Expression (R_Cno, Stat);
4755 end Install_Static_Check;
4757 ---------------------
4758 -- Kill_All_Checks --
4759 ---------------------
4761 procedure Kill_All_Checks is
4762 begin
4763 if Debug_Flag_CC then
4764 w ("Kill_All_Checks");
4765 end if;
4767 -- We reset the number of saved checks to zero, and also modify
4768 -- all stack entries for statement ranges to indicate that the
4769 -- number of checks at each level is now zero.
4771 Num_Saved_Checks := 0;
4773 for J in 1 .. Saved_Checks_TOS loop
4774 Saved_Checks_Stack (J) := 0;
4775 end loop;
4776 end Kill_All_Checks;
4778 -----------------
4779 -- Kill_Checks --
4780 -----------------
4782 procedure Kill_Checks (V : Entity_Id) is
4783 begin
4784 if Debug_Flag_CC then
4785 w ("Kill_Checks for entity", Int (V));
4786 end if;
4788 for J in 1 .. Num_Saved_Checks loop
4789 if Saved_Checks (J).Entity = V then
4790 if Debug_Flag_CC then
4791 w (" Checks killed for saved check ", J);
4792 end if;
4794 Saved_Checks (J).Killed := True;
4795 end if;
4796 end loop;
4797 end Kill_Checks;
4799 ------------------------------
4800 -- Length_Checks_Suppressed --
4801 ------------------------------
4803 function Length_Checks_Suppressed (E : Entity_Id) return Boolean is
4804 begin
4805 if Present (E) and then Checks_May_Be_Suppressed (E) then
4806 return Is_Check_Suppressed (E, Length_Check);
4807 else
4808 return Scope_Suppress (Length_Check);
4809 end if;
4810 end Length_Checks_Suppressed;
4812 --------------------------------
4813 -- Overflow_Checks_Suppressed --
4814 --------------------------------
4816 function Overflow_Checks_Suppressed (E : Entity_Id) return Boolean is
4817 begin
4818 if Present (E) and then Checks_May_Be_Suppressed (E) then
4819 return Is_Check_Suppressed (E, Overflow_Check);
4820 else
4821 return Scope_Suppress (Overflow_Check);
4822 end if;
4823 end Overflow_Checks_Suppressed;
4825 -----------------
4826 -- Range_Check --
4827 -----------------
4829 function Range_Check
4830 (Ck_Node : Node_Id;
4831 Target_Typ : Entity_Id;
4832 Source_Typ : Entity_Id := Empty;
4833 Warn_Node : Node_Id := Empty) return Check_Result
4835 begin
4836 return Selected_Range_Checks
4837 (Ck_Node, Target_Typ, Source_Typ, Warn_Node);
4838 end Range_Check;
4840 -----------------------------
4841 -- Range_Checks_Suppressed --
4842 -----------------------------
4844 function Range_Checks_Suppressed (E : Entity_Id) return Boolean is
4845 begin
4846 if Present (E) then
4848 -- Note: for now we always suppress range checks on Vax float types,
4849 -- since Gigi does not know how to generate these checks.
4851 if Vax_Float (E) then
4852 return True;
4853 elsif Kill_Range_Checks (E) then
4854 return True;
4855 elsif Checks_May_Be_Suppressed (E) then
4856 return Is_Check_Suppressed (E, Range_Check);
4857 end if;
4858 end if;
4860 return Scope_Suppress (Range_Check);
4861 end Range_Checks_Suppressed;
4863 -------------------
4864 -- Remove_Checks --
4865 -------------------
4867 procedure Remove_Checks (Expr : Node_Id) is
4868 Discard : Traverse_Result;
4869 pragma Warnings (Off, Discard);
4871 function Process (N : Node_Id) return Traverse_Result;
4872 -- Process a single node during the traversal
4874 function Traverse is new Traverse_Func (Process);
4875 -- The traversal function itself
4877 -------------
4878 -- Process --
4879 -------------
4881 function Process (N : Node_Id) return Traverse_Result is
4882 begin
4883 if Nkind (N) not in N_Subexpr then
4884 return Skip;
4885 end if;
4887 Set_Do_Range_Check (N, False);
4889 case Nkind (N) is
4890 when N_And_Then =>
4891 Discard := Traverse (Left_Opnd (N));
4892 return Skip;
4894 when N_Attribute_Reference =>
4895 Set_Do_Overflow_Check (N, False);
4897 when N_Function_Call =>
4898 Set_Do_Tag_Check (N, False);
4900 when N_Op =>
4901 Set_Do_Overflow_Check (N, False);
4903 case Nkind (N) is
4904 when N_Op_Divide =>
4905 Set_Do_Division_Check (N, False);
4907 when N_Op_And =>
4908 Set_Do_Length_Check (N, False);
4910 when N_Op_Mod =>
4911 Set_Do_Division_Check (N, False);
4913 when N_Op_Or =>
4914 Set_Do_Length_Check (N, False);
4916 when N_Op_Rem =>
4917 Set_Do_Division_Check (N, False);
4919 when N_Op_Xor =>
4920 Set_Do_Length_Check (N, False);
4922 when others =>
4923 null;
4924 end case;
4926 when N_Or_Else =>
4927 Discard := Traverse (Left_Opnd (N));
4928 return Skip;
4930 when N_Selected_Component =>
4931 Set_Do_Discriminant_Check (N, False);
4933 when N_Type_Conversion =>
4934 Set_Do_Length_Check (N, False);
4935 Set_Do_Tag_Check (N, False);
4936 Set_Do_Overflow_Check (N, False);
4938 when others =>
4939 null;
4940 end case;
4942 return OK;
4943 end Process;
4945 -- Start of processing for Remove_Checks
4947 begin
4948 Discard := Traverse (Expr);
4949 end Remove_Checks;
4951 ----------------------------
4952 -- Selected_Length_Checks --
4953 ----------------------------
4955 function Selected_Length_Checks
4956 (Ck_Node : Node_Id;
4957 Target_Typ : Entity_Id;
4958 Source_Typ : Entity_Id;
4959 Warn_Node : Node_Id) return Check_Result
4961 Loc : constant Source_Ptr := Sloc (Ck_Node);
4962 S_Typ : Entity_Id;
4963 T_Typ : Entity_Id;
4964 Expr_Actual : Node_Id;
4965 Exptyp : Entity_Id;
4966 Cond : Node_Id := Empty;
4967 Do_Access : Boolean := False;
4968 Wnode : Node_Id := Warn_Node;
4969 Ret_Result : Check_Result := (Empty, Empty);
4970 Num_Checks : Natural := 0;
4972 procedure Add_Check (N : Node_Id);
4973 -- Adds the action given to Ret_Result if N is non-Empty
4975 function Get_E_Length (E : Entity_Id; Indx : Nat) return Node_Id;
4976 function Get_N_Length (N : Node_Id; Indx : Nat) return Node_Id;
4977 -- Comments required ???
4979 function Same_Bounds (L : Node_Id; R : Node_Id) return Boolean;
4980 -- True for equal literals and for nodes that denote the same constant
4981 -- entity, even if its value is not a static constant. This includes the
4982 -- case of a discriminal reference within an init proc. Removes some
4983 -- obviously superfluous checks.
4985 function Length_E_Cond
4986 (Exptyp : Entity_Id;
4987 Typ : Entity_Id;
4988 Indx : Nat) return Node_Id;
4989 -- Returns expression to compute:
4990 -- Typ'Length /= Exptyp'Length
4992 function Length_N_Cond
4993 (Expr : Node_Id;
4994 Typ : Entity_Id;
4995 Indx : Nat) return Node_Id;
4996 -- Returns expression to compute:
4997 -- Typ'Length /= Expr'Length
4999 ---------------
5000 -- Add_Check --
5001 ---------------
5003 procedure Add_Check (N : Node_Id) is
5004 begin
5005 if Present (N) then
5007 -- For now, ignore attempt to place more than 2 checks ???
5009 if Num_Checks = 2 then
5010 return;
5011 end if;
5013 pragma Assert (Num_Checks <= 1);
5014 Num_Checks := Num_Checks + 1;
5015 Ret_Result (Num_Checks) := N;
5016 end if;
5017 end Add_Check;
5019 ------------------
5020 -- Get_E_Length --
5021 ------------------
5023 function Get_E_Length (E : Entity_Id; Indx : Nat) return Node_Id is
5024 Pt : constant Entity_Id := Scope (Scope (E));
5025 N : Node_Id;
5026 E1 : Entity_Id := E;
5028 begin
5029 if Ekind (Scope (E)) = E_Record_Type
5030 and then Has_Discriminants (Scope (E))
5031 then
5032 N := Build_Discriminal_Subtype_Of_Component (E);
5034 if Present (N) then
5035 Insert_Action (Ck_Node, N);
5036 E1 := Defining_Identifier (N);
5037 end if;
5038 end if;
5040 if Ekind (E1) = E_String_Literal_Subtype then
5041 return
5042 Make_Integer_Literal (Loc,
5043 Intval => String_Literal_Length (E1));
5045 elsif Ekind (Pt) = E_Protected_Type
5046 and then Has_Discriminants (Pt)
5047 and then Has_Completion (Pt)
5048 and then not Inside_Init_Proc
5049 then
5051 -- If the type whose length is needed is a private component
5052 -- constrained by a discriminant, we must expand the 'Length
5053 -- attribute into an explicit computation, using the discriminal
5054 -- of the current protected operation. This is because the actual
5055 -- type of the prival is constructed after the protected opera-
5056 -- tion has been fully expanded.
5058 declare
5059 Indx_Type : Node_Id;
5060 Lo : Node_Id;
5061 Hi : Node_Id;
5062 Do_Expand : Boolean := False;
5064 begin
5065 Indx_Type := First_Index (E);
5067 for J in 1 .. Indx - 1 loop
5068 Next_Index (Indx_Type);
5069 end loop;
5071 Get_Index_Bounds (Indx_Type, Lo, Hi);
5073 if Nkind (Lo) = N_Identifier
5074 and then Ekind (Entity (Lo)) = E_In_Parameter
5075 then
5076 Lo := Get_Discriminal (E, Lo);
5077 Do_Expand := True;
5078 end if;
5080 if Nkind (Hi) = N_Identifier
5081 and then Ekind (Entity (Hi)) = E_In_Parameter
5082 then
5083 Hi := Get_Discriminal (E, Hi);
5084 Do_Expand := True;
5085 end if;
5087 if Do_Expand then
5088 if not Is_Entity_Name (Lo) then
5089 Lo := Duplicate_Subexpr_No_Checks (Lo);
5090 end if;
5092 if not Is_Entity_Name (Hi) then
5093 Lo := Duplicate_Subexpr_No_Checks (Hi);
5094 end if;
5096 N :=
5097 Make_Op_Add (Loc,
5098 Left_Opnd =>
5099 Make_Op_Subtract (Loc,
5100 Left_Opnd => Hi,
5101 Right_Opnd => Lo),
5103 Right_Opnd => Make_Integer_Literal (Loc, 1));
5104 return N;
5106 else
5107 N :=
5108 Make_Attribute_Reference (Loc,
5109 Attribute_Name => Name_Length,
5110 Prefix =>
5111 New_Occurrence_Of (E1, Loc));
5113 if Indx > 1 then
5114 Set_Expressions (N, New_List (
5115 Make_Integer_Literal (Loc, Indx)));
5116 end if;
5118 return N;
5119 end if;
5120 end;
5122 else
5123 N :=
5124 Make_Attribute_Reference (Loc,
5125 Attribute_Name => Name_Length,
5126 Prefix =>
5127 New_Occurrence_Of (E1, Loc));
5129 if Indx > 1 then
5130 Set_Expressions (N, New_List (
5131 Make_Integer_Literal (Loc, Indx)));
5132 end if;
5134 return N;
5136 end if;
5137 end Get_E_Length;
5139 ------------------
5140 -- Get_N_Length --
5141 ------------------
5143 function Get_N_Length (N : Node_Id; Indx : Nat) return Node_Id is
5144 begin
5145 return
5146 Make_Attribute_Reference (Loc,
5147 Attribute_Name => Name_Length,
5148 Prefix =>
5149 Duplicate_Subexpr_No_Checks (N, Name_Req => True),
5150 Expressions => New_List (
5151 Make_Integer_Literal (Loc, Indx)));
5153 end Get_N_Length;
5155 -------------------
5156 -- Length_E_Cond --
5157 -------------------
5159 function Length_E_Cond
5160 (Exptyp : Entity_Id;
5161 Typ : Entity_Id;
5162 Indx : Nat) return Node_Id
5164 begin
5165 return
5166 Make_Op_Ne (Loc,
5167 Left_Opnd => Get_E_Length (Typ, Indx),
5168 Right_Opnd => Get_E_Length (Exptyp, Indx));
5170 end Length_E_Cond;
5172 -------------------
5173 -- Length_N_Cond --
5174 -------------------
5176 function Length_N_Cond
5177 (Expr : Node_Id;
5178 Typ : Entity_Id;
5179 Indx : Nat) return Node_Id
5181 begin
5182 return
5183 Make_Op_Ne (Loc,
5184 Left_Opnd => Get_E_Length (Typ, Indx),
5185 Right_Opnd => Get_N_Length (Expr, Indx));
5187 end Length_N_Cond;
5189 function Same_Bounds (L : Node_Id; R : Node_Id) return Boolean is
5190 begin
5191 return
5192 (Nkind (L) = N_Integer_Literal
5193 and then Nkind (R) = N_Integer_Literal
5194 and then Intval (L) = Intval (R))
5196 or else
5197 (Is_Entity_Name (L)
5198 and then Ekind (Entity (L)) = E_Constant
5199 and then ((Is_Entity_Name (R)
5200 and then Entity (L) = Entity (R))
5201 or else
5202 (Nkind (R) = N_Type_Conversion
5203 and then Is_Entity_Name (Expression (R))
5204 and then Entity (L) = Entity (Expression (R)))))
5206 or else
5207 (Is_Entity_Name (R)
5208 and then Ekind (Entity (R)) = E_Constant
5209 and then Nkind (L) = N_Type_Conversion
5210 and then Is_Entity_Name (Expression (L))
5211 and then Entity (R) = Entity (Expression (L)))
5213 or else
5214 (Is_Entity_Name (L)
5215 and then Is_Entity_Name (R)
5216 and then Entity (L) = Entity (R)
5217 and then Ekind (Entity (L)) = E_In_Parameter
5218 and then Inside_Init_Proc);
5219 end Same_Bounds;
5221 -- Start of processing for Selected_Length_Checks
5223 begin
5224 if not Expander_Active then
5225 return Ret_Result;
5226 end if;
5228 if Target_Typ = Any_Type
5229 or else Target_Typ = Any_Composite
5230 or else Raises_Constraint_Error (Ck_Node)
5231 then
5232 return Ret_Result;
5233 end if;
5235 if No (Wnode) then
5236 Wnode := Ck_Node;
5237 end if;
5239 T_Typ := Target_Typ;
5241 if No (Source_Typ) then
5242 S_Typ := Etype (Ck_Node);
5243 else
5244 S_Typ := Source_Typ;
5245 end if;
5247 if S_Typ = Any_Type or else S_Typ = Any_Composite then
5248 return Ret_Result;
5249 end if;
5251 if Is_Access_Type (T_Typ) and then Is_Access_Type (S_Typ) then
5252 S_Typ := Designated_Type (S_Typ);
5253 T_Typ := Designated_Type (T_Typ);
5254 Do_Access := True;
5256 -- A simple optimization
5258 if Nkind (Ck_Node) = N_Null then
5259 return Ret_Result;
5260 end if;
5261 end if;
5263 if Is_Array_Type (T_Typ) and then Is_Array_Type (S_Typ) then
5264 if Is_Constrained (T_Typ) then
5266 -- The checking code to be generated will freeze the
5267 -- corresponding array type. However, we must freeze the
5268 -- type now, so that the freeze node does not appear within
5269 -- the generated condional expression, but ahead of it.
5271 Freeze_Before (Ck_Node, T_Typ);
5273 Expr_Actual := Get_Referenced_Object (Ck_Node);
5274 Exptyp := Get_Actual_Subtype (Expr_Actual);
5276 if Is_Access_Type (Exptyp) then
5277 Exptyp := Designated_Type (Exptyp);
5278 end if;
5280 -- String_Literal case. This needs to be handled specially be-
5281 -- cause no index types are available for string literals. The
5282 -- condition is simply:
5284 -- T_Typ'Length = string-literal-length
5286 if Nkind (Expr_Actual) = N_String_Literal
5287 and then Ekind (Etype (Expr_Actual)) = E_String_Literal_Subtype
5288 then
5289 Cond :=
5290 Make_Op_Ne (Loc,
5291 Left_Opnd => Get_E_Length (T_Typ, 1),
5292 Right_Opnd =>
5293 Make_Integer_Literal (Loc,
5294 Intval =>
5295 String_Literal_Length (Etype (Expr_Actual))));
5297 -- General array case. Here we have a usable actual subtype for
5298 -- the expression, and the condition is built from the two types
5299 -- (Do_Length):
5301 -- T_Typ'Length /= Exptyp'Length or else
5302 -- T_Typ'Length (2) /= Exptyp'Length (2) or else
5303 -- T_Typ'Length (3) /= Exptyp'Length (3) or else
5304 -- ...
5306 elsif Is_Constrained (Exptyp) then
5307 declare
5308 Ndims : constant Nat := Number_Dimensions (T_Typ);
5310 L_Index : Node_Id;
5311 R_Index : Node_Id;
5312 L_Low : Node_Id;
5313 L_High : Node_Id;
5314 R_Low : Node_Id;
5315 R_High : Node_Id;
5316 L_Length : Uint;
5317 R_Length : Uint;
5318 Ref_Node : Node_Id;
5320 begin
5322 -- At the library level, we need to ensure that the
5323 -- type of the object is elaborated before the check
5324 -- itself is emitted. This is only done if the object
5325 -- is in the current compilation unit, otherwise the
5326 -- type is frozen and elaborated in its unit.
5328 if Is_Itype (Exptyp)
5329 and then
5330 Ekind (Cunit_Entity (Current_Sem_Unit)) = E_Package
5331 and then
5332 not In_Package_Body (Cunit_Entity (Current_Sem_Unit))
5333 and then In_Open_Scopes (Scope (Exptyp))
5334 then
5335 Ref_Node := Make_Itype_Reference (Sloc (Ck_Node));
5336 Set_Itype (Ref_Node, Exptyp);
5337 Insert_Action (Ck_Node, Ref_Node);
5338 end if;
5340 L_Index := First_Index (T_Typ);
5341 R_Index := First_Index (Exptyp);
5343 for Indx in 1 .. Ndims loop
5344 if not (Nkind (L_Index) = N_Raise_Constraint_Error
5345 or else
5346 Nkind (R_Index) = N_Raise_Constraint_Error)
5347 then
5348 Get_Index_Bounds (L_Index, L_Low, L_High);
5349 Get_Index_Bounds (R_Index, R_Low, R_High);
5351 -- Deal with compile time length check. Note that we
5352 -- skip this in the access case, because the access
5353 -- value may be null, so we cannot know statically.
5355 if not Do_Access
5356 and then Compile_Time_Known_Value (L_Low)
5357 and then Compile_Time_Known_Value (L_High)
5358 and then Compile_Time_Known_Value (R_Low)
5359 and then Compile_Time_Known_Value (R_High)
5360 then
5361 if Expr_Value (L_High) >= Expr_Value (L_Low) then
5362 L_Length := Expr_Value (L_High) -
5363 Expr_Value (L_Low) + 1;
5364 else
5365 L_Length := UI_From_Int (0);
5366 end if;
5368 if Expr_Value (R_High) >= Expr_Value (R_Low) then
5369 R_Length := Expr_Value (R_High) -
5370 Expr_Value (R_Low) + 1;
5371 else
5372 R_Length := UI_From_Int (0);
5373 end if;
5375 if L_Length > R_Length then
5376 Add_Check
5377 (Compile_Time_Constraint_Error
5378 (Wnode, "too few elements for}?", T_Typ));
5380 elsif L_Length < R_Length then
5381 Add_Check
5382 (Compile_Time_Constraint_Error
5383 (Wnode, "too many elements for}?", T_Typ));
5384 end if;
5386 -- The comparison for an individual index subtype
5387 -- is omitted if the corresponding index subtypes
5388 -- statically match, since the result is known to
5389 -- be true. Note that this test is worth while even
5390 -- though we do static evaluation, because non-static
5391 -- subtypes can statically match.
5393 elsif not
5394 Subtypes_Statically_Match
5395 (Etype (L_Index), Etype (R_Index))
5397 and then not
5398 (Same_Bounds (L_Low, R_Low)
5399 and then Same_Bounds (L_High, R_High))
5400 then
5401 Evolve_Or_Else
5402 (Cond, Length_E_Cond (Exptyp, T_Typ, Indx));
5403 end if;
5405 Next (L_Index);
5406 Next (R_Index);
5407 end if;
5408 end loop;
5409 end;
5411 -- Handle cases where we do not get a usable actual subtype that
5412 -- is constrained. This happens for example in the function call
5413 -- and explicit dereference cases. In these cases, we have to get
5414 -- the length or range from the expression itself, making sure we
5415 -- do not evaluate it more than once.
5417 -- Here Ck_Node is the original expression, or more properly the
5418 -- result of applying Duplicate_Expr to the original tree,
5419 -- forcing the result to be a name.
5421 else
5422 declare
5423 Ndims : constant Nat := Number_Dimensions (T_Typ);
5425 begin
5426 -- Build the condition for the explicit dereference case
5428 for Indx in 1 .. Ndims loop
5429 Evolve_Or_Else
5430 (Cond, Length_N_Cond (Ck_Node, T_Typ, Indx));
5431 end loop;
5432 end;
5433 end if;
5434 end if;
5435 end if;
5437 -- Construct the test and insert into the tree
5439 if Present (Cond) then
5440 if Do_Access then
5441 Cond := Guard_Access (Cond, Loc, Ck_Node);
5442 end if;
5444 Add_Check
5445 (Make_Raise_Constraint_Error (Loc,
5446 Condition => Cond,
5447 Reason => CE_Length_Check_Failed));
5448 end if;
5450 return Ret_Result;
5451 end Selected_Length_Checks;
5453 ---------------------------
5454 -- Selected_Range_Checks --
5455 ---------------------------
5457 function Selected_Range_Checks
5458 (Ck_Node : Node_Id;
5459 Target_Typ : Entity_Id;
5460 Source_Typ : Entity_Id;
5461 Warn_Node : Node_Id) return Check_Result
5463 Loc : constant Source_Ptr := Sloc (Ck_Node);
5464 S_Typ : Entity_Id;
5465 T_Typ : Entity_Id;
5466 Expr_Actual : Node_Id;
5467 Exptyp : Entity_Id;
5468 Cond : Node_Id := Empty;
5469 Do_Access : Boolean := False;
5470 Wnode : Node_Id := Warn_Node;
5471 Ret_Result : Check_Result := (Empty, Empty);
5472 Num_Checks : Integer := 0;
5474 procedure Add_Check (N : Node_Id);
5475 -- Adds the action given to Ret_Result if N is non-Empty
5477 function Discrete_Range_Cond
5478 (Expr : Node_Id;
5479 Typ : Entity_Id) return Node_Id;
5480 -- Returns expression to compute:
5481 -- Low_Bound (Expr) < Typ'First
5482 -- or else
5483 -- High_Bound (Expr) > Typ'Last
5485 function Discrete_Expr_Cond
5486 (Expr : Node_Id;
5487 Typ : Entity_Id) return Node_Id;
5488 -- Returns expression to compute:
5489 -- Expr < Typ'First
5490 -- or else
5491 -- Expr > Typ'Last
5493 function Get_E_First_Or_Last
5494 (E : Entity_Id;
5495 Indx : Nat;
5496 Nam : Name_Id) return Node_Id;
5497 -- Returns expression to compute:
5498 -- E'First or E'Last
5500 function Get_N_First (N : Node_Id; Indx : Nat) return Node_Id;
5501 function Get_N_Last (N : Node_Id; Indx : Nat) return Node_Id;
5502 -- Returns expression to compute:
5503 -- N'First or N'Last using Duplicate_Subexpr_No_Checks
5505 function Range_E_Cond
5506 (Exptyp : Entity_Id;
5507 Typ : Entity_Id;
5508 Indx : Nat)
5509 return Node_Id;
5510 -- Returns expression to compute:
5511 -- Exptyp'First < Typ'First or else Exptyp'Last > Typ'Last
5513 function Range_Equal_E_Cond
5514 (Exptyp : Entity_Id;
5515 Typ : Entity_Id;
5516 Indx : Nat) return Node_Id;
5517 -- Returns expression to compute:
5518 -- Exptyp'First /= Typ'First or else Exptyp'Last /= Typ'Last
5520 function Range_N_Cond
5521 (Expr : Node_Id;
5522 Typ : Entity_Id;
5523 Indx : Nat) return Node_Id;
5524 -- Return expression to compute:
5525 -- Expr'First < Typ'First or else Expr'Last > Typ'Last
5527 ---------------
5528 -- Add_Check --
5529 ---------------
5531 procedure Add_Check (N : Node_Id) is
5532 begin
5533 if Present (N) then
5535 -- For now, ignore attempt to place more than 2 checks ???
5537 if Num_Checks = 2 then
5538 return;
5539 end if;
5541 pragma Assert (Num_Checks <= 1);
5542 Num_Checks := Num_Checks + 1;
5543 Ret_Result (Num_Checks) := N;
5544 end if;
5545 end Add_Check;
5547 -------------------------
5548 -- Discrete_Expr_Cond --
5549 -------------------------
5551 function Discrete_Expr_Cond
5552 (Expr : Node_Id;
5553 Typ : Entity_Id) return Node_Id
5555 begin
5556 return
5557 Make_Or_Else (Loc,
5558 Left_Opnd =>
5559 Make_Op_Lt (Loc,
5560 Left_Opnd =>
5561 Convert_To (Base_Type (Typ),
5562 Duplicate_Subexpr_No_Checks (Expr)),
5563 Right_Opnd =>
5564 Convert_To (Base_Type (Typ),
5565 Get_E_First_Or_Last (Typ, 0, Name_First))),
5567 Right_Opnd =>
5568 Make_Op_Gt (Loc,
5569 Left_Opnd =>
5570 Convert_To (Base_Type (Typ),
5571 Duplicate_Subexpr_No_Checks (Expr)),
5572 Right_Opnd =>
5573 Convert_To
5574 (Base_Type (Typ),
5575 Get_E_First_Or_Last (Typ, 0, Name_Last))));
5576 end Discrete_Expr_Cond;
5578 -------------------------
5579 -- Discrete_Range_Cond --
5580 -------------------------
5582 function Discrete_Range_Cond
5583 (Expr : Node_Id;
5584 Typ : Entity_Id) return Node_Id
5586 LB : Node_Id := Low_Bound (Expr);
5587 HB : Node_Id := High_Bound (Expr);
5589 Left_Opnd : Node_Id;
5590 Right_Opnd : Node_Id;
5592 begin
5593 if Nkind (LB) = N_Identifier
5594 and then Ekind (Entity (LB)) = E_Discriminant then
5595 LB := New_Occurrence_Of (Discriminal (Entity (LB)), Loc);
5596 end if;
5598 if Nkind (HB) = N_Identifier
5599 and then Ekind (Entity (HB)) = E_Discriminant then
5600 HB := New_Occurrence_Of (Discriminal (Entity (HB)), Loc);
5601 end if;
5603 Left_Opnd :=
5604 Make_Op_Lt (Loc,
5605 Left_Opnd =>
5606 Convert_To
5607 (Base_Type (Typ), Duplicate_Subexpr_No_Checks (LB)),
5609 Right_Opnd =>
5610 Convert_To
5611 (Base_Type (Typ), Get_E_First_Or_Last (Typ, 0, Name_First)));
5613 if Base_Type (Typ) = Typ then
5614 return Left_Opnd;
5616 elsif Compile_Time_Known_Value (High_Bound (Scalar_Range (Typ)))
5617 and then
5618 Compile_Time_Known_Value (High_Bound (Scalar_Range
5619 (Base_Type (Typ))))
5620 then
5621 if Is_Floating_Point_Type (Typ) then
5622 if Expr_Value_R (High_Bound (Scalar_Range (Typ))) =
5623 Expr_Value_R (High_Bound (Scalar_Range (Base_Type (Typ))))
5624 then
5625 return Left_Opnd;
5626 end if;
5628 else
5629 if Expr_Value (High_Bound (Scalar_Range (Typ))) =
5630 Expr_Value (High_Bound (Scalar_Range (Base_Type (Typ))))
5631 then
5632 return Left_Opnd;
5633 end if;
5634 end if;
5635 end if;
5637 Right_Opnd :=
5638 Make_Op_Gt (Loc,
5639 Left_Opnd =>
5640 Convert_To
5641 (Base_Type (Typ), Duplicate_Subexpr_No_Checks (HB)),
5643 Right_Opnd =>
5644 Convert_To
5645 (Base_Type (Typ),
5646 Get_E_First_Or_Last (Typ, 0, Name_Last)));
5648 return Make_Or_Else (Loc, Left_Opnd, Right_Opnd);
5649 end Discrete_Range_Cond;
5651 -------------------------
5652 -- Get_E_First_Or_Last --
5653 -------------------------
5655 function Get_E_First_Or_Last
5656 (E : Entity_Id;
5657 Indx : Nat;
5658 Nam : Name_Id) return Node_Id
5660 N : Node_Id;
5661 LB : Node_Id;
5662 HB : Node_Id;
5663 Bound : Node_Id;
5665 begin
5666 if Is_Array_Type (E) then
5667 N := First_Index (E);
5669 for J in 2 .. Indx loop
5670 Next_Index (N);
5671 end loop;
5673 else
5674 N := Scalar_Range (E);
5675 end if;
5677 if Nkind (N) = N_Subtype_Indication then
5678 LB := Low_Bound (Range_Expression (Constraint (N)));
5679 HB := High_Bound (Range_Expression (Constraint (N)));
5681 elsif Is_Entity_Name (N) then
5682 LB := Type_Low_Bound (Etype (N));
5683 HB := Type_High_Bound (Etype (N));
5685 else
5686 LB := Low_Bound (N);
5687 HB := High_Bound (N);
5688 end if;
5690 if Nam = Name_First then
5691 Bound := LB;
5692 else
5693 Bound := HB;
5694 end if;
5696 if Nkind (Bound) = N_Identifier
5697 and then Ekind (Entity (Bound)) = E_Discriminant
5698 then
5699 -- If this is a task discriminant, and we are the body, we must
5700 -- retrieve the corresponding body discriminal. This is another
5701 -- consequence of the early creation of discriminals, and the
5702 -- need to generate constraint checks before their declarations
5703 -- are made visible.
5705 if Is_Concurrent_Record_Type (Scope (Entity (Bound))) then
5706 declare
5707 Tsk : constant Entity_Id :=
5708 Corresponding_Concurrent_Type
5709 (Scope (Entity (Bound)));
5710 Disc : Entity_Id;
5712 begin
5713 if In_Open_Scopes (Tsk)
5714 and then Has_Completion (Tsk)
5715 then
5716 -- Find discriminant of original task, and use its
5717 -- current discriminal, which is the renaming within
5718 -- the task body.
5720 Disc := First_Discriminant (Tsk);
5721 while Present (Disc) loop
5722 if Chars (Disc) = Chars (Entity (Bound)) then
5723 Set_Scope (Discriminal (Disc), Tsk);
5724 return New_Occurrence_Of (Discriminal (Disc), Loc);
5725 end if;
5727 Next_Discriminant (Disc);
5728 end loop;
5730 -- That loop should always succeed in finding a matching
5731 -- entry and returning. Fatal error if not.
5733 raise Program_Error;
5735 else
5736 return
5737 New_Occurrence_Of (Discriminal (Entity (Bound)), Loc);
5738 end if;
5739 end;
5740 else
5741 return New_Occurrence_Of (Discriminal (Entity (Bound)), Loc);
5742 end if;
5744 elsif Nkind (Bound) = N_Identifier
5745 and then Ekind (Entity (Bound)) = E_In_Parameter
5746 and then not Inside_Init_Proc
5747 then
5748 return Get_Discriminal (E, Bound);
5750 elsif Nkind (Bound) = N_Integer_Literal then
5751 return Make_Integer_Literal (Loc, Intval (Bound));
5753 -- Case of a bound that has been rewritten to an
5754 -- N_Raise_Constraint_Error node because it is an out-of-range
5755 -- value. We may not call Duplicate_Subexpr on this node because
5756 -- an N_Raise_Constraint_Error is not side effect free, and we may
5757 -- not assume that we are in the proper context to remove side
5758 -- effects on it at the point of reference.
5760 elsif Nkind (Bound) = N_Raise_Constraint_Error then
5761 return New_Copy_Tree (Bound);
5763 else
5764 return Duplicate_Subexpr_No_Checks (Bound);
5765 end if;
5766 end Get_E_First_Or_Last;
5768 -----------------
5769 -- Get_N_First --
5770 -----------------
5772 function Get_N_First (N : Node_Id; Indx : Nat) return Node_Id is
5773 begin
5774 return
5775 Make_Attribute_Reference (Loc,
5776 Attribute_Name => Name_First,
5777 Prefix =>
5778 Duplicate_Subexpr_No_Checks (N, Name_Req => True),
5779 Expressions => New_List (
5780 Make_Integer_Literal (Loc, Indx)));
5781 end Get_N_First;
5783 ----------------
5784 -- Get_N_Last --
5785 ----------------
5787 function Get_N_Last (N : Node_Id; Indx : Nat) return Node_Id is
5788 begin
5789 return
5790 Make_Attribute_Reference (Loc,
5791 Attribute_Name => Name_Last,
5792 Prefix =>
5793 Duplicate_Subexpr_No_Checks (N, Name_Req => True),
5794 Expressions => New_List (
5795 Make_Integer_Literal (Loc, Indx)));
5796 end Get_N_Last;
5798 ------------------
5799 -- Range_E_Cond --
5800 ------------------
5802 function Range_E_Cond
5803 (Exptyp : Entity_Id;
5804 Typ : Entity_Id;
5805 Indx : Nat) return Node_Id
5807 begin
5808 return
5809 Make_Or_Else (Loc,
5810 Left_Opnd =>
5811 Make_Op_Lt (Loc,
5812 Left_Opnd => Get_E_First_Or_Last (Exptyp, Indx, Name_First),
5813 Right_Opnd => Get_E_First_Or_Last (Typ, Indx, Name_First)),
5815 Right_Opnd =>
5816 Make_Op_Gt (Loc,
5817 Left_Opnd => Get_E_First_Or_Last (Exptyp, Indx, Name_Last),
5818 Right_Opnd => Get_E_First_Or_Last (Typ, Indx, Name_Last)));
5820 end Range_E_Cond;
5822 ------------------------
5823 -- Range_Equal_E_Cond --
5824 ------------------------
5826 function Range_Equal_E_Cond
5827 (Exptyp : Entity_Id;
5828 Typ : Entity_Id;
5829 Indx : Nat) return Node_Id
5831 begin
5832 return
5833 Make_Or_Else (Loc,
5834 Left_Opnd =>
5835 Make_Op_Ne (Loc,
5836 Left_Opnd => Get_E_First_Or_Last (Exptyp, Indx, Name_First),
5837 Right_Opnd => Get_E_First_Or_Last (Typ, Indx, Name_First)),
5838 Right_Opnd =>
5839 Make_Op_Ne (Loc,
5840 Left_Opnd => Get_E_First_Or_Last (Exptyp, Indx, Name_Last),
5841 Right_Opnd => Get_E_First_Or_Last (Typ, Indx, Name_Last)));
5842 end Range_Equal_E_Cond;
5844 ------------------
5845 -- Range_N_Cond --
5846 ------------------
5848 function Range_N_Cond
5849 (Expr : Node_Id;
5850 Typ : Entity_Id;
5851 Indx : Nat) return Node_Id
5853 begin
5854 return
5855 Make_Or_Else (Loc,
5856 Left_Opnd =>
5857 Make_Op_Lt (Loc,
5858 Left_Opnd => Get_N_First (Expr, Indx),
5859 Right_Opnd => Get_E_First_Or_Last (Typ, Indx, Name_First)),
5861 Right_Opnd =>
5862 Make_Op_Gt (Loc,
5863 Left_Opnd => Get_N_Last (Expr, Indx),
5864 Right_Opnd => Get_E_First_Or_Last (Typ, Indx, Name_Last)));
5865 end Range_N_Cond;
5867 -- Start of processing for Selected_Range_Checks
5869 begin
5870 if not Expander_Active then
5871 return Ret_Result;
5872 end if;
5874 if Target_Typ = Any_Type
5875 or else Target_Typ = Any_Composite
5876 or else Raises_Constraint_Error (Ck_Node)
5877 then
5878 return Ret_Result;
5879 end if;
5881 if No (Wnode) then
5882 Wnode := Ck_Node;
5883 end if;
5885 T_Typ := Target_Typ;
5887 if No (Source_Typ) then
5888 S_Typ := Etype (Ck_Node);
5889 else
5890 S_Typ := Source_Typ;
5891 end if;
5893 if S_Typ = Any_Type or else S_Typ = Any_Composite then
5894 return Ret_Result;
5895 end if;
5897 -- The order of evaluating T_Typ before S_Typ seems to be critical
5898 -- because S_Typ can be derived from Etype (Ck_Node), if it's not passed
5899 -- in, and since Node can be an N_Range node, it might be invalid.
5900 -- Should there be an assert check somewhere for taking the Etype of
5901 -- an N_Range node ???
5903 if Is_Access_Type (T_Typ) and then Is_Access_Type (S_Typ) then
5904 S_Typ := Designated_Type (S_Typ);
5905 T_Typ := Designated_Type (T_Typ);
5906 Do_Access := True;
5908 -- A simple optimization
5910 if Nkind (Ck_Node) = N_Null then
5911 return Ret_Result;
5912 end if;
5913 end if;
5915 -- For an N_Range Node, check for a null range and then if not
5916 -- null generate a range check action.
5918 if Nkind (Ck_Node) = N_Range then
5920 -- There's no point in checking a range against itself
5922 if Ck_Node = Scalar_Range (T_Typ) then
5923 return Ret_Result;
5924 end if;
5926 declare
5927 T_LB : constant Node_Id := Type_Low_Bound (T_Typ);
5928 T_HB : constant Node_Id := Type_High_Bound (T_Typ);
5929 LB : constant Node_Id := Low_Bound (Ck_Node);
5930 HB : constant Node_Id := High_Bound (Ck_Node);
5931 Null_Range : Boolean;
5933 Out_Of_Range_L : Boolean;
5934 Out_Of_Range_H : Boolean;
5936 begin
5937 -- Check for case where everything is static and we can
5938 -- do the check at compile time. This is skipped if we
5939 -- have an access type, since the access value may be null.
5941 -- ??? This code can be improved since you only need to know
5942 -- that the two respective bounds (LB & T_LB or HB & T_HB)
5943 -- are known at compile time to emit pertinent messages.
5945 if Compile_Time_Known_Value (LB)
5946 and then Compile_Time_Known_Value (HB)
5947 and then Compile_Time_Known_Value (T_LB)
5948 and then Compile_Time_Known_Value (T_HB)
5949 and then not Do_Access
5950 then
5951 -- Floating-point case
5953 if Is_Floating_Point_Type (S_Typ) then
5954 Null_Range := Expr_Value_R (HB) < Expr_Value_R (LB);
5955 Out_Of_Range_L :=
5956 (Expr_Value_R (LB) < Expr_Value_R (T_LB))
5957 or else
5958 (Expr_Value_R (LB) > Expr_Value_R (T_HB));
5960 Out_Of_Range_H :=
5961 (Expr_Value_R (HB) > Expr_Value_R (T_HB))
5962 or else
5963 (Expr_Value_R (HB) < Expr_Value_R (T_LB));
5965 -- Fixed or discrete type case
5967 else
5968 Null_Range := Expr_Value (HB) < Expr_Value (LB);
5969 Out_Of_Range_L :=
5970 (Expr_Value (LB) < Expr_Value (T_LB))
5971 or else
5972 (Expr_Value (LB) > Expr_Value (T_HB));
5974 Out_Of_Range_H :=
5975 (Expr_Value (HB) > Expr_Value (T_HB))
5976 or else
5977 (Expr_Value (HB) < Expr_Value (T_LB));
5978 end if;
5980 if not Null_Range then
5981 if Out_Of_Range_L then
5982 if No (Warn_Node) then
5983 Add_Check
5984 (Compile_Time_Constraint_Error
5985 (Low_Bound (Ck_Node),
5986 "static value out of range of}?", T_Typ));
5988 else
5989 Add_Check
5990 (Compile_Time_Constraint_Error
5991 (Wnode,
5992 "static range out of bounds of}?", T_Typ));
5993 end if;
5994 end if;
5996 if Out_Of_Range_H then
5997 if No (Warn_Node) then
5998 Add_Check
5999 (Compile_Time_Constraint_Error
6000 (High_Bound (Ck_Node),
6001 "static value out of range of}?", T_Typ));
6003 else
6004 Add_Check
6005 (Compile_Time_Constraint_Error
6006 (Wnode,
6007 "static range out of bounds of}?", T_Typ));
6008 end if;
6009 end if;
6011 end if;
6013 else
6014 declare
6015 LB : Node_Id := Low_Bound (Ck_Node);
6016 HB : Node_Id := High_Bound (Ck_Node);
6018 begin
6020 -- If either bound is a discriminant and we are within
6021 -- the record declaration, it is a use of the discriminant
6022 -- in a constraint of a component, and nothing can be
6023 -- checked here. The check will be emitted within the
6024 -- init proc. Before then, the discriminal has no real
6025 -- meaning.
6027 if Nkind (LB) = N_Identifier
6028 and then Ekind (Entity (LB)) = E_Discriminant
6029 then
6030 if Current_Scope = Scope (Entity (LB)) then
6031 return Ret_Result;
6032 else
6033 LB :=
6034 New_Occurrence_Of (Discriminal (Entity (LB)), Loc);
6035 end if;
6036 end if;
6038 if Nkind (HB) = N_Identifier
6039 and then Ekind (Entity (HB)) = E_Discriminant
6040 then
6041 if Current_Scope = Scope (Entity (HB)) then
6042 return Ret_Result;
6043 else
6044 HB :=
6045 New_Occurrence_Of (Discriminal (Entity (HB)), Loc);
6046 end if;
6047 end if;
6049 Cond := Discrete_Range_Cond (Ck_Node, T_Typ);
6050 Set_Paren_Count (Cond, 1);
6052 Cond :=
6053 Make_And_Then (Loc,
6054 Left_Opnd =>
6055 Make_Op_Ge (Loc,
6056 Left_Opnd => Duplicate_Subexpr_No_Checks (HB),
6057 Right_Opnd => Duplicate_Subexpr_No_Checks (LB)),
6058 Right_Opnd => Cond);
6059 end;
6061 end if;
6062 end;
6064 elsif Is_Scalar_Type (S_Typ) then
6066 -- This somewhat duplicates what Apply_Scalar_Range_Check does,
6067 -- except the above simply sets a flag in the node and lets
6068 -- gigi generate the check base on the Etype of the expression.
6069 -- Sometimes, however we want to do a dynamic check against an
6070 -- arbitrary target type, so we do that here.
6072 if Ekind (Base_Type (S_Typ)) /= Ekind (Base_Type (T_Typ)) then
6073 Cond := Discrete_Expr_Cond (Ck_Node, T_Typ);
6075 -- For literals, we can tell if the constraint error will be
6076 -- raised at compile time, so we never need a dynamic check, but
6077 -- if the exception will be raised, then post the usual warning,
6078 -- and replace the literal with a raise constraint error
6079 -- expression. As usual, skip this for access types
6081 elsif Compile_Time_Known_Value (Ck_Node)
6082 and then not Do_Access
6083 then
6084 declare
6085 LB : constant Node_Id := Type_Low_Bound (T_Typ);
6086 UB : constant Node_Id := Type_High_Bound (T_Typ);
6088 Out_Of_Range : Boolean;
6089 Static_Bounds : constant Boolean :=
6090 Compile_Time_Known_Value (LB)
6091 and Compile_Time_Known_Value (UB);
6093 begin
6094 -- Following range tests should use Sem_Eval routine ???
6096 if Static_Bounds then
6097 if Is_Floating_Point_Type (S_Typ) then
6098 Out_Of_Range :=
6099 (Expr_Value_R (Ck_Node) < Expr_Value_R (LB))
6100 or else
6101 (Expr_Value_R (Ck_Node) > Expr_Value_R (UB));
6103 else -- fixed or discrete type
6104 Out_Of_Range :=
6105 Expr_Value (Ck_Node) < Expr_Value (LB)
6106 or else
6107 Expr_Value (Ck_Node) > Expr_Value (UB);
6108 end if;
6110 -- Bounds of the type are static and the literal is
6111 -- out of range so make a warning message.
6113 if Out_Of_Range then
6114 if No (Warn_Node) then
6115 Add_Check
6116 (Compile_Time_Constraint_Error
6117 (Ck_Node,
6118 "static value out of range of}?", T_Typ));
6120 else
6121 Add_Check
6122 (Compile_Time_Constraint_Error
6123 (Wnode,
6124 "static value out of range of}?", T_Typ));
6125 end if;
6126 end if;
6128 else
6129 Cond := Discrete_Expr_Cond (Ck_Node, T_Typ);
6130 end if;
6131 end;
6133 -- Here for the case of a non-static expression, we need a runtime
6134 -- check unless the source type range is guaranteed to be in the
6135 -- range of the target type.
6137 else
6138 if not In_Subrange_Of (S_Typ, T_Typ) then
6139 Cond := Discrete_Expr_Cond (Ck_Node, T_Typ);
6140 end if;
6141 end if;
6142 end if;
6144 if Is_Array_Type (T_Typ) and then Is_Array_Type (S_Typ) then
6145 if Is_Constrained (T_Typ) then
6147 Expr_Actual := Get_Referenced_Object (Ck_Node);
6148 Exptyp := Get_Actual_Subtype (Expr_Actual);
6150 if Is_Access_Type (Exptyp) then
6151 Exptyp := Designated_Type (Exptyp);
6152 end if;
6154 -- String_Literal case. This needs to be handled specially be-
6155 -- cause no index types are available for string literals. The
6156 -- condition is simply:
6158 -- T_Typ'Length = string-literal-length
6160 if Nkind (Expr_Actual) = N_String_Literal then
6161 null;
6163 -- General array case. Here we have a usable actual subtype for
6164 -- the expression, and the condition is built from the two types
6166 -- T_Typ'First < Exptyp'First or else
6167 -- T_Typ'Last > Exptyp'Last or else
6168 -- T_Typ'First(1) < Exptyp'First(1) or else
6169 -- T_Typ'Last(1) > Exptyp'Last(1) or else
6170 -- ...
6172 elsif Is_Constrained (Exptyp) then
6173 declare
6174 Ndims : constant Nat := Number_Dimensions (T_Typ);
6176 L_Index : Node_Id;
6177 R_Index : Node_Id;
6178 L_Low : Node_Id;
6179 L_High : Node_Id;
6180 R_Low : Node_Id;
6181 R_High : Node_Id;
6183 begin
6184 L_Index := First_Index (T_Typ);
6185 R_Index := First_Index (Exptyp);
6187 for Indx in 1 .. Ndims loop
6188 if not (Nkind (L_Index) = N_Raise_Constraint_Error
6189 or else
6190 Nkind (R_Index) = N_Raise_Constraint_Error)
6191 then
6192 Get_Index_Bounds (L_Index, L_Low, L_High);
6193 Get_Index_Bounds (R_Index, R_Low, R_High);
6195 -- Deal with compile time length check. Note that we
6196 -- skip this in the access case, because the access
6197 -- value may be null, so we cannot know statically.
6199 if not
6200 Subtypes_Statically_Match
6201 (Etype (L_Index), Etype (R_Index))
6202 then
6203 -- If the target type is constrained then we
6204 -- have to check for exact equality of bounds
6205 -- (required for qualified expressions).
6207 if Is_Constrained (T_Typ) then
6208 Evolve_Or_Else
6209 (Cond,
6210 Range_Equal_E_Cond (Exptyp, T_Typ, Indx));
6212 else
6213 Evolve_Or_Else
6214 (Cond, Range_E_Cond (Exptyp, T_Typ, Indx));
6215 end if;
6216 end if;
6218 Next (L_Index);
6219 Next (R_Index);
6221 end if;
6222 end loop;
6223 end;
6225 -- Handle cases where we do not get a usable actual subtype that
6226 -- is constrained. This happens for example in the function call
6227 -- and explicit dereference cases. In these cases, we have to get
6228 -- the length or range from the expression itself, making sure we
6229 -- do not evaluate it more than once.
6231 -- Here Ck_Node is the original expression, or more properly the
6232 -- result of applying Duplicate_Expr to the original tree,
6233 -- forcing the result to be a name.
6235 else
6236 declare
6237 Ndims : constant Nat := Number_Dimensions (T_Typ);
6239 begin
6240 -- Build the condition for the explicit dereference case
6242 for Indx in 1 .. Ndims loop
6243 Evolve_Or_Else
6244 (Cond, Range_N_Cond (Ck_Node, T_Typ, Indx));
6245 end loop;
6246 end;
6248 end if;
6250 else
6251 -- Generate an Action to check that the bounds of the
6252 -- source value are within the constraints imposed by the
6253 -- target type for a conversion to an unconstrained type.
6254 -- Rule is 4.6(38).
6256 if Nkind (Parent (Ck_Node)) = N_Type_Conversion then
6257 declare
6258 Opnd_Index : Node_Id;
6259 Targ_Index : Node_Id;
6261 begin
6262 Opnd_Index
6263 := First_Index (Get_Actual_Subtype (Ck_Node));
6264 Targ_Index := First_Index (T_Typ);
6266 while Opnd_Index /= Empty loop
6267 if Nkind (Opnd_Index) = N_Range then
6268 if Is_In_Range
6269 (Low_Bound (Opnd_Index), Etype (Targ_Index))
6270 and then
6271 Is_In_Range
6272 (High_Bound (Opnd_Index), Etype (Targ_Index))
6273 then
6274 null;
6276 -- If null range, no check needed
6278 elsif
6279 Compile_Time_Known_Value (High_Bound (Opnd_Index))
6280 and then
6281 Compile_Time_Known_Value (Low_Bound (Opnd_Index))
6282 and then
6283 Expr_Value (High_Bound (Opnd_Index)) <
6284 Expr_Value (Low_Bound (Opnd_Index))
6285 then
6286 null;
6288 elsif Is_Out_Of_Range
6289 (Low_Bound (Opnd_Index), Etype (Targ_Index))
6290 or else
6291 Is_Out_Of_Range
6292 (High_Bound (Opnd_Index), Etype (Targ_Index))
6293 then
6294 Add_Check
6295 (Compile_Time_Constraint_Error
6296 (Wnode, "value out of range of}?", T_Typ));
6298 else
6299 Evolve_Or_Else
6300 (Cond,
6301 Discrete_Range_Cond
6302 (Opnd_Index, Etype (Targ_Index)));
6303 end if;
6304 end if;
6306 Next_Index (Opnd_Index);
6307 Next_Index (Targ_Index);
6308 end loop;
6309 end;
6310 end if;
6311 end if;
6312 end if;
6314 -- Construct the test and insert into the tree
6316 if Present (Cond) then
6317 if Do_Access then
6318 Cond := Guard_Access (Cond, Loc, Ck_Node);
6319 end if;
6321 Add_Check
6322 (Make_Raise_Constraint_Error (Loc,
6323 Condition => Cond,
6324 Reason => CE_Range_Check_Failed));
6325 end if;
6327 return Ret_Result;
6328 end Selected_Range_Checks;
6330 -------------------------------
6331 -- Storage_Checks_Suppressed --
6332 -------------------------------
6334 function Storage_Checks_Suppressed (E : Entity_Id) return Boolean is
6335 begin
6336 if Present (E) and then Checks_May_Be_Suppressed (E) then
6337 return Is_Check_Suppressed (E, Storage_Check);
6338 else
6339 return Scope_Suppress (Storage_Check);
6340 end if;
6341 end Storage_Checks_Suppressed;
6343 ---------------------------
6344 -- Tag_Checks_Suppressed --
6345 ---------------------------
6347 function Tag_Checks_Suppressed (E : Entity_Id) return Boolean is
6348 begin
6349 if Present (E) then
6350 if Kill_Tag_Checks (E) then
6351 return True;
6352 elsif Checks_May_Be_Suppressed (E) then
6353 return Is_Check_Suppressed (E, Tag_Check);
6354 end if;
6355 end if;
6357 return Scope_Suppress (Tag_Check);
6358 end Tag_Checks_Suppressed;
6360 end Checks;