* gnu/regexp/CharIndexedReader.java: Removed.
[official-gcc.git] / gcc / ada / checks.adb
blob713ea26306caef740cefb642a8fd778365309f17
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-2004 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_Ch8; use Sem_Ch8;
47 with Sem_Res; use Sem_Res;
48 with Sem_Util; use Sem_Util;
49 with Sem_Warn; use Sem_Warn;
50 with Sinfo; use Sinfo;
51 with Sinput; use Sinput;
52 with Snames; use Snames;
53 with Sprint; use Sprint;
54 with Stand; use Stand;
55 with Targparm; use Targparm;
56 with Tbuild; use Tbuild;
57 with Ttypes; use Ttypes;
58 with Urealp; use Urealp;
59 with Validsw; use Validsw;
61 package body Checks is
63 -- General note: many of these routines are concerned with generating
64 -- checking code to make sure that constraint error is raised at runtime.
65 -- Clearly this code is only needed if the expander is active, since
66 -- otherwise we will not be generating code or going into the runtime
67 -- execution anyway.
69 -- We therefore disconnect most of these checks if the expander is
70 -- inactive. This has the additional benefit that we do not need to
71 -- worry about the tree being messed up by previous errors (since errors
72 -- turn off expansion anyway).
74 -- There are a few exceptions to the above rule. For instance routines
75 -- such as Apply_Scalar_Range_Check that do not insert any code can be
76 -- safely called even when the Expander is inactive (but Errors_Detected
77 -- is 0). The benefit of executing this code when expansion is off, is
78 -- the ability to emit constraint error warning for static expressions
79 -- even when we are not generating code.
81 -------------------------------------
82 -- Suppression of Redundant Checks --
83 -------------------------------------
85 -- This unit implements a limited circuit for removal of redundant
86 -- checks. The processing is based on a tracing of simple sequential
87 -- flow. For any sequence of statements, we save expressions that are
88 -- marked to be checked, and then if the same expression appears later
89 -- with the same check, then under certain circumstances, the second
90 -- check can be suppressed.
92 -- Basically, we can suppress the check if we know for certain that
93 -- the previous expression has been elaborated (together with its
94 -- check), and we know that the exception frame is the same, and that
95 -- nothing has happened to change the result of the exception.
97 -- Let us examine each of these three conditions in turn to describe
98 -- how we ensure that this condition is met.
100 -- First, we need to know for certain that the previous expression has
101 -- been executed. This is done principly by the mechanism of calling
102 -- Conditional_Statements_Begin at the start of any statement sequence
103 -- and Conditional_Statements_End at the end. The End call causes all
104 -- checks remembered since the Begin call to be discarded. This does
105 -- miss a few cases, notably the case of a nested BEGIN-END block with
106 -- no exception handlers. But the important thing is to be conservative.
107 -- The other protection is that all checks are discarded if a label
108 -- is encountered, since then the assumption of sequential execution
109 -- is violated, and we don't know enough about the flow.
111 -- Second, we need to know that the exception frame is the same. We
112 -- do this by killing all remembered checks when we enter a new frame.
113 -- Again, that's over-conservative, but generally the cases we can help
114 -- with are pretty local anyway (like the body of a loop for example).
116 -- Third, we must be sure to forget any checks which are no longer valid.
117 -- This is done by two mechanisms, first the Kill_Checks_Variable call is
118 -- used to note any changes to local variables. We only attempt to deal
119 -- with checks involving local variables, so we do not need to worry
120 -- about global variables. Second, a call to any non-global procedure
121 -- causes us to abandon all stored checks, since such a all may affect
122 -- the values of any local variables.
124 -- The following define the data structures used to deal with remembering
125 -- checks so that redundant checks can be eliminated as described above.
127 -- Right now, the only expressions that we deal with are of the form of
128 -- simple local objects (either declared locally, or IN parameters) or
129 -- such objects plus/minus a compile time known constant. We can do
130 -- more later on if it seems worthwhile, but this catches many simple
131 -- cases in practice.
133 -- The following record type reflects a single saved check. An entry
134 -- is made in the stack of saved checks if and only if the expression
135 -- has been elaborated with the indicated checks.
137 type Saved_Check is record
138 Killed : Boolean;
139 -- Set True if entry is killed by Kill_Checks
141 Entity : Entity_Id;
142 -- The entity involved in the expression that is checked
144 Offset : Uint;
145 -- A compile time value indicating the result of adding or
146 -- subtracting a compile time value. This value is to be
147 -- added to the value of the Entity. A value of zero is
148 -- used for the case of a simple entity reference.
150 Check_Type : Character;
151 -- This is set to 'R' for a range check (in which case Target_Type
152 -- is set to the target type for the range check) or to 'O' for an
153 -- overflow check (in which case Target_Type is set to Empty).
155 Target_Type : Entity_Id;
156 -- Used only if Do_Range_Check is set. Records the target type for
157 -- the check. We need this, because a check is a duplicate only if
158 -- it has a the same target type (or more accurately one with a
159 -- range that is smaller or equal to the stored target type of a
160 -- saved check).
161 end record;
163 -- The following table keeps track of saved checks. Rather than use an
164 -- extensible table. We just use a table of fixed size, and we discard
165 -- any saved checks that do not fit. That's very unlikely to happen and
166 -- this is only an optimization in any case.
168 Saved_Checks : array (Int range 1 .. 200) of Saved_Check;
169 -- Array of saved checks
171 Num_Saved_Checks : Nat := 0;
172 -- Number of saved checks
174 -- The following stack keeps track of statement ranges. It is treated
175 -- as a stack. When Conditional_Statements_Begin is called, an entry
176 -- is pushed onto this stack containing the value of Num_Saved_Checks
177 -- at the time of the call. Then when Conditional_Statements_End is
178 -- called, this value is popped off and used to reset Num_Saved_Checks.
180 -- Note: again, this is a fixed length stack with a size that should
181 -- always be fine. If the value of the stack pointer goes above the
182 -- limit, then we just forget all saved checks.
184 Saved_Checks_Stack : array (Int range 1 .. 100) of Nat;
185 Saved_Checks_TOS : Nat := 0;
187 -----------------------
188 -- Local Subprograms --
189 -----------------------
191 procedure Apply_Float_Conversion_Check
192 (Ck_Node : Node_Id;
193 Target_Typ : Entity_Id);
194 -- The checks on a conversion from a floating-point type to an integer
195 -- type are delicate. They have to be performed before conversion, they
196 -- have to raise an exception when the operand is a NaN, and rounding must
197 -- be taken into account to determine the safe bounds of the operand.
199 procedure Apply_Selected_Length_Checks
200 (Ck_Node : Node_Id;
201 Target_Typ : Entity_Id;
202 Source_Typ : Entity_Id;
203 Do_Static : Boolean);
204 -- This is the subprogram that does all the work for Apply_Length_Check
205 -- and Apply_Static_Length_Check. Expr, Target_Typ and Source_Typ are as
206 -- described for the above routines. The Do_Static flag indicates that
207 -- only a static check is to be done.
209 procedure Apply_Selected_Range_Checks
210 (Ck_Node : Node_Id;
211 Target_Typ : Entity_Id;
212 Source_Typ : Entity_Id;
213 Do_Static : Boolean);
214 -- This is the subprogram that does all the work for Apply_Range_Check.
215 -- Expr, Target_Typ and Source_Typ are as described for the above
216 -- routine. The Do_Static flag indicates that only a static check is
217 -- to be done.
219 procedure Find_Check
220 (Expr : Node_Id;
221 Check_Type : Character;
222 Target_Type : Entity_Id;
223 Entry_OK : out Boolean;
224 Check_Num : out Nat;
225 Ent : out Entity_Id;
226 Ofs : out Uint);
227 -- This routine is used by Enable_Range_Check and Enable_Overflow_Check
228 -- to see if a check is of the form for optimization, and if so, to see
229 -- if it has already been performed. Expr is the expression to check,
230 -- and Check_Type is 'R' for a range check, 'O' for an overflow check.
231 -- Target_Type is the target type for a range check, and Empty for an
232 -- overflow check. If the entry is not of the form for optimization,
233 -- then Entry_OK is set to False, and the remaining out parameters
234 -- are undefined. If the entry is OK, then Ent/Ofs are set to the
235 -- entity and offset from the expression. Check_Num is the number of
236 -- a matching saved entry in Saved_Checks, or zero if no such entry
237 -- is located.
239 function Get_Discriminal (E : Entity_Id; Bound : Node_Id) return Node_Id;
240 -- If a discriminal is used in constraining a prival, Return reference
241 -- to the discriminal of the protected body (which renames the parameter
242 -- of the enclosing protected operation). This clumsy transformation is
243 -- needed because privals are created too late and their actual subtypes
244 -- are not available when analysing the bodies of the protected operations.
245 -- To be cleaned up???
247 function Guard_Access
248 (Cond : Node_Id;
249 Loc : Source_Ptr;
250 Ck_Node : Node_Id) return Node_Id;
251 -- In the access type case, guard the test with a test to ensure
252 -- that the access value is non-null, since the checks do not
253 -- not apply to null access values.
255 procedure Install_Null_Excluding_Check (N : Node_Id);
256 -- Determines whether an access node requires a runtime access check and
257 -- if so inserts the appropriate run-time check
259 procedure Install_Static_Check (R_Cno : Node_Id; Loc : Source_Ptr);
260 -- Called by Apply_{Length,Range}_Checks to rewrite the tree with the
261 -- Constraint_Error node.
263 function Selected_Length_Checks
264 (Ck_Node : Node_Id;
265 Target_Typ : Entity_Id;
266 Source_Typ : Entity_Id;
267 Warn_Node : Node_Id) return Check_Result;
268 -- Like Apply_Selected_Length_Checks, except it doesn't modify
269 -- anything, just returns a list of nodes as described in the spec of
270 -- this package for the Range_Check function.
272 function Selected_Range_Checks
273 (Ck_Node : Node_Id;
274 Target_Typ : Entity_Id;
275 Source_Typ : Entity_Id;
276 Warn_Node : Node_Id) return Check_Result;
277 -- Like Apply_Selected_Range_Checks, except it doesn't modify anything,
278 -- just returns a list of nodes as described in the spec of this package
279 -- for the Range_Check function.
281 ------------------------------
282 -- Access_Checks_Suppressed --
283 ------------------------------
285 function Access_Checks_Suppressed (E : Entity_Id) return Boolean is
286 begin
287 if Present (E) and then Checks_May_Be_Suppressed (E) then
288 return Is_Check_Suppressed (E, Access_Check);
289 else
290 return Scope_Suppress (Access_Check);
291 end if;
292 end Access_Checks_Suppressed;
294 -------------------------------------
295 -- Accessibility_Checks_Suppressed --
296 -------------------------------------
298 function Accessibility_Checks_Suppressed (E : Entity_Id) return Boolean is
299 begin
300 if Present (E) and then Checks_May_Be_Suppressed (E) then
301 return Is_Check_Suppressed (E, Accessibility_Check);
302 else
303 return Scope_Suppress (Accessibility_Check);
304 end if;
305 end Accessibility_Checks_Suppressed;
307 -------------------------
308 -- Append_Range_Checks --
309 -------------------------
311 procedure Append_Range_Checks
312 (Checks : Check_Result;
313 Stmts : List_Id;
314 Suppress_Typ : Entity_Id;
315 Static_Sloc : Source_Ptr;
316 Flag_Node : Node_Id)
318 Internal_Flag_Node : constant Node_Id := Flag_Node;
319 Internal_Static_Sloc : constant Source_Ptr := Static_Sloc;
321 Checks_On : constant Boolean :=
322 (not Index_Checks_Suppressed (Suppress_Typ))
323 or else
324 (not Range_Checks_Suppressed (Suppress_Typ));
326 begin
327 -- For now we just return if Checks_On is false, however this should
328 -- be enhanced to check for an always True value in the condition
329 -- and to generate a compilation warning???
331 if not Checks_On then
332 return;
333 end if;
335 for J in 1 .. 2 loop
336 exit when No (Checks (J));
338 if Nkind (Checks (J)) = N_Raise_Constraint_Error
339 and then Present (Condition (Checks (J)))
340 then
341 if not Has_Dynamic_Range_Check (Internal_Flag_Node) then
342 Append_To (Stmts, Checks (J));
343 Set_Has_Dynamic_Range_Check (Internal_Flag_Node);
344 end if;
346 else
347 Append_To
348 (Stmts,
349 Make_Raise_Constraint_Error (Internal_Static_Sloc,
350 Reason => CE_Range_Check_Failed));
351 end if;
352 end loop;
353 end Append_Range_Checks;
355 ------------------------
356 -- Apply_Access_Check --
357 ------------------------
359 procedure Apply_Access_Check (N : Node_Id) is
360 P : constant Node_Id := Prefix (N);
362 begin
363 if Inside_A_Generic then
364 return;
365 end if;
367 if Is_Entity_Name (P) then
368 Check_Unset_Reference (P);
369 end if;
371 -- Don't need access check if prefix is known to be non-null
373 if Known_Non_Null (P) then
374 return;
376 -- Don't need access checks if they are suppressed on the type
378 elsif Access_Checks_Suppressed (Etype (P)) then
379 return;
380 end if;
382 -- Case where P is an entity name
384 if Is_Entity_Name (P) then
385 declare
386 Ent : constant Entity_Id := Entity (P);
388 begin
389 if Access_Checks_Suppressed (Ent) then
390 return;
391 end if;
393 -- Otherwise we are going to generate an access check, and
394 -- are we have done it, the entity will now be known non null
395 -- But we have to check for safe sequential semantics here!
397 if Safe_To_Capture_Value (N, Ent) then
398 Set_Is_Known_Non_Null (Ent);
399 end if;
400 end;
401 end if;
403 -- Access check is required
405 Install_Null_Excluding_Check (P);
406 end Apply_Access_Check;
408 -------------------------------
409 -- Apply_Accessibility_Check --
410 -------------------------------
412 procedure Apply_Accessibility_Check (N : Node_Id; Typ : Entity_Id) is
413 Loc : constant Source_Ptr := Sloc (N);
414 Param_Ent : constant Entity_Id := Param_Entity (N);
415 Param_Level : Node_Id;
416 Type_Level : Node_Id;
418 begin
419 if Inside_A_Generic then
420 return;
422 -- Only apply the run-time check if the access parameter
423 -- has an associated extra access level parameter and
424 -- when the level of the type is less deep than the level
425 -- of the access parameter.
427 elsif Present (Param_Ent)
428 and then Present (Extra_Accessibility (Param_Ent))
429 and then UI_Gt (Object_Access_Level (N),
430 Type_Access_Level (Typ))
431 and then not Accessibility_Checks_Suppressed (Param_Ent)
432 and then not Accessibility_Checks_Suppressed (Typ)
433 then
434 Param_Level :=
435 New_Occurrence_Of (Extra_Accessibility (Param_Ent), Loc);
437 Type_Level :=
438 Make_Integer_Literal (Loc, Type_Access_Level (Typ));
440 -- Raise Program_Error if the accessibility level of the
441 -- the access parameter is deeper than the level of the
442 -- target access type.
444 Insert_Action (N,
445 Make_Raise_Program_Error (Loc,
446 Condition =>
447 Make_Op_Gt (Loc,
448 Left_Opnd => Param_Level,
449 Right_Opnd => Type_Level),
450 Reason => PE_Accessibility_Check_Failed));
452 Analyze_And_Resolve (N);
453 end if;
454 end Apply_Accessibility_Check;
456 ---------------------------
457 -- Apply_Alignment_Check --
458 ---------------------------
460 procedure Apply_Alignment_Check (E : Entity_Id; N : Node_Id) is
461 AC : constant Node_Id := Address_Clause (E);
462 Expr : Node_Id;
463 Loc : Source_Ptr;
465 Alignment_Required : constant Boolean := Maximum_Alignment > 1;
466 -- Constant to show whether target requires alignment checks
468 begin
469 -- See if check needed. Note that we never need a check if the
470 -- maximum alignment is one, since the check will always succeed
472 if No (AC)
473 or else not Check_Address_Alignment (AC)
474 or else not Alignment_Required
475 then
476 return;
477 end if;
479 Loc := Sloc (AC);
480 Expr := Expression (AC);
482 if Nkind (Expr) = N_Unchecked_Type_Conversion then
483 Expr := Expression (Expr);
485 elsif Nkind (Expr) = N_Function_Call
486 and then Is_RTE (Entity (Name (Expr)), RE_To_Address)
487 then
488 Expr := First (Parameter_Associations (Expr));
490 if Nkind (Expr) = N_Parameter_Association then
491 Expr := Explicit_Actual_Parameter (Expr);
492 end if;
493 end if;
495 -- Here Expr is the address value. See if we know that the
496 -- value is unacceptable at compile time.
498 if Compile_Time_Known_Value (Expr)
499 and then Known_Alignment (E)
500 then
501 if Expr_Value (Expr) mod Alignment (E) /= 0 then
502 Insert_Action (N,
503 Make_Raise_Program_Error (Loc,
504 Reason => PE_Misaligned_Address_Value));
505 Error_Msg_NE
506 ("?specified address for& not " &
507 "consistent with alignment ('R'M 13.3(27))", Expr, E);
508 end if;
510 -- Here we do not know if the value is acceptable, generate
511 -- code to raise PE if alignment is inappropriate.
513 else
514 -- Skip generation of this code if we don't want elab code
516 if not Restriction_Active (No_Elaboration_Code) then
517 Insert_After_And_Analyze (N,
518 Make_Raise_Program_Error (Loc,
519 Condition =>
520 Make_Op_Ne (Loc,
521 Left_Opnd =>
522 Make_Op_Mod (Loc,
523 Left_Opnd =>
524 Unchecked_Convert_To
525 (RTE (RE_Integer_Address),
526 Duplicate_Subexpr_No_Checks (Expr)),
527 Right_Opnd =>
528 Make_Attribute_Reference (Loc,
529 Prefix => New_Occurrence_Of (E, Loc),
530 Attribute_Name => Name_Alignment)),
531 Right_Opnd => Make_Integer_Literal (Loc, Uint_0)),
532 Reason => PE_Misaligned_Address_Value),
533 Suppress => All_Checks);
534 end if;
535 end if;
537 return;
539 exception
540 when RE_Not_Available =>
541 return;
542 end Apply_Alignment_Check;
544 -------------------------------------
545 -- Apply_Arithmetic_Overflow_Check --
546 -------------------------------------
548 -- This routine is called only if the type is an integer type, and
549 -- a software arithmetic overflow check must be performed for op
550 -- (add, subtract, multiply). The check is performed only if
551 -- Software_Overflow_Checking is enabled and Do_Overflow_Check
552 -- is set. In this case we expand the operation into a more complex
553 -- sequence of tests that ensures that overflow is properly caught.
555 procedure Apply_Arithmetic_Overflow_Check (N : Node_Id) is
556 Loc : constant Source_Ptr := Sloc (N);
557 Typ : constant Entity_Id := Etype (N);
558 Rtyp : constant Entity_Id := Root_Type (Typ);
559 Siz : constant Int := UI_To_Int (Esize (Rtyp));
560 Dsiz : constant Int := Siz * 2;
561 Opnod : Node_Id;
562 Ctyp : Entity_Id;
563 Opnd : Node_Id;
564 Cent : RE_Id;
566 begin
567 -- Skip this if overflow checks are done in back end, or the overflow
568 -- flag is not set anyway, or we are not doing code expansion.
570 if Backend_Overflow_Checks_On_Target
571 or not Do_Overflow_Check (N)
572 or not Expander_Active
573 then
574 return;
575 end if;
577 -- Otherwise, we generate the full general code for front end overflow
578 -- detection, which works by doing arithmetic in a larger type:
580 -- x op y
582 -- is expanded into
584 -- Typ (Checktyp (x) op Checktyp (y));
586 -- where Typ is the type of the original expression, and Checktyp is
587 -- an integer type of sufficient length to hold the largest possible
588 -- result.
590 -- In the case where check type exceeds the size of Long_Long_Integer,
591 -- we use a different approach, expanding to:
593 -- typ (xxx_With_Ovflo_Check (Integer_64 (x), Integer (y)))
595 -- where xxx is Add, Multiply or Subtract as appropriate
597 -- Find check type if one exists
599 if Dsiz <= Standard_Integer_Size then
600 Ctyp := Standard_Integer;
602 elsif Dsiz <= Standard_Long_Long_Integer_Size then
603 Ctyp := Standard_Long_Long_Integer;
605 -- No check type exists, use runtime call
607 else
608 if Nkind (N) = N_Op_Add then
609 Cent := RE_Add_With_Ovflo_Check;
611 elsif Nkind (N) = N_Op_Multiply then
612 Cent := RE_Multiply_With_Ovflo_Check;
614 else
615 pragma Assert (Nkind (N) = N_Op_Subtract);
616 Cent := RE_Subtract_With_Ovflo_Check;
617 end if;
619 Rewrite (N,
620 OK_Convert_To (Typ,
621 Make_Function_Call (Loc,
622 Name => New_Reference_To (RTE (Cent), Loc),
623 Parameter_Associations => New_List (
624 OK_Convert_To (RTE (RE_Integer_64), Left_Opnd (N)),
625 OK_Convert_To (RTE (RE_Integer_64), Right_Opnd (N))))));
627 Analyze_And_Resolve (N, Typ);
628 return;
629 end if;
631 -- If we fall through, we have the case where we do the arithmetic in
632 -- the next higher type and get the check by conversion. In these cases
633 -- Ctyp is set to the type to be used as the check type.
635 Opnod := Relocate_Node (N);
637 Opnd := OK_Convert_To (Ctyp, Left_Opnd (Opnod));
639 Analyze (Opnd);
640 Set_Etype (Opnd, Ctyp);
641 Set_Analyzed (Opnd, True);
642 Set_Left_Opnd (Opnod, Opnd);
644 Opnd := OK_Convert_To (Ctyp, Right_Opnd (Opnod));
646 Analyze (Opnd);
647 Set_Etype (Opnd, Ctyp);
648 Set_Analyzed (Opnd, True);
649 Set_Right_Opnd (Opnod, Opnd);
651 -- The type of the operation changes to the base type of the check
652 -- type, and we reset the overflow check indication, since clearly
653 -- no overflow is possible now that we are using a double length
654 -- type. We also set the Analyzed flag to avoid a recursive attempt
655 -- to expand the node.
657 Set_Etype (Opnod, Base_Type (Ctyp));
658 Set_Do_Overflow_Check (Opnod, False);
659 Set_Analyzed (Opnod, True);
661 -- Now build the outer conversion
663 Opnd := OK_Convert_To (Typ, Opnod);
664 Analyze (Opnd);
665 Set_Etype (Opnd, Typ);
667 -- In the discrete type case, we directly generate the range check
668 -- for the outer operand. This range check will implement the required
669 -- overflow check.
671 if Is_Discrete_Type (Typ) then
672 Rewrite (N, Opnd);
673 Generate_Range_Check (Expression (N), Typ, CE_Overflow_Check_Failed);
675 -- For other types, we enable overflow checking on the conversion,
676 -- after setting the node as analyzed to prevent recursive attempts
677 -- to expand the conversion node.
679 else
680 Set_Analyzed (Opnd, True);
681 Enable_Overflow_Check (Opnd);
682 Rewrite (N, Opnd);
683 end if;
685 exception
686 when RE_Not_Available =>
687 return;
688 end Apply_Arithmetic_Overflow_Check;
690 ----------------------------
691 -- Apply_Array_Size_Check --
692 ----------------------------
694 -- Note: Really of course this entre check should be in the backend,
695 -- and perhaps this is not quite the right value, but it is good
696 -- enough to catch the normal cases (and the relevant ACVC tests!)
698 procedure Apply_Array_Size_Check (N : Node_Id; Typ : Entity_Id) is
699 Loc : constant Source_Ptr := Sloc (N);
700 Ctyp : constant Entity_Id := Component_Type (Typ);
701 Ent : constant Entity_Id := Defining_Identifier (N);
702 Decl : Node_Id;
703 Lo : Node_Id;
704 Hi : Node_Id;
705 Lob : Uint;
706 Hib : Uint;
707 Siz : Uint;
708 Xtyp : Entity_Id;
709 Indx : Node_Id;
710 Sizx : Node_Id;
711 Code : Node_Id;
713 Static : Boolean := True;
714 -- Set false if any index subtye bound is non-static
716 Umark : constant Uintp.Save_Mark := Uintp.Mark;
717 -- We can throw away all the Uint computations here, since they are
718 -- done only to generate boolean test results.
720 Check_Siz : Uint;
721 -- Size to check against
723 function Is_Address_Or_Import (Decl : Node_Id) return Boolean;
724 -- Determines if Decl is an address clause or Import/Interface pragma
725 -- that references the defining identifier of the current declaration.
727 --------------------------
728 -- Is_Address_Or_Import --
729 --------------------------
731 function Is_Address_Or_Import (Decl : Node_Id) return Boolean is
732 begin
733 if Nkind (Decl) = N_At_Clause then
734 return Chars (Identifier (Decl)) = Chars (Ent);
736 elsif Nkind (Decl) = N_Attribute_Definition_Clause then
737 return
738 Chars (Decl) = Name_Address
739 and then
740 Nkind (Name (Decl)) = N_Identifier
741 and then
742 Chars (Name (Decl)) = Chars (Ent);
744 elsif Nkind (Decl) = N_Pragma then
745 if (Chars (Decl) = Name_Import
746 or else
747 Chars (Decl) = Name_Interface)
748 and then Present (Pragma_Argument_Associations (Decl))
749 then
750 declare
751 F : constant Node_Id :=
752 First (Pragma_Argument_Associations (Decl));
754 begin
755 return
756 Present (F)
757 and then
758 Present (Next (F))
759 and then
760 Nkind (Expression (Next (F))) = N_Identifier
761 and then
762 Chars (Expression (Next (F))) = Chars (Ent);
763 end;
765 else
766 return False;
767 end if;
769 else
770 return False;
771 end if;
772 end Is_Address_Or_Import;
774 -- Start of processing for Apply_Array_Size_Check
776 begin
777 if not Expander_Active
778 or else Storage_Checks_Suppressed (Typ)
779 then
780 return;
781 end if;
783 -- It is pointless to insert this check inside an init proc, because
784 -- that's too late, we have already built the object to be the right
785 -- size, and if it's too large, too bad!
787 if Inside_Init_Proc then
788 return;
789 end if;
791 -- Look head for pragma interface/import or address clause applying
792 -- to this entity. If found, we suppress the check entirely. For now
793 -- we only look ahead 20 declarations to stop this becoming too slow
794 -- Note that eventually this whole routine gets moved to gigi.
796 Decl := N;
797 for Ctr in 1 .. 20 loop
798 Next (Decl);
799 exit when No (Decl);
801 if Is_Address_Or_Import (Decl) then
802 return;
803 end if;
804 end loop;
806 -- First step is to calculate the maximum number of elements. For this
807 -- calculation, we use the actual size of the subtype if it is static,
808 -- and if a bound of a subtype is non-static, we go to the bound of the
809 -- base type.
811 Siz := Uint_1;
812 Indx := First_Index (Typ);
813 while Present (Indx) loop
814 Xtyp := Etype (Indx);
815 Lo := Type_Low_Bound (Xtyp);
816 Hi := Type_High_Bound (Xtyp);
818 -- If any bound raises constraint error, we will never get this
819 -- far, so there is no need to generate any kind of check.
821 if Raises_Constraint_Error (Lo)
822 or else
823 Raises_Constraint_Error (Hi)
824 then
825 Uintp.Release (Umark);
826 return;
827 end if;
829 -- Otherwise get bounds values
831 if Is_Static_Expression (Lo) then
832 Lob := Expr_Value (Lo);
833 else
834 Lob := Expr_Value (Type_Low_Bound (Base_Type (Xtyp)));
835 Static := False;
836 end if;
838 if Is_Static_Expression (Hi) then
839 Hib := Expr_Value (Hi);
840 else
841 Hib := Expr_Value (Type_High_Bound (Base_Type (Xtyp)));
842 Static := False;
843 end if;
845 Siz := Siz * UI_Max (Hib - Lob + 1, Uint_0);
846 Next_Index (Indx);
847 end loop;
849 -- Compute the limit against which we want to check. For subprograms,
850 -- where the array will go on the stack, we use 8*2**24, which (in
851 -- bits) is the size of a 16 megabyte array.
853 if Is_Subprogram (Scope (Ent)) then
854 Check_Siz := Uint_2 ** 27;
855 else
856 Check_Siz := Uint_2 ** 31;
857 end if;
859 -- If we have all static bounds and Siz is too large, then we know we
860 -- know we have a storage error right now, so generate message
862 if Static and then Siz >= Check_Siz then
863 Insert_Action (N,
864 Make_Raise_Storage_Error (Loc,
865 Reason => SE_Object_Too_Large));
866 Error_Msg_N ("?Storage_Error will be raised at run-time", N);
867 Uintp.Release (Umark);
868 return;
869 end if;
871 -- Case of component size known at compile time. If the array
872 -- size is definitely in range, then we do not need a check.
874 if Known_Esize (Ctyp)
875 and then Siz * Esize (Ctyp) < Check_Siz
876 then
877 Uintp.Release (Umark);
878 return;
879 end if;
881 -- Here if a dynamic check is required
883 -- What we do is to build an expression for the size of the array,
884 -- which is computed as the 'Size of the array component, times
885 -- the size of each dimension.
887 Uintp.Release (Umark);
889 Sizx :=
890 Make_Attribute_Reference (Loc,
891 Prefix => New_Occurrence_Of (Ctyp, Loc),
892 Attribute_Name => Name_Size);
894 Indx := First_Index (Typ);
896 for J in 1 .. Number_Dimensions (Typ) loop
897 if Sloc (Etype (Indx)) = Sloc (N) then
898 Ensure_Defined (Etype (Indx), N);
899 end if;
901 Sizx :=
902 Make_Op_Multiply (Loc,
903 Left_Opnd => Sizx,
904 Right_Opnd =>
905 Make_Attribute_Reference (Loc,
906 Prefix => New_Occurrence_Of (Typ, Loc),
907 Attribute_Name => Name_Length,
908 Expressions => New_List (
909 Make_Integer_Literal (Loc, J))));
910 Next_Index (Indx);
911 end loop;
913 Code :=
914 Make_Raise_Storage_Error (Loc,
915 Condition =>
916 Make_Op_Ge (Loc,
917 Left_Opnd => Sizx,
918 Right_Opnd =>
919 Make_Integer_Literal (Loc, Check_Siz)),
920 Reason => SE_Object_Too_Large);
922 Set_Size_Check_Code (Defining_Identifier (N), Code);
923 Insert_Action (N, Code);
924 end Apply_Array_Size_Check;
926 ----------------------------
927 -- Apply_Constraint_Check --
928 ----------------------------
930 procedure Apply_Constraint_Check
931 (N : Node_Id;
932 Typ : Entity_Id;
933 No_Sliding : Boolean := False)
935 Desig_Typ : Entity_Id;
937 begin
938 if Inside_A_Generic then
939 return;
941 elsif Is_Scalar_Type (Typ) then
942 Apply_Scalar_Range_Check (N, Typ);
944 elsif Is_Array_Type (Typ) then
946 -- A useful optimization: an aggregate with only an Others clause
947 -- always has the right bounds.
949 if Nkind (N) = N_Aggregate
950 and then No (Expressions (N))
951 and then Nkind
952 (First (Choices (First (Component_Associations (N)))))
953 = N_Others_Choice
954 then
955 return;
956 end if;
958 if Is_Constrained (Typ) then
959 Apply_Length_Check (N, Typ);
961 if No_Sliding then
962 Apply_Range_Check (N, Typ);
963 end if;
964 else
965 Apply_Range_Check (N, Typ);
966 end if;
968 elsif (Is_Record_Type (Typ)
969 or else Is_Private_Type (Typ))
970 and then Has_Discriminants (Base_Type (Typ))
971 and then Is_Constrained (Typ)
972 then
973 Apply_Discriminant_Check (N, Typ);
975 elsif Is_Access_Type (Typ) then
977 Desig_Typ := Designated_Type (Typ);
979 -- No checks necessary if expression statically null
981 if Nkind (N) = N_Null then
982 null;
984 -- No sliding possible on access to arrays
986 elsif Is_Array_Type (Desig_Typ) then
987 if Is_Constrained (Desig_Typ) then
988 Apply_Length_Check (N, Typ);
989 end if;
991 Apply_Range_Check (N, Typ);
993 elsif Has_Discriminants (Base_Type (Desig_Typ))
994 and then Is_Constrained (Desig_Typ)
995 then
996 Apply_Discriminant_Check (N, Typ);
997 end if;
999 if Can_Never_Be_Null (Typ)
1000 and then not Can_Never_Be_Null (Etype (N))
1001 then
1002 Install_Null_Excluding_Check (N);
1003 end if;
1004 end if;
1005 end Apply_Constraint_Check;
1007 ------------------------------
1008 -- Apply_Discriminant_Check --
1009 ------------------------------
1011 procedure Apply_Discriminant_Check
1012 (N : Node_Id;
1013 Typ : Entity_Id;
1014 Lhs : Node_Id := Empty)
1016 Loc : constant Source_Ptr := Sloc (N);
1017 Do_Access : constant Boolean := Is_Access_Type (Typ);
1018 S_Typ : Entity_Id := Etype (N);
1019 Cond : Node_Id;
1020 T_Typ : Entity_Id;
1022 function Is_Aliased_Unconstrained_Component return Boolean;
1023 -- It is possible for an aliased component to have a nominal
1024 -- unconstrained subtype (through instantiation). If this is a
1025 -- discriminated component assigned in the expansion of an aggregate
1026 -- in an initialization, the check must be suppressed. This unusual
1027 -- situation requires a predicate of its own (see 7503-008).
1029 ----------------------------------------
1030 -- Is_Aliased_Unconstrained_Component --
1031 ----------------------------------------
1033 function Is_Aliased_Unconstrained_Component return Boolean is
1034 Comp : Entity_Id;
1035 Pref : Node_Id;
1037 begin
1038 if Nkind (Lhs) /= N_Selected_Component then
1039 return False;
1040 else
1041 Comp := Entity (Selector_Name (Lhs));
1042 Pref := Prefix (Lhs);
1043 end if;
1045 if Ekind (Comp) /= E_Component
1046 or else not Is_Aliased (Comp)
1047 then
1048 return False;
1049 end if;
1051 return not Comes_From_Source (Pref)
1052 and then In_Instance
1053 and then not Is_Constrained (Etype (Comp));
1054 end Is_Aliased_Unconstrained_Component;
1056 -- Start of processing for Apply_Discriminant_Check
1058 begin
1059 if Do_Access then
1060 T_Typ := Designated_Type (Typ);
1061 else
1062 T_Typ := Typ;
1063 end if;
1065 -- Nothing to do if discriminant checks are suppressed or else no code
1066 -- is to be generated
1068 if not Expander_Active
1069 or else Discriminant_Checks_Suppressed (T_Typ)
1070 then
1071 return;
1072 end if;
1074 -- No discriminant checks necessary for access when expression
1075 -- is statically Null. This is not only an optimization, this is
1076 -- fundamental because otherwise discriminant checks may be generated
1077 -- in init procs for types containing an access to a non-frozen yet
1078 -- record, causing a deadly forward reference.
1080 -- Also, if the expression is of an access type whose designated
1081 -- type is incomplete, then the access value must be null and
1082 -- we suppress the check.
1084 if Nkind (N) = N_Null then
1085 return;
1087 elsif Is_Access_Type (S_Typ) then
1088 S_Typ := Designated_Type (S_Typ);
1090 if Ekind (S_Typ) = E_Incomplete_Type then
1091 return;
1092 end if;
1093 end if;
1095 -- If an assignment target is present, then we need to generate
1096 -- the actual subtype if the target is a parameter or aliased
1097 -- object with an unconstrained nominal subtype.
1099 if Present (Lhs)
1100 and then (Present (Param_Entity (Lhs))
1101 or else (not Is_Constrained (T_Typ)
1102 and then Is_Aliased_View (Lhs)
1103 and then not Is_Aliased_Unconstrained_Component))
1104 then
1105 T_Typ := Get_Actual_Subtype (Lhs);
1106 end if;
1108 -- Nothing to do if the type is unconstrained (this is the case
1109 -- where the actual subtype in the RM sense of N is unconstrained
1110 -- and no check is required).
1112 if not Is_Constrained (T_Typ) then
1113 return;
1114 end if;
1116 -- Suppress checks if the subtypes are the same.
1117 -- the check must be preserved in an assignment to a formal, because
1118 -- the constraint is given by the actual.
1120 if Nkind (Original_Node (N)) /= N_Allocator
1121 and then (No (Lhs)
1122 or else not Is_Entity_Name (Lhs)
1123 or else No (Param_Entity (Lhs)))
1124 then
1125 if (Etype (N) = Typ
1126 or else (Do_Access and then Designated_Type (Typ) = S_Typ))
1127 and then not Is_Aliased_View (Lhs)
1128 then
1129 return;
1130 end if;
1132 -- We can also eliminate checks on allocators with a subtype mark
1133 -- that coincides with the context type. The context type may be a
1134 -- subtype without a constraint (common case, a generic actual).
1136 elsif Nkind (Original_Node (N)) = N_Allocator
1137 and then Is_Entity_Name (Expression (Original_Node (N)))
1138 then
1139 declare
1140 Alloc_Typ : constant Entity_Id :=
1141 Entity (Expression (Original_Node (N)));
1143 begin
1144 if Alloc_Typ = T_Typ
1145 or else (Nkind (Parent (T_Typ)) = N_Subtype_Declaration
1146 and then Is_Entity_Name (
1147 Subtype_Indication (Parent (T_Typ)))
1148 and then Alloc_Typ = Base_Type (T_Typ))
1150 then
1151 return;
1152 end if;
1153 end;
1154 end if;
1156 -- See if we have a case where the types are both constrained, and
1157 -- all the constraints are constants. In this case, we can do the
1158 -- check successfully at compile time.
1160 -- We skip this check for the case where the node is a rewritten`
1161 -- allocator, because it already carries the context subtype, and
1162 -- extracting the discriminants from the aggregate is messy.
1164 if Is_Constrained (S_Typ)
1165 and then Nkind (Original_Node (N)) /= N_Allocator
1166 then
1167 declare
1168 DconT : Elmt_Id;
1169 Discr : Entity_Id;
1170 DconS : Elmt_Id;
1171 ItemS : Node_Id;
1172 ItemT : Node_Id;
1174 begin
1175 -- S_Typ may not have discriminants in the case where it is a
1176 -- private type completed by a default discriminated type. In
1177 -- that case, we need to get the constraints from the
1178 -- underlying_type. If the underlying type is unconstrained (i.e.
1179 -- has no default discriminants) no check is needed.
1181 if Has_Discriminants (S_Typ) then
1182 Discr := First_Discriminant (S_Typ);
1183 DconS := First_Elmt (Discriminant_Constraint (S_Typ));
1185 else
1186 Discr := First_Discriminant (Underlying_Type (S_Typ));
1187 DconS :=
1188 First_Elmt
1189 (Discriminant_Constraint (Underlying_Type (S_Typ)));
1191 if No (DconS) then
1192 return;
1193 end if;
1195 -- A further optimization: if T_Typ is derived from S_Typ
1196 -- without imposing a constraint, no check is needed.
1198 if Nkind (Original_Node (Parent (T_Typ))) =
1199 N_Full_Type_Declaration
1200 then
1201 declare
1202 Type_Def : constant Node_Id :=
1203 Type_Definition
1204 (Original_Node (Parent (T_Typ)));
1205 begin
1206 if Nkind (Type_Def) = N_Derived_Type_Definition
1207 and then Is_Entity_Name (Subtype_Indication (Type_Def))
1208 and then Entity (Subtype_Indication (Type_Def)) = S_Typ
1209 then
1210 return;
1211 end if;
1212 end;
1213 end if;
1214 end if;
1216 DconT := First_Elmt (Discriminant_Constraint (T_Typ));
1218 while Present (Discr) loop
1219 ItemS := Node (DconS);
1220 ItemT := Node (DconT);
1222 exit when
1223 not Is_OK_Static_Expression (ItemS)
1224 or else
1225 not Is_OK_Static_Expression (ItemT);
1227 if Expr_Value (ItemS) /= Expr_Value (ItemT) then
1228 if Do_Access then -- needs run-time check.
1229 exit;
1230 else
1231 Apply_Compile_Time_Constraint_Error
1232 (N, "incorrect value for discriminant&?",
1233 CE_Discriminant_Check_Failed, Ent => Discr);
1234 return;
1235 end if;
1236 end if;
1238 Next_Elmt (DconS);
1239 Next_Elmt (DconT);
1240 Next_Discriminant (Discr);
1241 end loop;
1243 if No (Discr) then
1244 return;
1245 end if;
1246 end;
1247 end if;
1249 -- Here we need a discriminant check. First build the expression
1250 -- for the comparisons of the discriminants:
1252 -- (n.disc1 /= typ.disc1) or else
1253 -- (n.disc2 /= typ.disc2) or else
1254 -- ...
1255 -- (n.discn /= typ.discn)
1257 Cond := Build_Discriminant_Checks (N, T_Typ);
1259 -- If Lhs is set and is a parameter, then the condition is
1260 -- guarded by: lhs'constrained and then (condition built above)
1262 if Present (Param_Entity (Lhs)) then
1263 Cond :=
1264 Make_And_Then (Loc,
1265 Left_Opnd =>
1266 Make_Attribute_Reference (Loc,
1267 Prefix => New_Occurrence_Of (Param_Entity (Lhs), Loc),
1268 Attribute_Name => Name_Constrained),
1269 Right_Opnd => Cond);
1270 end if;
1272 if Do_Access then
1273 Cond := Guard_Access (Cond, Loc, N);
1274 end if;
1276 Insert_Action (N,
1277 Make_Raise_Constraint_Error (Loc,
1278 Condition => Cond,
1279 Reason => CE_Discriminant_Check_Failed));
1280 end Apply_Discriminant_Check;
1282 ------------------------
1283 -- Apply_Divide_Check --
1284 ------------------------
1286 procedure Apply_Divide_Check (N : Node_Id) is
1287 Loc : constant Source_Ptr := Sloc (N);
1288 Typ : constant Entity_Id := Etype (N);
1289 Left : constant Node_Id := Left_Opnd (N);
1290 Right : constant Node_Id := Right_Opnd (N);
1292 LLB : Uint;
1293 Llo : Uint;
1294 Lhi : Uint;
1295 LOK : Boolean;
1296 Rlo : Uint;
1297 Rhi : Uint;
1298 ROK : Boolean;
1300 begin
1301 if Expander_Active
1302 and not Backend_Divide_Checks_On_Target
1303 then
1304 Determine_Range (Right, ROK, Rlo, Rhi);
1306 -- See if division by zero possible, and if so generate test. This
1307 -- part of the test is not controlled by the -gnato switch.
1309 if Do_Division_Check (N) then
1311 if (not ROK) or else (Rlo <= 0 and then 0 <= Rhi) then
1312 Insert_Action (N,
1313 Make_Raise_Constraint_Error (Loc,
1314 Condition =>
1315 Make_Op_Eq (Loc,
1316 Left_Opnd => Duplicate_Subexpr_Move_Checks (Right),
1317 Right_Opnd => Make_Integer_Literal (Loc, 0)),
1318 Reason => CE_Divide_By_Zero));
1319 end if;
1320 end if;
1322 -- Test for extremely annoying case of xxx'First divided by -1
1324 if Do_Overflow_Check (N) then
1326 if Nkind (N) = N_Op_Divide
1327 and then Is_Signed_Integer_Type (Typ)
1328 then
1329 Determine_Range (Left, LOK, Llo, Lhi);
1330 LLB := Expr_Value (Type_Low_Bound (Base_Type (Typ)));
1332 if ((not ROK) or else (Rlo <= (-1) and then (-1) <= Rhi))
1333 and then
1334 ((not LOK) or else (Llo = LLB))
1335 then
1336 Insert_Action (N,
1337 Make_Raise_Constraint_Error (Loc,
1338 Condition =>
1339 Make_And_Then (Loc,
1341 Make_Op_Eq (Loc,
1342 Left_Opnd =>
1343 Duplicate_Subexpr_Move_Checks (Left),
1344 Right_Opnd => Make_Integer_Literal (Loc, LLB)),
1346 Make_Op_Eq (Loc,
1347 Left_Opnd =>
1348 Duplicate_Subexpr (Right),
1349 Right_Opnd =>
1350 Make_Integer_Literal (Loc, -1))),
1351 Reason => CE_Overflow_Check_Failed));
1352 end if;
1353 end if;
1354 end if;
1355 end if;
1356 end Apply_Divide_Check;
1358 ----------------------------------
1359 -- Apply_Float_Conversion_Check --
1360 ----------------------------------
1362 -- Let F and I be the source and target types of the conversion.
1363 -- The Ada standard specifies that a floating-point value X is rounded
1364 -- to the nearest integer, with halfway cases being rounded away from
1365 -- zero. The rounded value of X is checked against I'Range.
1367 -- The catch in the above paragraph is that there is no good way
1368 -- to know whether the round-to-integer operation resulted in
1369 -- overflow. A remedy is to perform a range check in the floating-point
1370 -- domain instead, however:
1371 -- (1) The bounds may not be known at compile time
1372 -- (2) The check must take into account possible rounding.
1373 -- (3) The range of type I may not be exactly representable in F.
1374 -- (4) The end-points I'First - 0.5 and I'Last + 0.5 may or may
1375 -- not be in range, depending on the sign of I'First and I'Last.
1376 -- (5) X may be a NaN, which will fail any comparison
1378 -- The following steps take care of these issues converting X:
1379 -- (1) If either I'First or I'Last is not known at compile time, use
1380 -- I'Base instead of I in the next three steps and perform a
1381 -- regular range check against I'Range after conversion.
1382 -- (2) If I'First - 0.5 is representable in F then let Lo be that
1383 -- value and define Lo_OK as (I'First > 0). Otherwise, let Lo be
1384 -- F'Machine (T) and let Lo_OK be (Lo >= I'First). In other words,
1385 -- take one of the closest floating-point numbers to T, and see if
1386 -- it is in range or not.
1387 -- (3) If I'Last + 0.5 is representable in F then let Hi be that value
1388 -- and define Hi_OK as (I'Last < 0). Otherwise, let Hi be
1389 -- F'Rounding (T) and let Hi_OK be (Hi <= I'Last).
1390 -- (4) Raise CE when (Lo_OK and X < Lo) or (not Lo_OK and X <= Lo)
1391 -- or (Hi_OK and X > Hi) or (not Hi_OK and X >= Hi)
1393 procedure Apply_Float_Conversion_Check
1394 (Ck_Node : Node_Id;
1395 Target_Typ : Entity_Id)
1397 LB : constant Node_Id := Type_Low_Bound (Target_Typ);
1398 HB : constant Node_Id := Type_High_Bound (Target_Typ);
1399 Loc : constant Source_Ptr := Sloc (Ck_Node);
1400 Expr_Type : constant Entity_Id := Base_Type (Etype (Ck_Node));
1401 Target_Base : constant Entity_Id := Implementation_Base_Type
1402 (Target_Typ);
1403 Max_Bound : constant Uint := UI_Expon
1404 (Machine_Radix (Expr_Type),
1405 Machine_Mantissa (Expr_Type) - 1) - 1;
1406 -- Largest bound, so bound plus or minus half is a machine number of F
1408 Ifirst,
1409 Ilast : Uint; -- Bounds of integer type
1410 Lo, Hi : Ureal; -- Bounds to check in floating-point domain
1411 Lo_OK,
1412 Hi_OK : Boolean; -- True iff Lo resp. Hi belongs to I'Range
1414 Lo_Chk,
1415 Hi_Chk : Node_Id; -- Expressions that are False iff check fails
1417 Reason : RT_Exception_Code;
1419 begin
1420 if not Compile_Time_Known_Value (LB)
1421 or not Compile_Time_Known_Value (HB)
1422 then
1423 declare
1424 -- First check that the value falls in the range of the base
1425 -- type, to prevent overflow during conversion and then
1426 -- perform a regular range check against the (dynamic) bounds.
1428 Par : constant Node_Id := Parent (Ck_Node);
1430 pragma Assert (Target_Base /= Target_Typ);
1431 pragma Assert (Nkind (Par) = N_Type_Conversion);
1433 Temp : constant Entity_Id :=
1434 Make_Defining_Identifier (Loc,
1435 Chars => New_Internal_Name ('T'));
1437 begin
1438 Apply_Float_Conversion_Check (Ck_Node, Target_Base);
1439 Set_Etype (Temp, Target_Base);
1441 Insert_Action (Parent (Par),
1442 Make_Object_Declaration (Loc,
1443 Defining_Identifier => Temp,
1444 Object_Definition => New_Occurrence_Of (Target_Typ, Loc),
1445 Expression => New_Copy_Tree (Par)),
1446 Suppress => All_Checks);
1448 Insert_Action (Par,
1449 Make_Raise_Constraint_Error (Loc,
1450 Condition =>
1451 Make_Not_In (Loc,
1452 Left_Opnd => New_Occurrence_Of (Temp, Loc),
1453 Right_Opnd => New_Occurrence_Of (Target_Typ, Loc)),
1454 Reason => CE_Range_Check_Failed));
1455 Rewrite (Par, New_Occurrence_Of (Temp, Loc));
1457 return;
1458 end;
1459 end if;
1461 -- Get the bounds of the target type
1463 Ifirst := Expr_Value (LB);
1464 Ilast := Expr_Value (HB);
1466 -- Check against lower bound
1468 if abs (Ifirst) < Max_Bound then
1469 Lo := UR_From_Uint (Ifirst) - Ureal_Half;
1470 Lo_OK := (Ifirst > 0);
1471 else
1472 Lo := Machine (Expr_Type, UR_From_Uint (Ifirst), Round_Even, Ck_Node);
1473 Lo_OK := (Lo >= UR_From_Uint (Ifirst));
1474 end if;
1476 if Lo_OK then
1478 -- Lo_Chk := (X >= Lo)
1480 Lo_Chk := Make_Op_Ge (Loc,
1481 Left_Opnd => Duplicate_Subexpr_No_Checks (Ck_Node),
1482 Right_Opnd => Make_Real_Literal (Loc, Lo));
1484 else
1485 -- Lo_Chk := (X > Lo)
1487 Lo_Chk := Make_Op_Gt (Loc,
1488 Left_Opnd => Duplicate_Subexpr_No_Checks (Ck_Node),
1489 Right_Opnd => Make_Real_Literal (Loc, Lo));
1490 end if;
1492 -- Check against higher bound
1494 if abs (Ilast) < Max_Bound then
1495 Hi := UR_From_Uint (Ilast) + Ureal_Half;
1496 Hi_OK := (Ilast < 0);
1497 else
1498 Hi := Machine (Expr_Type, UR_From_Uint (Ilast), Round_Even, Ck_Node);
1499 Hi_OK := (Hi <= UR_From_Uint (Ilast));
1500 end if;
1502 if Hi_OK then
1504 -- Hi_Chk := (X <= Hi)
1506 Hi_Chk := Make_Op_Le (Loc,
1507 Left_Opnd => Duplicate_Subexpr_No_Checks (Ck_Node),
1508 Right_Opnd => Make_Real_Literal (Loc, Hi));
1510 else
1511 -- Hi_Chk := (X < Hi)
1513 Hi_Chk := Make_Op_Lt (Loc,
1514 Left_Opnd => Duplicate_Subexpr_No_Checks (Ck_Node),
1515 Right_Opnd => Make_Real_Literal (Loc, Hi));
1516 end if;
1518 -- If the bounds of the target type are the same as those of the
1519 -- base type, the check is an overflow check as a range check is
1520 -- not performed in these cases.
1522 if Expr_Value (Type_Low_Bound (Target_Base)) = Ifirst
1523 and then Expr_Value (Type_High_Bound (Target_Base)) = Ilast
1524 then
1525 Reason := CE_Overflow_Check_Failed;
1526 else
1527 Reason := CE_Range_Check_Failed;
1528 end if;
1530 -- Raise CE if either conditions does not hold
1532 Insert_Action (Ck_Node,
1533 Make_Raise_Constraint_Error (Loc,
1534 Condition => Make_Op_Not (Loc, Make_Op_And (Loc, Lo_Chk, Hi_Chk)),
1535 Reason => Reason));
1536 end Apply_Float_Conversion_Check;
1538 ------------------------
1539 -- Apply_Length_Check --
1540 ------------------------
1542 procedure Apply_Length_Check
1543 (Ck_Node : Node_Id;
1544 Target_Typ : Entity_Id;
1545 Source_Typ : Entity_Id := Empty)
1547 begin
1548 Apply_Selected_Length_Checks
1549 (Ck_Node, Target_Typ, Source_Typ, Do_Static => False);
1550 end Apply_Length_Check;
1552 -----------------------
1553 -- Apply_Range_Check --
1554 -----------------------
1556 procedure Apply_Range_Check
1557 (Ck_Node : Node_Id;
1558 Target_Typ : Entity_Id;
1559 Source_Typ : Entity_Id := Empty)
1561 begin
1562 Apply_Selected_Range_Checks
1563 (Ck_Node, Target_Typ, Source_Typ, Do_Static => False);
1564 end Apply_Range_Check;
1566 ------------------------------
1567 -- Apply_Scalar_Range_Check --
1568 ------------------------------
1570 -- Note that Apply_Scalar_Range_Check never turns the Do_Range_Check
1571 -- flag off if it is already set on.
1573 procedure Apply_Scalar_Range_Check
1574 (Expr : Node_Id;
1575 Target_Typ : Entity_Id;
1576 Source_Typ : Entity_Id := Empty;
1577 Fixed_Int : Boolean := False)
1579 Parnt : constant Node_Id := Parent (Expr);
1580 S_Typ : Entity_Id;
1581 Arr : Node_Id := Empty; -- initialize to prevent warning
1582 Arr_Typ : Entity_Id := Empty; -- initialize to prevent warning
1583 OK : Boolean;
1585 Is_Subscr_Ref : Boolean;
1586 -- Set true if Expr is a subscript
1588 Is_Unconstrained_Subscr_Ref : Boolean;
1589 -- Set true if Expr is a subscript of an unconstrained array. In this
1590 -- case we do not attempt to do an analysis of the value against the
1591 -- range of the subscript, since we don't know the actual subtype.
1593 Int_Real : Boolean;
1594 -- Set to True if Expr should be regarded as a real value
1595 -- even though the type of Expr might be discrete.
1597 procedure Bad_Value;
1598 -- Procedure called if value is determined to be out of range
1600 ---------------
1601 -- Bad_Value --
1602 ---------------
1604 procedure Bad_Value is
1605 begin
1606 Apply_Compile_Time_Constraint_Error
1607 (Expr, "value not in range of}?", CE_Range_Check_Failed,
1608 Ent => Target_Typ,
1609 Typ => Target_Typ);
1610 end Bad_Value;
1612 -- Start of processing for Apply_Scalar_Range_Check
1614 begin
1615 if Inside_A_Generic then
1616 return;
1618 -- Return if check obviously not needed. Note that we do not check
1619 -- for the expander being inactive, since this routine does not
1620 -- insert any code, but it does generate useful warnings sometimes,
1621 -- which we would like even if we are in semantics only mode.
1623 elsif Target_Typ = Any_Type
1624 or else not Is_Scalar_Type (Target_Typ)
1625 or else Raises_Constraint_Error (Expr)
1626 then
1627 return;
1628 end if;
1630 -- Now, see if checks are suppressed
1632 Is_Subscr_Ref :=
1633 Is_List_Member (Expr) and then Nkind (Parnt) = N_Indexed_Component;
1635 if Is_Subscr_Ref then
1636 Arr := Prefix (Parnt);
1637 Arr_Typ := Get_Actual_Subtype_If_Available (Arr);
1638 end if;
1640 if not Do_Range_Check (Expr) then
1642 -- Subscript reference. Check for Index_Checks suppressed
1644 if Is_Subscr_Ref then
1646 -- Check array type and its base type
1648 if Index_Checks_Suppressed (Arr_Typ)
1649 or else Index_Checks_Suppressed (Base_Type (Arr_Typ))
1650 then
1651 return;
1653 -- Check array itself if it is an entity name
1655 elsif Is_Entity_Name (Arr)
1656 and then Index_Checks_Suppressed (Entity (Arr))
1657 then
1658 return;
1660 -- Check expression itself if it is an entity name
1662 elsif Is_Entity_Name (Expr)
1663 and then Index_Checks_Suppressed (Entity (Expr))
1664 then
1665 return;
1666 end if;
1668 -- All other cases, check for Range_Checks suppressed
1670 else
1671 -- Check target type and its base type
1673 if Range_Checks_Suppressed (Target_Typ)
1674 or else Range_Checks_Suppressed (Base_Type (Target_Typ))
1675 then
1676 return;
1678 -- Check expression itself if it is an entity name
1680 elsif Is_Entity_Name (Expr)
1681 and then Range_Checks_Suppressed (Entity (Expr))
1682 then
1683 return;
1685 -- If Expr is part of an assignment statement, then check
1686 -- left side of assignment if it is an entity name.
1688 elsif Nkind (Parnt) = N_Assignment_Statement
1689 and then Is_Entity_Name (Name (Parnt))
1690 and then Range_Checks_Suppressed (Entity (Name (Parnt)))
1691 then
1692 return;
1693 end if;
1694 end if;
1695 end if;
1697 -- Do not set range checks if they are killed
1699 if Nkind (Expr) = N_Unchecked_Type_Conversion
1700 and then Kill_Range_Check (Expr)
1701 then
1702 return;
1703 end if;
1705 -- Do not set range checks for any values from System.Scalar_Values
1706 -- since the whole idea of such values is to avoid checking them!
1708 if Is_Entity_Name (Expr)
1709 and then Is_RTU (Scope (Entity (Expr)), System_Scalar_Values)
1710 then
1711 return;
1712 end if;
1714 -- Now see if we need a check
1716 if No (Source_Typ) then
1717 S_Typ := Etype (Expr);
1718 else
1719 S_Typ := Source_Typ;
1720 end if;
1722 if not Is_Scalar_Type (S_Typ) or else S_Typ = Any_Type then
1723 return;
1724 end if;
1726 Is_Unconstrained_Subscr_Ref :=
1727 Is_Subscr_Ref and then not Is_Constrained (Arr_Typ);
1729 -- Always do a range check if the source type includes infinities
1730 -- and the target type does not include infinities. We do not do
1731 -- this if range checks are killed.
1733 if Is_Floating_Point_Type (S_Typ)
1734 and then Has_Infinities (S_Typ)
1735 and then not Has_Infinities (Target_Typ)
1736 then
1737 Enable_Range_Check (Expr);
1738 end if;
1740 -- Return if we know expression is definitely in the range of
1741 -- the target type as determined by Determine_Range. Right now
1742 -- we only do this for discrete types, and not fixed-point or
1743 -- floating-point types.
1745 -- The additional less-precise tests below catch these cases.
1747 -- Note: skip this if we are given a source_typ, since the point
1748 -- of supplying a Source_Typ is to stop us looking at the expression.
1749 -- could sharpen this test to be out parameters only ???
1751 if Is_Discrete_Type (Target_Typ)
1752 and then Is_Discrete_Type (Etype (Expr))
1753 and then not Is_Unconstrained_Subscr_Ref
1754 and then No (Source_Typ)
1755 then
1756 declare
1757 Tlo : constant Node_Id := Type_Low_Bound (Target_Typ);
1758 Thi : constant Node_Id := Type_High_Bound (Target_Typ);
1759 Lo : Uint;
1760 Hi : Uint;
1762 begin
1763 if Compile_Time_Known_Value (Tlo)
1764 and then Compile_Time_Known_Value (Thi)
1765 then
1766 declare
1767 Lov : constant Uint := Expr_Value (Tlo);
1768 Hiv : constant Uint := Expr_Value (Thi);
1770 begin
1771 -- If range is null, we for sure have a constraint error
1772 -- (we don't even need to look at the value involved,
1773 -- since all possible values will raise CE).
1775 if Lov > Hiv then
1776 Bad_Value;
1777 return;
1778 end if;
1780 -- Otherwise determine range of value
1782 Determine_Range (Expr, OK, Lo, Hi);
1784 if OK then
1786 -- If definitely in range, all OK
1788 if Lo >= Lov and then Hi <= Hiv then
1789 return;
1791 -- If definitely not in range, warn
1793 elsif Lov > Hi or else Hiv < Lo then
1794 Bad_Value;
1795 return;
1797 -- Otherwise we don't know
1799 else
1800 null;
1801 end if;
1802 end if;
1803 end;
1804 end if;
1805 end;
1806 end if;
1808 Int_Real :=
1809 Is_Floating_Point_Type (S_Typ)
1810 or else (Is_Fixed_Point_Type (S_Typ) and then not Fixed_Int);
1812 -- Check if we can determine at compile time whether Expr is in the
1813 -- range of the target type. Note that if S_Typ is within the bounds
1814 -- of Target_Typ then this must be the case. This check is meaningful
1815 -- only if this is not a conversion between integer and real types.
1817 if not Is_Unconstrained_Subscr_Ref
1818 and then
1819 Is_Discrete_Type (S_Typ) = Is_Discrete_Type (Target_Typ)
1820 and then
1821 (In_Subrange_Of (S_Typ, Target_Typ, Fixed_Int)
1822 or else
1823 Is_In_Range (Expr, Target_Typ, Fixed_Int, Int_Real))
1824 then
1825 return;
1827 elsif Is_Out_Of_Range (Expr, Target_Typ, Fixed_Int, Int_Real) then
1828 Bad_Value;
1829 return;
1831 -- In the floating-point case, we only do range checks if the
1832 -- type is constrained. We definitely do NOT want range checks
1833 -- for unconstrained types, since we want to have infinities
1835 elsif Is_Floating_Point_Type (S_Typ) then
1836 if Is_Constrained (S_Typ) then
1837 Enable_Range_Check (Expr);
1838 end if;
1840 -- For all other cases we enable a range check unconditionally
1842 else
1843 Enable_Range_Check (Expr);
1844 return;
1845 end if;
1846 end Apply_Scalar_Range_Check;
1848 ----------------------------------
1849 -- Apply_Selected_Length_Checks --
1850 ----------------------------------
1852 procedure Apply_Selected_Length_Checks
1853 (Ck_Node : Node_Id;
1854 Target_Typ : Entity_Id;
1855 Source_Typ : Entity_Id;
1856 Do_Static : Boolean)
1858 Cond : Node_Id;
1859 R_Result : Check_Result;
1860 R_Cno : Node_Id;
1862 Loc : constant Source_Ptr := Sloc (Ck_Node);
1863 Checks_On : constant Boolean :=
1864 (not Index_Checks_Suppressed (Target_Typ))
1865 or else
1866 (not Length_Checks_Suppressed (Target_Typ));
1868 begin
1869 if not Expander_Active then
1870 return;
1871 end if;
1873 R_Result :=
1874 Selected_Length_Checks (Ck_Node, Target_Typ, Source_Typ, Empty);
1876 for J in 1 .. 2 loop
1877 R_Cno := R_Result (J);
1878 exit when No (R_Cno);
1880 -- A length check may mention an Itype which is attached to a
1881 -- subsequent node. At the top level in a package this can cause
1882 -- an order-of-elaboration problem, so we make sure that the itype
1883 -- is referenced now.
1885 if Ekind (Current_Scope) = E_Package
1886 and then Is_Compilation_Unit (Current_Scope)
1887 then
1888 Ensure_Defined (Target_Typ, Ck_Node);
1890 if Present (Source_Typ) then
1891 Ensure_Defined (Source_Typ, Ck_Node);
1893 elsif Is_Itype (Etype (Ck_Node)) then
1894 Ensure_Defined (Etype (Ck_Node), Ck_Node);
1895 end if;
1896 end if;
1898 -- If the item is a conditional raise of constraint error,
1899 -- then have a look at what check is being performed and
1900 -- ???
1902 if Nkind (R_Cno) = N_Raise_Constraint_Error
1903 and then Present (Condition (R_Cno))
1904 then
1905 Cond := Condition (R_Cno);
1907 if not Has_Dynamic_Length_Check (Ck_Node)
1908 and then Checks_On
1909 then
1910 Insert_Action (Ck_Node, R_Cno);
1912 if not Do_Static then
1913 Set_Has_Dynamic_Length_Check (Ck_Node);
1914 end if;
1915 end if;
1917 -- Output a warning if the condition is known to be True
1919 if Is_Entity_Name (Cond)
1920 and then Entity (Cond) = Standard_True
1921 then
1922 Apply_Compile_Time_Constraint_Error
1923 (Ck_Node, "wrong length for array of}?",
1924 CE_Length_Check_Failed,
1925 Ent => Target_Typ,
1926 Typ => Target_Typ);
1928 -- If we were only doing a static check, or if checks are not
1929 -- on, then we want to delete the check, since it is not needed.
1930 -- We do this by replacing the if statement by a null statement
1932 elsif Do_Static or else not Checks_On then
1933 Rewrite (R_Cno, Make_Null_Statement (Loc));
1934 end if;
1936 else
1937 Install_Static_Check (R_Cno, Loc);
1938 end if;
1940 end loop;
1942 end Apply_Selected_Length_Checks;
1944 ---------------------------------
1945 -- Apply_Selected_Range_Checks --
1946 ---------------------------------
1948 procedure Apply_Selected_Range_Checks
1949 (Ck_Node : Node_Id;
1950 Target_Typ : Entity_Id;
1951 Source_Typ : Entity_Id;
1952 Do_Static : Boolean)
1954 Cond : Node_Id;
1955 R_Result : Check_Result;
1956 R_Cno : Node_Id;
1958 Loc : constant Source_Ptr := Sloc (Ck_Node);
1959 Checks_On : constant Boolean :=
1960 (not Index_Checks_Suppressed (Target_Typ))
1961 or else
1962 (not Range_Checks_Suppressed (Target_Typ));
1964 begin
1965 if not Expander_Active or else not Checks_On then
1966 return;
1967 end if;
1969 R_Result :=
1970 Selected_Range_Checks (Ck_Node, Target_Typ, Source_Typ, Empty);
1972 for J in 1 .. 2 loop
1974 R_Cno := R_Result (J);
1975 exit when No (R_Cno);
1977 -- If the item is a conditional raise of constraint error,
1978 -- then have a look at what check is being performed and
1979 -- ???
1981 if Nkind (R_Cno) = N_Raise_Constraint_Error
1982 and then Present (Condition (R_Cno))
1983 then
1984 Cond := Condition (R_Cno);
1986 if not Has_Dynamic_Range_Check (Ck_Node) then
1987 Insert_Action (Ck_Node, R_Cno);
1989 if not Do_Static then
1990 Set_Has_Dynamic_Range_Check (Ck_Node);
1991 end if;
1992 end if;
1994 -- Output a warning if the condition is known to be True
1996 if Is_Entity_Name (Cond)
1997 and then Entity (Cond) = Standard_True
1998 then
1999 -- Since an N_Range is technically not an expression, we
2000 -- have to set one of the bounds to C_E and then just flag
2001 -- the N_Range. The warning message will point to the
2002 -- lower bound and complain about a range, which seems OK.
2004 if Nkind (Ck_Node) = N_Range then
2005 Apply_Compile_Time_Constraint_Error
2006 (Low_Bound (Ck_Node), "static range out of bounds of}?",
2007 CE_Range_Check_Failed,
2008 Ent => Target_Typ,
2009 Typ => Target_Typ);
2011 Set_Raises_Constraint_Error (Ck_Node);
2013 else
2014 Apply_Compile_Time_Constraint_Error
2015 (Ck_Node, "static value out of range of}?",
2016 CE_Range_Check_Failed,
2017 Ent => Target_Typ,
2018 Typ => Target_Typ);
2019 end if;
2021 -- If we were only doing a static check, or if checks are not
2022 -- on, then we want to delete the check, since it is not needed.
2023 -- We do this by replacing the if statement by a null statement
2025 elsif Do_Static or else not Checks_On then
2026 Rewrite (R_Cno, Make_Null_Statement (Loc));
2027 end if;
2029 else
2030 Install_Static_Check (R_Cno, Loc);
2031 end if;
2032 end loop;
2033 end Apply_Selected_Range_Checks;
2035 -------------------------------
2036 -- Apply_Static_Length_Check --
2037 -------------------------------
2039 procedure Apply_Static_Length_Check
2040 (Expr : Node_Id;
2041 Target_Typ : Entity_Id;
2042 Source_Typ : Entity_Id := Empty)
2044 begin
2045 Apply_Selected_Length_Checks
2046 (Expr, Target_Typ, Source_Typ, Do_Static => True);
2047 end Apply_Static_Length_Check;
2049 -------------------------------------
2050 -- Apply_Subscript_Validity_Checks --
2051 -------------------------------------
2053 procedure Apply_Subscript_Validity_Checks (Expr : Node_Id) is
2054 Sub : Node_Id;
2056 begin
2057 pragma Assert (Nkind (Expr) = N_Indexed_Component);
2059 -- Loop through subscripts
2061 Sub := First (Expressions (Expr));
2062 while Present (Sub) loop
2064 -- Check one subscript. Note that we do not worry about
2065 -- enumeration type with holes, since we will convert the
2066 -- value to a Pos value for the subscript, and that convert
2067 -- will do the necessary validity check.
2069 Ensure_Valid (Sub, Holes_OK => True);
2071 -- Move to next subscript
2073 Sub := Next (Sub);
2074 end loop;
2075 end Apply_Subscript_Validity_Checks;
2077 ----------------------------------
2078 -- Apply_Type_Conversion_Checks --
2079 ----------------------------------
2081 procedure Apply_Type_Conversion_Checks (N : Node_Id) is
2082 Target_Type : constant Entity_Id := Etype (N);
2083 Target_Base : constant Entity_Id := Base_Type (Target_Type);
2084 Expr : constant Node_Id := Expression (N);
2085 Expr_Type : constant Entity_Id := Etype (Expr);
2087 begin
2088 if Inside_A_Generic then
2089 return;
2091 -- Skip these checks if serious errors detected, there are some nasty
2092 -- situations of incomplete trees that blow things up.
2094 elsif Serious_Errors_Detected > 0 then
2095 return;
2097 -- Scalar type conversions of the form Target_Type (Expr) require
2098 -- a range check if we cannot be sure that Expr is in the base type
2099 -- of Target_Typ and also that Expr is in the range of Target_Typ.
2100 -- These are not quite the same condition from an implementation
2101 -- point of view, but clearly the second includes the first.
2103 elsif Is_Scalar_Type (Target_Type) then
2104 declare
2105 Conv_OK : constant Boolean := Conversion_OK (N);
2106 -- If the Conversion_OK flag on the type conversion is set
2107 -- and no floating point type is involved in the type conversion
2108 -- then fixed point values must be read as integral values.
2110 Float_To_Int : constant Boolean :=
2111 Is_Floating_Point_Type (Expr_Type)
2112 and then Is_Integer_Type (Target_Type);
2114 begin
2115 if not Overflow_Checks_Suppressed (Target_Base)
2116 and then not In_Subrange_Of (Expr_Type, Target_Base, Conv_OK)
2117 and then not Float_To_Int
2118 then
2119 Set_Do_Overflow_Check (N);
2120 end if;
2122 if not Range_Checks_Suppressed (Target_Type)
2123 and then not Range_Checks_Suppressed (Expr_Type)
2124 then
2125 if Float_To_Int then
2126 Apply_Float_Conversion_Check (Expr, Target_Type);
2127 else
2128 Apply_Scalar_Range_Check
2129 (Expr, Target_Type, Fixed_Int => Conv_OK);
2130 end if;
2131 end if;
2132 end;
2134 elsif Comes_From_Source (N)
2135 and then Is_Record_Type (Target_Type)
2136 and then Is_Derived_Type (Target_Type)
2137 and then not Is_Tagged_Type (Target_Type)
2138 and then not Is_Constrained (Target_Type)
2139 and then Present (Stored_Constraint (Target_Type))
2140 then
2141 -- An unconstrained derived type may have inherited discriminant
2142 -- Build an actual discriminant constraint list using the stored
2143 -- constraint, to verify that the expression of the parent type
2144 -- satisfies the constraints imposed by the (unconstrained!)
2145 -- derived type. This applies to value conversions, not to view
2146 -- conversions of tagged types.
2148 declare
2149 Loc : constant Source_Ptr := Sloc (N);
2150 Cond : Node_Id;
2151 Constraint : Elmt_Id;
2152 Discr_Value : Node_Id;
2153 Discr : Entity_Id;
2155 New_Constraints : constant Elist_Id := New_Elmt_List;
2156 Old_Constraints : constant Elist_Id :=
2157 Discriminant_Constraint (Expr_Type);
2159 begin
2160 Constraint := First_Elmt (Stored_Constraint (Target_Type));
2162 while Present (Constraint) loop
2163 Discr_Value := Node (Constraint);
2165 if Is_Entity_Name (Discr_Value)
2166 and then Ekind (Entity (Discr_Value)) = E_Discriminant
2167 then
2168 Discr := Corresponding_Discriminant (Entity (Discr_Value));
2170 if Present (Discr)
2171 and then Scope (Discr) = Base_Type (Expr_Type)
2172 then
2173 -- Parent is constrained by new discriminant. Obtain
2174 -- Value of original discriminant in expression. If
2175 -- the new discriminant has been used to constrain more
2176 -- than one of the stored discriminants, this will
2177 -- provide the required consistency check.
2179 Append_Elmt (
2180 Make_Selected_Component (Loc,
2181 Prefix =>
2182 Duplicate_Subexpr_No_Checks
2183 (Expr, Name_Req => True),
2184 Selector_Name =>
2185 Make_Identifier (Loc, Chars (Discr))),
2186 New_Constraints);
2188 else
2189 -- Discriminant of more remote ancestor ???
2191 return;
2192 end if;
2194 -- Derived type definition has an explicit value for
2195 -- this stored discriminant.
2197 else
2198 Append_Elmt
2199 (Duplicate_Subexpr_No_Checks (Discr_Value),
2200 New_Constraints);
2201 end if;
2203 Next_Elmt (Constraint);
2204 end loop;
2206 -- Use the unconstrained expression type to retrieve the
2207 -- discriminants of the parent, and apply momentarily the
2208 -- discriminant constraint synthesized above.
2210 Set_Discriminant_Constraint (Expr_Type, New_Constraints);
2211 Cond := Build_Discriminant_Checks (Expr, Expr_Type);
2212 Set_Discriminant_Constraint (Expr_Type, Old_Constraints);
2214 Insert_Action (N,
2215 Make_Raise_Constraint_Error (Loc,
2216 Condition => Cond,
2217 Reason => CE_Discriminant_Check_Failed));
2218 end;
2220 -- For arrays, conversions are applied during expansion, to take
2221 -- into accounts changes of representation. The checks become range
2222 -- checks on the base type or length checks on the subtype, depending
2223 -- on whether the target type is unconstrained or constrained.
2225 else
2226 null;
2227 end if;
2228 end Apply_Type_Conversion_Checks;
2230 ----------------------------------------------
2231 -- Apply_Universal_Integer_Attribute_Checks --
2232 ----------------------------------------------
2234 procedure Apply_Universal_Integer_Attribute_Checks (N : Node_Id) is
2235 Loc : constant Source_Ptr := Sloc (N);
2236 Typ : constant Entity_Id := Etype (N);
2238 begin
2239 if Inside_A_Generic then
2240 return;
2242 -- Nothing to do if checks are suppressed
2244 elsif Range_Checks_Suppressed (Typ)
2245 and then Overflow_Checks_Suppressed (Typ)
2246 then
2247 return;
2249 -- Nothing to do if the attribute does not come from source. The
2250 -- internal attributes we generate of this type do not need checks,
2251 -- and furthermore the attempt to check them causes some circular
2252 -- elaboration orders when dealing with packed types.
2254 elsif not Comes_From_Source (N) then
2255 return;
2257 -- If the prefix is a selected component that depends on a discriminant
2258 -- the check may improperly expose a discriminant instead of using
2259 -- the bounds of the object itself. Set the type of the attribute to
2260 -- the base type of the context, so that a check will be imposed when
2261 -- needed (e.g. if the node appears as an index).
2263 elsif Nkind (Prefix (N)) = N_Selected_Component
2264 and then Ekind (Typ) = E_Signed_Integer_Subtype
2265 and then Depends_On_Discriminant (Scalar_Range (Typ))
2266 then
2267 Set_Etype (N, Base_Type (Typ));
2269 -- Otherwise, replace the attribute node with a type conversion
2270 -- node whose expression is the attribute, retyped to universal
2271 -- integer, and whose subtype mark is the target type. The call
2272 -- to analyze this conversion will set range and overflow checks
2273 -- as required for proper detection of an out of range value.
2275 else
2276 Set_Etype (N, Universal_Integer);
2277 Set_Analyzed (N, True);
2279 Rewrite (N,
2280 Make_Type_Conversion (Loc,
2281 Subtype_Mark => New_Occurrence_Of (Typ, Loc),
2282 Expression => Relocate_Node (N)));
2284 Analyze_And_Resolve (N, Typ);
2285 return;
2286 end if;
2288 end Apply_Universal_Integer_Attribute_Checks;
2290 -------------------------------
2291 -- Build_Discriminant_Checks --
2292 -------------------------------
2294 function Build_Discriminant_Checks
2295 (N : Node_Id;
2296 T_Typ : Entity_Id) return Node_Id
2298 Loc : constant Source_Ptr := Sloc (N);
2299 Cond : Node_Id;
2300 Disc : Elmt_Id;
2301 Disc_Ent : Entity_Id;
2302 Dref : Node_Id;
2303 Dval : Node_Id;
2305 begin
2306 Cond := Empty;
2307 Disc := First_Elmt (Discriminant_Constraint (T_Typ));
2309 -- For a fully private type, use the discriminants of the parent type
2311 if Is_Private_Type (T_Typ)
2312 and then No (Full_View (T_Typ))
2313 then
2314 Disc_Ent := First_Discriminant (Etype (Base_Type (T_Typ)));
2315 else
2316 Disc_Ent := First_Discriminant (T_Typ);
2317 end if;
2319 while Present (Disc) loop
2320 Dval := Node (Disc);
2322 if Nkind (Dval) = N_Identifier
2323 and then Ekind (Entity (Dval)) = E_Discriminant
2324 then
2325 Dval := New_Occurrence_Of (Discriminal (Entity (Dval)), Loc);
2326 else
2327 Dval := Duplicate_Subexpr_No_Checks (Dval);
2328 end if;
2330 Dref :=
2331 Make_Selected_Component (Loc,
2332 Prefix =>
2333 Duplicate_Subexpr_No_Checks (N, Name_Req => True),
2334 Selector_Name =>
2335 Make_Identifier (Loc, Chars (Disc_Ent)));
2337 Set_Is_In_Discriminant_Check (Dref);
2339 Evolve_Or_Else (Cond,
2340 Make_Op_Ne (Loc,
2341 Left_Opnd => Dref,
2342 Right_Opnd => Dval));
2344 Next_Elmt (Disc);
2345 Next_Discriminant (Disc_Ent);
2346 end loop;
2348 return Cond;
2349 end Build_Discriminant_Checks;
2351 -----------------------------------
2352 -- Check_Valid_Lvalue_Subscripts --
2353 -----------------------------------
2355 procedure Check_Valid_Lvalue_Subscripts (Expr : Node_Id) is
2356 begin
2357 -- Skip this if range checks are suppressed
2359 if Range_Checks_Suppressed (Etype (Expr)) then
2360 return;
2362 -- Only do this check for expressions that come from source. We
2363 -- assume that expander generated assignments explicitly include
2364 -- any necessary checks. Note that this is not just an optimization,
2365 -- it avoids infinite recursions!
2367 elsif not Comes_From_Source (Expr) then
2368 return;
2370 -- For a selected component, check the prefix
2372 elsif Nkind (Expr) = N_Selected_Component then
2373 Check_Valid_Lvalue_Subscripts (Prefix (Expr));
2374 return;
2376 -- Case of indexed component
2378 elsif Nkind (Expr) = N_Indexed_Component then
2379 Apply_Subscript_Validity_Checks (Expr);
2381 -- Prefix may itself be or contain an indexed component, and
2382 -- these subscripts need checking as well
2384 Check_Valid_Lvalue_Subscripts (Prefix (Expr));
2385 end if;
2386 end Check_Valid_Lvalue_Subscripts;
2388 ----------------------------------
2389 -- Null_Exclusion_Static_Checks --
2390 ----------------------------------
2392 procedure Null_Exclusion_Static_Checks (N : Node_Id) is
2393 K : constant Node_Kind := Nkind (N);
2394 Typ : Entity_Id;
2395 Related_Nod : Node_Id;
2396 Has_Null_Exclusion : Boolean := False;
2398 type Msg_Kind is (Components, Formals, Objects);
2399 Msg_K : Msg_Kind := Objects;
2400 -- Used by local subprograms to generate precise error messages
2402 procedure Check_Must_Be_Access
2403 (Typ : Entity_Id;
2404 Has_Null_Exclusion : Boolean);
2405 -- ??? local subprograms must have comment on spec
2407 procedure Check_Already_Null_Excluding_Type
2408 (Typ : Entity_Id;
2409 Has_Null_Exclusion : Boolean;
2410 Related_Nod : Node_Id);
2411 -- ??? local subprograms must have comment on spec
2413 procedure Check_Must_Be_Initialized
2414 (N : Node_Id;
2415 Related_Nod : Node_Id);
2416 -- ??? local subprograms must have comment on spec
2418 procedure Check_Null_Not_Allowed (N : Node_Id);
2419 -- ??? local subprograms must have comment on spec
2421 -- ??? following bodies lack comments
2423 --------------------------
2424 -- Check_Must_Be_Access --
2425 --------------------------
2427 procedure Check_Must_Be_Access
2428 (Typ : Entity_Id;
2429 Has_Null_Exclusion : Boolean)
2431 begin
2432 if Has_Null_Exclusion
2433 and then not Is_Access_Type (Typ)
2434 then
2435 Error_Msg_N ("(Ada 0Y) must be an access type", Related_Nod);
2436 end if;
2437 end Check_Must_Be_Access;
2439 ---------------------------------------
2440 -- Check_Already_Null_Excluding_Type --
2441 ---------------------------------------
2443 procedure Check_Already_Null_Excluding_Type
2444 (Typ : Entity_Id;
2445 Has_Null_Exclusion : Boolean;
2446 Related_Nod : Node_Id)
2448 begin
2449 if Has_Null_Exclusion
2450 and then Can_Never_Be_Null (Typ)
2451 then
2452 Error_Msg_N
2453 ("(Ada 0Y) already a null-excluding type", Related_Nod);
2454 end if;
2455 end Check_Already_Null_Excluding_Type;
2457 -------------------------------
2458 -- Check_Must_Be_Initialized --
2459 -------------------------------
2461 procedure Check_Must_Be_Initialized
2462 (N : Node_Id;
2463 Related_Nod : Node_Id)
2465 Expr : constant Node_Id := Expression (N);
2467 begin
2468 pragma Assert (Nkind (N) = N_Component_Declaration
2469 or else Nkind (N) = N_Object_Declaration);
2471 if not Present (Expr) then
2472 case Msg_K is
2473 when Components =>
2474 Error_Msg_N
2475 ("(Ada 0Y) null-excluding components must be initialized",
2476 Related_Nod);
2478 when Formals =>
2479 Error_Msg_N
2480 ("(Ada 0Y) null-excluding formals must be initialized",
2481 Related_Nod);
2483 when Objects =>
2484 Error_Msg_N
2485 ("(Ada 0Y) null-excluding objects must be initialized",
2486 Related_Nod);
2487 end case;
2488 end if;
2489 end Check_Must_Be_Initialized;
2491 ----------------------------
2492 -- Check_Null_Not_Allowed --
2493 ----------------------------
2495 procedure Check_Null_Not_Allowed (N : Node_Id) is
2496 Expr : constant Node_Id := Expression (N);
2498 begin
2499 if Present (Expr)
2500 and then Nkind (Expr) = N_Null
2501 then
2502 case Msg_K is
2503 when Components =>
2504 Error_Msg_N
2505 ("(Ada 0Y) NULL not allowed in null-excluding components",
2506 Expr);
2508 when Formals =>
2509 Error_Msg_N
2510 ("(Ada 0Y) NULL not allowed in null-excluding formals",
2511 Expr);
2513 when Objects =>
2514 Error_Msg_N
2515 ("(Ada 0Y) NULL not allowed in null-excluding objects",
2516 Expr);
2517 end case;
2518 end if;
2519 end Check_Null_Not_Allowed;
2521 -- Start of processing for Null_Exclusion_Static_Checks
2523 begin
2524 pragma Assert (K = N_Component_Declaration
2525 or else K = N_Parameter_Specification
2526 or else K = N_Object_Declaration
2527 or else K = N_Discriminant_Specification
2528 or else K = N_Allocator);
2530 case K is
2531 when N_Component_Declaration =>
2532 Msg_K := Components;
2534 if not Present (Access_Definition (Component_Definition (N))) then
2535 Has_Null_Exclusion := Null_Exclusion_Present
2536 (Component_Definition (N));
2537 Typ := Etype (Subtype_Indication (Component_Definition (N)));
2538 Related_Nod := Subtype_Indication (Component_Definition (N));
2539 Check_Must_Be_Access (Typ, Has_Null_Exclusion);
2540 Check_Already_Null_Excluding_Type
2541 (Typ, Has_Null_Exclusion, Related_Nod);
2542 Check_Must_Be_Initialized (N, Related_Nod);
2543 end if;
2545 Check_Null_Not_Allowed (N);
2547 when N_Parameter_Specification =>
2548 Msg_K := Formals;
2549 Has_Null_Exclusion := Null_Exclusion_Present (N);
2550 Typ := Entity (Parameter_Type (N));
2551 Related_Nod := Parameter_Type (N);
2552 Check_Must_Be_Access (Typ, Has_Null_Exclusion);
2553 Check_Already_Null_Excluding_Type
2554 (Typ, Has_Null_Exclusion, Related_Nod);
2555 Check_Null_Not_Allowed (N);
2557 when N_Object_Declaration =>
2558 Msg_K := Objects;
2559 Has_Null_Exclusion := Null_Exclusion_Present (N);
2560 Typ := Entity (Object_Definition (N));
2561 Related_Nod := Object_Definition (N);
2562 Check_Must_Be_Access (Typ, Has_Null_Exclusion);
2563 Check_Already_Null_Excluding_Type
2564 (Typ, Has_Null_Exclusion, Related_Nod);
2565 Check_Must_Be_Initialized (N, Related_Nod);
2566 Check_Null_Not_Allowed (N);
2568 when N_Discriminant_Specification =>
2569 Msg_K := Components;
2571 if Nkind (Discriminant_Type (N)) /= N_Access_Definition then
2572 Has_Null_Exclusion := Null_Exclusion_Present (N);
2573 Typ := Etype (Defining_Identifier (N));
2574 Related_Nod := Discriminant_Type (N);
2575 Check_Must_Be_Access (Typ, Has_Null_Exclusion);
2576 Check_Already_Null_Excluding_Type
2577 (Typ, Has_Null_Exclusion, Related_Nod);
2578 end if;
2580 Check_Null_Not_Allowed (N);
2582 when N_Allocator =>
2583 Msg_K := Objects;
2584 Has_Null_Exclusion := Null_Exclusion_Present (N);
2585 Typ := Etype (Expression (N));
2587 if Nkind (Expression (N)) = N_Qualified_Expression then
2588 Related_Nod := Subtype_Mark (Expression (N));
2589 else
2590 Related_Nod := Expression (N);
2591 end if;
2593 Check_Must_Be_Access (Typ, Has_Null_Exclusion);
2594 Check_Already_Null_Excluding_Type
2595 (Typ, Has_Null_Exclusion, Related_Nod);
2596 Check_Null_Not_Allowed (N);
2598 when others =>
2599 raise Program_Error;
2600 end case;
2601 end Null_Exclusion_Static_Checks;
2603 ----------------------------------
2604 -- Conditional_Statements_Begin --
2605 ----------------------------------
2607 procedure Conditional_Statements_Begin is
2608 begin
2609 Saved_Checks_TOS := Saved_Checks_TOS + 1;
2611 -- If stack overflows, kill all checks, that way we know to
2612 -- simply reset the number of saved checks to zero on return.
2613 -- This should never occur in practice.
2615 if Saved_Checks_TOS > Saved_Checks_Stack'Last then
2616 Kill_All_Checks;
2618 -- In the normal case, we just make a new stack entry saving
2619 -- the current number of saved checks for a later restore.
2621 else
2622 Saved_Checks_Stack (Saved_Checks_TOS) := Num_Saved_Checks;
2624 if Debug_Flag_CC then
2625 w ("Conditional_Statements_Begin: Num_Saved_Checks = ",
2626 Num_Saved_Checks);
2627 end if;
2628 end if;
2629 end Conditional_Statements_Begin;
2631 --------------------------------
2632 -- Conditional_Statements_End --
2633 --------------------------------
2635 procedure Conditional_Statements_End is
2636 begin
2637 pragma Assert (Saved_Checks_TOS > 0);
2639 -- If the saved checks stack overflowed, then we killed all
2640 -- checks, so setting the number of saved checks back to
2641 -- zero is correct. This should never occur in practice.
2643 if Saved_Checks_TOS > Saved_Checks_Stack'Last then
2644 Num_Saved_Checks := 0;
2646 -- In the normal case, restore the number of saved checks
2647 -- from the top stack entry.
2649 else
2650 Num_Saved_Checks := Saved_Checks_Stack (Saved_Checks_TOS);
2651 if Debug_Flag_CC then
2652 w ("Conditional_Statements_End: Num_Saved_Checks = ",
2653 Num_Saved_Checks);
2654 end if;
2655 end if;
2657 Saved_Checks_TOS := Saved_Checks_TOS - 1;
2658 end Conditional_Statements_End;
2660 ---------------------
2661 -- Determine_Range --
2662 ---------------------
2664 Cache_Size : constant := 2 ** 10;
2665 type Cache_Index is range 0 .. Cache_Size - 1;
2666 -- Determine size of below cache (power of 2 is more efficient!)
2668 Determine_Range_Cache_N : array (Cache_Index) of Node_Id;
2669 Determine_Range_Cache_Lo : array (Cache_Index) of Uint;
2670 Determine_Range_Cache_Hi : array (Cache_Index) of Uint;
2671 -- The above arrays are used to implement a small direct cache
2672 -- for Determine_Range calls. Because of the way Determine_Range
2673 -- recursively traces subexpressions, and because overflow checking
2674 -- calls the routine on the way up the tree, a quadratic behavior
2675 -- can otherwise be encountered in large expressions. The cache
2676 -- entry for node N is stored in the (N mod Cache_Size) entry, and
2677 -- can be validated by checking the actual node value stored there.
2679 procedure Determine_Range
2680 (N : Node_Id;
2681 OK : out Boolean;
2682 Lo : out Uint;
2683 Hi : out Uint)
2685 Typ : constant Entity_Id := Etype (N);
2687 Lo_Left : Uint;
2688 Hi_Left : Uint;
2689 -- Lo and Hi bounds of left operand
2691 Lo_Right : Uint;
2692 Hi_Right : Uint;
2693 -- Lo and Hi bounds of right (or only) operand
2695 Bound : Node_Id;
2696 -- Temp variable used to hold a bound node
2698 Hbound : Uint;
2699 -- High bound of base type of expression
2701 Lor : Uint;
2702 Hir : Uint;
2703 -- Refined values for low and high bounds, after tightening
2705 OK1 : Boolean;
2706 -- Used in lower level calls to indicate if call succeeded
2708 Cindex : Cache_Index;
2709 -- Used to search cache
2711 function OK_Operands return Boolean;
2712 -- Used for binary operators. Determines the ranges of the left and
2713 -- right operands, and if they are both OK, returns True, and puts
2714 -- the results in Lo_Right, Hi_Right, Lo_Left, Hi_Left
2716 -----------------
2717 -- OK_Operands --
2718 -----------------
2720 function OK_Operands return Boolean is
2721 begin
2722 Determine_Range (Left_Opnd (N), OK1, Lo_Left, Hi_Left);
2724 if not OK1 then
2725 return False;
2726 end if;
2728 Determine_Range (Right_Opnd (N), OK1, Lo_Right, Hi_Right);
2729 return OK1;
2730 end OK_Operands;
2732 -- Start of processing for Determine_Range
2734 begin
2735 -- Prevent junk warnings by initializing range variables
2737 Lo := No_Uint;
2738 Hi := No_Uint;
2739 Lor := No_Uint;
2740 Hir := No_Uint;
2742 -- If the type is not discrete, or is undefined, then we can't
2743 -- do anything about determining the range.
2745 if No (Typ) or else not Is_Discrete_Type (Typ)
2746 or else Error_Posted (N)
2747 then
2748 OK := False;
2749 return;
2750 end if;
2752 -- For all other cases, we can determine the range
2754 OK := True;
2756 -- If value is compile time known, then the possible range is the
2757 -- one value that we know this expression definitely has!
2759 if Compile_Time_Known_Value (N) then
2760 Lo := Expr_Value (N);
2761 Hi := Lo;
2762 return;
2763 end if;
2765 -- Return if already in the cache
2767 Cindex := Cache_Index (N mod Cache_Size);
2769 if Determine_Range_Cache_N (Cindex) = N then
2770 Lo := Determine_Range_Cache_Lo (Cindex);
2771 Hi := Determine_Range_Cache_Hi (Cindex);
2772 return;
2773 end if;
2775 -- Otherwise, start by finding the bounds of the type of the
2776 -- expression, the value cannot be outside this range (if it
2777 -- is, then we have an overflow situation, which is a separate
2778 -- check, we are talking here only about the expression value).
2780 -- We use the actual bound unless it is dynamic, in which case
2781 -- use the corresponding base type bound if possible. If we can't
2782 -- get a bound then we figure we can't determine the range (a
2783 -- peculiar case, that perhaps cannot happen, but there is no
2784 -- point in bombing in this optimization circuit.
2786 -- First the low bound
2788 Bound := Type_Low_Bound (Typ);
2790 if Compile_Time_Known_Value (Bound) then
2791 Lo := Expr_Value (Bound);
2793 elsif Compile_Time_Known_Value (Type_Low_Bound (Base_Type (Typ))) then
2794 Lo := Expr_Value (Type_Low_Bound (Base_Type (Typ)));
2796 else
2797 OK := False;
2798 return;
2799 end if;
2801 -- Now the high bound
2803 Bound := Type_High_Bound (Typ);
2805 -- We need the high bound of the base type later on, and this should
2806 -- always be compile time known. Again, it is not clear that this
2807 -- can ever be false, but no point in bombing.
2809 if Compile_Time_Known_Value (Type_High_Bound (Base_Type (Typ))) then
2810 Hbound := Expr_Value (Type_High_Bound (Base_Type (Typ)));
2811 Hi := Hbound;
2813 else
2814 OK := False;
2815 return;
2816 end if;
2818 -- If we have a static subtype, then that may have a tighter bound
2819 -- so use the upper bound of the subtype instead in this case.
2821 if Compile_Time_Known_Value (Bound) then
2822 Hi := Expr_Value (Bound);
2823 end if;
2825 -- We may be able to refine this value in certain situations. If
2826 -- refinement is possible, then Lor and Hir are set to possibly
2827 -- tighter bounds, and OK1 is set to True.
2829 case Nkind (N) is
2831 -- For unary plus, result is limited by range of operand
2833 when N_Op_Plus =>
2834 Determine_Range (Right_Opnd (N), OK1, Lor, Hir);
2836 -- For unary minus, determine range of operand, and negate it
2838 when N_Op_Minus =>
2839 Determine_Range (Right_Opnd (N), OK1, Lo_Right, Hi_Right);
2841 if OK1 then
2842 Lor := -Hi_Right;
2843 Hir := -Lo_Right;
2844 end if;
2846 -- For binary addition, get range of each operand and do the
2847 -- addition to get the result range.
2849 when N_Op_Add =>
2850 if OK_Operands then
2851 Lor := Lo_Left + Lo_Right;
2852 Hir := Hi_Left + Hi_Right;
2853 end if;
2855 -- Division is tricky. The only case we consider is where the
2856 -- right operand is a positive constant, and in this case we
2857 -- simply divide the bounds of the left operand
2859 when N_Op_Divide =>
2860 if OK_Operands then
2861 if Lo_Right = Hi_Right
2862 and then Lo_Right > 0
2863 then
2864 Lor := Lo_Left / Lo_Right;
2865 Hir := Hi_Left / Lo_Right;
2867 else
2868 OK1 := False;
2869 end if;
2870 end if;
2872 -- For binary subtraction, get range of each operand and do
2873 -- the worst case subtraction to get the result range.
2875 when N_Op_Subtract =>
2876 if OK_Operands then
2877 Lor := Lo_Left - Hi_Right;
2878 Hir := Hi_Left - Lo_Right;
2879 end if;
2881 -- For MOD, if right operand is a positive constant, then
2882 -- result must be in the allowable range of mod results.
2884 when N_Op_Mod =>
2885 if OK_Operands then
2886 if Lo_Right = Hi_Right
2887 and then Lo_Right /= 0
2888 then
2889 if Lo_Right > 0 then
2890 Lor := Uint_0;
2891 Hir := Lo_Right - 1;
2893 else -- Lo_Right < 0
2894 Lor := Lo_Right + 1;
2895 Hir := Uint_0;
2896 end if;
2898 else
2899 OK1 := False;
2900 end if;
2901 end if;
2903 -- For REM, if right operand is a positive constant, then
2904 -- result must be in the allowable range of mod results.
2906 when N_Op_Rem =>
2907 if OK_Operands then
2908 if Lo_Right = Hi_Right
2909 and then Lo_Right /= 0
2910 then
2911 declare
2912 Dval : constant Uint := (abs Lo_Right) - 1;
2914 begin
2915 -- The sign of the result depends on the sign of the
2916 -- dividend (but not on the sign of the divisor, hence
2917 -- the abs operation above).
2919 if Lo_Left < 0 then
2920 Lor := -Dval;
2921 else
2922 Lor := Uint_0;
2923 end if;
2925 if Hi_Left < 0 then
2926 Hir := Uint_0;
2927 else
2928 Hir := Dval;
2929 end if;
2930 end;
2932 else
2933 OK1 := False;
2934 end if;
2935 end if;
2937 -- Attribute reference cases
2939 when N_Attribute_Reference =>
2940 case Attribute_Name (N) is
2942 -- For Pos/Val attributes, we can refine the range using the
2943 -- possible range of values of the attribute expression
2945 when Name_Pos | Name_Val =>
2946 Determine_Range (First (Expressions (N)), OK1, Lor, Hir);
2948 -- For Length attribute, use the bounds of the corresponding
2949 -- index type to refine the range.
2951 when Name_Length =>
2952 declare
2953 Atyp : Entity_Id := Etype (Prefix (N));
2954 Inum : Nat;
2955 Indx : Node_Id;
2957 LL, LU : Uint;
2958 UL, UU : Uint;
2960 begin
2961 if Is_Access_Type (Atyp) then
2962 Atyp := Designated_Type (Atyp);
2963 end if;
2965 -- For string literal, we know exact value
2967 if Ekind (Atyp) = E_String_Literal_Subtype then
2968 OK := True;
2969 Lo := String_Literal_Length (Atyp);
2970 Hi := String_Literal_Length (Atyp);
2971 return;
2972 end if;
2974 -- Otherwise check for expression given
2976 if No (Expressions (N)) then
2977 Inum := 1;
2978 else
2979 Inum :=
2980 UI_To_Int (Expr_Value (First (Expressions (N))));
2981 end if;
2983 Indx := First_Index (Atyp);
2984 for J in 2 .. Inum loop
2985 Indx := Next_Index (Indx);
2986 end loop;
2988 Determine_Range
2989 (Type_Low_Bound (Etype (Indx)), OK1, LL, LU);
2991 if OK1 then
2992 Determine_Range
2993 (Type_High_Bound (Etype (Indx)), OK1, UL, UU);
2995 if OK1 then
2997 -- The maximum value for Length is the biggest
2998 -- possible gap between the values of the bounds.
2999 -- But of course, this value cannot be negative.
3001 Hir := UI_Max (Uint_0, UU - LL);
3003 -- For constrained arrays, the minimum value for
3004 -- Length is taken from the actual value of the
3005 -- bounds, since the index will be exactly of
3006 -- this subtype.
3008 if Is_Constrained (Atyp) then
3009 Lor := UI_Max (Uint_0, UL - LU);
3011 -- For an unconstrained array, the minimum value
3012 -- for length is always zero.
3014 else
3015 Lor := Uint_0;
3016 end if;
3017 end if;
3018 end if;
3019 end;
3021 -- No special handling for other attributes
3022 -- Probably more opportunities exist here ???
3024 when others =>
3025 OK1 := False;
3027 end case;
3029 -- For type conversion from one discrete type to another, we
3030 -- can refine the range using the converted value.
3032 when N_Type_Conversion =>
3033 Determine_Range (Expression (N), OK1, Lor, Hir);
3035 -- Nothing special to do for all other expression kinds
3037 when others =>
3038 OK1 := False;
3039 Lor := No_Uint;
3040 Hir := No_Uint;
3041 end case;
3043 -- At this stage, if OK1 is true, then we know that the actual
3044 -- result of the computed expression is in the range Lor .. Hir.
3045 -- We can use this to restrict the possible range of results.
3047 if OK1 then
3049 -- If the refined value of the low bound is greater than the
3050 -- type high bound, then reset it to the more restrictive
3051 -- value. However, we do NOT do this for the case of a modular
3052 -- type where the possible upper bound on the value is above the
3053 -- base type high bound, because that means the result could wrap.
3055 if Lor > Lo
3056 and then not (Is_Modular_Integer_Type (Typ)
3057 and then Hir > Hbound)
3058 then
3059 Lo := Lor;
3060 end if;
3062 -- Similarly, if the refined value of the high bound is less
3063 -- than the value so far, then reset it to the more restrictive
3064 -- value. Again, we do not do this if the refined low bound is
3065 -- negative for a modular type, since this would wrap.
3067 if Hir < Hi
3068 and then not (Is_Modular_Integer_Type (Typ)
3069 and then Lor < Uint_0)
3070 then
3071 Hi := Hir;
3072 end if;
3073 end if;
3075 -- Set cache entry for future call and we are all done
3077 Determine_Range_Cache_N (Cindex) := N;
3078 Determine_Range_Cache_Lo (Cindex) := Lo;
3079 Determine_Range_Cache_Hi (Cindex) := Hi;
3080 return;
3082 -- If any exception occurs, it means that we have some bug in the compiler
3083 -- possibly triggered by a previous error, or by some unforseen peculiar
3084 -- occurrence. However, this is only an optimization attempt, so there is
3085 -- really no point in crashing the compiler. Instead we just decide, too
3086 -- bad, we can't figure out a range in this case after all.
3088 exception
3089 when others =>
3091 -- Debug flag K disables this behavior (useful for debugging)
3093 if Debug_Flag_K then
3094 raise;
3095 else
3096 OK := False;
3097 Lo := No_Uint;
3098 Hi := No_Uint;
3099 return;
3100 end if;
3101 end Determine_Range;
3103 ------------------------------------
3104 -- Discriminant_Checks_Suppressed --
3105 ------------------------------------
3107 function Discriminant_Checks_Suppressed (E : Entity_Id) return Boolean is
3108 begin
3109 if Present (E) then
3110 if Is_Unchecked_Union (E) then
3111 return True;
3112 elsif Checks_May_Be_Suppressed (E) then
3113 return Is_Check_Suppressed (E, Discriminant_Check);
3114 end if;
3115 end if;
3117 return Scope_Suppress (Discriminant_Check);
3118 end Discriminant_Checks_Suppressed;
3120 --------------------------------
3121 -- Division_Checks_Suppressed --
3122 --------------------------------
3124 function Division_Checks_Suppressed (E : Entity_Id) return Boolean is
3125 begin
3126 if Present (E) and then Checks_May_Be_Suppressed (E) then
3127 return Is_Check_Suppressed (E, Division_Check);
3128 else
3129 return Scope_Suppress (Division_Check);
3130 end if;
3131 end Division_Checks_Suppressed;
3133 -----------------------------------
3134 -- Elaboration_Checks_Suppressed --
3135 -----------------------------------
3137 function Elaboration_Checks_Suppressed (E : Entity_Id) return Boolean is
3138 begin
3139 if Present (E) then
3140 if Kill_Elaboration_Checks (E) then
3141 return True;
3142 elsif Checks_May_Be_Suppressed (E) then
3143 return Is_Check_Suppressed (E, Elaboration_Check);
3144 end if;
3145 end if;
3147 return Scope_Suppress (Elaboration_Check);
3148 end Elaboration_Checks_Suppressed;
3150 ---------------------------
3151 -- Enable_Overflow_Check --
3152 ---------------------------
3154 procedure Enable_Overflow_Check (N : Node_Id) is
3155 Typ : constant Entity_Id := Base_Type (Etype (N));
3156 Chk : Nat;
3157 OK : Boolean;
3158 Ent : Entity_Id;
3159 Ofs : Uint;
3160 Lo : Uint;
3161 Hi : Uint;
3163 begin
3164 if Debug_Flag_CC then
3165 w ("Enable_Overflow_Check for node ", Int (N));
3166 Write_Str (" Source location = ");
3167 wl (Sloc (N));
3168 pg (N);
3169 end if;
3171 -- Nothing to do if the range of the result is known OK. We skip
3172 -- this for conversions, since the caller already did the check,
3173 -- and in any case the condition for deleting the check for a
3174 -- type conversion is different in any case.
3176 if Nkind (N) /= N_Type_Conversion then
3177 Determine_Range (N, OK, Lo, Hi);
3179 -- Note in the test below that we assume that if a bound of the
3180 -- range is equal to that of the type. That's not quite accurate
3181 -- but we do this for the following reasons:
3183 -- a) The way that Determine_Range works, it will typically report
3184 -- the bounds of the value as being equal to the bounds of the
3185 -- type, because it either can't tell anything more precise, or
3186 -- does not think it is worth the effort to be more precise.
3188 -- b) It is very unusual to have a situation in which this would
3189 -- generate an unnecessary overflow check (an example would be
3190 -- a subtype with a range 0 .. Integer'Last - 1 to which the
3191 -- literal value one is added.
3193 -- c) The alternative is a lot of special casing in this routine
3194 -- which would partially duplicate Determine_Range processing.
3196 if OK
3197 and then Lo > Expr_Value (Type_Low_Bound (Typ))
3198 and then Hi < Expr_Value (Type_High_Bound (Typ))
3199 then
3200 if Debug_Flag_CC then
3201 w ("No overflow check required");
3202 end if;
3204 return;
3205 end if;
3206 end if;
3208 -- If not in optimizing mode, set flag and we are done. We are also
3209 -- done (and just set the flag) if the type is not a discrete type,
3210 -- since it is not worth the effort to eliminate checks for other
3211 -- than discrete types. In addition, we take this same path if we
3212 -- have stored the maximum number of checks possible already (a
3213 -- very unlikely situation, but we do not want to blow up!)
3215 if Optimization_Level = 0
3216 or else not Is_Discrete_Type (Etype (N))
3217 or else Num_Saved_Checks = Saved_Checks'Last
3218 then
3219 Set_Do_Overflow_Check (N, True);
3221 if Debug_Flag_CC then
3222 w ("Optimization off");
3223 end if;
3225 return;
3226 end if;
3228 -- Otherwise evaluate and check the expression
3230 Find_Check
3231 (Expr => N,
3232 Check_Type => 'O',
3233 Target_Type => Empty,
3234 Entry_OK => OK,
3235 Check_Num => Chk,
3236 Ent => Ent,
3237 Ofs => Ofs);
3239 if Debug_Flag_CC then
3240 w ("Called Find_Check");
3241 w (" OK = ", OK);
3243 if OK then
3244 w (" Check_Num = ", Chk);
3245 w (" Ent = ", Int (Ent));
3246 Write_Str (" Ofs = ");
3247 pid (Ofs);
3248 end if;
3249 end if;
3251 -- If check is not of form to optimize, then set flag and we are done
3253 if not OK then
3254 Set_Do_Overflow_Check (N, True);
3255 return;
3256 end if;
3258 -- If check is already performed, then return without setting flag
3260 if Chk /= 0 then
3261 if Debug_Flag_CC then
3262 w ("Check suppressed!");
3263 end if;
3265 return;
3266 end if;
3268 -- Here we will make a new entry for the new check
3270 Set_Do_Overflow_Check (N, True);
3271 Num_Saved_Checks := Num_Saved_Checks + 1;
3272 Saved_Checks (Num_Saved_Checks) :=
3273 (Killed => False,
3274 Entity => Ent,
3275 Offset => Ofs,
3276 Check_Type => 'O',
3277 Target_Type => Empty);
3279 if Debug_Flag_CC then
3280 w ("Make new entry, check number = ", Num_Saved_Checks);
3281 w (" Entity = ", Int (Ent));
3282 Write_Str (" Offset = ");
3283 pid (Ofs);
3284 w (" Check_Type = O");
3285 w (" Target_Type = Empty");
3286 end if;
3288 -- If we get an exception, then something went wrong, probably because
3289 -- of an error in the structure of the tree due to an incorrect program.
3290 -- Or it may be a bug in the optimization circuit. In either case the
3291 -- safest thing is simply to set the check flag unconditionally.
3293 exception
3294 when others =>
3295 Set_Do_Overflow_Check (N, True);
3297 if Debug_Flag_CC then
3298 w (" exception occurred, overflow flag set");
3299 end if;
3301 return;
3302 end Enable_Overflow_Check;
3304 ------------------------
3305 -- Enable_Range_Check --
3306 ------------------------
3308 procedure Enable_Range_Check (N : Node_Id) is
3309 Chk : Nat;
3310 OK : Boolean;
3311 Ent : Entity_Id;
3312 Ofs : Uint;
3313 Ttyp : Entity_Id;
3314 P : Node_Id;
3316 begin
3317 -- Return if unchecked type conversion with range check killed.
3318 -- In this case we never set the flag (that's what Kill_Range_Check
3319 -- is all about!)
3321 if Nkind (N) = N_Unchecked_Type_Conversion
3322 and then Kill_Range_Check (N)
3323 then
3324 return;
3325 end if;
3327 -- Debug trace output
3329 if Debug_Flag_CC then
3330 w ("Enable_Range_Check for node ", Int (N));
3331 Write_Str (" Source location = ");
3332 wl (Sloc (N));
3333 pg (N);
3334 end if;
3336 -- If not in optimizing mode, set flag and we are done. We are also
3337 -- done (and just set the flag) if the type is not a discrete type,
3338 -- since it is not worth the effort to eliminate checks for other
3339 -- than discrete types. In addition, we take this same path if we
3340 -- have stored the maximum number of checks possible already (a
3341 -- very unlikely situation, but we do not want to blow up!)
3343 if Optimization_Level = 0
3344 or else No (Etype (N))
3345 or else not Is_Discrete_Type (Etype (N))
3346 or else Num_Saved_Checks = Saved_Checks'Last
3347 then
3348 Set_Do_Range_Check (N, True);
3350 if Debug_Flag_CC then
3351 w ("Optimization off");
3352 end if;
3354 return;
3355 end if;
3357 -- Otherwise find out the target type
3359 P := Parent (N);
3361 -- For assignment, use left side subtype
3363 if Nkind (P) = N_Assignment_Statement
3364 and then Expression (P) = N
3365 then
3366 Ttyp := Etype (Name (P));
3368 -- For indexed component, use subscript subtype
3370 elsif Nkind (P) = N_Indexed_Component then
3371 declare
3372 Atyp : Entity_Id;
3373 Indx : Node_Id;
3374 Subs : Node_Id;
3376 begin
3377 Atyp := Etype (Prefix (P));
3379 if Is_Access_Type (Atyp) then
3380 Atyp := Designated_Type (Atyp);
3382 -- If the prefix is an access to an unconstrained array,
3383 -- perform check unconditionally: it depends on the bounds
3384 -- of an object and we cannot currently recognize whether
3385 -- the test may be redundant.
3387 if not Is_Constrained (Atyp) then
3388 Set_Do_Range_Check (N, True);
3389 return;
3390 end if;
3391 end if;
3393 Indx := First_Index (Atyp);
3394 Subs := First (Expressions (P));
3395 loop
3396 if Subs = N then
3397 Ttyp := Etype (Indx);
3398 exit;
3399 end if;
3401 Next_Index (Indx);
3402 Next (Subs);
3403 end loop;
3404 end;
3406 -- For now, ignore all other cases, they are not so interesting
3408 else
3409 if Debug_Flag_CC then
3410 w (" target type not found, flag set");
3411 end if;
3413 Set_Do_Range_Check (N, True);
3414 return;
3415 end if;
3417 -- Evaluate and check the expression
3419 Find_Check
3420 (Expr => N,
3421 Check_Type => 'R',
3422 Target_Type => Ttyp,
3423 Entry_OK => OK,
3424 Check_Num => Chk,
3425 Ent => Ent,
3426 Ofs => Ofs);
3428 if Debug_Flag_CC then
3429 w ("Called Find_Check");
3430 w ("Target_Typ = ", Int (Ttyp));
3431 w (" OK = ", OK);
3433 if OK then
3434 w (" Check_Num = ", Chk);
3435 w (" Ent = ", Int (Ent));
3436 Write_Str (" Ofs = ");
3437 pid (Ofs);
3438 end if;
3439 end if;
3441 -- If check is not of form to optimize, then set flag and we are done
3443 if not OK then
3444 if Debug_Flag_CC then
3445 w (" expression not of optimizable type, flag set");
3446 end if;
3448 Set_Do_Range_Check (N, True);
3449 return;
3450 end if;
3452 -- If check is already performed, then return without setting flag
3454 if Chk /= 0 then
3455 if Debug_Flag_CC then
3456 w ("Check suppressed!");
3457 end if;
3459 return;
3460 end if;
3462 -- Here we will make a new entry for the new check
3464 Set_Do_Range_Check (N, True);
3465 Num_Saved_Checks := Num_Saved_Checks + 1;
3466 Saved_Checks (Num_Saved_Checks) :=
3467 (Killed => False,
3468 Entity => Ent,
3469 Offset => Ofs,
3470 Check_Type => 'R',
3471 Target_Type => Ttyp);
3473 if Debug_Flag_CC then
3474 w ("Make new entry, check number = ", Num_Saved_Checks);
3475 w (" Entity = ", Int (Ent));
3476 Write_Str (" Offset = ");
3477 pid (Ofs);
3478 w (" Check_Type = R");
3479 w (" Target_Type = ", Int (Ttyp));
3480 pg (Ttyp);
3481 end if;
3483 -- If we get an exception, then something went wrong, probably because
3484 -- of an error in the structure of the tree due to an incorrect program.
3485 -- Or it may be a bug in the optimization circuit. In either case the
3486 -- safest thing is simply to set the check flag unconditionally.
3488 exception
3489 when others =>
3490 Set_Do_Range_Check (N, True);
3492 if Debug_Flag_CC then
3493 w (" exception occurred, range flag set");
3494 end if;
3496 return;
3497 end Enable_Range_Check;
3499 ------------------
3500 -- Ensure_Valid --
3501 ------------------
3503 procedure Ensure_Valid (Expr : Node_Id; Holes_OK : Boolean := False) is
3504 Typ : constant Entity_Id := Etype (Expr);
3506 begin
3507 -- Ignore call if we are not doing any validity checking
3509 if not Validity_Checks_On then
3510 return;
3512 -- Ignore call if range checks suppressed on entity in question
3514 elsif Is_Entity_Name (Expr)
3515 and then Range_Checks_Suppressed (Entity (Expr))
3516 then
3517 return;
3519 -- No check required if expression is from the expander, we assume
3520 -- the expander will generate whatever checks are needed. Note that
3521 -- this is not just an optimization, it avoids infinite recursions!
3523 -- Unchecked conversions must be checked, unless they are initialized
3524 -- scalar values, as in a component assignment in an init proc.
3526 -- In addition, we force a check if Force_Validity_Checks is set
3528 elsif not Comes_From_Source (Expr)
3529 and then not Force_Validity_Checks
3530 and then (Nkind (Expr) /= N_Unchecked_Type_Conversion
3531 or else Kill_Range_Check (Expr))
3532 then
3533 return;
3535 -- No check required if expression is known to have valid value
3537 elsif Expr_Known_Valid (Expr) then
3538 return;
3540 -- No check required if checks off
3542 elsif Range_Checks_Suppressed (Typ) then
3543 return;
3545 -- Ignore case of enumeration with holes where the flag is set not
3546 -- to worry about holes, since no special validity check is needed
3548 elsif Is_Enumeration_Type (Typ)
3549 and then Has_Non_Standard_Rep (Typ)
3550 and then Holes_OK
3551 then
3552 return;
3554 -- No check required on the left-hand side of an assignment.
3556 elsif Nkind (Parent (Expr)) = N_Assignment_Statement
3557 and then Expr = Name (Parent (Expr))
3558 then
3559 return;
3561 -- An annoying special case. If this is an out parameter of a scalar
3562 -- type, then the value is not going to be accessed, therefore it is
3563 -- inappropriate to do any validity check at the call site.
3565 else
3566 -- Only need to worry about scalar types
3568 if Is_Scalar_Type (Typ) then
3569 declare
3570 P : Node_Id;
3571 N : Node_Id;
3572 E : Entity_Id;
3573 F : Entity_Id;
3574 A : Node_Id;
3575 L : List_Id;
3577 begin
3578 -- Find actual argument (which may be a parameter association)
3579 -- and the parent of the actual argument (the call statement)
3581 N := Expr;
3582 P := Parent (Expr);
3584 if Nkind (P) = N_Parameter_Association then
3585 N := P;
3586 P := Parent (N);
3587 end if;
3589 -- Only need to worry if we are argument of a procedure
3590 -- call since functions don't have out parameters. If this
3591 -- is an indirect or dispatching call, get signature from
3592 -- the subprogram type.
3594 if Nkind (P) = N_Procedure_Call_Statement then
3595 L := Parameter_Associations (P);
3597 if Is_Entity_Name (Name (P)) then
3598 E := Entity (Name (P));
3599 else
3600 pragma Assert (Nkind (Name (P)) = N_Explicit_Dereference);
3601 E := Etype (Name (P));
3602 end if;
3604 -- Only need to worry if there are indeed actuals, and
3605 -- if this could be a procedure call, otherwise we cannot
3606 -- get a match (either we are not an argument, or the
3607 -- mode of the formal is not OUT). This test also filters
3608 -- out the generic case.
3610 if Is_Non_Empty_List (L)
3611 and then Is_Subprogram (E)
3612 then
3613 -- This is the loop through parameters, looking to
3614 -- see if there is an OUT parameter for which we are
3615 -- the argument.
3617 F := First_Formal (E);
3618 A := First (L);
3620 while Present (F) loop
3621 if Ekind (F) = E_Out_Parameter and then A = N then
3622 return;
3623 end if;
3625 Next_Formal (F);
3626 Next (A);
3627 end loop;
3628 end if;
3629 end if;
3630 end;
3631 end if;
3632 end if;
3634 -- If we fall through, a validity check is required. Note that it would
3635 -- not be good to set Do_Range_Check, even in contexts where this is
3636 -- permissible, since this flag causes checking against the target type,
3637 -- not the source type in contexts such as assignments
3639 Insert_Valid_Check (Expr);
3640 end Ensure_Valid;
3642 ----------------------
3643 -- Expr_Known_Valid --
3644 ----------------------
3646 function Expr_Known_Valid (Expr : Node_Id) return Boolean is
3647 Typ : constant Entity_Id := Etype (Expr);
3649 begin
3650 -- Non-scalar types are always consdered valid, since they never
3651 -- give rise to the issues of erroneous or bounded error behavior
3652 -- that are the concern. In formal reference manual terms the
3653 -- notion of validity only applies to scalar types.
3655 if not Is_Scalar_Type (Typ) then
3656 return True;
3658 -- If no validity checking, then everything is considered valid
3660 elsif not Validity_Checks_On then
3661 return True;
3663 -- Floating-point types are considered valid unless floating-point
3664 -- validity checks have been specifically turned on.
3666 elsif Is_Floating_Point_Type (Typ)
3667 and then not Validity_Check_Floating_Point
3668 then
3669 return True;
3671 -- If the expression is the value of an object that is known to
3672 -- be valid, then clearly the expression value itself is valid.
3674 elsif Is_Entity_Name (Expr)
3675 and then Is_Known_Valid (Entity (Expr))
3676 then
3677 return True;
3679 -- If the type is one for which all values are known valid, then
3680 -- we are sure that the value is valid except in the slightly odd
3681 -- case where the expression is a reference to a variable whose size
3682 -- has been explicitly set to a value greater than the object size.
3684 elsif Is_Known_Valid (Typ) then
3685 if Is_Entity_Name (Expr)
3686 and then Ekind (Entity (Expr)) = E_Variable
3687 and then Esize (Entity (Expr)) > Esize (Typ)
3688 then
3689 return False;
3690 else
3691 return True;
3692 end if;
3694 -- Integer and character literals always have valid values, where
3695 -- appropriate these will be range checked in any case.
3697 elsif Nkind (Expr) = N_Integer_Literal
3698 or else
3699 Nkind (Expr) = N_Character_Literal
3700 then
3701 return True;
3703 -- If we have a type conversion or a qualification of a known valid
3704 -- value, then the result will always be valid.
3706 elsif Nkind (Expr) = N_Type_Conversion
3707 or else
3708 Nkind (Expr) = N_Qualified_Expression
3709 then
3710 return Expr_Known_Valid (Expression (Expr));
3712 -- The result of any function call or operator is always considered
3713 -- valid, since we assume the necessary checks are done by the call.
3715 elsif Nkind (Expr) in N_Binary_Op
3716 or else
3717 Nkind (Expr) in N_Unary_Op
3718 or else
3719 Nkind (Expr) = N_Function_Call
3720 then
3721 return True;
3723 -- For all other cases, we do not know the expression is valid
3725 else
3726 return False;
3727 end if;
3728 end Expr_Known_Valid;
3730 ----------------
3731 -- Find_Check --
3732 ----------------
3734 procedure Find_Check
3735 (Expr : Node_Id;
3736 Check_Type : Character;
3737 Target_Type : Entity_Id;
3738 Entry_OK : out Boolean;
3739 Check_Num : out Nat;
3740 Ent : out Entity_Id;
3741 Ofs : out Uint)
3743 function Within_Range_Of
3744 (Target_Type : Entity_Id;
3745 Check_Type : Entity_Id) return Boolean;
3746 -- Given a requirement for checking a range against Target_Type, and
3747 -- and a range Check_Type against which a check has already been made,
3748 -- determines if the check against check type is sufficient to ensure
3749 -- that no check against Target_Type is required.
3751 ---------------------
3752 -- Within_Range_Of --
3753 ---------------------
3755 function Within_Range_Of
3756 (Target_Type : Entity_Id;
3757 Check_Type : Entity_Id) return Boolean
3759 begin
3760 if Target_Type = Check_Type then
3761 return True;
3763 else
3764 declare
3765 Tlo : constant Node_Id := Type_Low_Bound (Target_Type);
3766 Thi : constant Node_Id := Type_High_Bound (Target_Type);
3767 Clo : constant Node_Id := Type_Low_Bound (Check_Type);
3768 Chi : constant Node_Id := Type_High_Bound (Check_Type);
3770 begin
3771 if (Tlo = Clo
3772 or else (Compile_Time_Known_Value (Tlo)
3773 and then
3774 Compile_Time_Known_Value (Clo)
3775 and then
3776 Expr_Value (Clo) >= Expr_Value (Tlo)))
3777 and then
3778 (Thi = Chi
3779 or else (Compile_Time_Known_Value (Thi)
3780 and then
3781 Compile_Time_Known_Value (Chi)
3782 and then
3783 Expr_Value (Chi) <= Expr_Value (Clo)))
3784 then
3785 return True;
3786 else
3787 return False;
3788 end if;
3789 end;
3790 end if;
3791 end Within_Range_Of;
3793 -- Start of processing for Find_Check
3795 begin
3796 -- Establish default, to avoid warnings from GCC.
3798 Check_Num := 0;
3800 -- Case of expression is simple entity reference
3802 if Is_Entity_Name (Expr) then
3803 Ent := Entity (Expr);
3804 Ofs := Uint_0;
3806 -- Case of expression is entity + known constant
3808 elsif Nkind (Expr) = N_Op_Add
3809 and then Compile_Time_Known_Value (Right_Opnd (Expr))
3810 and then Is_Entity_Name (Left_Opnd (Expr))
3811 then
3812 Ent := Entity (Left_Opnd (Expr));
3813 Ofs := Expr_Value (Right_Opnd (Expr));
3815 -- Case of expression is entity - known constant
3817 elsif Nkind (Expr) = N_Op_Subtract
3818 and then Compile_Time_Known_Value (Right_Opnd (Expr))
3819 and then Is_Entity_Name (Left_Opnd (Expr))
3820 then
3821 Ent := Entity (Left_Opnd (Expr));
3822 Ofs := UI_Negate (Expr_Value (Right_Opnd (Expr)));
3824 -- Any other expression is not of the right form
3826 else
3827 Ent := Empty;
3828 Ofs := Uint_0;
3829 Entry_OK := False;
3830 return;
3831 end if;
3833 -- Come here with expression of appropriate form, check if
3834 -- entity is an appropriate one for our purposes.
3836 if (Ekind (Ent) = E_Variable
3837 or else
3838 Ekind (Ent) = E_Constant
3839 or else
3840 Ekind (Ent) = E_Loop_Parameter
3841 or else
3842 Ekind (Ent) = E_In_Parameter)
3843 and then not Is_Library_Level_Entity (Ent)
3844 then
3845 Entry_OK := True;
3846 else
3847 Entry_OK := False;
3848 return;
3849 end if;
3851 -- See if there is matching check already
3853 for J in reverse 1 .. Num_Saved_Checks loop
3854 declare
3855 SC : Saved_Check renames Saved_Checks (J);
3857 begin
3858 if SC.Killed = False
3859 and then SC.Entity = Ent
3860 and then SC.Offset = Ofs
3861 and then SC.Check_Type = Check_Type
3862 and then Within_Range_Of (Target_Type, SC.Target_Type)
3863 then
3864 Check_Num := J;
3865 return;
3866 end if;
3867 end;
3868 end loop;
3870 -- If we fall through entry was not found
3872 Check_Num := 0;
3873 return;
3874 end Find_Check;
3876 ---------------------------------
3877 -- Generate_Discriminant_Check --
3878 ---------------------------------
3880 -- Note: the code for this procedure is derived from the
3881 -- emit_discriminant_check routine a-trans.c v1.659.
3883 procedure Generate_Discriminant_Check (N : Node_Id) is
3884 Loc : constant Source_Ptr := Sloc (N);
3885 Pref : constant Node_Id := Prefix (N);
3886 Sel : constant Node_Id := Selector_Name (N);
3888 Orig_Comp : constant Entity_Id :=
3889 Original_Record_Component (Entity (Sel));
3890 -- The original component to be checked
3892 Discr_Fct : constant Entity_Id :=
3893 Discriminant_Checking_Func (Orig_Comp);
3894 -- The discriminant checking function
3896 Discr : Entity_Id;
3897 -- One discriminant to be checked in the type
3899 Real_Discr : Entity_Id;
3900 -- Actual discriminant in the call
3902 Pref_Type : Entity_Id;
3903 -- Type of relevant prefix (ignoring private/access stuff)
3905 Args : List_Id;
3906 -- List of arguments for function call
3908 Formal : Entity_Id;
3909 -- Keep track of the formal corresponding to the actual we build
3910 -- for each discriminant, in order to be able to perform the
3911 -- necessary type conversions.
3913 Scomp : Node_Id;
3914 -- Selected component reference for checking function argument
3916 begin
3917 Pref_Type := Etype (Pref);
3919 -- Force evaluation of the prefix, so that it does not get evaluated
3920 -- twice (once for the check, once for the actual reference). Such a
3921 -- double evaluation is always a potential source of inefficiency,
3922 -- and is functionally incorrect in the volatile case, or when the
3923 -- prefix may have side-effects. An entity or a component of an
3924 -- entity requires no evaluation.
3926 if Is_Entity_Name (Pref) then
3927 if Treat_As_Volatile (Entity (Pref)) then
3928 Force_Evaluation (Pref, Name_Req => True);
3929 end if;
3931 elsif Treat_As_Volatile (Etype (Pref)) then
3932 Force_Evaluation (Pref, Name_Req => True);
3934 elsif Nkind (Pref) = N_Selected_Component
3935 and then Is_Entity_Name (Prefix (Pref))
3936 then
3937 null;
3939 else
3940 Force_Evaluation (Pref, Name_Req => True);
3941 end if;
3943 -- For a tagged type, use the scope of the original component to
3944 -- obtain the type, because ???
3946 if Is_Tagged_Type (Scope (Orig_Comp)) then
3947 Pref_Type := Scope (Orig_Comp);
3949 -- For an untagged derived type, use the discriminants of the
3950 -- parent which have been renamed in the derivation, possibly
3951 -- by a one-to-many discriminant constraint.
3952 -- For non-tagged type, initially get the Etype of the prefix
3954 else
3955 if Is_Derived_Type (Pref_Type)
3956 and then Number_Discriminants (Pref_Type) /=
3957 Number_Discriminants (Etype (Base_Type (Pref_Type)))
3958 then
3959 Pref_Type := Etype (Base_Type (Pref_Type));
3960 end if;
3961 end if;
3963 -- We definitely should have a checking function, This routine should
3964 -- not be called if no discriminant checking function is present.
3966 pragma Assert (Present (Discr_Fct));
3968 -- Create the list of the actual parameters for the call. This list
3969 -- is the list of the discriminant fields of the record expression to
3970 -- be discriminant checked.
3972 Args := New_List;
3973 Formal := First_Formal (Discr_Fct);
3974 Discr := First_Discriminant (Pref_Type);
3975 while Present (Discr) loop
3977 -- If we have a corresponding discriminant field, and a parent
3978 -- subtype is present, then we want to use the corresponding
3979 -- discriminant since this is the one with the useful value.
3981 if Present (Corresponding_Discriminant (Discr))
3982 and then Ekind (Pref_Type) = E_Record_Type
3983 and then Present (Parent_Subtype (Pref_Type))
3984 then
3985 Real_Discr := Corresponding_Discriminant (Discr);
3986 else
3987 Real_Discr := Discr;
3988 end if;
3990 -- Construct the reference to the discriminant
3992 Scomp :=
3993 Make_Selected_Component (Loc,
3994 Prefix =>
3995 Unchecked_Convert_To (Pref_Type,
3996 Duplicate_Subexpr (Pref)),
3997 Selector_Name => New_Occurrence_Of (Real_Discr, Loc));
3999 -- Manually analyze and resolve this selected component. We really
4000 -- want it just as it appears above, and do not want the expander
4001 -- playing discriminal games etc with this reference. Then we
4002 -- append the argument to the list we are gathering.
4004 Set_Etype (Scomp, Etype (Real_Discr));
4005 Set_Analyzed (Scomp, True);
4006 Append_To (Args, Convert_To (Etype (Formal), Scomp));
4008 Next_Formal_With_Extras (Formal);
4009 Next_Discriminant (Discr);
4010 end loop;
4012 -- Now build and insert the call
4014 Insert_Action (N,
4015 Make_Raise_Constraint_Error (Loc,
4016 Condition =>
4017 Make_Function_Call (Loc,
4018 Name => New_Occurrence_Of (Discr_Fct, Loc),
4019 Parameter_Associations => Args),
4020 Reason => CE_Discriminant_Check_Failed));
4021 end Generate_Discriminant_Check;
4023 ----------------------------
4024 -- Generate_Index_Checks --
4025 ----------------------------
4027 procedure Generate_Index_Checks (N : Node_Id) is
4028 Loc : constant Source_Ptr := Sloc (N);
4029 A : constant Node_Id := Prefix (N);
4030 Sub : Node_Id;
4031 Ind : Nat;
4032 Num : List_Id;
4034 begin
4035 Sub := First (Expressions (N));
4036 Ind := 1;
4037 while Present (Sub) loop
4038 if Do_Range_Check (Sub) then
4039 Set_Do_Range_Check (Sub, False);
4041 -- Force evaluation except for the case of a simple name of
4042 -- a non-volatile entity.
4044 if not Is_Entity_Name (Sub)
4045 or else Treat_As_Volatile (Entity (Sub))
4046 then
4047 Force_Evaluation (Sub);
4048 end if;
4050 -- Generate a raise of constraint error with the appropriate
4051 -- reason and a condition of the form:
4053 -- Base_Type(Sub) not in array'range (subscript)
4055 -- Note that the reason we generate the conversion to the
4056 -- base type here is that we definitely want the range check
4057 -- to take place, even if it looks like the subtype is OK.
4058 -- Optimization considerations that allow us to omit the
4059 -- check have already been taken into account in the setting
4060 -- of the Do_Range_Check flag earlier on.
4062 if Ind = 1 then
4063 Num := No_List;
4064 else
4065 Num := New_List (Make_Integer_Literal (Loc, Ind));
4066 end if;
4068 Insert_Action (N,
4069 Make_Raise_Constraint_Error (Loc,
4070 Condition =>
4071 Make_Not_In (Loc,
4072 Left_Opnd =>
4073 Convert_To (Base_Type (Etype (Sub)),
4074 Duplicate_Subexpr_Move_Checks (Sub)),
4075 Right_Opnd =>
4076 Make_Attribute_Reference (Loc,
4077 Prefix => Duplicate_Subexpr_Move_Checks (A),
4078 Attribute_Name => Name_Range,
4079 Expressions => Num)),
4080 Reason => CE_Index_Check_Failed));
4081 end if;
4083 Ind := Ind + 1;
4084 Next (Sub);
4085 end loop;
4086 end Generate_Index_Checks;
4088 --------------------------
4089 -- Generate_Range_Check --
4090 --------------------------
4092 procedure Generate_Range_Check
4093 (N : Node_Id;
4094 Target_Type : Entity_Id;
4095 Reason : RT_Exception_Code)
4097 Loc : constant Source_Ptr := Sloc (N);
4098 Source_Type : constant Entity_Id := Etype (N);
4099 Source_Base_Type : constant Entity_Id := Base_Type (Source_Type);
4100 Target_Base_Type : constant Entity_Id := Base_Type (Target_Type);
4102 begin
4103 -- First special case, if the source type is already within the
4104 -- range of the target type, then no check is needed (probably we
4105 -- should have stopped Do_Range_Check from being set in the first
4106 -- place, but better late than later in preventing junk code!
4108 -- We do NOT apply this if the source node is a literal, since in
4109 -- this case the literal has already been labeled as having the
4110 -- subtype of the target.
4112 if In_Subrange_Of (Source_Type, Target_Type)
4113 and then not
4114 (Nkind (N) = N_Integer_Literal
4115 or else
4116 Nkind (N) = N_Real_Literal
4117 or else
4118 Nkind (N) = N_Character_Literal
4119 or else
4120 (Is_Entity_Name (N)
4121 and then Ekind (Entity (N)) = E_Enumeration_Literal))
4122 then
4123 return;
4124 end if;
4126 -- We need a check, so force evaluation of the node, so that it does
4127 -- not get evaluated twice (once for the check, once for the actual
4128 -- reference). Such a double evaluation is always a potential source
4129 -- of inefficiency, and is functionally incorrect in the volatile case.
4131 if not Is_Entity_Name (N)
4132 or else Treat_As_Volatile (Entity (N))
4133 then
4134 Force_Evaluation (N);
4135 end if;
4137 -- The easiest case is when Source_Base_Type and Target_Base_Type
4138 -- are the same since in this case we can simply do a direct
4139 -- check of the value of N against the bounds of Target_Type.
4141 -- [constraint_error when N not in Target_Type]
4143 -- Note: this is by far the most common case, for example all cases of
4144 -- checks on the RHS of assignments are in this category, but not all
4145 -- cases are like this. Notably conversions can involve two types.
4147 if Source_Base_Type = Target_Base_Type then
4148 Insert_Action (N,
4149 Make_Raise_Constraint_Error (Loc,
4150 Condition =>
4151 Make_Not_In (Loc,
4152 Left_Opnd => Duplicate_Subexpr (N),
4153 Right_Opnd => New_Occurrence_Of (Target_Type, Loc)),
4154 Reason => Reason));
4156 -- Next test for the case where the target type is within the bounds
4157 -- of the base type of the source type, since in this case we can
4158 -- simply convert these bounds to the base type of T to do the test.
4160 -- [constraint_error when N not in
4161 -- Source_Base_Type (Target_Type'First)
4162 -- ..
4163 -- Source_Base_Type(Target_Type'Last))]
4165 -- The conversions will always work and need no check.
4167 elsif In_Subrange_Of (Target_Type, Source_Base_Type) then
4168 Insert_Action (N,
4169 Make_Raise_Constraint_Error (Loc,
4170 Condition =>
4171 Make_Not_In (Loc,
4172 Left_Opnd => Duplicate_Subexpr (N),
4174 Right_Opnd =>
4175 Make_Range (Loc,
4176 Low_Bound =>
4177 Convert_To (Source_Base_Type,
4178 Make_Attribute_Reference (Loc,
4179 Prefix =>
4180 New_Occurrence_Of (Target_Type, Loc),
4181 Attribute_Name => Name_First)),
4183 High_Bound =>
4184 Convert_To (Source_Base_Type,
4185 Make_Attribute_Reference (Loc,
4186 Prefix =>
4187 New_Occurrence_Of (Target_Type, Loc),
4188 Attribute_Name => Name_Last)))),
4189 Reason => Reason));
4191 -- Note that at this stage we now that the Target_Base_Type is
4192 -- not in the range of the Source_Base_Type (since even the
4193 -- Target_Type itself is not in this range). It could still be
4194 -- the case that the Source_Type is in range of the target base
4195 -- type, since we have not checked that case.
4197 -- If that is the case, we can freely convert the source to the
4198 -- target, and then test the target result against the bounds.
4200 elsif In_Subrange_Of (Source_Type, Target_Base_Type) then
4202 -- We make a temporary to hold the value of the converted
4203 -- value (converted to the base type), and then we will
4204 -- do the test against this temporary.
4206 -- Tnn : constant Target_Base_Type := Target_Base_Type (N);
4207 -- [constraint_error when Tnn not in Target_Type]
4209 -- Then the conversion itself is replaced by an occurrence of Tnn
4211 declare
4212 Tnn : constant Entity_Id :=
4213 Make_Defining_Identifier (Loc,
4214 Chars => New_Internal_Name ('T'));
4216 begin
4217 Insert_Actions (N, New_List (
4218 Make_Object_Declaration (Loc,
4219 Defining_Identifier => Tnn,
4220 Object_Definition =>
4221 New_Occurrence_Of (Target_Base_Type, Loc),
4222 Constant_Present => True,
4223 Expression =>
4224 Make_Type_Conversion (Loc,
4225 Subtype_Mark => New_Occurrence_Of (Target_Base_Type, Loc),
4226 Expression => Duplicate_Subexpr (N))),
4228 Make_Raise_Constraint_Error (Loc,
4229 Condition =>
4230 Make_Not_In (Loc,
4231 Left_Opnd => New_Occurrence_Of (Tnn, Loc),
4232 Right_Opnd => New_Occurrence_Of (Target_Type, Loc)),
4234 Reason => Reason)));
4236 Rewrite (N, New_Occurrence_Of (Tnn, Loc));
4237 end;
4239 -- At this stage, we know that we have two scalar types, which are
4240 -- directly convertible, and where neither scalar type has a base
4241 -- range that is in the range of the other scalar type.
4243 -- The only way this can happen is with a signed and unsigned type.
4244 -- So test for these two cases:
4246 else
4247 -- Case of the source is unsigned and the target is signed
4249 if Is_Unsigned_Type (Source_Base_Type)
4250 and then not Is_Unsigned_Type (Target_Base_Type)
4251 then
4252 -- If the source is unsigned and the target is signed, then we
4253 -- know that the source is not shorter than the target (otherwise
4254 -- the source base type would be in the target base type range).
4256 -- In other words, the unsigned type is either the same size
4257 -- as the target, or it is larger. It cannot be smaller.
4259 pragma Assert
4260 (Esize (Source_Base_Type) >= Esize (Target_Base_Type));
4262 -- We only need to check the low bound if the low bound of the
4263 -- target type is non-negative. If the low bound of the target
4264 -- type is negative, then we know that we will fit fine.
4266 -- If the high bound of the target type is negative, then we
4267 -- know we have a constraint error, since we can't possibly
4268 -- have a negative source.
4270 -- With these two checks out of the way, we can do the check
4271 -- using the source type safely
4273 -- This is definitely the most annoying case!
4275 -- [constraint_error
4276 -- when (Target_Type'First >= 0
4277 -- and then
4278 -- N < Source_Base_Type (Target_Type'First))
4279 -- or else Target_Type'Last < 0
4280 -- or else N > Source_Base_Type (Target_Type'Last)];
4282 -- We turn off all checks since we know that the conversions
4283 -- will work fine, given the guards for negative values.
4285 Insert_Action (N,
4286 Make_Raise_Constraint_Error (Loc,
4287 Condition =>
4288 Make_Or_Else (Loc,
4289 Make_Or_Else (Loc,
4290 Left_Opnd =>
4291 Make_And_Then (Loc,
4292 Left_Opnd => Make_Op_Ge (Loc,
4293 Left_Opnd =>
4294 Make_Attribute_Reference (Loc,
4295 Prefix =>
4296 New_Occurrence_Of (Target_Type, Loc),
4297 Attribute_Name => Name_First),
4298 Right_Opnd => Make_Integer_Literal (Loc, Uint_0)),
4300 Right_Opnd =>
4301 Make_Op_Lt (Loc,
4302 Left_Opnd => Duplicate_Subexpr (N),
4303 Right_Opnd =>
4304 Convert_To (Source_Base_Type,
4305 Make_Attribute_Reference (Loc,
4306 Prefix =>
4307 New_Occurrence_Of (Target_Type, Loc),
4308 Attribute_Name => Name_First)))),
4310 Right_Opnd =>
4311 Make_Op_Lt (Loc,
4312 Left_Opnd =>
4313 Make_Attribute_Reference (Loc,
4314 Prefix => New_Occurrence_Of (Target_Type, Loc),
4315 Attribute_Name => Name_Last),
4316 Right_Opnd => Make_Integer_Literal (Loc, Uint_0))),
4318 Right_Opnd =>
4319 Make_Op_Gt (Loc,
4320 Left_Opnd => Duplicate_Subexpr (N),
4321 Right_Opnd =>
4322 Convert_To (Source_Base_Type,
4323 Make_Attribute_Reference (Loc,
4324 Prefix => New_Occurrence_Of (Target_Type, Loc),
4325 Attribute_Name => Name_Last)))),
4327 Reason => Reason),
4328 Suppress => All_Checks);
4330 -- Only remaining possibility is that the source is signed and
4331 -- the target is unsigned
4333 else
4334 pragma Assert (not Is_Unsigned_Type (Source_Base_Type)
4335 and then Is_Unsigned_Type (Target_Base_Type));
4337 -- If the source is signed and the target is unsigned, then
4338 -- we know that the target is not shorter than the source
4339 -- (otherwise the target base type would be in the source
4340 -- base type range).
4342 -- In other words, the unsigned type is either the same size
4343 -- as the target, or it is larger. It cannot be smaller.
4345 -- Clearly we have an error if the source value is negative
4346 -- since no unsigned type can have negative values. If the
4347 -- source type is non-negative, then the check can be done
4348 -- using the target type.
4350 -- Tnn : constant Target_Base_Type (N) := Target_Type;
4352 -- [constraint_error
4353 -- when N < 0 or else Tnn not in Target_Type];
4355 -- We turn off all checks for the conversion of N to the
4356 -- target base type, since we generate the explicit check
4357 -- to ensure that the value is non-negative
4359 declare
4360 Tnn : constant Entity_Id :=
4361 Make_Defining_Identifier (Loc,
4362 Chars => New_Internal_Name ('T'));
4364 begin
4365 Insert_Actions (N, New_List (
4366 Make_Object_Declaration (Loc,
4367 Defining_Identifier => Tnn,
4368 Object_Definition =>
4369 New_Occurrence_Of (Target_Base_Type, Loc),
4370 Constant_Present => True,
4371 Expression =>
4372 Make_Type_Conversion (Loc,
4373 Subtype_Mark =>
4374 New_Occurrence_Of (Target_Base_Type, Loc),
4375 Expression => Duplicate_Subexpr (N))),
4377 Make_Raise_Constraint_Error (Loc,
4378 Condition =>
4379 Make_Or_Else (Loc,
4380 Left_Opnd =>
4381 Make_Op_Lt (Loc,
4382 Left_Opnd => Duplicate_Subexpr (N),
4383 Right_Opnd => Make_Integer_Literal (Loc, Uint_0)),
4385 Right_Opnd =>
4386 Make_Not_In (Loc,
4387 Left_Opnd => New_Occurrence_Of (Tnn, Loc),
4388 Right_Opnd =>
4389 New_Occurrence_Of (Target_Type, Loc))),
4391 Reason => Reason)),
4392 Suppress => All_Checks);
4394 -- Set the Etype explicitly, because Insert_Actions may
4395 -- have placed the declaration in the freeze list for an
4396 -- enclosing construct, and thus it is not analyzed yet.
4398 Set_Etype (Tnn, Target_Base_Type);
4399 Rewrite (N, New_Occurrence_Of (Tnn, Loc));
4400 end;
4401 end if;
4402 end if;
4403 end Generate_Range_Check;
4405 ---------------------
4406 -- Get_Discriminal --
4407 ---------------------
4409 function Get_Discriminal (E : Entity_Id; Bound : Node_Id) return Node_Id is
4410 Loc : constant Source_Ptr := Sloc (E);
4411 D : Entity_Id;
4412 Sc : Entity_Id;
4414 begin
4415 -- The entity E is the type of a private component of the protected
4416 -- type, or the type of a renaming of that component within a protected
4417 -- operation of that type.
4419 Sc := Scope (E);
4421 if Ekind (Sc) /= E_Protected_Type then
4422 Sc := Scope (Sc);
4424 if Ekind (Sc) /= E_Protected_Type then
4425 return Bound;
4426 end if;
4427 end if;
4429 D := First_Discriminant (Sc);
4431 while Present (D)
4432 and then Chars (D) /= Chars (Bound)
4433 loop
4434 Next_Discriminant (D);
4435 end loop;
4437 return New_Occurrence_Of (Discriminal (D), Loc);
4438 end Get_Discriminal;
4440 ------------------
4441 -- Guard_Access --
4442 ------------------
4444 function Guard_Access
4445 (Cond : Node_Id;
4446 Loc : Source_Ptr;
4447 Ck_Node : Node_Id) return Node_Id
4449 begin
4450 if Nkind (Cond) = N_Or_Else then
4451 Set_Paren_Count (Cond, 1);
4452 end if;
4454 if Nkind (Ck_Node) = N_Allocator then
4455 return Cond;
4456 else
4457 return
4458 Make_And_Then (Loc,
4459 Left_Opnd =>
4460 Make_Op_Ne (Loc,
4461 Left_Opnd => Duplicate_Subexpr_No_Checks (Ck_Node),
4462 Right_Opnd => Make_Null (Loc)),
4463 Right_Opnd => Cond);
4464 end if;
4465 end Guard_Access;
4467 -----------------------------
4468 -- Index_Checks_Suppressed --
4469 -----------------------------
4471 function Index_Checks_Suppressed (E : Entity_Id) return Boolean is
4472 begin
4473 if Present (E) and then Checks_May_Be_Suppressed (E) then
4474 return Is_Check_Suppressed (E, Index_Check);
4475 else
4476 return Scope_Suppress (Index_Check);
4477 end if;
4478 end Index_Checks_Suppressed;
4480 ----------------
4481 -- Initialize --
4482 ----------------
4484 procedure Initialize is
4485 begin
4486 for J in Determine_Range_Cache_N'Range loop
4487 Determine_Range_Cache_N (J) := Empty;
4488 end loop;
4489 end Initialize;
4491 -------------------------
4492 -- Insert_Range_Checks --
4493 -------------------------
4495 procedure Insert_Range_Checks
4496 (Checks : Check_Result;
4497 Node : Node_Id;
4498 Suppress_Typ : Entity_Id;
4499 Static_Sloc : Source_Ptr := No_Location;
4500 Flag_Node : Node_Id := Empty;
4501 Do_Before : Boolean := False)
4503 Internal_Flag_Node : Node_Id := Flag_Node;
4504 Internal_Static_Sloc : Source_Ptr := Static_Sloc;
4506 Check_Node : Node_Id;
4507 Checks_On : constant Boolean :=
4508 (not Index_Checks_Suppressed (Suppress_Typ))
4509 or else
4510 (not Range_Checks_Suppressed (Suppress_Typ));
4512 begin
4513 -- For now we just return if Checks_On is false, however this should
4514 -- be enhanced to check for an always True value in the condition
4515 -- and to generate a compilation warning???
4517 if not Expander_Active or else not Checks_On then
4518 return;
4519 end if;
4521 if Static_Sloc = No_Location then
4522 Internal_Static_Sloc := Sloc (Node);
4523 end if;
4525 if No (Flag_Node) then
4526 Internal_Flag_Node := Node;
4527 end if;
4529 for J in 1 .. 2 loop
4530 exit when No (Checks (J));
4532 if Nkind (Checks (J)) = N_Raise_Constraint_Error
4533 and then Present (Condition (Checks (J)))
4534 then
4535 if not Has_Dynamic_Range_Check (Internal_Flag_Node) then
4536 Check_Node := Checks (J);
4537 Mark_Rewrite_Insertion (Check_Node);
4539 if Do_Before then
4540 Insert_Before_And_Analyze (Node, Check_Node);
4541 else
4542 Insert_After_And_Analyze (Node, Check_Node);
4543 end if;
4545 Set_Has_Dynamic_Range_Check (Internal_Flag_Node);
4546 end if;
4548 else
4549 Check_Node :=
4550 Make_Raise_Constraint_Error (Internal_Static_Sloc,
4551 Reason => CE_Range_Check_Failed);
4552 Mark_Rewrite_Insertion (Check_Node);
4554 if Do_Before then
4555 Insert_Before_And_Analyze (Node, Check_Node);
4556 else
4557 Insert_After_And_Analyze (Node, Check_Node);
4558 end if;
4559 end if;
4560 end loop;
4561 end Insert_Range_Checks;
4563 ------------------------
4564 -- Insert_Valid_Check --
4565 ------------------------
4567 procedure Insert_Valid_Check (Expr : Node_Id) is
4568 Loc : constant Source_Ptr := Sloc (Expr);
4569 Exp : Node_Id;
4571 begin
4572 -- Do not insert if checks off, or if not checking validity
4574 if Range_Checks_Suppressed (Etype (Expr))
4575 or else (not Validity_Checks_On)
4576 then
4577 return;
4578 end if;
4580 -- If we have a checked conversion, then validity check applies to
4581 -- the expression inside the conversion, not the result, since if
4582 -- the expression inside is valid, then so is the conversion result.
4584 Exp := Expr;
4585 while Nkind (Exp) = N_Type_Conversion loop
4586 Exp := Expression (Exp);
4587 end loop;
4589 -- Insert the validity check. Note that we do this with validity
4590 -- checks turned off, to avoid recursion, we do not want validity
4591 -- checks on the validity checking code itself!
4593 Validity_Checks_On := False;
4594 Insert_Action
4595 (Expr,
4596 Make_Raise_Constraint_Error (Loc,
4597 Condition =>
4598 Make_Op_Not (Loc,
4599 Right_Opnd =>
4600 Make_Attribute_Reference (Loc,
4601 Prefix =>
4602 Duplicate_Subexpr_No_Checks (Exp, Name_Req => True),
4603 Attribute_Name => Name_Valid)),
4604 Reason => CE_Invalid_Data),
4605 Suppress => All_Checks);
4606 Validity_Checks_On := True;
4607 end Insert_Valid_Check;
4609 ----------------------------------
4610 -- Install_Null_Excluding_Check --
4611 ----------------------------------
4613 procedure Install_Null_Excluding_Check (N : Node_Id) is
4614 Loc : constant Source_Ptr := Sloc (N);
4615 Etyp : constant Entity_Id := Etype (N);
4617 begin
4618 pragma Assert (Is_Access_Type (Etyp));
4620 -- Don't need access check if: 1) we are analyzing a generic, 2) it is
4621 -- known to be non-null, or 3) the check was suppressed on the type
4623 if Inside_A_Generic
4624 or else Access_Checks_Suppressed (Etyp)
4625 then
4626 return;
4628 -- Otherwise install access check
4630 else
4631 Insert_Action (N,
4632 Make_Raise_Constraint_Error (Loc,
4633 Condition =>
4634 Make_Op_Eq (Loc,
4635 Left_Opnd => Duplicate_Subexpr_Move_Checks (N),
4636 Right_Opnd => Make_Null (Loc)),
4637 Reason => CE_Access_Check_Failed));
4638 end if;
4639 end Install_Null_Excluding_Check;
4641 --------------------------
4642 -- Install_Static_Check --
4643 --------------------------
4645 procedure Install_Static_Check (R_Cno : Node_Id; Loc : Source_Ptr) is
4646 Stat : constant Boolean := Is_Static_Expression (R_Cno);
4647 Typ : constant Entity_Id := Etype (R_Cno);
4649 begin
4650 Rewrite (R_Cno,
4651 Make_Raise_Constraint_Error (Loc,
4652 Reason => CE_Range_Check_Failed));
4653 Set_Analyzed (R_Cno);
4654 Set_Etype (R_Cno, Typ);
4655 Set_Raises_Constraint_Error (R_Cno);
4656 Set_Is_Static_Expression (R_Cno, Stat);
4657 end Install_Static_Check;
4659 ---------------------
4660 -- Kill_All_Checks --
4661 ---------------------
4663 procedure Kill_All_Checks is
4664 begin
4665 if Debug_Flag_CC then
4666 w ("Kill_All_Checks");
4667 end if;
4669 -- We reset the number of saved checks to zero, and also modify
4670 -- all stack entries for statement ranges to indicate that the
4671 -- number of checks at each level is now zero.
4673 Num_Saved_Checks := 0;
4675 for J in 1 .. Saved_Checks_TOS loop
4676 Saved_Checks_Stack (J) := 0;
4677 end loop;
4678 end Kill_All_Checks;
4680 -----------------
4681 -- Kill_Checks --
4682 -----------------
4684 procedure Kill_Checks (V : Entity_Id) is
4685 begin
4686 if Debug_Flag_CC then
4687 w ("Kill_Checks for entity", Int (V));
4688 end if;
4690 for J in 1 .. Num_Saved_Checks loop
4691 if Saved_Checks (J).Entity = V then
4692 if Debug_Flag_CC then
4693 w (" Checks killed for saved check ", J);
4694 end if;
4696 Saved_Checks (J).Killed := True;
4697 end if;
4698 end loop;
4699 end Kill_Checks;
4701 ------------------------------
4702 -- Length_Checks_Suppressed --
4703 ------------------------------
4705 function Length_Checks_Suppressed (E : Entity_Id) return Boolean is
4706 begin
4707 if Present (E) and then Checks_May_Be_Suppressed (E) then
4708 return Is_Check_Suppressed (E, Length_Check);
4709 else
4710 return Scope_Suppress (Length_Check);
4711 end if;
4712 end Length_Checks_Suppressed;
4714 --------------------------------
4715 -- Overflow_Checks_Suppressed --
4716 --------------------------------
4718 function Overflow_Checks_Suppressed (E : Entity_Id) return Boolean is
4719 begin
4720 if Present (E) and then Checks_May_Be_Suppressed (E) then
4721 return Is_Check_Suppressed (E, Overflow_Check);
4722 else
4723 return Scope_Suppress (Overflow_Check);
4724 end if;
4725 end Overflow_Checks_Suppressed;
4727 -----------------
4728 -- Range_Check --
4729 -----------------
4731 function Range_Check
4732 (Ck_Node : Node_Id;
4733 Target_Typ : Entity_Id;
4734 Source_Typ : Entity_Id := Empty;
4735 Warn_Node : Node_Id := Empty) return Check_Result
4737 begin
4738 return Selected_Range_Checks
4739 (Ck_Node, Target_Typ, Source_Typ, Warn_Node);
4740 end Range_Check;
4742 -----------------------------
4743 -- Range_Checks_Suppressed --
4744 -----------------------------
4746 function Range_Checks_Suppressed (E : Entity_Id) return Boolean is
4747 begin
4748 if Present (E) then
4750 -- Note: for now we always suppress range checks on Vax float types,
4751 -- since Gigi does not know how to generate these checks.
4753 if Vax_Float (E) then
4754 return True;
4755 elsif Kill_Range_Checks (E) then
4756 return True;
4757 elsif Checks_May_Be_Suppressed (E) then
4758 return Is_Check_Suppressed (E, Range_Check);
4759 end if;
4760 end if;
4762 return Scope_Suppress (Range_Check);
4763 end Range_Checks_Suppressed;
4765 -------------------
4766 -- Remove_Checks --
4767 -------------------
4769 procedure Remove_Checks (Expr : Node_Id) is
4770 Discard : Traverse_Result;
4771 pragma Warnings (Off, Discard);
4773 function Process (N : Node_Id) return Traverse_Result;
4774 -- Process a single node during the traversal
4776 function Traverse is new Traverse_Func (Process);
4777 -- The traversal function itself
4779 -------------
4780 -- Process --
4781 -------------
4783 function Process (N : Node_Id) return Traverse_Result is
4784 begin
4785 if Nkind (N) not in N_Subexpr then
4786 return Skip;
4787 end if;
4789 Set_Do_Range_Check (N, False);
4791 case Nkind (N) is
4792 when N_And_Then =>
4793 Discard := Traverse (Left_Opnd (N));
4794 return Skip;
4796 when N_Attribute_Reference =>
4797 Set_Do_Overflow_Check (N, False);
4799 when N_Function_Call =>
4800 Set_Do_Tag_Check (N, False);
4802 when N_Op =>
4803 Set_Do_Overflow_Check (N, False);
4805 case Nkind (N) is
4806 when N_Op_Divide =>
4807 Set_Do_Division_Check (N, False);
4809 when N_Op_And =>
4810 Set_Do_Length_Check (N, False);
4812 when N_Op_Mod =>
4813 Set_Do_Division_Check (N, False);
4815 when N_Op_Or =>
4816 Set_Do_Length_Check (N, False);
4818 when N_Op_Rem =>
4819 Set_Do_Division_Check (N, False);
4821 when N_Op_Xor =>
4822 Set_Do_Length_Check (N, False);
4824 when others =>
4825 null;
4826 end case;
4828 when N_Or_Else =>
4829 Discard := Traverse (Left_Opnd (N));
4830 return Skip;
4832 when N_Selected_Component =>
4833 Set_Do_Discriminant_Check (N, False);
4835 when N_Type_Conversion =>
4836 Set_Do_Length_Check (N, False);
4837 Set_Do_Tag_Check (N, False);
4838 Set_Do_Overflow_Check (N, False);
4840 when others =>
4841 null;
4842 end case;
4844 return OK;
4845 end Process;
4847 -- Start of processing for Remove_Checks
4849 begin
4850 Discard := Traverse (Expr);
4851 end Remove_Checks;
4853 ----------------------------
4854 -- Selected_Length_Checks --
4855 ----------------------------
4857 function Selected_Length_Checks
4858 (Ck_Node : Node_Id;
4859 Target_Typ : Entity_Id;
4860 Source_Typ : Entity_Id;
4861 Warn_Node : Node_Id) return Check_Result
4863 Loc : constant Source_Ptr := Sloc (Ck_Node);
4864 S_Typ : Entity_Id;
4865 T_Typ : Entity_Id;
4866 Expr_Actual : Node_Id;
4867 Exptyp : Entity_Id;
4868 Cond : Node_Id := Empty;
4869 Do_Access : Boolean := False;
4870 Wnode : Node_Id := Warn_Node;
4871 Ret_Result : Check_Result := (Empty, Empty);
4872 Num_Checks : Natural := 0;
4874 procedure Add_Check (N : Node_Id);
4875 -- Adds the action given to Ret_Result if N is non-Empty
4877 function Get_E_Length (E : Entity_Id; Indx : Nat) return Node_Id;
4878 function Get_N_Length (N : Node_Id; Indx : Nat) return Node_Id;
4879 -- Comments required ???
4881 function Same_Bounds (L : Node_Id; R : Node_Id) return Boolean;
4882 -- True for equal literals and for nodes that denote the same constant
4883 -- entity, even if its value is not a static constant. This includes the
4884 -- case of a discriminal reference within an init proc. Removes some
4885 -- obviously superfluous checks.
4887 function Length_E_Cond
4888 (Exptyp : Entity_Id;
4889 Typ : Entity_Id;
4890 Indx : Nat) return Node_Id;
4891 -- Returns expression to compute:
4892 -- Typ'Length /= Exptyp'Length
4894 function Length_N_Cond
4895 (Expr : Node_Id;
4896 Typ : Entity_Id;
4897 Indx : Nat) return Node_Id;
4898 -- Returns expression to compute:
4899 -- Typ'Length /= Expr'Length
4901 ---------------
4902 -- Add_Check --
4903 ---------------
4905 procedure Add_Check (N : Node_Id) is
4906 begin
4907 if Present (N) then
4909 -- For now, ignore attempt to place more than 2 checks ???
4911 if Num_Checks = 2 then
4912 return;
4913 end if;
4915 pragma Assert (Num_Checks <= 1);
4916 Num_Checks := Num_Checks + 1;
4917 Ret_Result (Num_Checks) := N;
4918 end if;
4919 end Add_Check;
4921 ------------------
4922 -- Get_E_Length --
4923 ------------------
4925 function Get_E_Length (E : Entity_Id; Indx : Nat) return Node_Id is
4926 Pt : constant Entity_Id := Scope (Scope (E));
4927 N : Node_Id;
4928 E1 : Entity_Id := E;
4930 begin
4931 if Ekind (Scope (E)) = E_Record_Type
4932 and then Has_Discriminants (Scope (E))
4933 then
4934 N := Build_Discriminal_Subtype_Of_Component (E);
4936 if Present (N) then
4937 Insert_Action (Ck_Node, N);
4938 E1 := Defining_Identifier (N);
4939 end if;
4940 end if;
4942 if Ekind (E1) = E_String_Literal_Subtype then
4943 return
4944 Make_Integer_Literal (Loc,
4945 Intval => String_Literal_Length (E1));
4947 elsif Ekind (Pt) = E_Protected_Type
4948 and then Has_Discriminants (Pt)
4949 and then Has_Completion (Pt)
4950 and then not Inside_Init_Proc
4951 then
4953 -- If the type whose length is needed is a private component
4954 -- constrained by a discriminant, we must expand the 'Length
4955 -- attribute into an explicit computation, using the discriminal
4956 -- of the current protected operation. This is because the actual
4957 -- type of the prival is constructed after the protected opera-
4958 -- tion has been fully expanded.
4960 declare
4961 Indx_Type : Node_Id;
4962 Lo : Node_Id;
4963 Hi : Node_Id;
4964 Do_Expand : Boolean := False;
4966 begin
4967 Indx_Type := First_Index (E);
4969 for J in 1 .. Indx - 1 loop
4970 Next_Index (Indx_Type);
4971 end loop;
4973 Get_Index_Bounds (Indx_Type, Lo, Hi);
4975 if Nkind (Lo) = N_Identifier
4976 and then Ekind (Entity (Lo)) = E_In_Parameter
4977 then
4978 Lo := Get_Discriminal (E, Lo);
4979 Do_Expand := True;
4980 end if;
4982 if Nkind (Hi) = N_Identifier
4983 and then Ekind (Entity (Hi)) = E_In_Parameter
4984 then
4985 Hi := Get_Discriminal (E, Hi);
4986 Do_Expand := True;
4987 end if;
4989 if Do_Expand then
4990 if not Is_Entity_Name (Lo) then
4991 Lo := Duplicate_Subexpr_No_Checks (Lo);
4992 end if;
4994 if not Is_Entity_Name (Hi) then
4995 Lo := Duplicate_Subexpr_No_Checks (Hi);
4996 end if;
4998 N :=
4999 Make_Op_Add (Loc,
5000 Left_Opnd =>
5001 Make_Op_Subtract (Loc,
5002 Left_Opnd => Hi,
5003 Right_Opnd => Lo),
5005 Right_Opnd => Make_Integer_Literal (Loc, 1));
5006 return N;
5008 else
5009 N :=
5010 Make_Attribute_Reference (Loc,
5011 Attribute_Name => Name_Length,
5012 Prefix =>
5013 New_Occurrence_Of (E1, Loc));
5015 if Indx > 1 then
5016 Set_Expressions (N, New_List (
5017 Make_Integer_Literal (Loc, Indx)));
5018 end if;
5020 return N;
5021 end if;
5022 end;
5024 else
5025 N :=
5026 Make_Attribute_Reference (Loc,
5027 Attribute_Name => Name_Length,
5028 Prefix =>
5029 New_Occurrence_Of (E1, Loc));
5031 if Indx > 1 then
5032 Set_Expressions (N, New_List (
5033 Make_Integer_Literal (Loc, Indx)));
5034 end if;
5036 return N;
5038 end if;
5039 end Get_E_Length;
5041 ------------------
5042 -- Get_N_Length --
5043 ------------------
5045 function Get_N_Length (N : Node_Id; Indx : Nat) return Node_Id is
5046 begin
5047 return
5048 Make_Attribute_Reference (Loc,
5049 Attribute_Name => Name_Length,
5050 Prefix =>
5051 Duplicate_Subexpr_No_Checks (N, Name_Req => True),
5052 Expressions => New_List (
5053 Make_Integer_Literal (Loc, Indx)));
5055 end Get_N_Length;
5057 -------------------
5058 -- Length_E_Cond --
5059 -------------------
5061 function Length_E_Cond
5062 (Exptyp : Entity_Id;
5063 Typ : Entity_Id;
5064 Indx : Nat) return Node_Id
5066 begin
5067 return
5068 Make_Op_Ne (Loc,
5069 Left_Opnd => Get_E_Length (Typ, Indx),
5070 Right_Opnd => Get_E_Length (Exptyp, Indx));
5072 end Length_E_Cond;
5074 -------------------
5075 -- Length_N_Cond --
5076 -------------------
5078 function Length_N_Cond
5079 (Expr : Node_Id;
5080 Typ : Entity_Id;
5081 Indx : Nat) return Node_Id
5083 begin
5084 return
5085 Make_Op_Ne (Loc,
5086 Left_Opnd => Get_E_Length (Typ, Indx),
5087 Right_Opnd => Get_N_Length (Expr, Indx));
5089 end Length_N_Cond;
5091 function Same_Bounds (L : Node_Id; R : Node_Id) return Boolean is
5092 begin
5093 return
5094 (Nkind (L) = N_Integer_Literal
5095 and then Nkind (R) = N_Integer_Literal
5096 and then Intval (L) = Intval (R))
5098 or else
5099 (Is_Entity_Name (L)
5100 and then Ekind (Entity (L)) = E_Constant
5101 and then ((Is_Entity_Name (R)
5102 and then Entity (L) = Entity (R))
5103 or else
5104 (Nkind (R) = N_Type_Conversion
5105 and then Is_Entity_Name (Expression (R))
5106 and then Entity (L) = Entity (Expression (R)))))
5108 or else
5109 (Is_Entity_Name (R)
5110 and then Ekind (Entity (R)) = E_Constant
5111 and then Nkind (L) = N_Type_Conversion
5112 and then Is_Entity_Name (Expression (L))
5113 and then Entity (R) = Entity (Expression (L)))
5115 or else
5116 (Is_Entity_Name (L)
5117 and then Is_Entity_Name (R)
5118 and then Entity (L) = Entity (R)
5119 and then Ekind (Entity (L)) = E_In_Parameter
5120 and then Inside_Init_Proc);
5121 end Same_Bounds;
5123 -- Start of processing for Selected_Length_Checks
5125 begin
5126 if not Expander_Active then
5127 return Ret_Result;
5128 end if;
5130 if Target_Typ = Any_Type
5131 or else Target_Typ = Any_Composite
5132 or else Raises_Constraint_Error (Ck_Node)
5133 then
5134 return Ret_Result;
5135 end if;
5137 if No (Wnode) then
5138 Wnode := Ck_Node;
5139 end if;
5141 T_Typ := Target_Typ;
5143 if No (Source_Typ) then
5144 S_Typ := Etype (Ck_Node);
5145 else
5146 S_Typ := Source_Typ;
5147 end if;
5149 if S_Typ = Any_Type or else S_Typ = Any_Composite then
5150 return Ret_Result;
5151 end if;
5153 if Is_Access_Type (T_Typ) and then Is_Access_Type (S_Typ) then
5154 S_Typ := Designated_Type (S_Typ);
5155 T_Typ := Designated_Type (T_Typ);
5156 Do_Access := True;
5158 -- A simple optimization
5160 if Nkind (Ck_Node) = N_Null then
5161 return Ret_Result;
5162 end if;
5163 end if;
5165 if Is_Array_Type (T_Typ) and then Is_Array_Type (S_Typ) then
5166 if Is_Constrained (T_Typ) then
5168 -- The checking code to be generated will freeze the
5169 -- corresponding array type. However, we must freeze the
5170 -- type now, so that the freeze node does not appear within
5171 -- the generated condional expression, but ahead of it.
5173 Freeze_Before (Ck_Node, T_Typ);
5175 Expr_Actual := Get_Referenced_Object (Ck_Node);
5176 Exptyp := Get_Actual_Subtype (Expr_Actual);
5178 if Is_Access_Type (Exptyp) then
5179 Exptyp := Designated_Type (Exptyp);
5180 end if;
5182 -- String_Literal case. This needs to be handled specially be-
5183 -- cause no index types are available for string literals. The
5184 -- condition is simply:
5186 -- T_Typ'Length = string-literal-length
5188 if Nkind (Expr_Actual) = N_String_Literal
5189 and then Ekind (Etype (Expr_Actual)) = E_String_Literal_Subtype
5190 then
5191 Cond :=
5192 Make_Op_Ne (Loc,
5193 Left_Opnd => Get_E_Length (T_Typ, 1),
5194 Right_Opnd =>
5195 Make_Integer_Literal (Loc,
5196 Intval =>
5197 String_Literal_Length (Etype (Expr_Actual))));
5199 -- General array case. Here we have a usable actual subtype for
5200 -- the expression, and the condition is built from the two types
5201 -- (Do_Length):
5203 -- T_Typ'Length /= Exptyp'Length or else
5204 -- T_Typ'Length (2) /= Exptyp'Length (2) or else
5205 -- T_Typ'Length (3) /= Exptyp'Length (3) or else
5206 -- ...
5208 elsif Is_Constrained (Exptyp) then
5209 declare
5210 Ndims : constant Nat := Number_Dimensions (T_Typ);
5212 L_Index : Node_Id;
5213 R_Index : Node_Id;
5214 L_Low : Node_Id;
5215 L_High : Node_Id;
5216 R_Low : Node_Id;
5217 R_High : Node_Id;
5218 L_Length : Uint;
5219 R_Length : Uint;
5220 Ref_Node : Node_Id;
5222 begin
5224 -- At the library level, we need to ensure that the
5225 -- type of the object is elaborated before the check
5226 -- itself is emitted. This is only done if the object
5227 -- is in the current compilation unit, otherwise the
5228 -- type is frozen and elaborated in its unit.
5230 if Is_Itype (Exptyp)
5231 and then
5232 Ekind (Cunit_Entity (Current_Sem_Unit)) = E_Package
5233 and then
5234 not In_Package_Body (Cunit_Entity (Current_Sem_Unit))
5235 and then In_Open_Scopes (Scope (Exptyp))
5236 then
5237 Ref_Node := Make_Itype_Reference (Sloc (Ck_Node));
5238 Set_Itype (Ref_Node, Exptyp);
5239 Insert_Action (Ck_Node, Ref_Node);
5240 end if;
5242 L_Index := First_Index (T_Typ);
5243 R_Index := First_Index (Exptyp);
5245 for Indx in 1 .. Ndims loop
5246 if not (Nkind (L_Index) = N_Raise_Constraint_Error
5247 or else
5248 Nkind (R_Index) = N_Raise_Constraint_Error)
5249 then
5250 Get_Index_Bounds (L_Index, L_Low, L_High);
5251 Get_Index_Bounds (R_Index, R_Low, R_High);
5253 -- Deal with compile time length check. Note that we
5254 -- skip this in the access case, because the access
5255 -- value may be null, so we cannot know statically.
5257 if not Do_Access
5258 and then Compile_Time_Known_Value (L_Low)
5259 and then Compile_Time_Known_Value (L_High)
5260 and then Compile_Time_Known_Value (R_Low)
5261 and then Compile_Time_Known_Value (R_High)
5262 then
5263 if Expr_Value (L_High) >= Expr_Value (L_Low) then
5264 L_Length := Expr_Value (L_High) -
5265 Expr_Value (L_Low) + 1;
5266 else
5267 L_Length := UI_From_Int (0);
5268 end if;
5270 if Expr_Value (R_High) >= Expr_Value (R_Low) then
5271 R_Length := Expr_Value (R_High) -
5272 Expr_Value (R_Low) + 1;
5273 else
5274 R_Length := UI_From_Int (0);
5275 end if;
5277 if L_Length > R_Length then
5278 Add_Check
5279 (Compile_Time_Constraint_Error
5280 (Wnode, "too few elements for}?", T_Typ));
5282 elsif L_Length < R_Length then
5283 Add_Check
5284 (Compile_Time_Constraint_Error
5285 (Wnode, "too many elements for}?", T_Typ));
5286 end if;
5288 -- The comparison for an individual index subtype
5289 -- is omitted if the corresponding index subtypes
5290 -- statically match, since the result is known to
5291 -- be true. Note that this test is worth while even
5292 -- though we do static evaluation, because non-static
5293 -- subtypes can statically match.
5295 elsif not
5296 Subtypes_Statically_Match
5297 (Etype (L_Index), Etype (R_Index))
5299 and then not
5300 (Same_Bounds (L_Low, R_Low)
5301 and then Same_Bounds (L_High, R_High))
5302 then
5303 Evolve_Or_Else
5304 (Cond, Length_E_Cond (Exptyp, T_Typ, Indx));
5305 end if;
5307 Next (L_Index);
5308 Next (R_Index);
5309 end if;
5310 end loop;
5311 end;
5313 -- Handle cases where we do not get a usable actual subtype that
5314 -- is constrained. This happens for example in the function call
5315 -- and explicit dereference cases. In these cases, we have to get
5316 -- the length or range from the expression itself, making sure we
5317 -- do not evaluate it more than once.
5319 -- Here Ck_Node is the original expression, or more properly the
5320 -- result of applying Duplicate_Expr to the original tree,
5321 -- forcing the result to be a name.
5323 else
5324 declare
5325 Ndims : constant Nat := Number_Dimensions (T_Typ);
5327 begin
5328 -- Build the condition for the explicit dereference case
5330 for Indx in 1 .. Ndims loop
5331 Evolve_Or_Else
5332 (Cond, Length_N_Cond (Ck_Node, T_Typ, Indx));
5333 end loop;
5334 end;
5335 end if;
5336 end if;
5337 end if;
5339 -- Construct the test and insert into the tree
5341 if Present (Cond) then
5342 if Do_Access then
5343 Cond := Guard_Access (Cond, Loc, Ck_Node);
5344 end if;
5346 Add_Check
5347 (Make_Raise_Constraint_Error (Loc,
5348 Condition => Cond,
5349 Reason => CE_Length_Check_Failed));
5350 end if;
5352 return Ret_Result;
5353 end Selected_Length_Checks;
5355 ---------------------------
5356 -- Selected_Range_Checks --
5357 ---------------------------
5359 function Selected_Range_Checks
5360 (Ck_Node : Node_Id;
5361 Target_Typ : Entity_Id;
5362 Source_Typ : Entity_Id;
5363 Warn_Node : Node_Id) return Check_Result
5365 Loc : constant Source_Ptr := Sloc (Ck_Node);
5366 S_Typ : Entity_Id;
5367 T_Typ : Entity_Id;
5368 Expr_Actual : Node_Id;
5369 Exptyp : Entity_Id;
5370 Cond : Node_Id := Empty;
5371 Do_Access : Boolean := False;
5372 Wnode : Node_Id := Warn_Node;
5373 Ret_Result : Check_Result := (Empty, Empty);
5374 Num_Checks : Integer := 0;
5376 procedure Add_Check (N : Node_Id);
5377 -- Adds the action given to Ret_Result if N is non-Empty
5379 function Discrete_Range_Cond
5380 (Expr : Node_Id;
5381 Typ : Entity_Id) return Node_Id;
5382 -- Returns expression to compute:
5383 -- Low_Bound (Expr) < Typ'First
5384 -- or else
5385 -- High_Bound (Expr) > Typ'Last
5387 function Discrete_Expr_Cond
5388 (Expr : Node_Id;
5389 Typ : Entity_Id) return Node_Id;
5390 -- Returns expression to compute:
5391 -- Expr < Typ'First
5392 -- or else
5393 -- Expr > Typ'Last
5395 function Get_E_First_Or_Last
5396 (E : Entity_Id;
5397 Indx : Nat;
5398 Nam : Name_Id) return Node_Id;
5399 -- Returns expression to compute:
5400 -- E'First or E'Last
5402 function Get_N_First (N : Node_Id; Indx : Nat) return Node_Id;
5403 function Get_N_Last (N : Node_Id; Indx : Nat) return Node_Id;
5404 -- Returns expression to compute:
5405 -- N'First or N'Last using Duplicate_Subexpr_No_Checks
5407 function Range_E_Cond
5408 (Exptyp : Entity_Id;
5409 Typ : Entity_Id;
5410 Indx : Nat)
5411 return Node_Id;
5412 -- Returns expression to compute:
5413 -- Exptyp'First < Typ'First or else Exptyp'Last > Typ'Last
5415 function Range_Equal_E_Cond
5416 (Exptyp : Entity_Id;
5417 Typ : Entity_Id;
5418 Indx : Nat) return Node_Id;
5419 -- Returns expression to compute:
5420 -- Exptyp'First /= Typ'First or else Exptyp'Last /= Typ'Last
5422 function Range_N_Cond
5423 (Expr : Node_Id;
5424 Typ : Entity_Id;
5425 Indx : Nat) return Node_Id;
5426 -- Return expression to compute:
5427 -- Expr'First < Typ'First or else Expr'Last > Typ'Last
5429 ---------------
5430 -- Add_Check --
5431 ---------------
5433 procedure Add_Check (N : Node_Id) is
5434 begin
5435 if Present (N) then
5437 -- For now, ignore attempt to place more than 2 checks ???
5439 if Num_Checks = 2 then
5440 return;
5441 end if;
5443 pragma Assert (Num_Checks <= 1);
5444 Num_Checks := Num_Checks + 1;
5445 Ret_Result (Num_Checks) := N;
5446 end if;
5447 end Add_Check;
5449 -------------------------
5450 -- Discrete_Expr_Cond --
5451 -------------------------
5453 function Discrete_Expr_Cond
5454 (Expr : Node_Id;
5455 Typ : Entity_Id) return Node_Id
5457 begin
5458 return
5459 Make_Or_Else (Loc,
5460 Left_Opnd =>
5461 Make_Op_Lt (Loc,
5462 Left_Opnd =>
5463 Convert_To (Base_Type (Typ),
5464 Duplicate_Subexpr_No_Checks (Expr)),
5465 Right_Opnd =>
5466 Convert_To (Base_Type (Typ),
5467 Get_E_First_Or_Last (Typ, 0, Name_First))),
5469 Right_Opnd =>
5470 Make_Op_Gt (Loc,
5471 Left_Opnd =>
5472 Convert_To (Base_Type (Typ),
5473 Duplicate_Subexpr_No_Checks (Expr)),
5474 Right_Opnd =>
5475 Convert_To
5476 (Base_Type (Typ),
5477 Get_E_First_Or_Last (Typ, 0, Name_Last))));
5478 end Discrete_Expr_Cond;
5480 -------------------------
5481 -- Discrete_Range_Cond --
5482 -------------------------
5484 function Discrete_Range_Cond
5485 (Expr : Node_Id;
5486 Typ : Entity_Id) return Node_Id
5488 LB : Node_Id := Low_Bound (Expr);
5489 HB : Node_Id := High_Bound (Expr);
5491 Left_Opnd : Node_Id;
5492 Right_Opnd : Node_Id;
5494 begin
5495 if Nkind (LB) = N_Identifier
5496 and then Ekind (Entity (LB)) = E_Discriminant then
5497 LB := New_Occurrence_Of (Discriminal (Entity (LB)), Loc);
5498 end if;
5500 if Nkind (HB) = N_Identifier
5501 and then Ekind (Entity (HB)) = E_Discriminant then
5502 HB := New_Occurrence_Of (Discriminal (Entity (HB)), Loc);
5503 end if;
5505 Left_Opnd :=
5506 Make_Op_Lt (Loc,
5507 Left_Opnd =>
5508 Convert_To
5509 (Base_Type (Typ), Duplicate_Subexpr_No_Checks (LB)),
5511 Right_Opnd =>
5512 Convert_To
5513 (Base_Type (Typ), Get_E_First_Or_Last (Typ, 0, Name_First)));
5515 if Base_Type (Typ) = Typ then
5516 return Left_Opnd;
5518 elsif Compile_Time_Known_Value (High_Bound (Scalar_Range (Typ)))
5519 and then
5520 Compile_Time_Known_Value (High_Bound (Scalar_Range
5521 (Base_Type (Typ))))
5522 then
5523 if Is_Floating_Point_Type (Typ) then
5524 if Expr_Value_R (High_Bound (Scalar_Range (Typ))) =
5525 Expr_Value_R (High_Bound (Scalar_Range (Base_Type (Typ))))
5526 then
5527 return Left_Opnd;
5528 end if;
5530 else
5531 if Expr_Value (High_Bound (Scalar_Range (Typ))) =
5532 Expr_Value (High_Bound (Scalar_Range (Base_Type (Typ))))
5533 then
5534 return Left_Opnd;
5535 end if;
5536 end if;
5537 end if;
5539 Right_Opnd :=
5540 Make_Op_Gt (Loc,
5541 Left_Opnd =>
5542 Convert_To
5543 (Base_Type (Typ), Duplicate_Subexpr_No_Checks (HB)),
5545 Right_Opnd =>
5546 Convert_To
5547 (Base_Type (Typ),
5548 Get_E_First_Or_Last (Typ, 0, Name_Last)));
5550 return Make_Or_Else (Loc, Left_Opnd, Right_Opnd);
5551 end Discrete_Range_Cond;
5553 -------------------------
5554 -- Get_E_First_Or_Last --
5555 -------------------------
5557 function Get_E_First_Or_Last
5558 (E : Entity_Id;
5559 Indx : Nat;
5560 Nam : Name_Id) return Node_Id
5562 N : Node_Id;
5563 LB : Node_Id;
5564 HB : Node_Id;
5565 Bound : Node_Id;
5567 begin
5568 if Is_Array_Type (E) then
5569 N := First_Index (E);
5571 for J in 2 .. Indx loop
5572 Next_Index (N);
5573 end loop;
5575 else
5576 N := Scalar_Range (E);
5577 end if;
5579 if Nkind (N) = N_Subtype_Indication then
5580 LB := Low_Bound (Range_Expression (Constraint (N)));
5581 HB := High_Bound (Range_Expression (Constraint (N)));
5583 elsif Is_Entity_Name (N) then
5584 LB := Type_Low_Bound (Etype (N));
5585 HB := Type_High_Bound (Etype (N));
5587 else
5588 LB := Low_Bound (N);
5589 HB := High_Bound (N);
5590 end if;
5592 if Nam = Name_First then
5593 Bound := LB;
5594 else
5595 Bound := HB;
5596 end if;
5598 if Nkind (Bound) = N_Identifier
5599 and then Ekind (Entity (Bound)) = E_Discriminant
5600 then
5601 -- If this is a task discriminant, and we are the body, we must
5602 -- retrieve the corresponding body discriminal. This is another
5603 -- consequence of the early creation of discriminals, and the
5604 -- need to generate constraint checks before their declarations
5605 -- are made visible.
5607 if Is_Concurrent_Record_Type (Scope (Entity (Bound))) then
5608 declare
5609 Tsk : constant Entity_Id :=
5610 Corresponding_Concurrent_Type
5611 (Scope (Entity (Bound)));
5612 Disc : Entity_Id;
5614 begin
5615 if In_Open_Scopes (Tsk)
5616 and then Has_Completion (Tsk)
5617 then
5618 -- Find discriminant of original task, and use its
5619 -- current discriminal, which is the renaming within
5620 -- the task body.
5622 Disc := First_Discriminant (Tsk);
5623 while Present (Disc) loop
5624 if Chars (Disc) = Chars (Entity (Bound)) then
5625 Set_Scope (Discriminal (Disc), Tsk);
5626 return New_Occurrence_Of (Discriminal (Disc), Loc);
5627 end if;
5629 Next_Discriminant (Disc);
5630 end loop;
5632 -- That loop should always succeed in finding a matching
5633 -- entry and returning. Fatal error if not.
5635 raise Program_Error;
5637 else
5638 return
5639 New_Occurrence_Of (Discriminal (Entity (Bound)), Loc);
5640 end if;
5641 end;
5642 else
5643 return New_Occurrence_Of (Discriminal (Entity (Bound)), Loc);
5644 end if;
5646 elsif Nkind (Bound) = N_Identifier
5647 and then Ekind (Entity (Bound)) = E_In_Parameter
5648 and then not Inside_Init_Proc
5649 then
5650 return Get_Discriminal (E, Bound);
5652 elsif Nkind (Bound) = N_Integer_Literal then
5653 return Make_Integer_Literal (Loc, Intval (Bound));
5655 else
5656 return Duplicate_Subexpr_No_Checks (Bound);
5657 end if;
5658 end Get_E_First_Or_Last;
5660 -----------------
5661 -- Get_N_First --
5662 -----------------
5664 function Get_N_First (N : Node_Id; Indx : Nat) return Node_Id is
5665 begin
5666 return
5667 Make_Attribute_Reference (Loc,
5668 Attribute_Name => Name_First,
5669 Prefix =>
5670 Duplicate_Subexpr_No_Checks (N, Name_Req => True),
5671 Expressions => New_List (
5672 Make_Integer_Literal (Loc, Indx)));
5673 end Get_N_First;
5675 ----------------
5676 -- Get_N_Last --
5677 ----------------
5679 function Get_N_Last (N : Node_Id; Indx : Nat) return Node_Id is
5680 begin
5681 return
5682 Make_Attribute_Reference (Loc,
5683 Attribute_Name => Name_Last,
5684 Prefix =>
5685 Duplicate_Subexpr_No_Checks (N, Name_Req => True),
5686 Expressions => New_List (
5687 Make_Integer_Literal (Loc, Indx)));
5688 end Get_N_Last;
5690 ------------------
5691 -- Range_E_Cond --
5692 ------------------
5694 function Range_E_Cond
5695 (Exptyp : Entity_Id;
5696 Typ : Entity_Id;
5697 Indx : Nat) return Node_Id
5699 begin
5700 return
5701 Make_Or_Else (Loc,
5702 Left_Opnd =>
5703 Make_Op_Lt (Loc,
5704 Left_Opnd => Get_E_First_Or_Last (Exptyp, Indx, Name_First),
5705 Right_Opnd => Get_E_First_Or_Last (Typ, Indx, Name_First)),
5707 Right_Opnd =>
5708 Make_Op_Gt (Loc,
5709 Left_Opnd => Get_E_First_Or_Last (Exptyp, Indx, Name_Last),
5710 Right_Opnd => Get_E_First_Or_Last (Typ, Indx, Name_Last)));
5712 end Range_E_Cond;
5714 ------------------------
5715 -- Range_Equal_E_Cond --
5716 ------------------------
5718 function Range_Equal_E_Cond
5719 (Exptyp : Entity_Id;
5720 Typ : Entity_Id;
5721 Indx : Nat) return Node_Id
5723 begin
5724 return
5725 Make_Or_Else (Loc,
5726 Left_Opnd =>
5727 Make_Op_Ne (Loc,
5728 Left_Opnd => Get_E_First_Or_Last (Exptyp, Indx, Name_First),
5729 Right_Opnd => Get_E_First_Or_Last (Typ, Indx, Name_First)),
5730 Right_Opnd =>
5731 Make_Op_Ne (Loc,
5732 Left_Opnd => Get_E_First_Or_Last (Exptyp, Indx, Name_Last),
5733 Right_Opnd => Get_E_First_Or_Last (Typ, Indx, Name_Last)));
5734 end Range_Equal_E_Cond;
5736 ------------------
5737 -- Range_N_Cond --
5738 ------------------
5740 function Range_N_Cond
5741 (Expr : Node_Id;
5742 Typ : Entity_Id;
5743 Indx : Nat) return Node_Id
5745 begin
5746 return
5747 Make_Or_Else (Loc,
5748 Left_Opnd =>
5749 Make_Op_Lt (Loc,
5750 Left_Opnd => Get_N_First (Expr, Indx),
5751 Right_Opnd => Get_E_First_Or_Last (Typ, Indx, Name_First)),
5753 Right_Opnd =>
5754 Make_Op_Gt (Loc,
5755 Left_Opnd => Get_N_Last (Expr, Indx),
5756 Right_Opnd => Get_E_First_Or_Last (Typ, Indx, Name_Last)));
5757 end Range_N_Cond;
5759 -- Start of processing for Selected_Range_Checks
5761 begin
5762 if not Expander_Active then
5763 return Ret_Result;
5764 end if;
5766 if Target_Typ = Any_Type
5767 or else Target_Typ = Any_Composite
5768 or else Raises_Constraint_Error (Ck_Node)
5769 then
5770 return Ret_Result;
5771 end if;
5773 if No (Wnode) then
5774 Wnode := Ck_Node;
5775 end if;
5777 T_Typ := Target_Typ;
5779 if No (Source_Typ) then
5780 S_Typ := Etype (Ck_Node);
5781 else
5782 S_Typ := Source_Typ;
5783 end if;
5785 if S_Typ = Any_Type or else S_Typ = Any_Composite then
5786 return Ret_Result;
5787 end if;
5789 -- The order of evaluating T_Typ before S_Typ seems to be critical
5790 -- because S_Typ can be derived from Etype (Ck_Node), if it's not passed
5791 -- in, and since Node can be an N_Range node, it might be invalid.
5792 -- Should there be an assert check somewhere for taking the Etype of
5793 -- an N_Range node ???
5795 if Is_Access_Type (T_Typ) and then Is_Access_Type (S_Typ) then
5796 S_Typ := Designated_Type (S_Typ);
5797 T_Typ := Designated_Type (T_Typ);
5798 Do_Access := True;
5800 -- A simple optimization
5802 if Nkind (Ck_Node) = N_Null then
5803 return Ret_Result;
5804 end if;
5805 end if;
5807 -- For an N_Range Node, check for a null range and then if not
5808 -- null generate a range check action.
5810 if Nkind (Ck_Node) = N_Range then
5812 -- There's no point in checking a range against itself
5814 if Ck_Node = Scalar_Range (T_Typ) then
5815 return Ret_Result;
5816 end if;
5818 declare
5819 T_LB : constant Node_Id := Type_Low_Bound (T_Typ);
5820 T_HB : constant Node_Id := Type_High_Bound (T_Typ);
5821 LB : constant Node_Id := Low_Bound (Ck_Node);
5822 HB : constant Node_Id := High_Bound (Ck_Node);
5823 Null_Range : Boolean;
5825 Out_Of_Range_L : Boolean;
5826 Out_Of_Range_H : Boolean;
5828 begin
5829 -- Check for case where everything is static and we can
5830 -- do the check at compile time. This is skipped if we
5831 -- have an access type, since the access value may be null.
5833 -- ??? This code can be improved since you only need to know
5834 -- that the two respective bounds (LB & T_LB or HB & T_HB)
5835 -- are known at compile time to emit pertinent messages.
5837 if Compile_Time_Known_Value (LB)
5838 and then Compile_Time_Known_Value (HB)
5839 and then Compile_Time_Known_Value (T_LB)
5840 and then Compile_Time_Known_Value (T_HB)
5841 and then not Do_Access
5842 then
5843 -- Floating-point case
5845 if Is_Floating_Point_Type (S_Typ) then
5846 Null_Range := Expr_Value_R (HB) < Expr_Value_R (LB);
5847 Out_Of_Range_L :=
5848 (Expr_Value_R (LB) < Expr_Value_R (T_LB))
5849 or else
5850 (Expr_Value_R (LB) > Expr_Value_R (T_HB));
5852 Out_Of_Range_H :=
5853 (Expr_Value_R (HB) > Expr_Value_R (T_HB))
5854 or else
5855 (Expr_Value_R (HB) < Expr_Value_R (T_LB));
5857 -- Fixed or discrete type case
5859 else
5860 Null_Range := Expr_Value (HB) < Expr_Value (LB);
5861 Out_Of_Range_L :=
5862 (Expr_Value (LB) < Expr_Value (T_LB))
5863 or else
5864 (Expr_Value (LB) > Expr_Value (T_HB));
5866 Out_Of_Range_H :=
5867 (Expr_Value (HB) > Expr_Value (T_HB))
5868 or else
5869 (Expr_Value (HB) < Expr_Value (T_LB));
5870 end if;
5872 if not Null_Range then
5873 if Out_Of_Range_L then
5874 if No (Warn_Node) then
5875 Add_Check
5876 (Compile_Time_Constraint_Error
5877 (Low_Bound (Ck_Node),
5878 "static value out of range of}?", T_Typ));
5880 else
5881 Add_Check
5882 (Compile_Time_Constraint_Error
5883 (Wnode,
5884 "static range out of bounds of}?", T_Typ));
5885 end if;
5886 end if;
5888 if Out_Of_Range_H then
5889 if No (Warn_Node) then
5890 Add_Check
5891 (Compile_Time_Constraint_Error
5892 (High_Bound (Ck_Node),
5893 "static value out of range of}?", T_Typ));
5895 else
5896 Add_Check
5897 (Compile_Time_Constraint_Error
5898 (Wnode,
5899 "static range out of bounds of}?", T_Typ));
5900 end if;
5901 end if;
5903 end if;
5905 else
5906 declare
5907 LB : Node_Id := Low_Bound (Ck_Node);
5908 HB : Node_Id := High_Bound (Ck_Node);
5910 begin
5912 -- If either bound is a discriminant and we are within
5913 -- the record declaration, it is a use of the discriminant
5914 -- in a constraint of a component, and nothing can be
5915 -- checked here. The check will be emitted within the
5916 -- init proc. Before then, the discriminal has no real
5917 -- meaning.
5919 if Nkind (LB) = N_Identifier
5920 and then Ekind (Entity (LB)) = E_Discriminant
5921 then
5922 if Current_Scope = Scope (Entity (LB)) then
5923 return Ret_Result;
5924 else
5925 LB :=
5926 New_Occurrence_Of (Discriminal (Entity (LB)), Loc);
5927 end if;
5928 end if;
5930 if Nkind (HB) = N_Identifier
5931 and then Ekind (Entity (HB)) = E_Discriminant
5932 then
5933 if Current_Scope = Scope (Entity (HB)) then
5934 return Ret_Result;
5935 else
5936 HB :=
5937 New_Occurrence_Of (Discriminal (Entity (HB)), Loc);
5938 end if;
5939 end if;
5941 Cond := Discrete_Range_Cond (Ck_Node, T_Typ);
5942 Set_Paren_Count (Cond, 1);
5944 Cond :=
5945 Make_And_Then (Loc,
5946 Left_Opnd =>
5947 Make_Op_Ge (Loc,
5948 Left_Opnd => Duplicate_Subexpr_No_Checks (HB),
5949 Right_Opnd => Duplicate_Subexpr_No_Checks (LB)),
5950 Right_Opnd => Cond);
5951 end;
5953 end if;
5954 end;
5956 elsif Is_Scalar_Type (S_Typ) then
5958 -- This somewhat duplicates what Apply_Scalar_Range_Check does,
5959 -- except the above simply sets a flag in the node and lets
5960 -- gigi generate the check base on the Etype of the expression.
5961 -- Sometimes, however we want to do a dynamic check against an
5962 -- arbitrary target type, so we do that here.
5964 if Ekind (Base_Type (S_Typ)) /= Ekind (Base_Type (T_Typ)) then
5965 Cond := Discrete_Expr_Cond (Ck_Node, T_Typ);
5967 -- For literals, we can tell if the constraint error will be
5968 -- raised at compile time, so we never need a dynamic check, but
5969 -- if the exception will be raised, then post the usual warning,
5970 -- and replace the literal with a raise constraint error
5971 -- expression. As usual, skip this for access types
5973 elsif Compile_Time_Known_Value (Ck_Node)
5974 and then not Do_Access
5975 then
5976 declare
5977 LB : constant Node_Id := Type_Low_Bound (T_Typ);
5978 UB : constant Node_Id := Type_High_Bound (T_Typ);
5980 Out_Of_Range : Boolean;
5981 Static_Bounds : constant Boolean :=
5982 Compile_Time_Known_Value (LB)
5983 and Compile_Time_Known_Value (UB);
5985 begin
5986 -- Following range tests should use Sem_Eval routine ???
5988 if Static_Bounds then
5989 if Is_Floating_Point_Type (S_Typ) then
5990 Out_Of_Range :=
5991 (Expr_Value_R (Ck_Node) < Expr_Value_R (LB))
5992 or else
5993 (Expr_Value_R (Ck_Node) > Expr_Value_R (UB));
5995 else -- fixed or discrete type
5996 Out_Of_Range :=
5997 Expr_Value (Ck_Node) < Expr_Value (LB)
5998 or else
5999 Expr_Value (Ck_Node) > Expr_Value (UB);
6000 end if;
6002 -- Bounds of the type are static and the literal is
6003 -- out of range so make a warning message.
6005 if Out_Of_Range then
6006 if No (Warn_Node) then
6007 Add_Check
6008 (Compile_Time_Constraint_Error
6009 (Ck_Node,
6010 "static value out of range of}?", T_Typ));
6012 else
6013 Add_Check
6014 (Compile_Time_Constraint_Error
6015 (Wnode,
6016 "static value out of range of}?", T_Typ));
6017 end if;
6018 end if;
6020 else
6021 Cond := Discrete_Expr_Cond (Ck_Node, T_Typ);
6022 end if;
6023 end;
6025 -- Here for the case of a non-static expression, we need a runtime
6026 -- check unless the source type range is guaranteed to be in the
6027 -- range of the target type.
6029 else
6030 if not In_Subrange_Of (S_Typ, T_Typ) then
6031 Cond := Discrete_Expr_Cond (Ck_Node, T_Typ);
6032 end if;
6033 end if;
6034 end if;
6036 if Is_Array_Type (T_Typ) and then Is_Array_Type (S_Typ) then
6037 if Is_Constrained (T_Typ) then
6039 Expr_Actual := Get_Referenced_Object (Ck_Node);
6040 Exptyp := Get_Actual_Subtype (Expr_Actual);
6042 if Is_Access_Type (Exptyp) then
6043 Exptyp := Designated_Type (Exptyp);
6044 end if;
6046 -- String_Literal case. This needs to be handled specially be-
6047 -- cause no index types are available for string literals. The
6048 -- condition is simply:
6050 -- T_Typ'Length = string-literal-length
6052 if Nkind (Expr_Actual) = N_String_Literal then
6053 null;
6055 -- General array case. Here we have a usable actual subtype for
6056 -- the expression, and the condition is built from the two types
6058 -- T_Typ'First < Exptyp'First or else
6059 -- T_Typ'Last > Exptyp'Last or else
6060 -- T_Typ'First(1) < Exptyp'First(1) or else
6061 -- T_Typ'Last(1) > Exptyp'Last(1) or else
6062 -- ...
6064 elsif Is_Constrained (Exptyp) then
6065 declare
6066 Ndims : constant Nat := Number_Dimensions (T_Typ);
6068 L_Index : Node_Id;
6069 R_Index : Node_Id;
6070 L_Low : Node_Id;
6071 L_High : Node_Id;
6072 R_Low : Node_Id;
6073 R_High : Node_Id;
6075 begin
6076 L_Index := First_Index (T_Typ);
6077 R_Index := First_Index (Exptyp);
6079 for Indx in 1 .. Ndims loop
6080 if not (Nkind (L_Index) = N_Raise_Constraint_Error
6081 or else
6082 Nkind (R_Index) = N_Raise_Constraint_Error)
6083 then
6084 Get_Index_Bounds (L_Index, L_Low, L_High);
6085 Get_Index_Bounds (R_Index, R_Low, R_High);
6087 -- Deal with compile time length check. Note that we
6088 -- skip this in the access case, because the access
6089 -- value may be null, so we cannot know statically.
6091 if not
6092 Subtypes_Statically_Match
6093 (Etype (L_Index), Etype (R_Index))
6094 then
6095 -- If the target type is constrained then we
6096 -- have to check for exact equality of bounds
6097 -- (required for qualified expressions).
6099 if Is_Constrained (T_Typ) then
6100 Evolve_Or_Else
6101 (Cond,
6102 Range_Equal_E_Cond (Exptyp, T_Typ, Indx));
6104 else
6105 Evolve_Or_Else
6106 (Cond, Range_E_Cond (Exptyp, T_Typ, Indx));
6107 end if;
6108 end if;
6110 Next (L_Index);
6111 Next (R_Index);
6113 end if;
6114 end loop;
6115 end;
6117 -- Handle cases where we do not get a usable actual subtype that
6118 -- is constrained. This happens for example in the function call
6119 -- and explicit dereference cases. In these cases, we have to get
6120 -- the length or range from the expression itself, making sure we
6121 -- do not evaluate it more than once.
6123 -- Here Ck_Node is the original expression, or more properly the
6124 -- result of applying Duplicate_Expr to the original tree,
6125 -- forcing the result to be a name.
6127 else
6128 declare
6129 Ndims : constant Nat := Number_Dimensions (T_Typ);
6131 begin
6132 -- Build the condition for the explicit dereference case
6134 for Indx in 1 .. Ndims loop
6135 Evolve_Or_Else
6136 (Cond, Range_N_Cond (Ck_Node, T_Typ, Indx));
6137 end loop;
6138 end;
6140 end if;
6142 else
6143 -- Generate an Action to check that the bounds of the
6144 -- source value are within the constraints imposed by the
6145 -- target type for a conversion to an unconstrained type.
6146 -- Rule is 4.6(38).
6148 if Nkind (Parent (Ck_Node)) = N_Type_Conversion then
6149 declare
6150 Opnd_Index : Node_Id;
6151 Targ_Index : Node_Id;
6153 begin
6154 Opnd_Index
6155 := First_Index (Get_Actual_Subtype (Ck_Node));
6156 Targ_Index := First_Index (T_Typ);
6158 while Opnd_Index /= Empty loop
6159 if Nkind (Opnd_Index) = N_Range then
6160 if Is_In_Range
6161 (Low_Bound (Opnd_Index), Etype (Targ_Index))
6162 and then
6163 Is_In_Range
6164 (High_Bound (Opnd_Index), Etype (Targ_Index))
6165 then
6166 null;
6168 -- If null range, no check needed.
6169 elsif
6170 Compile_Time_Known_Value (High_Bound (Opnd_Index))
6171 and then
6172 Compile_Time_Known_Value (Low_Bound (Opnd_Index))
6173 and then
6174 Expr_Value (High_Bound (Opnd_Index)) <
6175 Expr_Value (Low_Bound (Opnd_Index))
6176 then
6177 null;
6179 elsif Is_Out_Of_Range
6180 (Low_Bound (Opnd_Index), Etype (Targ_Index))
6181 or else
6182 Is_Out_Of_Range
6183 (High_Bound (Opnd_Index), Etype (Targ_Index))
6184 then
6185 Add_Check
6186 (Compile_Time_Constraint_Error
6187 (Wnode, "value out of range of}?", T_Typ));
6189 else
6190 Evolve_Or_Else
6191 (Cond,
6192 Discrete_Range_Cond
6193 (Opnd_Index, Etype (Targ_Index)));
6194 end if;
6195 end if;
6197 Next_Index (Opnd_Index);
6198 Next_Index (Targ_Index);
6199 end loop;
6200 end;
6201 end if;
6202 end if;
6203 end if;
6205 -- Construct the test and insert into the tree
6207 if Present (Cond) then
6208 if Do_Access then
6209 Cond := Guard_Access (Cond, Loc, Ck_Node);
6210 end if;
6212 Add_Check
6213 (Make_Raise_Constraint_Error (Loc,
6214 Condition => Cond,
6215 Reason => CE_Range_Check_Failed));
6216 end if;
6218 return Ret_Result;
6219 end Selected_Range_Checks;
6221 -------------------------------
6222 -- Storage_Checks_Suppressed --
6223 -------------------------------
6225 function Storage_Checks_Suppressed (E : Entity_Id) return Boolean is
6226 begin
6227 if Present (E) and then Checks_May_Be_Suppressed (E) then
6228 return Is_Check_Suppressed (E, Storage_Check);
6229 else
6230 return Scope_Suppress (Storage_Check);
6231 end if;
6232 end Storage_Checks_Suppressed;
6234 ---------------------------
6235 -- Tag_Checks_Suppressed --
6236 ---------------------------
6238 function Tag_Checks_Suppressed (E : Entity_Id) return Boolean is
6239 begin
6240 if Present (E) then
6241 if Kill_Tag_Checks (E) then
6242 return True;
6243 elsif Checks_May_Be_Suppressed (E) then
6244 return Is_Check_Suppressed (E, Tag_Check);
6245 end if;
6246 end if;
6248 return Scope_Suppress (Tag_Check);
6249 end Tag_Checks_Suppressed;
6251 end Checks;