Daily bump.
[official-gcc.git] / gcc / ada / checks.adb
blobd1a2b460c9089b9a72158ad1501f2e784c8d7261
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-2009, Free Software Foundation, Inc. --
10 -- --
11 -- GNAT is free software; you can redistribute it and/or modify it under --
12 -- terms of the GNU General Public License as published by the Free Soft- --
13 -- ware Foundation; either version 3, or (at your option) any later ver- --
14 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
17 -- for more details. You should have received a copy of the GNU General --
18 -- Public License distributed with GNAT; see file COPYING3. If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license. --
20 -- --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
23 -- --
24 ------------------------------------------------------------------------------
26 with Atree; use Atree;
27 with Debug; use Debug;
28 with Einfo; use Einfo;
29 with Errout; use Errout;
30 with Exp_Ch2; use Exp_Ch2;
31 with Exp_Ch11; use Exp_Ch11;
32 with Exp_Pakd; use Exp_Pakd;
33 with Exp_Util; use Exp_Util;
34 with Elists; use Elists;
35 with Eval_Fat; use Eval_Fat;
36 with Freeze; use Freeze;
37 with Lib; use Lib;
38 with Nlists; use Nlists;
39 with Nmake; use Nmake;
40 with Opt; use Opt;
41 with Output; use Output;
42 with Restrict; use Restrict;
43 with Rident; use Rident;
44 with Rtsfind; use Rtsfind;
45 with Sem; use Sem;
46 with Sem_Aux; use Sem_Aux;
47 with Sem_Eval; use Sem_Eval;
48 with Sem_Ch3; use Sem_Ch3;
49 with Sem_Ch8; use Sem_Ch8;
50 with Sem_Res; use Sem_Res;
51 with Sem_Util; use Sem_Util;
52 with Sem_Warn; use Sem_Warn;
53 with Sinfo; use Sinfo;
54 with Sinput; use Sinput;
55 with Snames; use Snames;
56 with Sprint; use Sprint;
57 with Stand; use Stand;
58 with Targparm; use Targparm;
59 with Tbuild; use Tbuild;
60 with Ttypes; use Ttypes;
61 with Urealp; use Urealp;
62 with Validsw; use Validsw;
64 package body Checks is
66 -- General note: many of these routines are concerned with generating
67 -- checking code to make sure that constraint error is raised at runtime.
68 -- Clearly this code is only needed if the expander is active, since
69 -- otherwise we will not be generating code or going into the runtime
70 -- execution anyway.
72 -- We therefore disconnect most of these checks if the expander is
73 -- inactive. This has the additional benefit that we do not need to
74 -- worry about the tree being messed up by previous errors (since errors
75 -- turn off expansion anyway).
77 -- There are a few exceptions to the above rule. For instance routines
78 -- such as Apply_Scalar_Range_Check that do not insert any code can be
79 -- safely called even when the Expander is inactive (but Errors_Detected
80 -- is 0). The benefit of executing this code when expansion is off, is
81 -- the ability to emit constraint error warning for static expressions
82 -- even when we are not generating code.
84 -------------------------------------
85 -- Suppression of Redundant Checks --
86 -------------------------------------
88 -- This unit implements a limited circuit for removal of redundant
89 -- checks. The processing is based on a tracing of simple sequential
90 -- flow. For any sequence of statements, we save expressions that are
91 -- marked to be checked, and then if the same expression appears later
92 -- with the same check, then under certain circumstances, the second
93 -- check can be suppressed.
95 -- Basically, we can suppress the check if we know for certain that
96 -- the previous expression has been elaborated (together with its
97 -- check), and we know that the exception frame is the same, and that
98 -- nothing has happened to change the result of the exception.
100 -- Let us examine each of these three conditions in turn to describe
101 -- how we ensure that this condition is met.
103 -- First, we need to know for certain that the previous expression has
104 -- been executed. This is done principly by the mechanism of calling
105 -- Conditional_Statements_Begin at the start of any statement sequence
106 -- and Conditional_Statements_End at the end. The End call causes all
107 -- checks remembered since the Begin call to be discarded. This does
108 -- miss a few cases, notably the case of a nested BEGIN-END block with
109 -- no exception handlers. But the important thing is to be conservative.
110 -- The other protection is that all checks are discarded if a label
111 -- is encountered, since then the assumption of sequential execution
112 -- is violated, and we don't know enough about the flow.
114 -- Second, we need to know that the exception frame is the same. We
115 -- do this by killing all remembered checks when we enter a new frame.
116 -- Again, that's over-conservative, but generally the cases we can help
117 -- with are pretty local anyway (like the body of a loop for example).
119 -- Third, we must be sure to forget any checks which are no longer valid.
120 -- This is done by two mechanisms, first the Kill_Checks_Variable call is
121 -- used to note any changes to local variables. We only attempt to deal
122 -- with checks involving local variables, so we do not need to worry
123 -- about global variables. Second, a call to any non-global procedure
124 -- causes us to abandon all stored checks, since such a all may affect
125 -- the values of any local variables.
127 -- The following define the data structures used to deal with remembering
128 -- checks so that redundant checks can be eliminated as described above.
130 -- Right now, the only expressions that we deal with are of the form of
131 -- simple local objects (either declared locally, or IN parameters) or
132 -- such objects plus/minus a compile time known constant. We can do
133 -- more later on if it seems worthwhile, but this catches many simple
134 -- cases in practice.
136 -- The following record type reflects a single saved check. An entry
137 -- is made in the stack of saved checks if and only if the expression
138 -- has been elaborated with the indicated checks.
140 type Saved_Check is record
141 Killed : Boolean;
142 -- Set True if entry is killed by Kill_Checks
144 Entity : Entity_Id;
145 -- The entity involved in the expression that is checked
147 Offset : Uint;
148 -- A compile time value indicating the result of adding or
149 -- subtracting a compile time value. This value is to be
150 -- added to the value of the Entity. A value of zero is
151 -- used for the case of a simple entity reference.
153 Check_Type : Character;
154 -- This is set to 'R' for a range check (in which case Target_Type
155 -- is set to the target type for the range check) or to 'O' for an
156 -- overflow check (in which case Target_Type is set to Empty).
158 Target_Type : Entity_Id;
159 -- Used only if Do_Range_Check is set. Records the target type for
160 -- the check. We need this, because a check is a duplicate only if
161 -- it has a the same target type (or more accurately one with a
162 -- range that is smaller or equal to the stored target type of a
163 -- saved check).
164 end record;
166 -- The following table keeps track of saved checks. Rather than use an
167 -- extensible table. We just use a table of fixed size, and we discard
168 -- any saved checks that do not fit. That's very unlikely to happen and
169 -- this is only an optimization in any case.
171 Saved_Checks : array (Int range 1 .. 200) of Saved_Check;
172 -- Array of saved checks
174 Num_Saved_Checks : Nat := 0;
175 -- Number of saved checks
177 -- The following stack keeps track of statement ranges. It is treated
178 -- as a stack. When Conditional_Statements_Begin is called, an entry
179 -- is pushed onto this stack containing the value of Num_Saved_Checks
180 -- at the time of the call. Then when Conditional_Statements_End is
181 -- called, this value is popped off and used to reset Num_Saved_Checks.
183 -- Note: again, this is a fixed length stack with a size that should
184 -- always be fine. If the value of the stack pointer goes above the
185 -- limit, then we just forget all saved checks.
187 Saved_Checks_Stack : array (Int range 1 .. 100) of Nat;
188 Saved_Checks_TOS : Nat := 0;
190 -----------------------
191 -- Local Subprograms --
192 -----------------------
194 procedure Apply_Float_Conversion_Check
195 (Ck_Node : Node_Id;
196 Target_Typ : Entity_Id);
197 -- The checks on a conversion from a floating-point type to an integer
198 -- type are delicate. They have to be performed before conversion, they
199 -- have to raise an exception when the operand is a NaN, and rounding must
200 -- be taken into account to determine the safe bounds of the operand.
202 procedure Apply_Selected_Length_Checks
203 (Ck_Node : Node_Id;
204 Target_Typ : Entity_Id;
205 Source_Typ : Entity_Id;
206 Do_Static : Boolean);
207 -- This is the subprogram that does all the work for Apply_Length_Check
208 -- and Apply_Static_Length_Check. Expr, Target_Typ and Source_Typ are as
209 -- described for the above routines. The Do_Static flag indicates that
210 -- only a static check is to be done.
212 procedure Apply_Selected_Range_Checks
213 (Ck_Node : Node_Id;
214 Target_Typ : Entity_Id;
215 Source_Typ : Entity_Id;
216 Do_Static : Boolean);
217 -- This is the subprogram that does all the work for Apply_Range_Check.
218 -- Expr, Target_Typ and Source_Typ are as described for the above
219 -- routine. The Do_Static flag indicates that only a static check is
220 -- to be done.
222 type Check_Type is new Check_Id range Access_Check .. Division_Check;
223 function Check_Needed (Nod : Node_Id; Check : Check_Type) return Boolean;
224 -- This function is used to see if an access or division by zero check is
225 -- needed. The check is to be applied to a single variable appearing in the
226 -- source, and N is the node for the reference. If N is not of this form,
227 -- True is returned with no further processing. If N is of the right form,
228 -- then further processing determines if the given Check is needed.
230 -- The particular circuit is to see if we have the case of a check that is
231 -- not needed because it appears in the right operand of a short circuited
232 -- conditional where the left operand guards the check. For example:
234 -- if Var = 0 or else Q / Var > 12 then
235 -- ...
236 -- end if;
238 -- In this example, the division check is not required. At the same time
239 -- we can issue warnings for suspicious use of non-short-circuited forms,
240 -- such as:
242 -- if Var = 0 or Q / Var > 12 then
243 -- ...
244 -- end if;
246 procedure Find_Check
247 (Expr : Node_Id;
248 Check_Type : Character;
249 Target_Type : Entity_Id;
250 Entry_OK : out Boolean;
251 Check_Num : out Nat;
252 Ent : out Entity_Id;
253 Ofs : out Uint);
254 -- This routine is used by Enable_Range_Check and Enable_Overflow_Check
255 -- to see if a check is of the form for optimization, and if so, to see
256 -- if it has already been performed. Expr is the expression to check,
257 -- and Check_Type is 'R' for a range check, 'O' for an overflow check.
258 -- Target_Type is the target type for a range check, and Empty for an
259 -- overflow check. If the entry is not of the form for optimization,
260 -- then Entry_OK is set to False, and the remaining out parameters
261 -- are undefined. If the entry is OK, then Ent/Ofs are set to the
262 -- entity and offset from the expression. Check_Num is the number of
263 -- a matching saved entry in Saved_Checks, or zero if no such entry
264 -- is located.
266 function Get_Discriminal (E : Entity_Id; Bound : Node_Id) return Node_Id;
267 -- If a discriminal is used in constraining a prival, Return reference
268 -- to the discriminal of the protected body (which renames the parameter
269 -- of the enclosing protected operation). This clumsy transformation is
270 -- needed because privals are created too late and their actual subtypes
271 -- are not available when analysing the bodies of the protected operations.
272 -- This function is called whenever the bound is an entity and the scope
273 -- indicates a protected operation. If the bound is an in-parameter of
274 -- a protected operation that is not a prival, the function returns the
275 -- bound itself.
276 -- To be cleaned up???
278 function Guard_Access
279 (Cond : Node_Id;
280 Loc : Source_Ptr;
281 Ck_Node : Node_Id) return Node_Id;
282 -- In the access type case, guard the test with a test to ensure
283 -- that the access value is non-null, since the checks do not
284 -- not apply to null access values.
286 procedure Install_Static_Check (R_Cno : Node_Id; Loc : Source_Ptr);
287 -- Called by Apply_{Length,Range}_Checks to rewrite the tree with the
288 -- Constraint_Error node.
290 function Range_Or_Validity_Checks_Suppressed
291 (Expr : Node_Id) return Boolean;
292 -- Returns True if either range or validity checks or both are suppressed
293 -- for the type of the given expression, or, if the expression is the name
294 -- of an entity, if these checks are suppressed for the entity.
296 function Selected_Length_Checks
297 (Ck_Node : Node_Id;
298 Target_Typ : Entity_Id;
299 Source_Typ : Entity_Id;
300 Warn_Node : Node_Id) return Check_Result;
301 -- Like Apply_Selected_Length_Checks, except it doesn't modify
302 -- anything, just returns a list of nodes as described in the spec of
303 -- this package for the Range_Check function.
305 function Selected_Range_Checks
306 (Ck_Node : Node_Id;
307 Target_Typ : Entity_Id;
308 Source_Typ : Entity_Id;
309 Warn_Node : Node_Id) return Check_Result;
310 -- Like Apply_Selected_Range_Checks, except it doesn't modify anything,
311 -- just returns a list of nodes as described in the spec of this package
312 -- for the Range_Check function.
314 ------------------------------
315 -- Access_Checks_Suppressed --
316 ------------------------------
318 function Access_Checks_Suppressed (E : Entity_Id) return Boolean is
319 begin
320 if Present (E) and then Checks_May_Be_Suppressed (E) then
321 return Is_Check_Suppressed (E, Access_Check);
322 else
323 return Scope_Suppress (Access_Check);
324 end if;
325 end Access_Checks_Suppressed;
327 -------------------------------------
328 -- Accessibility_Checks_Suppressed --
329 -------------------------------------
331 function Accessibility_Checks_Suppressed (E : Entity_Id) return Boolean is
332 begin
333 if Present (E) and then Checks_May_Be_Suppressed (E) then
334 return Is_Check_Suppressed (E, Accessibility_Check);
335 else
336 return Scope_Suppress (Accessibility_Check);
337 end if;
338 end Accessibility_Checks_Suppressed;
340 -----------------------------
341 -- Activate_Division_Check --
342 -----------------------------
344 procedure Activate_Division_Check (N : Node_Id) is
345 begin
346 Set_Do_Division_Check (N, True);
347 Possible_Local_Raise (N, Standard_Constraint_Error);
348 end Activate_Division_Check;
350 -----------------------------
351 -- Activate_Overflow_Check --
352 -----------------------------
354 procedure Activate_Overflow_Check (N : Node_Id) is
355 begin
356 Set_Do_Overflow_Check (N, True);
357 Possible_Local_Raise (N, Standard_Constraint_Error);
358 end Activate_Overflow_Check;
360 --------------------------
361 -- Activate_Range_Check --
362 --------------------------
364 procedure Activate_Range_Check (N : Node_Id) is
365 begin
366 Set_Do_Range_Check (N, True);
367 Possible_Local_Raise (N, Standard_Constraint_Error);
368 end Activate_Range_Check;
370 ---------------------------------
371 -- Alignment_Checks_Suppressed --
372 ---------------------------------
374 function Alignment_Checks_Suppressed (E : Entity_Id) return Boolean is
375 begin
376 if Present (E) and then Checks_May_Be_Suppressed (E) then
377 return Is_Check_Suppressed (E, Alignment_Check);
378 else
379 return Scope_Suppress (Alignment_Check);
380 end if;
381 end Alignment_Checks_Suppressed;
383 -------------------------
384 -- Append_Range_Checks --
385 -------------------------
387 procedure Append_Range_Checks
388 (Checks : Check_Result;
389 Stmts : List_Id;
390 Suppress_Typ : Entity_Id;
391 Static_Sloc : Source_Ptr;
392 Flag_Node : Node_Id)
394 Internal_Flag_Node : constant Node_Id := Flag_Node;
395 Internal_Static_Sloc : constant Source_Ptr := Static_Sloc;
397 Checks_On : constant Boolean :=
398 (not Index_Checks_Suppressed (Suppress_Typ))
399 or else
400 (not Range_Checks_Suppressed (Suppress_Typ));
402 begin
403 -- For now we just return if Checks_On is false, however this should
404 -- be enhanced to check for an always True value in the condition
405 -- and to generate a compilation warning???
407 if not Checks_On then
408 return;
409 end if;
411 for J in 1 .. 2 loop
412 exit when No (Checks (J));
414 if Nkind (Checks (J)) = N_Raise_Constraint_Error
415 and then Present (Condition (Checks (J)))
416 then
417 if not Has_Dynamic_Range_Check (Internal_Flag_Node) then
418 Append_To (Stmts, Checks (J));
419 Set_Has_Dynamic_Range_Check (Internal_Flag_Node);
420 end if;
422 else
423 Append_To
424 (Stmts,
425 Make_Raise_Constraint_Error (Internal_Static_Sloc,
426 Reason => CE_Range_Check_Failed));
427 end if;
428 end loop;
429 end Append_Range_Checks;
431 ------------------------
432 -- Apply_Access_Check --
433 ------------------------
435 procedure Apply_Access_Check (N : Node_Id) is
436 P : constant Node_Id := Prefix (N);
438 begin
439 -- We do not need checks if we are not generating code (i.e. the
440 -- expander is not active). This is not just an optimization, there
441 -- are cases (e.g. with pragma Debug) where generating the checks
442 -- can cause real trouble).
444 if not Expander_Active then
445 return;
446 end if;
448 -- No check if short circuiting makes check unnecessary
450 if not Check_Needed (P, Access_Check) then
451 return;
452 end if;
454 -- No check if accessing the Offset_To_Top component of a dispatch
455 -- table. They are safe by construction.
457 if Tagged_Type_Expansion
458 and then Present (Etype (P))
459 and then RTU_Loaded (Ada_Tags)
460 and then RTE_Available (RE_Offset_To_Top_Ptr)
461 and then Etype (P) = RTE (RE_Offset_To_Top_Ptr)
462 then
463 return;
464 end if;
466 -- Otherwise go ahead and install the check
468 Install_Null_Excluding_Check (P);
469 end Apply_Access_Check;
471 -------------------------------
472 -- Apply_Accessibility_Check --
473 -------------------------------
475 procedure Apply_Accessibility_Check
476 (N : Node_Id;
477 Typ : Entity_Id;
478 Insert_Node : Node_Id)
480 Loc : constant Source_Ptr := Sloc (N);
481 Param_Ent : constant Entity_Id := Param_Entity (N);
482 Param_Level : Node_Id;
483 Type_Level : Node_Id;
485 begin
486 if Inside_A_Generic then
487 return;
489 -- Only apply the run-time check if the access parameter has an
490 -- associated extra access level parameter and when the level of the
491 -- type is less deep than the level of the access parameter, and
492 -- accessibility checks are not suppressed.
494 elsif Present (Param_Ent)
495 and then Present (Extra_Accessibility (Param_Ent))
496 and then UI_Gt (Object_Access_Level (N), Type_Access_Level (Typ))
497 and then not Accessibility_Checks_Suppressed (Param_Ent)
498 and then not Accessibility_Checks_Suppressed (Typ)
499 then
500 Param_Level :=
501 New_Occurrence_Of (Extra_Accessibility (Param_Ent), Loc);
503 Type_Level :=
504 Make_Integer_Literal (Loc, Type_Access_Level (Typ));
506 -- Raise Program_Error if the accessibility level of the access
507 -- parameter is deeper than the level of the target access type.
509 Insert_Action (Insert_Node,
510 Make_Raise_Program_Error (Loc,
511 Condition =>
512 Make_Op_Gt (Loc,
513 Left_Opnd => Param_Level,
514 Right_Opnd => Type_Level),
515 Reason => PE_Accessibility_Check_Failed));
517 Analyze_And_Resolve (N);
518 end if;
519 end Apply_Accessibility_Check;
521 --------------------------------
522 -- Apply_Address_Clause_Check --
523 --------------------------------
525 procedure Apply_Address_Clause_Check (E : Entity_Id; N : Node_Id) is
526 AC : constant Node_Id := Address_Clause (E);
527 Loc : constant Source_Ptr := Sloc (AC);
528 Typ : constant Entity_Id := Etype (E);
529 Aexp : constant Node_Id := Expression (AC);
531 Expr : Node_Id;
532 -- Address expression (not necessarily the same as Aexp, for example
533 -- when Aexp is a reference to a constant, in which case Expr gets
534 -- reset to reference the value expression of the constant.
536 procedure Compile_Time_Bad_Alignment;
537 -- Post error warnings when alignment is known to be incompatible. Note
538 -- that we do not go as far as inserting a raise of Program_Error since
539 -- this is an erroneous case, and it may happen that we are lucky and an
540 -- underaligned address turns out to be OK after all.
542 --------------------------------
543 -- Compile_Time_Bad_Alignment --
544 --------------------------------
546 procedure Compile_Time_Bad_Alignment is
547 begin
548 if Address_Clause_Overlay_Warnings then
549 Error_Msg_FE
550 ("?specified address for& may be inconsistent with alignment ",
551 Aexp, E);
552 Error_Msg_FE
553 ("\?program execution may be erroneous (RM 13.3(27))",
554 Aexp, E);
555 Set_Address_Warning_Posted (AC);
556 end if;
557 end Compile_Time_Bad_Alignment;
559 -- Start of processing for Apply_Address_Clause_Check
561 begin
562 -- See if alignment check needed. Note that we never need a check if the
563 -- maximum alignment is one, since the check will always succeed.
565 -- Note: we do not check for checks suppressed here, since that check
566 -- was done in Sem_Ch13 when the address clause was processed. We are
567 -- only called if checks were not suppressed. The reason for this is
568 -- that we have to delay the call to Apply_Alignment_Check till freeze
569 -- time (so that all types etc are elaborated), but we have to check
570 -- the status of check suppressing at the point of the address clause.
572 if No (AC)
573 or else not Check_Address_Alignment (AC)
574 or else Maximum_Alignment = 1
575 then
576 return;
577 end if;
579 -- Obtain expression from address clause
581 Expr := Expression (AC);
583 -- The following loop digs for the real expression to use in the check
585 loop
586 -- For constant, get constant expression
588 if Is_Entity_Name (Expr)
589 and then Ekind (Entity (Expr)) = E_Constant
590 then
591 Expr := Constant_Value (Entity (Expr));
593 -- For unchecked conversion, get result to convert
595 elsif Nkind (Expr) = N_Unchecked_Type_Conversion then
596 Expr := Expression (Expr);
598 -- For (common case) of To_Address call, get argument
600 elsif Nkind (Expr) = N_Function_Call
601 and then Is_Entity_Name (Name (Expr))
602 and then Is_RTE (Entity (Name (Expr)), RE_To_Address)
603 then
604 Expr := First (Parameter_Associations (Expr));
606 if Nkind (Expr) = N_Parameter_Association then
607 Expr := Explicit_Actual_Parameter (Expr);
608 end if;
610 -- We finally have the real expression
612 else
613 exit;
614 end if;
615 end loop;
617 -- See if we know that Expr has a bad alignment at compile time
619 if Compile_Time_Known_Value (Expr)
620 and then (Known_Alignment (E) or else Known_Alignment (Typ))
621 then
622 declare
623 AL : Uint := Alignment (Typ);
625 begin
626 -- The object alignment might be more restrictive than the
627 -- type alignment.
629 if Known_Alignment (E) then
630 AL := Alignment (E);
631 end if;
633 if Expr_Value (Expr) mod AL /= 0 then
634 Compile_Time_Bad_Alignment;
635 else
636 return;
637 end if;
638 end;
640 -- If the expression has the form X'Address, then we can find out if
641 -- the object X has an alignment that is compatible with the object E.
642 -- If it hasn't or we don't know, we defer issuing the warning until
643 -- the end of the compilation to take into account back end annotations.
645 elsif Nkind (Expr) = N_Attribute_Reference
646 and then Attribute_Name (Expr) = Name_Address
647 and then Has_Compatible_Alignment (E, Prefix (Expr)) = Known_Compatible
648 then
649 return;
650 end if;
652 -- Here we do not know if the value is acceptable. Stricly we don't have
653 -- to do anything, since if the alignment is bad, we have an erroneous
654 -- program. However we are allowed to check for erroneous conditions and
655 -- we decide to do this by default if the check is not suppressed.
657 -- However, don't do the check if elaboration code is unwanted
659 if Restriction_Active (No_Elaboration_Code) then
660 return;
662 -- Generate a check to raise PE if alignment may be inappropriate
664 else
665 -- If the original expression is a non-static constant, use the
666 -- name of the constant itself rather than duplicating its
667 -- defining expression, which was extracted above.
669 -- Note: Expr is empty if the address-clause is applied to in-mode
670 -- actuals (allowed by 13.1(22)).
672 if not Present (Expr)
673 or else
674 (Is_Entity_Name (Expression (AC))
675 and then Ekind (Entity (Expression (AC))) = E_Constant
676 and then Nkind (Parent (Entity (Expression (AC))))
677 = N_Object_Declaration)
678 then
679 Expr := New_Copy_Tree (Expression (AC));
680 else
681 Remove_Side_Effects (Expr);
682 end if;
684 Insert_After_And_Analyze (N,
685 Make_Raise_Program_Error (Loc,
686 Condition =>
687 Make_Op_Ne (Loc,
688 Left_Opnd =>
689 Make_Op_Mod (Loc,
690 Left_Opnd =>
691 Unchecked_Convert_To
692 (RTE (RE_Integer_Address), Expr),
693 Right_Opnd =>
694 Make_Attribute_Reference (Loc,
695 Prefix => New_Occurrence_Of (E, Loc),
696 Attribute_Name => Name_Alignment)),
697 Right_Opnd => Make_Integer_Literal (Loc, Uint_0)),
698 Reason => PE_Misaligned_Address_Value),
699 Suppress => All_Checks);
700 return;
701 end if;
703 exception
704 -- If we have some missing run time component in configurable run time
705 -- mode then just skip the check (it is not required in any case).
707 when RE_Not_Available =>
708 return;
709 end Apply_Address_Clause_Check;
711 -------------------------------------
712 -- Apply_Arithmetic_Overflow_Check --
713 -------------------------------------
715 -- This routine is called only if the type is an integer type, and a
716 -- software arithmetic overflow check may be needed for op (add, subtract,
717 -- or multiply). This check is performed only if Software_Overflow_Checking
718 -- is enabled and Do_Overflow_Check is set. In this case we expand the
719 -- operation into a more complex sequence of tests that ensures that
720 -- overflow is properly caught.
722 procedure Apply_Arithmetic_Overflow_Check (N : Node_Id) is
723 Loc : constant Source_Ptr := Sloc (N);
724 Typ : Entity_Id := Etype (N);
725 Rtyp : Entity_Id := Root_Type (Typ);
727 begin
728 -- An interesting special case. If the arithmetic operation appears as
729 -- the operand of a type conversion:
731 -- type1 (x op y)
733 -- and all the following conditions apply:
735 -- arithmetic operation is for a signed integer type
736 -- target type type1 is a static integer subtype
737 -- range of x and y are both included in the range of type1
738 -- range of x op y is included in the range of type1
739 -- size of type1 is at least twice the result size of op
741 -- then we don't do an overflow check in any case, instead we transform
742 -- the operation so that we end up with:
744 -- type1 (type1 (x) op type1 (y))
746 -- This avoids intermediate overflow before the conversion. It is
747 -- explicitly permitted by RM 3.5.4(24):
749 -- For the execution of a predefined operation of a signed integer
750 -- type, the implementation need not raise Constraint_Error if the
751 -- result is outside the base range of the type, so long as the
752 -- correct result is produced.
754 -- It's hard to imagine that any programmer counts on the exception
755 -- being raised in this case, and in any case it's wrong coding to
756 -- have this expectation, given the RM permission. Furthermore, other
757 -- Ada compilers do allow such out of range results.
759 -- Note that we do this transformation even if overflow checking is
760 -- off, since this is precisely about giving the "right" result and
761 -- avoiding the need for an overflow check.
763 -- Note: this circuit is partially redundant with respect to the similar
764 -- processing in Exp_Ch4.Expand_N_Type_Conversion, but the latter deals
765 -- with cases that do not come through here. We still need the following
766 -- processing even with the Exp_Ch4 code in place, since we want to be
767 -- sure not to generate the arithmetic overflow check in these cases
768 -- (Exp_Ch4 would have a hard time removing them once generated).
770 if Is_Signed_Integer_Type (Typ)
771 and then Nkind (Parent (N)) = N_Type_Conversion
772 then
773 declare
774 Target_Type : constant Entity_Id :=
775 Base_Type (Entity (Subtype_Mark (Parent (N))));
777 Llo, Lhi : Uint;
778 Rlo, Rhi : Uint;
779 LOK, ROK : Boolean;
781 Vlo : Uint;
782 Vhi : Uint;
783 VOK : Boolean;
785 Tlo : Uint;
786 Thi : Uint;
788 begin
789 if Is_Integer_Type (Target_Type)
790 and then RM_Size (Root_Type (Target_Type)) >= 2 * RM_Size (Rtyp)
791 then
792 Tlo := Expr_Value (Type_Low_Bound (Target_Type));
793 Thi := Expr_Value (Type_High_Bound (Target_Type));
795 Determine_Range
796 (Left_Opnd (N), LOK, Llo, Lhi, Assume_Valid => True);
797 Determine_Range
798 (Right_Opnd (N), ROK, Rlo, Rhi, Assume_Valid => True);
800 if (LOK and ROK)
801 and then Tlo <= Llo and then Lhi <= Thi
802 and then Tlo <= Rlo and then Rhi <= Thi
803 then
804 Determine_Range (N, VOK, Vlo, Vhi, Assume_Valid => True);
806 if VOK and then Tlo <= Vlo and then Vhi <= Thi then
807 Rewrite (Left_Opnd (N),
808 Make_Type_Conversion (Loc,
809 Subtype_Mark => New_Occurrence_Of (Target_Type, Loc),
810 Expression => Relocate_Node (Left_Opnd (N))));
812 Rewrite (Right_Opnd (N),
813 Make_Type_Conversion (Loc,
814 Subtype_Mark => New_Occurrence_Of (Target_Type, Loc),
815 Expression => Relocate_Node (Right_Opnd (N))));
817 Set_Etype (N, Target_Type);
818 Typ := Target_Type;
819 Rtyp := Root_Type (Typ);
820 Analyze_And_Resolve (Left_Opnd (N), Target_Type);
821 Analyze_And_Resolve (Right_Opnd (N), Target_Type);
823 -- Given that the target type is twice the size of the
824 -- source type, overflow is now impossible, so we can
825 -- safely kill the overflow check and return.
827 Set_Do_Overflow_Check (N, False);
828 return;
829 end if;
830 end if;
831 end if;
832 end;
833 end if;
835 -- Now see if an overflow check is required
837 declare
838 Siz : constant Int := UI_To_Int (Esize (Rtyp));
839 Dsiz : constant Int := Siz * 2;
840 Opnod : Node_Id;
841 Ctyp : Entity_Id;
842 Opnd : Node_Id;
843 Cent : RE_Id;
845 begin
846 -- Skip check if back end does overflow checks, or the overflow flag
847 -- is not set anyway, or we are not doing code expansion.
849 -- Special case CLI target, where arithmetic overflow checks can be
850 -- performed for integer and long_integer
852 if Backend_Overflow_Checks_On_Target
853 or else not Do_Overflow_Check (N)
854 or else not Expander_Active
855 or else
856 (VM_Target = CLI_Target and then Siz >= Standard_Integer_Size)
857 then
858 return;
859 end if;
861 -- Otherwise, generate the full general code for front end overflow
862 -- detection, which works by doing arithmetic in a larger type:
864 -- x op y
866 -- is expanded into
868 -- Typ (Checktyp (x) op Checktyp (y));
870 -- where Typ is the type of the original expression, and Checktyp is
871 -- an integer type of sufficient length to hold the largest possible
872 -- result.
874 -- If the size of check type exceeds the size of Long_Long_Integer,
875 -- we use a different approach, expanding to:
877 -- typ (xxx_With_Ovflo_Check (Integer_64 (x), Integer (y)))
879 -- where xxx is Add, Multiply or Subtract as appropriate
881 -- Find check type if one exists
883 if Dsiz <= Standard_Integer_Size then
884 Ctyp := Standard_Integer;
886 elsif Dsiz <= Standard_Long_Long_Integer_Size then
887 Ctyp := Standard_Long_Long_Integer;
889 -- No check type exists, use runtime call
891 else
892 if Nkind (N) = N_Op_Add then
893 Cent := RE_Add_With_Ovflo_Check;
895 elsif Nkind (N) = N_Op_Multiply then
896 Cent := RE_Multiply_With_Ovflo_Check;
898 else
899 pragma Assert (Nkind (N) = N_Op_Subtract);
900 Cent := RE_Subtract_With_Ovflo_Check;
901 end if;
903 Rewrite (N,
904 OK_Convert_To (Typ,
905 Make_Function_Call (Loc,
906 Name => New_Reference_To (RTE (Cent), Loc),
907 Parameter_Associations => New_List (
908 OK_Convert_To (RTE (RE_Integer_64), Left_Opnd (N)),
909 OK_Convert_To (RTE (RE_Integer_64), Right_Opnd (N))))));
911 Analyze_And_Resolve (N, Typ);
912 return;
913 end if;
915 -- If we fall through, we have the case where we do the arithmetic
916 -- in the next higher type and get the check by conversion. In these
917 -- cases Ctyp is set to the type to be used as the check type.
919 Opnod := Relocate_Node (N);
921 Opnd := OK_Convert_To (Ctyp, Left_Opnd (Opnod));
923 Analyze (Opnd);
924 Set_Etype (Opnd, Ctyp);
925 Set_Analyzed (Opnd, True);
926 Set_Left_Opnd (Opnod, Opnd);
928 Opnd := OK_Convert_To (Ctyp, Right_Opnd (Opnod));
930 Analyze (Opnd);
931 Set_Etype (Opnd, Ctyp);
932 Set_Analyzed (Opnd, True);
933 Set_Right_Opnd (Opnod, Opnd);
935 -- The type of the operation changes to the base type of the check
936 -- type, and we reset the overflow check indication, since clearly no
937 -- overflow is possible now that we are using a double length type.
938 -- We also set the Analyzed flag to avoid a recursive attempt to
939 -- expand the node.
941 Set_Etype (Opnod, Base_Type (Ctyp));
942 Set_Do_Overflow_Check (Opnod, False);
943 Set_Analyzed (Opnod, True);
945 -- Now build the outer conversion
947 Opnd := OK_Convert_To (Typ, Opnod);
948 Analyze (Opnd);
949 Set_Etype (Opnd, Typ);
951 -- In the discrete type case, we directly generate the range check
952 -- for the outer operand. This range check will implement the
953 -- required overflow check.
955 if Is_Discrete_Type (Typ) then
956 Rewrite (N, Opnd);
957 Generate_Range_Check
958 (Expression (N), Typ, CE_Overflow_Check_Failed);
960 -- For other types, we enable overflow checking on the conversion,
961 -- after setting the node as analyzed to prevent recursive attempts
962 -- to expand the conversion node.
964 else
965 Set_Analyzed (Opnd, True);
966 Enable_Overflow_Check (Opnd);
967 Rewrite (N, Opnd);
968 end if;
970 exception
971 when RE_Not_Available =>
972 return;
973 end;
974 end Apply_Arithmetic_Overflow_Check;
976 ----------------------------
977 -- Apply_Constraint_Check --
978 ----------------------------
980 procedure Apply_Constraint_Check
981 (N : Node_Id;
982 Typ : Entity_Id;
983 No_Sliding : Boolean := False)
985 Desig_Typ : Entity_Id;
987 begin
988 if Inside_A_Generic then
989 return;
991 elsif Is_Scalar_Type (Typ) then
992 Apply_Scalar_Range_Check (N, Typ);
994 elsif Is_Array_Type (Typ) then
996 -- A useful optimization: an aggregate with only an others clause
997 -- always has the right bounds.
999 if Nkind (N) = N_Aggregate
1000 and then No (Expressions (N))
1001 and then Nkind
1002 (First (Choices (First (Component_Associations (N)))))
1003 = N_Others_Choice
1004 then
1005 return;
1006 end if;
1008 if Is_Constrained (Typ) then
1009 Apply_Length_Check (N, Typ);
1011 if No_Sliding then
1012 Apply_Range_Check (N, Typ);
1013 end if;
1014 else
1015 Apply_Range_Check (N, Typ);
1016 end if;
1018 elsif (Is_Record_Type (Typ)
1019 or else Is_Private_Type (Typ))
1020 and then Has_Discriminants (Base_Type (Typ))
1021 and then Is_Constrained (Typ)
1022 then
1023 Apply_Discriminant_Check (N, Typ);
1025 elsif Is_Access_Type (Typ) then
1027 Desig_Typ := Designated_Type (Typ);
1029 -- No checks necessary if expression statically null
1031 if Known_Null (N) then
1032 if Can_Never_Be_Null (Typ) then
1033 Install_Null_Excluding_Check (N);
1034 end if;
1036 -- No sliding possible on access to arrays
1038 elsif Is_Array_Type (Desig_Typ) then
1039 if Is_Constrained (Desig_Typ) then
1040 Apply_Length_Check (N, Typ);
1041 end if;
1043 Apply_Range_Check (N, Typ);
1045 elsif Has_Discriminants (Base_Type (Desig_Typ))
1046 and then Is_Constrained (Desig_Typ)
1047 then
1048 Apply_Discriminant_Check (N, Typ);
1049 end if;
1051 -- Apply the 2005 Null_Excluding check. Note that we do not apply
1052 -- this check if the constraint node is illegal, as shown by having
1053 -- an error posted. This additional guard prevents cascaded errors
1054 -- and compiler aborts on illegal programs involving Ada 2005 checks.
1056 if Can_Never_Be_Null (Typ)
1057 and then not Can_Never_Be_Null (Etype (N))
1058 and then not Error_Posted (N)
1059 then
1060 Install_Null_Excluding_Check (N);
1061 end if;
1062 end if;
1063 end Apply_Constraint_Check;
1065 ------------------------------
1066 -- Apply_Discriminant_Check --
1067 ------------------------------
1069 procedure Apply_Discriminant_Check
1070 (N : Node_Id;
1071 Typ : Entity_Id;
1072 Lhs : Node_Id := Empty)
1074 Loc : constant Source_Ptr := Sloc (N);
1075 Do_Access : constant Boolean := Is_Access_Type (Typ);
1076 S_Typ : Entity_Id := Etype (N);
1077 Cond : Node_Id;
1078 T_Typ : Entity_Id;
1080 function Is_Aliased_Unconstrained_Component return Boolean;
1081 -- It is possible for an aliased component to have a nominal
1082 -- unconstrained subtype (through instantiation). If this is a
1083 -- discriminated component assigned in the expansion of an aggregate
1084 -- in an initialization, the check must be suppressed. This unusual
1085 -- situation requires a predicate of its own.
1087 ----------------------------------------
1088 -- Is_Aliased_Unconstrained_Component --
1089 ----------------------------------------
1091 function Is_Aliased_Unconstrained_Component return Boolean is
1092 Comp : Entity_Id;
1093 Pref : Node_Id;
1095 begin
1096 if Nkind (Lhs) /= N_Selected_Component then
1097 return False;
1098 else
1099 Comp := Entity (Selector_Name (Lhs));
1100 Pref := Prefix (Lhs);
1101 end if;
1103 if Ekind (Comp) /= E_Component
1104 or else not Is_Aliased (Comp)
1105 then
1106 return False;
1107 end if;
1109 return not Comes_From_Source (Pref)
1110 and then In_Instance
1111 and then not Is_Constrained (Etype (Comp));
1112 end Is_Aliased_Unconstrained_Component;
1114 -- Start of processing for Apply_Discriminant_Check
1116 begin
1117 if Do_Access then
1118 T_Typ := Designated_Type (Typ);
1119 else
1120 T_Typ := Typ;
1121 end if;
1123 -- Nothing to do if discriminant checks are suppressed or else no code
1124 -- is to be generated
1126 if not Expander_Active
1127 or else Discriminant_Checks_Suppressed (T_Typ)
1128 then
1129 return;
1130 end if;
1132 -- No discriminant checks necessary for an access when expression is
1133 -- statically Null. This is not only an optimization, it is fundamental
1134 -- because otherwise discriminant checks may be generated in init procs
1135 -- for types containing an access to a not-yet-frozen record, causing a
1136 -- deadly forward reference.
1138 -- Also, if the expression is of an access type whose designated type is
1139 -- incomplete, then the access value must be null and we suppress the
1140 -- check.
1142 if Known_Null (N) then
1143 return;
1145 elsif Is_Access_Type (S_Typ) then
1146 S_Typ := Designated_Type (S_Typ);
1148 if Ekind (S_Typ) = E_Incomplete_Type then
1149 return;
1150 end if;
1151 end if;
1153 -- If an assignment target is present, then we need to generate the
1154 -- actual subtype if the target is a parameter or aliased object with
1155 -- an unconstrained nominal subtype.
1157 -- Ada 2005 (AI-363): For Ada 2005, we limit the building of the actual
1158 -- subtype to the parameter and dereference cases, since other aliased
1159 -- objects are unconstrained (unless the nominal subtype is explicitly
1160 -- constrained). (But we also need to test for renamings???)
1162 if Present (Lhs)
1163 and then (Present (Param_Entity (Lhs))
1164 or else (Ada_Version < Ada_05
1165 and then not Is_Constrained (T_Typ)
1166 and then Is_Aliased_View (Lhs)
1167 and then not Is_Aliased_Unconstrained_Component)
1168 or else (Ada_Version >= Ada_05
1169 and then not Is_Constrained (T_Typ)
1170 and then Nkind (Lhs) = N_Explicit_Dereference
1171 and then Nkind (Original_Node (Lhs)) /=
1172 N_Function_Call))
1173 then
1174 T_Typ := Get_Actual_Subtype (Lhs);
1175 end if;
1177 -- Nothing to do if the type is unconstrained (this is the case where
1178 -- the actual subtype in the RM sense of N is unconstrained and no check
1179 -- is required).
1181 if not Is_Constrained (T_Typ) then
1182 return;
1184 -- Ada 2005: nothing to do if the type is one for which there is a
1185 -- partial view that is constrained.
1187 elsif Ada_Version >= Ada_05
1188 and then Has_Constrained_Partial_View (Base_Type (T_Typ))
1189 then
1190 return;
1191 end if;
1193 -- Nothing to do if the type is an Unchecked_Union
1195 if Is_Unchecked_Union (Base_Type (T_Typ)) then
1196 return;
1197 end if;
1199 -- Suppress checks if the subtypes are the same. the check must be
1200 -- preserved in an assignment to a formal, because the constraint is
1201 -- given by the actual.
1203 if Nkind (Original_Node (N)) /= N_Allocator
1204 and then (No (Lhs)
1205 or else not Is_Entity_Name (Lhs)
1206 or else No (Param_Entity (Lhs)))
1207 then
1208 if (Etype (N) = Typ
1209 or else (Do_Access and then Designated_Type (Typ) = S_Typ))
1210 and then not Is_Aliased_View (Lhs)
1211 then
1212 return;
1213 end if;
1215 -- We can also eliminate checks on allocators with a subtype mark that
1216 -- coincides with the context type. The context type may be a subtype
1217 -- without a constraint (common case, a generic actual).
1219 elsif Nkind (Original_Node (N)) = N_Allocator
1220 and then Is_Entity_Name (Expression (Original_Node (N)))
1221 then
1222 declare
1223 Alloc_Typ : constant Entity_Id :=
1224 Entity (Expression (Original_Node (N)));
1226 begin
1227 if Alloc_Typ = T_Typ
1228 or else (Nkind (Parent (T_Typ)) = N_Subtype_Declaration
1229 and then Is_Entity_Name (
1230 Subtype_Indication (Parent (T_Typ)))
1231 and then Alloc_Typ = Base_Type (T_Typ))
1233 then
1234 return;
1235 end if;
1236 end;
1237 end if;
1239 -- See if we have a case where the types are both constrained, and all
1240 -- the constraints are constants. In this case, we can do the check
1241 -- successfully at compile time.
1243 -- We skip this check for the case where the node is a rewritten`
1244 -- allocator, because it already carries the context subtype, and
1245 -- extracting the discriminants from the aggregate is messy.
1247 if Is_Constrained (S_Typ)
1248 and then Nkind (Original_Node (N)) /= N_Allocator
1249 then
1250 declare
1251 DconT : Elmt_Id;
1252 Discr : Entity_Id;
1253 DconS : Elmt_Id;
1254 ItemS : Node_Id;
1255 ItemT : Node_Id;
1257 begin
1258 -- S_Typ may not have discriminants in the case where it is a
1259 -- private type completed by a default discriminated type. In that
1260 -- case, we need to get the constraints from the underlying_type.
1261 -- If the underlying type is unconstrained (i.e. has no default
1262 -- discriminants) no check is needed.
1264 if Has_Discriminants (S_Typ) then
1265 Discr := First_Discriminant (S_Typ);
1266 DconS := First_Elmt (Discriminant_Constraint (S_Typ));
1268 else
1269 Discr := First_Discriminant (Underlying_Type (S_Typ));
1270 DconS :=
1271 First_Elmt
1272 (Discriminant_Constraint (Underlying_Type (S_Typ)));
1274 if No (DconS) then
1275 return;
1276 end if;
1278 -- A further optimization: if T_Typ is derived from S_Typ
1279 -- without imposing a constraint, no check is needed.
1281 if Nkind (Original_Node (Parent (T_Typ))) =
1282 N_Full_Type_Declaration
1283 then
1284 declare
1285 Type_Def : constant Node_Id :=
1286 Type_Definition
1287 (Original_Node (Parent (T_Typ)));
1288 begin
1289 if Nkind (Type_Def) = N_Derived_Type_Definition
1290 and then Is_Entity_Name (Subtype_Indication (Type_Def))
1291 and then Entity (Subtype_Indication (Type_Def)) = S_Typ
1292 then
1293 return;
1294 end if;
1295 end;
1296 end if;
1297 end if;
1299 DconT := First_Elmt (Discriminant_Constraint (T_Typ));
1301 while Present (Discr) loop
1302 ItemS := Node (DconS);
1303 ItemT := Node (DconT);
1305 -- For a discriminated component type constrained by the
1306 -- current instance of an enclosing type, there is no
1307 -- applicable discriminant check.
1309 if Nkind (ItemT) = N_Attribute_Reference
1310 and then Is_Access_Type (Etype (ItemT))
1311 and then Is_Entity_Name (Prefix (ItemT))
1312 and then Is_Type (Entity (Prefix (ItemT)))
1313 then
1314 return;
1315 end if;
1317 -- If the expressions for the discriminants are identical
1318 -- and it is side-effect free (for now just an entity),
1319 -- this may be a shared constraint, e.g. from a subtype
1320 -- without a constraint introduced as a generic actual.
1321 -- Examine other discriminants if any.
1323 if ItemS = ItemT
1324 and then Is_Entity_Name (ItemS)
1325 then
1326 null;
1328 elsif not Is_OK_Static_Expression (ItemS)
1329 or else not Is_OK_Static_Expression (ItemT)
1330 then
1331 exit;
1333 elsif Expr_Value (ItemS) /= Expr_Value (ItemT) then
1334 if Do_Access then -- needs run-time check.
1335 exit;
1336 else
1337 Apply_Compile_Time_Constraint_Error
1338 (N, "incorrect value for discriminant&?",
1339 CE_Discriminant_Check_Failed, Ent => Discr);
1340 return;
1341 end if;
1342 end if;
1344 Next_Elmt (DconS);
1345 Next_Elmt (DconT);
1346 Next_Discriminant (Discr);
1347 end loop;
1349 if No (Discr) then
1350 return;
1351 end if;
1352 end;
1353 end if;
1355 -- Here we need a discriminant check. First build the expression
1356 -- for the comparisons of the discriminants:
1358 -- (n.disc1 /= typ.disc1) or else
1359 -- (n.disc2 /= typ.disc2) or else
1360 -- ...
1361 -- (n.discn /= typ.discn)
1363 Cond := Build_Discriminant_Checks (N, T_Typ);
1365 -- If Lhs is set and is a parameter, then the condition is
1366 -- guarded by: lhs'constrained and then (condition built above)
1368 if Present (Param_Entity (Lhs)) then
1369 Cond :=
1370 Make_And_Then (Loc,
1371 Left_Opnd =>
1372 Make_Attribute_Reference (Loc,
1373 Prefix => New_Occurrence_Of (Param_Entity (Lhs), Loc),
1374 Attribute_Name => Name_Constrained),
1375 Right_Opnd => Cond);
1376 end if;
1378 if Do_Access then
1379 Cond := Guard_Access (Cond, Loc, N);
1380 end if;
1382 Insert_Action (N,
1383 Make_Raise_Constraint_Error (Loc,
1384 Condition => Cond,
1385 Reason => CE_Discriminant_Check_Failed));
1386 end Apply_Discriminant_Check;
1388 ------------------------
1389 -- Apply_Divide_Check --
1390 ------------------------
1392 procedure Apply_Divide_Check (N : Node_Id) is
1393 Loc : constant Source_Ptr := Sloc (N);
1394 Typ : constant Entity_Id := Etype (N);
1395 Left : constant Node_Id := Left_Opnd (N);
1396 Right : constant Node_Id := Right_Opnd (N);
1398 LLB : Uint;
1399 Llo : Uint;
1400 Lhi : Uint;
1401 LOK : Boolean;
1402 Rlo : Uint;
1403 Rhi : Uint;
1404 ROK : Boolean;
1406 pragma Warnings (Off, Lhi);
1407 -- Don't actually use this value
1409 begin
1410 if Expander_Active
1411 and then not Backend_Divide_Checks_On_Target
1412 and then Check_Needed (Right, Division_Check)
1413 then
1414 Determine_Range (Right, ROK, Rlo, Rhi, Assume_Valid => True);
1416 -- See if division by zero possible, and if so generate test. This
1417 -- part of the test is not controlled by the -gnato switch.
1419 if Do_Division_Check (N) then
1420 if (not ROK) or else (Rlo <= 0 and then 0 <= Rhi) then
1421 Insert_Action (N,
1422 Make_Raise_Constraint_Error (Loc,
1423 Condition =>
1424 Make_Op_Eq (Loc,
1425 Left_Opnd => Duplicate_Subexpr_Move_Checks (Right),
1426 Right_Opnd => Make_Integer_Literal (Loc, 0)),
1427 Reason => CE_Divide_By_Zero));
1428 end if;
1429 end if;
1431 -- Test for extremely annoying case of xxx'First divided by -1
1433 if Do_Overflow_Check (N) then
1434 if Nkind (N) = N_Op_Divide
1435 and then Is_Signed_Integer_Type (Typ)
1436 then
1437 Determine_Range (Left, LOK, Llo, Lhi, Assume_Valid => True);
1438 LLB := Expr_Value (Type_Low_Bound (Base_Type (Typ)));
1440 if ((not ROK) or else (Rlo <= (-1) and then (-1) <= Rhi))
1441 and then
1442 ((not LOK) or else (Llo = LLB))
1443 then
1444 Insert_Action (N,
1445 Make_Raise_Constraint_Error (Loc,
1446 Condition =>
1447 Make_And_Then (Loc,
1449 Make_Op_Eq (Loc,
1450 Left_Opnd =>
1451 Duplicate_Subexpr_Move_Checks (Left),
1452 Right_Opnd => Make_Integer_Literal (Loc, LLB)),
1454 Make_Op_Eq (Loc,
1455 Left_Opnd =>
1456 Duplicate_Subexpr (Right),
1457 Right_Opnd =>
1458 Make_Integer_Literal (Loc, -1))),
1459 Reason => CE_Overflow_Check_Failed));
1460 end if;
1461 end if;
1462 end if;
1463 end if;
1464 end Apply_Divide_Check;
1466 ----------------------------------
1467 -- Apply_Float_Conversion_Check --
1468 ----------------------------------
1470 -- Let F and I be the source and target types of the conversion. The RM
1471 -- specifies that a floating-point value X is rounded to the nearest
1472 -- integer, with halfway cases being rounded away from zero. The rounded
1473 -- value of X is checked against I'Range.
1475 -- The catch in the above paragraph is that there is no good way to know
1476 -- whether the round-to-integer operation resulted in overflow. A remedy is
1477 -- to perform a range check in the floating-point domain instead, however:
1479 -- (1) The bounds may not be known at compile time
1480 -- (2) The check must take into account rounding or truncation.
1481 -- (3) The range of type I may not be exactly representable in F.
1482 -- (4) For the rounding case, The end-points I'First - 0.5 and
1483 -- I'Last + 0.5 may or may not be in range, depending on the
1484 -- sign of I'First and I'Last.
1485 -- (5) X may be a NaN, which will fail any comparison
1487 -- The following steps correctly convert X with rounding:
1489 -- (1) If either I'First or I'Last is not known at compile time, use
1490 -- I'Base instead of I in the next three steps and perform a
1491 -- regular range check against I'Range after conversion.
1492 -- (2) If I'First - 0.5 is representable in F then let Lo be that
1493 -- value and define Lo_OK as (I'First > 0). Otherwise, let Lo be
1494 -- F'Machine (I'First) and let Lo_OK be (Lo >= I'First).
1495 -- In other words, take one of the closest floating-point numbers
1496 -- (which is an integer value) to I'First, and see if it is in
1497 -- range or not.
1498 -- (3) If I'Last + 0.5 is representable in F then let Hi be that value
1499 -- and define Hi_OK as (I'Last < 0). Otherwise, let Hi be
1500 -- F'Machine (I'Last) and let Hi_OK be (Hi <= I'Last).
1501 -- (4) Raise CE when (Lo_OK and X < Lo) or (not Lo_OK and X <= Lo)
1502 -- or (Hi_OK and X > Hi) or (not Hi_OK and X >= Hi)
1504 -- For the truncating case, replace steps (2) and (3) as follows:
1505 -- (2) If I'First > 0, then let Lo be F'Pred (I'First) and let Lo_OK
1506 -- be False. Otherwise, let Lo be F'Succ (I'First - 1) and let
1507 -- Lo_OK be True.
1508 -- (3) If I'Last < 0, then let Hi be F'Succ (I'Last) and let Hi_OK
1509 -- be False. Otherwise let Hi be F'Pred (I'Last + 1) and let
1510 -- Hi_OK be False
1512 procedure Apply_Float_Conversion_Check
1513 (Ck_Node : Node_Id;
1514 Target_Typ : Entity_Id)
1516 LB : constant Node_Id := Type_Low_Bound (Target_Typ);
1517 HB : constant Node_Id := Type_High_Bound (Target_Typ);
1518 Loc : constant Source_Ptr := Sloc (Ck_Node);
1519 Expr_Type : constant Entity_Id := Base_Type (Etype (Ck_Node));
1520 Target_Base : constant Entity_Id :=
1521 Implementation_Base_Type (Target_Typ);
1523 Par : constant Node_Id := Parent (Ck_Node);
1524 pragma Assert (Nkind (Par) = N_Type_Conversion);
1525 -- Parent of check node, must be a type conversion
1527 Truncate : constant Boolean := Float_Truncate (Par);
1528 Max_Bound : constant Uint :=
1529 UI_Expon
1530 (Machine_Radix (Expr_Type),
1531 Machine_Mantissa (Expr_Type) - 1) - 1;
1533 -- Largest bound, so bound plus or minus half is a machine number of F
1535 Ifirst, Ilast : Uint;
1536 -- Bounds of integer type
1538 Lo, Hi : Ureal;
1539 -- Bounds to check in floating-point domain
1541 Lo_OK, Hi_OK : Boolean;
1542 -- True iff Lo resp. Hi belongs to I'Range
1544 Lo_Chk, Hi_Chk : Node_Id;
1545 -- Expressions that are False iff check fails
1547 Reason : RT_Exception_Code;
1549 begin
1550 if not Compile_Time_Known_Value (LB)
1551 or not Compile_Time_Known_Value (HB)
1552 then
1553 declare
1554 -- First check that the value falls in the range of the base type,
1555 -- to prevent overflow during conversion and then perform a
1556 -- regular range check against the (dynamic) bounds.
1558 pragma Assert (Target_Base /= Target_Typ);
1560 Temp : constant Entity_Id :=
1561 Make_Defining_Identifier (Loc,
1562 Chars => New_Internal_Name ('T'));
1564 begin
1565 Apply_Float_Conversion_Check (Ck_Node, Target_Base);
1566 Set_Etype (Temp, Target_Base);
1568 Insert_Action (Parent (Par),
1569 Make_Object_Declaration (Loc,
1570 Defining_Identifier => Temp,
1571 Object_Definition => New_Occurrence_Of (Target_Typ, Loc),
1572 Expression => New_Copy_Tree (Par)),
1573 Suppress => All_Checks);
1575 Insert_Action (Par,
1576 Make_Raise_Constraint_Error (Loc,
1577 Condition =>
1578 Make_Not_In (Loc,
1579 Left_Opnd => New_Occurrence_Of (Temp, Loc),
1580 Right_Opnd => New_Occurrence_Of (Target_Typ, Loc)),
1581 Reason => CE_Range_Check_Failed));
1582 Rewrite (Par, New_Occurrence_Of (Temp, Loc));
1584 return;
1585 end;
1586 end if;
1588 -- Get the (static) bounds of the target type
1590 Ifirst := Expr_Value (LB);
1591 Ilast := Expr_Value (HB);
1593 -- A simple optimization: if the expression is a universal literal,
1594 -- we can do the comparison with the bounds and the conversion to
1595 -- an integer type statically. The range checks are unchanged.
1597 if Nkind (Ck_Node) = N_Real_Literal
1598 and then Etype (Ck_Node) = Universal_Real
1599 and then Is_Integer_Type (Target_Typ)
1600 and then Nkind (Parent (Ck_Node)) = N_Type_Conversion
1601 then
1602 declare
1603 Int_Val : constant Uint := UR_To_Uint (Realval (Ck_Node));
1605 begin
1606 if Int_Val <= Ilast and then Int_Val >= Ifirst then
1608 -- Conversion is safe
1610 Rewrite (Parent (Ck_Node),
1611 Make_Integer_Literal (Loc, UI_To_Int (Int_Val)));
1612 Analyze_And_Resolve (Parent (Ck_Node), Target_Typ);
1613 return;
1614 end if;
1615 end;
1616 end if;
1618 -- Check against lower bound
1620 if Truncate and then Ifirst > 0 then
1621 Lo := Pred (Expr_Type, UR_From_Uint (Ifirst));
1622 Lo_OK := False;
1624 elsif Truncate then
1625 Lo := Succ (Expr_Type, UR_From_Uint (Ifirst - 1));
1626 Lo_OK := True;
1628 elsif abs (Ifirst) < Max_Bound then
1629 Lo := UR_From_Uint (Ifirst) - Ureal_Half;
1630 Lo_OK := (Ifirst > 0);
1632 else
1633 Lo := Machine (Expr_Type, UR_From_Uint (Ifirst), Round_Even, Ck_Node);
1634 Lo_OK := (Lo >= UR_From_Uint (Ifirst));
1635 end if;
1637 if Lo_OK then
1639 -- Lo_Chk := (X >= Lo)
1641 Lo_Chk := Make_Op_Ge (Loc,
1642 Left_Opnd => Duplicate_Subexpr_No_Checks (Ck_Node),
1643 Right_Opnd => Make_Real_Literal (Loc, Lo));
1645 else
1646 -- Lo_Chk := (X > Lo)
1648 Lo_Chk := Make_Op_Gt (Loc,
1649 Left_Opnd => Duplicate_Subexpr_No_Checks (Ck_Node),
1650 Right_Opnd => Make_Real_Literal (Loc, Lo));
1651 end if;
1653 -- Check against higher bound
1655 if Truncate and then Ilast < 0 then
1656 Hi := Succ (Expr_Type, UR_From_Uint (Ilast));
1657 Lo_OK := False;
1659 elsif Truncate then
1660 Hi := Pred (Expr_Type, UR_From_Uint (Ilast + 1));
1661 Hi_OK := True;
1663 elsif abs (Ilast) < Max_Bound then
1664 Hi := UR_From_Uint (Ilast) + Ureal_Half;
1665 Hi_OK := (Ilast < 0);
1666 else
1667 Hi := Machine (Expr_Type, UR_From_Uint (Ilast), Round_Even, Ck_Node);
1668 Hi_OK := (Hi <= UR_From_Uint (Ilast));
1669 end if;
1671 if Hi_OK then
1673 -- Hi_Chk := (X <= Hi)
1675 Hi_Chk := Make_Op_Le (Loc,
1676 Left_Opnd => Duplicate_Subexpr_No_Checks (Ck_Node),
1677 Right_Opnd => Make_Real_Literal (Loc, Hi));
1679 else
1680 -- Hi_Chk := (X < Hi)
1682 Hi_Chk := Make_Op_Lt (Loc,
1683 Left_Opnd => Duplicate_Subexpr_No_Checks (Ck_Node),
1684 Right_Opnd => Make_Real_Literal (Loc, Hi));
1685 end if;
1687 -- If the bounds of the target type are the same as those of the base
1688 -- type, the check is an overflow check as a range check is not
1689 -- performed in these cases.
1691 if Expr_Value (Type_Low_Bound (Target_Base)) = Ifirst
1692 and then Expr_Value (Type_High_Bound (Target_Base)) = Ilast
1693 then
1694 Reason := CE_Overflow_Check_Failed;
1695 else
1696 Reason := CE_Range_Check_Failed;
1697 end if;
1699 -- Raise CE if either conditions does not hold
1701 Insert_Action (Ck_Node,
1702 Make_Raise_Constraint_Error (Loc,
1703 Condition => Make_Op_Not (Loc, Make_And_Then (Loc, Lo_Chk, Hi_Chk)),
1704 Reason => Reason));
1705 end Apply_Float_Conversion_Check;
1707 ------------------------
1708 -- Apply_Length_Check --
1709 ------------------------
1711 procedure Apply_Length_Check
1712 (Ck_Node : Node_Id;
1713 Target_Typ : Entity_Id;
1714 Source_Typ : Entity_Id := Empty)
1716 begin
1717 Apply_Selected_Length_Checks
1718 (Ck_Node, Target_Typ, Source_Typ, Do_Static => False);
1719 end Apply_Length_Check;
1721 -----------------------
1722 -- Apply_Range_Check --
1723 -----------------------
1725 procedure Apply_Range_Check
1726 (Ck_Node : Node_Id;
1727 Target_Typ : Entity_Id;
1728 Source_Typ : Entity_Id := Empty)
1730 begin
1731 Apply_Selected_Range_Checks
1732 (Ck_Node, Target_Typ, Source_Typ, Do_Static => False);
1733 end Apply_Range_Check;
1735 ------------------------------
1736 -- Apply_Scalar_Range_Check --
1737 ------------------------------
1739 -- Note that Apply_Scalar_Range_Check never turns the Do_Range_Check flag
1740 -- off if it is already set on.
1742 procedure Apply_Scalar_Range_Check
1743 (Expr : Node_Id;
1744 Target_Typ : Entity_Id;
1745 Source_Typ : Entity_Id := Empty;
1746 Fixed_Int : Boolean := False)
1748 Parnt : constant Node_Id := Parent (Expr);
1749 S_Typ : Entity_Id;
1750 Arr : Node_Id := Empty; -- initialize to prevent warning
1751 Arr_Typ : Entity_Id := Empty; -- initialize to prevent warning
1752 OK : Boolean;
1754 Is_Subscr_Ref : Boolean;
1755 -- Set true if Expr is a subscript
1757 Is_Unconstrained_Subscr_Ref : Boolean;
1758 -- Set true if Expr is a subscript of an unconstrained array. In this
1759 -- case we do not attempt to do an analysis of the value against the
1760 -- range of the subscript, since we don't know the actual subtype.
1762 Int_Real : Boolean;
1763 -- Set to True if Expr should be regarded as a real value even though
1764 -- the type of Expr might be discrete.
1766 procedure Bad_Value;
1767 -- Procedure called if value is determined to be out of range
1769 ---------------
1770 -- Bad_Value --
1771 ---------------
1773 procedure Bad_Value is
1774 begin
1775 Apply_Compile_Time_Constraint_Error
1776 (Expr, "value not in range of}?", CE_Range_Check_Failed,
1777 Ent => Target_Typ,
1778 Typ => Target_Typ);
1779 end Bad_Value;
1781 -- Start of processing for Apply_Scalar_Range_Check
1783 begin
1784 -- Return if check obviously not needed
1787 -- Not needed inside generic
1789 Inside_A_Generic
1791 -- Not needed if previous error
1793 or else Target_Typ = Any_Type
1794 or else Nkind (Expr) = N_Error
1796 -- Not needed for non-scalar type
1798 or else not Is_Scalar_Type (Target_Typ)
1800 -- Not needed if we know node raises CE already
1802 or else Raises_Constraint_Error (Expr)
1803 then
1804 return;
1805 end if;
1807 -- Now, see if checks are suppressed
1809 Is_Subscr_Ref :=
1810 Is_List_Member (Expr) and then Nkind (Parnt) = N_Indexed_Component;
1812 if Is_Subscr_Ref then
1813 Arr := Prefix (Parnt);
1814 Arr_Typ := Get_Actual_Subtype_If_Available (Arr);
1815 end if;
1817 if not Do_Range_Check (Expr) then
1819 -- Subscript reference. Check for Index_Checks suppressed
1821 if Is_Subscr_Ref then
1823 -- Check array type and its base type
1825 if Index_Checks_Suppressed (Arr_Typ)
1826 or else Index_Checks_Suppressed (Base_Type (Arr_Typ))
1827 then
1828 return;
1830 -- Check array itself if it is an entity name
1832 elsif Is_Entity_Name (Arr)
1833 and then Index_Checks_Suppressed (Entity (Arr))
1834 then
1835 return;
1837 -- Check expression itself if it is an entity name
1839 elsif Is_Entity_Name (Expr)
1840 and then Index_Checks_Suppressed (Entity (Expr))
1841 then
1842 return;
1843 end if;
1845 -- All other cases, check for Range_Checks suppressed
1847 else
1848 -- Check target type and its base type
1850 if Range_Checks_Suppressed (Target_Typ)
1851 or else Range_Checks_Suppressed (Base_Type (Target_Typ))
1852 then
1853 return;
1855 -- Check expression itself if it is an entity name
1857 elsif Is_Entity_Name (Expr)
1858 and then Range_Checks_Suppressed (Entity (Expr))
1859 then
1860 return;
1862 -- If Expr is part of an assignment statement, then check left
1863 -- side of assignment if it is an entity name.
1865 elsif Nkind (Parnt) = N_Assignment_Statement
1866 and then Is_Entity_Name (Name (Parnt))
1867 and then Range_Checks_Suppressed (Entity (Name (Parnt)))
1868 then
1869 return;
1870 end if;
1871 end if;
1872 end if;
1874 -- Do not set range checks if they are killed
1876 if Nkind (Expr) = N_Unchecked_Type_Conversion
1877 and then Kill_Range_Check (Expr)
1878 then
1879 return;
1880 end if;
1882 -- Do not set range checks for any values from System.Scalar_Values
1883 -- since the whole idea of such values is to avoid checking them!
1885 if Is_Entity_Name (Expr)
1886 and then Is_RTU (Scope (Entity (Expr)), System_Scalar_Values)
1887 then
1888 return;
1889 end if;
1891 -- Now see if we need a check
1893 if No (Source_Typ) then
1894 S_Typ := Etype (Expr);
1895 else
1896 S_Typ := Source_Typ;
1897 end if;
1899 if not Is_Scalar_Type (S_Typ) or else S_Typ = Any_Type then
1900 return;
1901 end if;
1903 Is_Unconstrained_Subscr_Ref :=
1904 Is_Subscr_Ref and then not Is_Constrained (Arr_Typ);
1906 -- Always do a range check if the source type includes infinities and
1907 -- the target type does not include infinities. We do not do this if
1908 -- range checks are killed.
1910 if Is_Floating_Point_Type (S_Typ)
1911 and then Has_Infinities (S_Typ)
1912 and then not Has_Infinities (Target_Typ)
1913 then
1914 Enable_Range_Check (Expr);
1915 end if;
1917 -- Return if we know expression is definitely in the range of the target
1918 -- type as determined by Determine_Range. Right now we only do this for
1919 -- discrete types, and not fixed-point or floating-point types.
1921 -- The additional less-precise tests below catch these cases
1923 -- Note: skip this if we are given a source_typ, since the point of
1924 -- supplying a Source_Typ is to stop us looking at the expression.
1925 -- We could sharpen this test to be out parameters only ???
1927 if Is_Discrete_Type (Target_Typ)
1928 and then Is_Discrete_Type (Etype (Expr))
1929 and then not Is_Unconstrained_Subscr_Ref
1930 and then No (Source_Typ)
1931 then
1932 declare
1933 Tlo : constant Node_Id := Type_Low_Bound (Target_Typ);
1934 Thi : constant Node_Id := Type_High_Bound (Target_Typ);
1935 Lo : Uint;
1936 Hi : Uint;
1938 begin
1939 if Compile_Time_Known_Value (Tlo)
1940 and then Compile_Time_Known_Value (Thi)
1941 then
1942 declare
1943 Lov : constant Uint := Expr_Value (Tlo);
1944 Hiv : constant Uint := Expr_Value (Thi);
1946 begin
1947 -- If range is null, we for sure have a constraint error
1948 -- (we don't even need to look at the value involved,
1949 -- since all possible values will raise CE).
1951 if Lov > Hiv then
1952 Bad_Value;
1953 return;
1954 end if;
1956 -- Otherwise determine range of value
1958 Determine_Range (Expr, OK, Lo, Hi, Assume_Valid => True);
1960 if OK then
1962 -- If definitely in range, all OK
1964 if Lo >= Lov and then Hi <= Hiv then
1965 return;
1967 -- If definitely not in range, warn
1969 elsif Lov > Hi or else Hiv < Lo then
1970 Bad_Value;
1971 return;
1973 -- Otherwise we don't know
1975 else
1976 null;
1977 end if;
1978 end if;
1979 end;
1980 end if;
1981 end;
1982 end if;
1984 Int_Real :=
1985 Is_Floating_Point_Type (S_Typ)
1986 or else (Is_Fixed_Point_Type (S_Typ) and then not Fixed_Int);
1988 -- Check if we can determine at compile time whether Expr is in the
1989 -- range of the target type. Note that if S_Typ is within the bounds
1990 -- of Target_Typ then this must be the case. This check is meaningful
1991 -- only if this is not a conversion between integer and real types.
1993 if not Is_Unconstrained_Subscr_Ref
1994 and then
1995 Is_Discrete_Type (S_Typ) = Is_Discrete_Type (Target_Typ)
1996 and then
1997 (In_Subrange_Of (S_Typ, Target_Typ, Fixed_Int)
1998 or else
1999 Is_In_Range (Expr, Target_Typ,
2000 Assume_Valid => True,
2001 Fixed_Int => Fixed_Int,
2002 Int_Real => Int_Real))
2003 then
2004 return;
2006 elsif Is_Out_Of_Range (Expr, Target_Typ,
2007 Assume_Valid => True,
2008 Fixed_Int => Fixed_Int,
2009 Int_Real => Int_Real)
2010 then
2011 Bad_Value;
2012 return;
2014 -- In the floating-point case, we only do range checks if the type is
2015 -- constrained. We definitely do NOT want range checks for unconstrained
2016 -- types, since we want to have infinities
2018 elsif Is_Floating_Point_Type (S_Typ) then
2019 if Is_Constrained (S_Typ) then
2020 Enable_Range_Check (Expr);
2021 end if;
2023 -- For all other cases we enable a range check unconditionally
2025 else
2026 Enable_Range_Check (Expr);
2027 return;
2028 end if;
2029 end Apply_Scalar_Range_Check;
2031 ----------------------------------
2032 -- Apply_Selected_Length_Checks --
2033 ----------------------------------
2035 procedure Apply_Selected_Length_Checks
2036 (Ck_Node : Node_Id;
2037 Target_Typ : Entity_Id;
2038 Source_Typ : Entity_Id;
2039 Do_Static : Boolean)
2041 Cond : Node_Id;
2042 R_Result : Check_Result;
2043 R_Cno : Node_Id;
2045 Loc : constant Source_Ptr := Sloc (Ck_Node);
2046 Checks_On : constant Boolean :=
2047 (not Index_Checks_Suppressed (Target_Typ))
2048 or else
2049 (not Length_Checks_Suppressed (Target_Typ));
2051 begin
2052 if not Expander_Active then
2053 return;
2054 end if;
2056 R_Result :=
2057 Selected_Length_Checks (Ck_Node, Target_Typ, Source_Typ, Empty);
2059 for J in 1 .. 2 loop
2060 R_Cno := R_Result (J);
2061 exit when No (R_Cno);
2063 -- A length check may mention an Itype which is attached to a
2064 -- subsequent node. At the top level in a package this can cause
2065 -- an order-of-elaboration problem, so we make sure that the itype
2066 -- is referenced now.
2068 if Ekind (Current_Scope) = E_Package
2069 and then Is_Compilation_Unit (Current_Scope)
2070 then
2071 Ensure_Defined (Target_Typ, Ck_Node);
2073 if Present (Source_Typ) then
2074 Ensure_Defined (Source_Typ, Ck_Node);
2076 elsif Is_Itype (Etype (Ck_Node)) then
2077 Ensure_Defined (Etype (Ck_Node), Ck_Node);
2078 end if;
2079 end if;
2081 -- If the item is a conditional raise of constraint error, then have
2082 -- a look at what check is being performed and ???
2084 if Nkind (R_Cno) = N_Raise_Constraint_Error
2085 and then Present (Condition (R_Cno))
2086 then
2087 Cond := Condition (R_Cno);
2089 -- Case where node does not now have a dynamic check
2091 if not Has_Dynamic_Length_Check (Ck_Node) then
2093 -- If checks are on, just insert the check
2095 if Checks_On then
2096 Insert_Action (Ck_Node, R_Cno);
2098 if not Do_Static then
2099 Set_Has_Dynamic_Length_Check (Ck_Node);
2100 end if;
2102 -- If checks are off, then analyze the length check after
2103 -- temporarily attaching it to the tree in case the relevant
2104 -- condition can be evaluted at compile time. We still want a
2105 -- compile time warning in this case.
2107 else
2108 Set_Parent (R_Cno, Ck_Node);
2109 Analyze (R_Cno);
2110 end if;
2111 end if;
2113 -- Output a warning if the condition is known to be True
2115 if Is_Entity_Name (Cond)
2116 and then Entity (Cond) = Standard_True
2117 then
2118 Apply_Compile_Time_Constraint_Error
2119 (Ck_Node, "wrong length for array of}?",
2120 CE_Length_Check_Failed,
2121 Ent => Target_Typ,
2122 Typ => Target_Typ);
2124 -- If we were only doing a static check, or if checks are not
2125 -- on, then we want to delete the check, since it is not needed.
2126 -- We do this by replacing the if statement by a null statement
2128 elsif Do_Static or else not Checks_On then
2129 Remove_Warning_Messages (R_Cno);
2130 Rewrite (R_Cno, Make_Null_Statement (Loc));
2131 end if;
2133 else
2134 Install_Static_Check (R_Cno, Loc);
2135 end if;
2136 end loop;
2137 end Apply_Selected_Length_Checks;
2139 ---------------------------------
2140 -- Apply_Selected_Range_Checks --
2141 ---------------------------------
2143 procedure Apply_Selected_Range_Checks
2144 (Ck_Node : Node_Id;
2145 Target_Typ : Entity_Id;
2146 Source_Typ : Entity_Id;
2147 Do_Static : Boolean)
2149 Cond : Node_Id;
2150 R_Result : Check_Result;
2151 R_Cno : Node_Id;
2153 Loc : constant Source_Ptr := Sloc (Ck_Node);
2154 Checks_On : constant Boolean :=
2155 (not Index_Checks_Suppressed (Target_Typ))
2156 or else
2157 (not Range_Checks_Suppressed (Target_Typ));
2159 begin
2160 if not Expander_Active or else not Checks_On then
2161 return;
2162 end if;
2164 R_Result :=
2165 Selected_Range_Checks (Ck_Node, Target_Typ, Source_Typ, Empty);
2167 for J in 1 .. 2 loop
2169 R_Cno := R_Result (J);
2170 exit when No (R_Cno);
2172 -- If the item is a conditional raise of constraint error, then have
2173 -- a look at what check is being performed and ???
2175 if Nkind (R_Cno) = N_Raise_Constraint_Error
2176 and then Present (Condition (R_Cno))
2177 then
2178 Cond := Condition (R_Cno);
2180 if not Has_Dynamic_Range_Check (Ck_Node) then
2181 Insert_Action (Ck_Node, R_Cno);
2183 if not Do_Static then
2184 Set_Has_Dynamic_Range_Check (Ck_Node);
2185 end if;
2186 end if;
2188 -- Output a warning if the condition is known to be True
2190 if Is_Entity_Name (Cond)
2191 and then Entity (Cond) = Standard_True
2192 then
2193 -- Since an N_Range is technically not an expression, we have
2194 -- to set one of the bounds to C_E and then just flag the
2195 -- N_Range. The warning message will point to the lower bound
2196 -- and complain about a range, which seems OK.
2198 if Nkind (Ck_Node) = N_Range then
2199 Apply_Compile_Time_Constraint_Error
2200 (Low_Bound (Ck_Node), "static range out of bounds of}?",
2201 CE_Range_Check_Failed,
2202 Ent => Target_Typ,
2203 Typ => Target_Typ);
2205 Set_Raises_Constraint_Error (Ck_Node);
2207 else
2208 Apply_Compile_Time_Constraint_Error
2209 (Ck_Node, "static value out of range of}?",
2210 CE_Range_Check_Failed,
2211 Ent => Target_Typ,
2212 Typ => Target_Typ);
2213 end if;
2215 -- If we were only doing a static check, or if checks are not
2216 -- on, then we want to delete the check, since it is not needed.
2217 -- We do this by replacing the if statement by a null statement
2219 elsif Do_Static or else not Checks_On then
2220 Remove_Warning_Messages (R_Cno);
2221 Rewrite (R_Cno, Make_Null_Statement (Loc));
2222 end if;
2224 else
2225 Install_Static_Check (R_Cno, Loc);
2226 end if;
2227 end loop;
2228 end Apply_Selected_Range_Checks;
2230 -------------------------------
2231 -- Apply_Static_Length_Check --
2232 -------------------------------
2234 procedure Apply_Static_Length_Check
2235 (Expr : Node_Id;
2236 Target_Typ : Entity_Id;
2237 Source_Typ : Entity_Id := Empty)
2239 begin
2240 Apply_Selected_Length_Checks
2241 (Expr, Target_Typ, Source_Typ, Do_Static => True);
2242 end Apply_Static_Length_Check;
2244 -------------------------------------
2245 -- Apply_Subscript_Validity_Checks --
2246 -------------------------------------
2248 procedure Apply_Subscript_Validity_Checks (Expr : Node_Id) is
2249 Sub : Node_Id;
2251 begin
2252 pragma Assert (Nkind (Expr) = N_Indexed_Component);
2254 -- Loop through subscripts
2256 Sub := First (Expressions (Expr));
2257 while Present (Sub) loop
2259 -- Check one subscript. Note that we do not worry about enumeration
2260 -- type with holes, since we will convert the value to a Pos value
2261 -- for the subscript, and that convert will do the necessary validity
2262 -- check.
2264 Ensure_Valid (Sub, Holes_OK => True);
2266 -- Move to next subscript
2268 Sub := Next (Sub);
2269 end loop;
2270 end Apply_Subscript_Validity_Checks;
2272 ----------------------------------
2273 -- Apply_Type_Conversion_Checks --
2274 ----------------------------------
2276 procedure Apply_Type_Conversion_Checks (N : Node_Id) is
2277 Target_Type : constant Entity_Id := Etype (N);
2278 Target_Base : constant Entity_Id := Base_Type (Target_Type);
2279 Expr : constant Node_Id := Expression (N);
2280 Expr_Type : constant Entity_Id := Etype (Expr);
2282 begin
2283 if Inside_A_Generic then
2284 return;
2286 -- Skip these checks if serious errors detected, there are some nasty
2287 -- situations of incomplete trees that blow things up.
2289 elsif Serious_Errors_Detected > 0 then
2290 return;
2292 -- Scalar type conversions of the form Target_Type (Expr) require a
2293 -- range check if we cannot be sure that Expr is in the base type of
2294 -- Target_Typ and also that Expr is in the range of Target_Typ. These
2295 -- are not quite the same condition from an implementation point of
2296 -- view, but clearly the second includes the first.
2298 elsif Is_Scalar_Type (Target_Type) then
2299 declare
2300 Conv_OK : constant Boolean := Conversion_OK (N);
2301 -- If the Conversion_OK flag on the type conversion is set and no
2302 -- floating point type is involved in the type conversion then
2303 -- fixed point values must be read as integral values.
2305 Float_To_Int : constant Boolean :=
2306 Is_Floating_Point_Type (Expr_Type)
2307 and then Is_Integer_Type (Target_Type);
2309 begin
2310 if not Overflow_Checks_Suppressed (Target_Base)
2311 and then not
2312 In_Subrange_Of (Expr_Type, Target_Base, Fixed_Int => Conv_OK)
2313 and then not Float_To_Int
2314 then
2315 Activate_Overflow_Check (N);
2316 end if;
2318 if not Range_Checks_Suppressed (Target_Type)
2319 and then not Range_Checks_Suppressed (Expr_Type)
2320 then
2321 if Float_To_Int then
2322 Apply_Float_Conversion_Check (Expr, Target_Type);
2323 else
2324 Apply_Scalar_Range_Check
2325 (Expr, Target_Type, Fixed_Int => Conv_OK);
2326 end if;
2327 end if;
2328 end;
2330 elsif Comes_From_Source (N)
2331 and then not Discriminant_Checks_Suppressed (Target_Type)
2332 and then Is_Record_Type (Target_Type)
2333 and then Is_Derived_Type (Target_Type)
2334 and then not Is_Tagged_Type (Target_Type)
2335 and then not Is_Constrained (Target_Type)
2336 and then Present (Stored_Constraint (Target_Type))
2337 then
2338 -- An unconstrained derived type may have inherited discriminant
2339 -- Build an actual discriminant constraint list using the stored
2340 -- constraint, to verify that the expression of the parent type
2341 -- satisfies the constraints imposed by the (unconstrained!)
2342 -- derived type. This applies to value conversions, not to view
2343 -- conversions of tagged types.
2345 declare
2346 Loc : constant Source_Ptr := Sloc (N);
2347 Cond : Node_Id;
2348 Constraint : Elmt_Id;
2349 Discr_Value : Node_Id;
2350 Discr : Entity_Id;
2352 New_Constraints : constant Elist_Id := New_Elmt_List;
2353 Old_Constraints : constant Elist_Id :=
2354 Discriminant_Constraint (Expr_Type);
2356 begin
2357 Constraint := First_Elmt (Stored_Constraint (Target_Type));
2358 while Present (Constraint) loop
2359 Discr_Value := Node (Constraint);
2361 if Is_Entity_Name (Discr_Value)
2362 and then Ekind (Entity (Discr_Value)) = E_Discriminant
2363 then
2364 Discr := Corresponding_Discriminant (Entity (Discr_Value));
2366 if Present (Discr)
2367 and then Scope (Discr) = Base_Type (Expr_Type)
2368 then
2369 -- Parent is constrained by new discriminant. Obtain
2370 -- Value of original discriminant in expression. If the
2371 -- new discriminant has been used to constrain more than
2372 -- one of the stored discriminants, this will provide the
2373 -- required consistency check.
2375 Append_Elmt (
2376 Make_Selected_Component (Loc,
2377 Prefix =>
2378 Duplicate_Subexpr_No_Checks
2379 (Expr, Name_Req => True),
2380 Selector_Name =>
2381 Make_Identifier (Loc, Chars (Discr))),
2382 New_Constraints);
2384 else
2385 -- Discriminant of more remote ancestor ???
2387 return;
2388 end if;
2390 -- Derived type definition has an explicit value for this
2391 -- stored discriminant.
2393 else
2394 Append_Elmt
2395 (Duplicate_Subexpr_No_Checks (Discr_Value),
2396 New_Constraints);
2397 end if;
2399 Next_Elmt (Constraint);
2400 end loop;
2402 -- Use the unconstrained expression type to retrieve the
2403 -- discriminants of the parent, and apply momentarily the
2404 -- discriminant constraint synthesized above.
2406 Set_Discriminant_Constraint (Expr_Type, New_Constraints);
2407 Cond := Build_Discriminant_Checks (Expr, Expr_Type);
2408 Set_Discriminant_Constraint (Expr_Type, Old_Constraints);
2410 Insert_Action (N,
2411 Make_Raise_Constraint_Error (Loc,
2412 Condition => Cond,
2413 Reason => CE_Discriminant_Check_Failed));
2414 end;
2416 -- For arrays, conversions are applied during expansion, to take into
2417 -- accounts changes of representation. The checks become range checks on
2418 -- the base type or length checks on the subtype, depending on whether
2419 -- the target type is unconstrained or constrained.
2421 else
2422 null;
2423 end if;
2424 end Apply_Type_Conversion_Checks;
2426 ----------------------------------------------
2427 -- Apply_Universal_Integer_Attribute_Checks --
2428 ----------------------------------------------
2430 procedure Apply_Universal_Integer_Attribute_Checks (N : Node_Id) is
2431 Loc : constant Source_Ptr := Sloc (N);
2432 Typ : constant Entity_Id := Etype (N);
2434 begin
2435 if Inside_A_Generic then
2436 return;
2438 -- Nothing to do if checks are suppressed
2440 elsif Range_Checks_Suppressed (Typ)
2441 and then Overflow_Checks_Suppressed (Typ)
2442 then
2443 return;
2445 -- Nothing to do if the attribute does not come from source. The
2446 -- internal attributes we generate of this type do not need checks,
2447 -- and furthermore the attempt to check them causes some circular
2448 -- elaboration orders when dealing with packed types.
2450 elsif not Comes_From_Source (N) then
2451 return;
2453 -- If the prefix is a selected component that depends on a discriminant
2454 -- the check may improperly expose a discriminant instead of using
2455 -- the bounds of the object itself. Set the type of the attribute to
2456 -- the base type of the context, so that a check will be imposed when
2457 -- needed (e.g. if the node appears as an index).
2459 elsif Nkind (Prefix (N)) = N_Selected_Component
2460 and then Ekind (Typ) = E_Signed_Integer_Subtype
2461 and then Depends_On_Discriminant (Scalar_Range (Typ))
2462 then
2463 Set_Etype (N, Base_Type (Typ));
2465 -- Otherwise, replace the attribute node with a type conversion node
2466 -- whose expression is the attribute, retyped to universal integer, and
2467 -- whose subtype mark is the target type. The call to analyze this
2468 -- conversion will set range and overflow checks as required for proper
2469 -- detection of an out of range value.
2471 else
2472 Set_Etype (N, Universal_Integer);
2473 Set_Analyzed (N, True);
2475 Rewrite (N,
2476 Make_Type_Conversion (Loc,
2477 Subtype_Mark => New_Occurrence_Of (Typ, Loc),
2478 Expression => Relocate_Node (N)));
2480 Analyze_And_Resolve (N, Typ);
2481 return;
2482 end if;
2483 end Apply_Universal_Integer_Attribute_Checks;
2485 -------------------------------
2486 -- Build_Discriminant_Checks --
2487 -------------------------------
2489 function Build_Discriminant_Checks
2490 (N : Node_Id;
2491 T_Typ : Entity_Id) return Node_Id
2493 Loc : constant Source_Ptr := Sloc (N);
2494 Cond : Node_Id;
2495 Disc : Elmt_Id;
2496 Disc_Ent : Entity_Id;
2497 Dref : Node_Id;
2498 Dval : Node_Id;
2500 function Aggregate_Discriminant_Val (Disc : Entity_Id) return Node_Id;
2502 ----------------------------------
2503 -- Aggregate_Discriminant_Value --
2504 ----------------------------------
2506 function Aggregate_Discriminant_Val (Disc : Entity_Id) return Node_Id is
2507 Assoc : Node_Id;
2509 begin
2510 -- The aggregate has been normalized with named associations. We use
2511 -- the Chars field to locate the discriminant to take into account
2512 -- discriminants in derived types, which carry the same name as those
2513 -- in the parent.
2515 Assoc := First (Component_Associations (N));
2516 while Present (Assoc) loop
2517 if Chars (First (Choices (Assoc))) = Chars (Disc) then
2518 return Expression (Assoc);
2519 else
2520 Next (Assoc);
2521 end if;
2522 end loop;
2524 -- Discriminant must have been found in the loop above
2526 raise Program_Error;
2527 end Aggregate_Discriminant_Val;
2529 -- Start of processing for Build_Discriminant_Checks
2531 begin
2532 -- Loop through discriminants evolving the condition
2534 Cond := Empty;
2535 Disc := First_Elmt (Discriminant_Constraint (T_Typ));
2537 -- For a fully private type, use the discriminants of the parent type
2539 if Is_Private_Type (T_Typ)
2540 and then No (Full_View (T_Typ))
2541 then
2542 Disc_Ent := First_Discriminant (Etype (Base_Type (T_Typ)));
2543 else
2544 Disc_Ent := First_Discriminant (T_Typ);
2545 end if;
2547 while Present (Disc) loop
2548 Dval := Node (Disc);
2550 if Nkind (Dval) = N_Identifier
2551 and then Ekind (Entity (Dval)) = E_Discriminant
2552 then
2553 Dval := New_Occurrence_Of (Discriminal (Entity (Dval)), Loc);
2554 else
2555 Dval := Duplicate_Subexpr_No_Checks (Dval);
2556 end if;
2558 -- If we have an Unchecked_Union node, we can infer the discriminants
2559 -- of the node.
2561 if Is_Unchecked_Union (Base_Type (T_Typ)) then
2562 Dref := New_Copy (
2563 Get_Discriminant_Value (
2564 First_Discriminant (T_Typ),
2565 T_Typ,
2566 Stored_Constraint (T_Typ)));
2568 elsif Nkind (N) = N_Aggregate then
2569 Dref :=
2570 Duplicate_Subexpr_No_Checks
2571 (Aggregate_Discriminant_Val (Disc_Ent));
2573 else
2574 Dref :=
2575 Make_Selected_Component (Loc,
2576 Prefix =>
2577 Duplicate_Subexpr_No_Checks (N, Name_Req => True),
2578 Selector_Name =>
2579 Make_Identifier (Loc, Chars (Disc_Ent)));
2581 Set_Is_In_Discriminant_Check (Dref);
2582 end if;
2584 Evolve_Or_Else (Cond,
2585 Make_Op_Ne (Loc,
2586 Left_Opnd => Dref,
2587 Right_Opnd => Dval));
2589 Next_Elmt (Disc);
2590 Next_Discriminant (Disc_Ent);
2591 end loop;
2593 return Cond;
2594 end Build_Discriminant_Checks;
2596 ------------------
2597 -- Check_Needed --
2598 ------------------
2600 function Check_Needed (Nod : Node_Id; Check : Check_Type) return Boolean is
2601 N : Node_Id;
2602 P : Node_Id;
2603 K : Node_Kind;
2604 L : Node_Id;
2605 R : Node_Id;
2607 begin
2608 -- Always check if not simple entity
2610 if Nkind (Nod) not in N_Has_Entity
2611 or else not Comes_From_Source (Nod)
2612 then
2613 return True;
2614 end if;
2616 -- Look up tree for short circuit
2618 N := Nod;
2619 loop
2620 P := Parent (N);
2621 K := Nkind (P);
2623 -- Done if out of subexpression (note that we allow generated stuff
2624 -- such as itype declarations in this context, to keep the loop going
2625 -- since we may well have generated such stuff in complex situations.
2626 -- Also done if no parent (probably an error condition, but no point
2627 -- in behaving nasty if we find it!)
2629 if No (P)
2630 or else (K not in N_Subexpr and then Comes_From_Source (P))
2631 then
2632 return True;
2634 -- Or/Or Else case, where test is part of the right operand, or is
2635 -- part of one of the actions associated with the right operand, and
2636 -- the left operand is an equality test.
2638 elsif K = N_Op_Or then
2639 exit when N = Right_Opnd (P)
2640 and then Nkind (Left_Opnd (P)) = N_Op_Eq;
2642 elsif K = N_Or_Else then
2643 exit when (N = Right_Opnd (P)
2644 or else
2645 (Is_List_Member (N)
2646 and then List_Containing (N) = Actions (P)))
2647 and then Nkind (Left_Opnd (P)) = N_Op_Eq;
2649 -- Similar test for the And/And then case, where the left operand
2650 -- is an inequality test.
2652 elsif K = N_Op_And then
2653 exit when N = Right_Opnd (P)
2654 and then Nkind (Left_Opnd (P)) = N_Op_Ne;
2656 elsif K = N_And_Then then
2657 exit when (N = Right_Opnd (P)
2658 or else
2659 (Is_List_Member (N)
2660 and then List_Containing (N) = Actions (P)))
2661 and then Nkind (Left_Opnd (P)) = N_Op_Ne;
2662 end if;
2664 N := P;
2665 end loop;
2667 -- If we fall through the loop, then we have a conditional with an
2668 -- appropriate test as its left operand. So test further.
2670 L := Left_Opnd (P);
2671 R := Right_Opnd (L);
2672 L := Left_Opnd (L);
2674 -- Left operand of test must match original variable
2676 if Nkind (L) not in N_Has_Entity
2677 or else Entity (L) /= Entity (Nod)
2678 then
2679 return True;
2680 end if;
2682 -- Right operand of test must be key value (zero or null)
2684 case Check is
2685 when Access_Check =>
2686 if not Known_Null (R) then
2687 return True;
2688 end if;
2690 when Division_Check =>
2691 if not Compile_Time_Known_Value (R)
2692 or else Expr_Value (R) /= Uint_0
2693 then
2694 return True;
2695 end if;
2697 when others =>
2698 raise Program_Error;
2699 end case;
2701 -- Here we have the optimizable case, warn if not short-circuited
2703 if K = N_Op_And or else K = N_Op_Or then
2704 case Check is
2705 when Access_Check =>
2706 Error_Msg_N
2707 ("Constraint_Error may be raised (access check)?",
2708 Parent (Nod));
2709 when Division_Check =>
2710 Error_Msg_N
2711 ("Constraint_Error may be raised (zero divide)?",
2712 Parent (Nod));
2714 when others =>
2715 raise Program_Error;
2716 end case;
2718 if K = N_Op_And then
2719 Error_Msg_N ("use `AND THEN` instead of AND?", P);
2720 else
2721 Error_Msg_N ("use `OR ELSE` instead of OR?", P);
2722 end if;
2724 -- If not short-circuited, we need the ckeck
2726 return True;
2728 -- If short-circuited, we can omit the check
2730 else
2731 return False;
2732 end if;
2733 end Check_Needed;
2735 -----------------------------------
2736 -- Check_Valid_Lvalue_Subscripts --
2737 -----------------------------------
2739 procedure Check_Valid_Lvalue_Subscripts (Expr : Node_Id) is
2740 begin
2741 -- Skip this if range checks are suppressed
2743 if Range_Checks_Suppressed (Etype (Expr)) then
2744 return;
2746 -- Only do this check for expressions that come from source. We assume
2747 -- that expander generated assignments explicitly include any necessary
2748 -- checks. Note that this is not just an optimization, it avoids
2749 -- infinite recursions!
2751 elsif not Comes_From_Source (Expr) then
2752 return;
2754 -- For a selected component, check the prefix
2756 elsif Nkind (Expr) = N_Selected_Component then
2757 Check_Valid_Lvalue_Subscripts (Prefix (Expr));
2758 return;
2760 -- Case of indexed component
2762 elsif Nkind (Expr) = N_Indexed_Component then
2763 Apply_Subscript_Validity_Checks (Expr);
2765 -- Prefix may itself be or contain an indexed component, and these
2766 -- subscripts need checking as well.
2768 Check_Valid_Lvalue_Subscripts (Prefix (Expr));
2769 end if;
2770 end Check_Valid_Lvalue_Subscripts;
2772 ----------------------------------
2773 -- Null_Exclusion_Static_Checks --
2774 ----------------------------------
2776 procedure Null_Exclusion_Static_Checks (N : Node_Id) is
2777 Error_Node : Node_Id;
2778 Expr : Node_Id;
2779 Has_Null : constant Boolean := Has_Null_Exclusion (N);
2780 K : constant Node_Kind := Nkind (N);
2781 Typ : Entity_Id;
2783 begin
2784 pragma Assert
2785 (K = N_Component_Declaration
2786 or else K = N_Discriminant_Specification
2787 or else K = N_Function_Specification
2788 or else K = N_Object_Declaration
2789 or else K = N_Parameter_Specification);
2791 if K = N_Function_Specification then
2792 Typ := Etype (Defining_Entity (N));
2793 else
2794 Typ := Etype (Defining_Identifier (N));
2795 end if;
2797 case K is
2798 when N_Component_Declaration =>
2799 if Present (Access_Definition (Component_Definition (N))) then
2800 Error_Node := Component_Definition (N);
2801 else
2802 Error_Node := Subtype_Indication (Component_Definition (N));
2803 end if;
2805 when N_Discriminant_Specification =>
2806 Error_Node := Discriminant_Type (N);
2808 when N_Function_Specification =>
2809 Error_Node := Result_Definition (N);
2811 when N_Object_Declaration =>
2812 Error_Node := Object_Definition (N);
2814 when N_Parameter_Specification =>
2815 Error_Node := Parameter_Type (N);
2817 when others =>
2818 raise Program_Error;
2819 end case;
2821 if Has_Null then
2823 -- Enforce legality rule 3.10 (13): A null exclusion can only be
2824 -- applied to an access [sub]type.
2826 if not Is_Access_Type (Typ) then
2827 Error_Msg_N
2828 ("`NOT NULL` allowed only for an access type", Error_Node);
2830 -- Enforce legality rule RM 3.10(14/1): A null exclusion can only
2831 -- be applied to a [sub]type that does not exclude null already.
2833 elsif Can_Never_Be_Null (Typ)
2834 and then Comes_From_Source (Typ)
2835 then
2836 Error_Msg_NE
2837 ("`NOT NULL` not allowed (& already excludes null)",
2838 Error_Node, Typ);
2839 end if;
2840 end if;
2842 -- Check that null-excluding objects are always initialized, except for
2843 -- deferred constants, for which the expression will appear in the full
2844 -- declaration.
2846 if K = N_Object_Declaration
2847 and then No (Expression (N))
2848 and then not Constant_Present (N)
2849 and then not No_Initialization (N)
2850 then
2851 -- Add an expression that assigns null. This node is needed by
2852 -- Apply_Compile_Time_Constraint_Error, which will replace this with
2853 -- a Constraint_Error node.
2855 Set_Expression (N, Make_Null (Sloc (N)));
2856 Set_Etype (Expression (N), Etype (Defining_Identifier (N)));
2858 Apply_Compile_Time_Constraint_Error
2859 (N => Expression (N),
2860 Msg => "(Ada 2005) null-excluding objects must be initialized?",
2861 Reason => CE_Null_Not_Allowed);
2862 end if;
2864 -- Check that a null-excluding component, formal or object is not being
2865 -- assigned a null value. Otherwise generate a warning message and
2866 -- replace Expression (N) by an N_Constraint_Error node.
2868 if K /= N_Function_Specification then
2869 Expr := Expression (N);
2871 if Present (Expr) and then Known_Null (Expr) then
2872 case K is
2873 when N_Component_Declaration |
2874 N_Discriminant_Specification =>
2875 Apply_Compile_Time_Constraint_Error
2876 (N => Expr,
2877 Msg => "(Ada 2005) null not allowed " &
2878 "in null-excluding components?",
2879 Reason => CE_Null_Not_Allowed);
2881 when N_Object_Declaration =>
2882 Apply_Compile_Time_Constraint_Error
2883 (N => Expr,
2884 Msg => "(Ada 2005) null not allowed " &
2885 "in null-excluding objects?",
2886 Reason => CE_Null_Not_Allowed);
2888 when N_Parameter_Specification =>
2889 Apply_Compile_Time_Constraint_Error
2890 (N => Expr,
2891 Msg => "(Ada 2005) null not allowed " &
2892 "in null-excluding formals?",
2893 Reason => CE_Null_Not_Allowed);
2895 when others =>
2896 null;
2897 end case;
2898 end if;
2899 end if;
2900 end Null_Exclusion_Static_Checks;
2902 ----------------------------------
2903 -- Conditional_Statements_Begin --
2904 ----------------------------------
2906 procedure Conditional_Statements_Begin is
2907 begin
2908 Saved_Checks_TOS := Saved_Checks_TOS + 1;
2910 -- If stack overflows, kill all checks, that way we know to simply reset
2911 -- the number of saved checks to zero on return. This should never occur
2912 -- in practice.
2914 if Saved_Checks_TOS > Saved_Checks_Stack'Last then
2915 Kill_All_Checks;
2917 -- In the normal case, we just make a new stack entry saving the current
2918 -- number of saved checks for a later restore.
2920 else
2921 Saved_Checks_Stack (Saved_Checks_TOS) := Num_Saved_Checks;
2923 if Debug_Flag_CC then
2924 w ("Conditional_Statements_Begin: Num_Saved_Checks = ",
2925 Num_Saved_Checks);
2926 end if;
2927 end if;
2928 end Conditional_Statements_Begin;
2930 --------------------------------
2931 -- Conditional_Statements_End --
2932 --------------------------------
2934 procedure Conditional_Statements_End is
2935 begin
2936 pragma Assert (Saved_Checks_TOS > 0);
2938 -- If the saved checks stack overflowed, then we killed all checks, so
2939 -- setting the number of saved checks back to zero is correct. This
2940 -- should never occur in practice.
2942 if Saved_Checks_TOS > Saved_Checks_Stack'Last then
2943 Num_Saved_Checks := 0;
2945 -- In the normal case, restore the number of saved checks from the top
2946 -- stack entry.
2948 else
2949 Num_Saved_Checks := Saved_Checks_Stack (Saved_Checks_TOS);
2950 if Debug_Flag_CC then
2951 w ("Conditional_Statements_End: Num_Saved_Checks = ",
2952 Num_Saved_Checks);
2953 end if;
2954 end if;
2956 Saved_Checks_TOS := Saved_Checks_TOS - 1;
2957 end Conditional_Statements_End;
2959 ---------------------
2960 -- Determine_Range --
2961 ---------------------
2963 Cache_Size : constant := 2 ** 10;
2964 type Cache_Index is range 0 .. Cache_Size - 1;
2965 -- Determine size of below cache (power of 2 is more efficient!)
2967 Determine_Range_Cache_N : array (Cache_Index) of Node_Id;
2968 Determine_Range_Cache_V : array (Cache_Index) of Boolean;
2969 Determine_Range_Cache_Lo : array (Cache_Index) of Uint;
2970 Determine_Range_Cache_Hi : array (Cache_Index) of Uint;
2971 -- The above arrays are used to implement a small direct cache for
2972 -- Determine_Range calls. Because of the way Determine_Range recursively
2973 -- traces subexpressions, and because overflow checking calls the routine
2974 -- on the way up the tree, a quadratic behavior can otherwise be
2975 -- encountered in large expressions. The cache entry for node N is stored
2976 -- in the (N mod Cache_Size) entry, and can be validated by checking the
2977 -- actual node value stored there. The Range_Cache_V array records the
2978 -- setting of Assume_Valid for the cache entry.
2980 procedure Determine_Range
2981 (N : Node_Id;
2982 OK : out Boolean;
2983 Lo : out Uint;
2984 Hi : out Uint;
2985 Assume_Valid : Boolean := False)
2987 Typ : Entity_Id := Etype (N);
2988 -- Type to use, may get reset to base type for possibly invalid entity
2990 Lo_Left : Uint;
2991 Hi_Left : Uint;
2992 -- Lo and Hi bounds of left operand
2994 Lo_Right : Uint;
2995 Hi_Right : Uint;
2996 -- Lo and Hi bounds of right (or only) operand
2998 Bound : Node_Id;
2999 -- Temp variable used to hold a bound node
3001 Hbound : Uint;
3002 -- High bound of base type of expression
3004 Lor : Uint;
3005 Hir : Uint;
3006 -- Refined values for low and high bounds, after tightening
3008 OK1 : Boolean;
3009 -- Used in lower level calls to indicate if call succeeded
3011 Cindex : Cache_Index;
3012 -- Used to search cache
3014 function OK_Operands return Boolean;
3015 -- Used for binary operators. Determines the ranges of the left and
3016 -- right operands, and if they are both OK, returns True, and puts
3017 -- the results in Lo_Right, Hi_Right, Lo_Left, Hi_Left.
3019 -----------------
3020 -- OK_Operands --
3021 -----------------
3023 function OK_Operands return Boolean is
3024 begin
3025 Determine_Range
3026 (Left_Opnd (N), OK1, Lo_Left, Hi_Left, Assume_Valid);
3028 if not OK1 then
3029 return False;
3030 end if;
3032 Determine_Range
3033 (Right_Opnd (N), OK1, Lo_Right, Hi_Right, Assume_Valid);
3034 return OK1;
3035 end OK_Operands;
3037 -- Start of processing for Determine_Range
3039 begin
3040 -- Prevent junk warnings by initializing range variables
3042 Lo := No_Uint;
3043 Hi := No_Uint;
3044 Lor := No_Uint;
3045 Hir := No_Uint;
3047 -- If type is not defined, we can't determine its range
3049 if No (Typ)
3051 -- We don't deal with anything except discrete types
3053 or else not Is_Discrete_Type (Typ)
3055 -- Ignore type for which an error has been posted, since range in
3056 -- this case may well be a bogosity deriving from the error. Also
3057 -- ignore if error posted on the reference node.
3059 or else Error_Posted (N) or else Error_Posted (Typ)
3060 then
3061 OK := False;
3062 return;
3063 end if;
3065 -- For all other cases, we can determine the range
3067 OK := True;
3069 -- If value is compile time known, then the possible range is the one
3070 -- value that we know this expression definitely has!
3072 if Compile_Time_Known_Value (N) then
3073 Lo := Expr_Value (N);
3074 Hi := Lo;
3075 return;
3076 end if;
3078 -- Return if already in the cache
3080 Cindex := Cache_Index (N mod Cache_Size);
3082 if Determine_Range_Cache_N (Cindex) = N
3083 and then
3084 Determine_Range_Cache_V (Cindex) = Assume_Valid
3085 then
3086 Lo := Determine_Range_Cache_Lo (Cindex);
3087 Hi := Determine_Range_Cache_Hi (Cindex);
3088 return;
3089 end if;
3091 -- Otherwise, start by finding the bounds of the type of the expression,
3092 -- the value cannot be outside this range (if it is, then we have an
3093 -- overflow situation, which is a separate check, we are talking here
3094 -- only about the expression value).
3096 -- First a check, never try to find the bounds of a generic type, since
3097 -- these bounds are always junk values, and it is only valid to look at
3098 -- the bounds in an instance.
3100 if Is_Generic_Type (Typ) then
3101 OK := False;
3102 return;
3103 end if;
3105 -- First step, change to use base type unless we know the value is valid
3107 if (Is_Entity_Name (N) and then Is_Known_Valid (Entity (N)))
3108 or else Assume_No_Invalid_Values
3109 or else Assume_Valid
3110 then
3111 null;
3112 else
3113 Typ := Underlying_Type (Base_Type (Typ));
3114 end if;
3116 -- We use the actual bound unless it is dynamic, in which case use the
3117 -- corresponding base type bound if possible. If we can't get a bound
3118 -- then we figure we can't determine the range (a peculiar case, that
3119 -- perhaps cannot happen, but there is no point in bombing in this
3120 -- optimization circuit.
3122 -- First the low bound
3124 Bound := Type_Low_Bound (Typ);
3126 if Compile_Time_Known_Value (Bound) then
3127 Lo := Expr_Value (Bound);
3129 elsif Compile_Time_Known_Value (Type_Low_Bound (Base_Type (Typ))) then
3130 Lo := Expr_Value (Type_Low_Bound (Base_Type (Typ)));
3132 else
3133 OK := False;
3134 return;
3135 end if;
3137 -- Now the high bound
3139 Bound := Type_High_Bound (Typ);
3141 -- We need the high bound of the base type later on, and this should
3142 -- always be compile time known. Again, it is not clear that this
3143 -- can ever be false, but no point in bombing.
3145 if Compile_Time_Known_Value (Type_High_Bound (Base_Type (Typ))) then
3146 Hbound := Expr_Value (Type_High_Bound (Base_Type (Typ)));
3147 Hi := Hbound;
3149 else
3150 OK := False;
3151 return;
3152 end if;
3154 -- If we have a static subtype, then that may have a tighter bound so
3155 -- use the upper bound of the subtype instead in this case.
3157 if Compile_Time_Known_Value (Bound) then
3158 Hi := Expr_Value (Bound);
3159 end if;
3161 -- We may be able to refine this value in certain situations. If any
3162 -- refinement is possible, then Lor and Hir are set to possibly tighter
3163 -- bounds, and OK1 is set to True.
3165 case Nkind (N) is
3167 -- For unary plus, result is limited by range of operand
3169 when N_Op_Plus =>
3170 Determine_Range
3171 (Right_Opnd (N), OK1, Lor, Hir, Assume_Valid);
3173 -- For unary minus, determine range of operand, and negate it
3175 when N_Op_Minus =>
3176 Determine_Range
3177 (Right_Opnd (N), OK1, Lo_Right, Hi_Right, Assume_Valid);
3179 if OK1 then
3180 Lor := -Hi_Right;
3181 Hir := -Lo_Right;
3182 end if;
3184 -- For binary addition, get range of each operand and do the
3185 -- addition to get the result range.
3187 when N_Op_Add =>
3188 if OK_Operands then
3189 Lor := Lo_Left + Lo_Right;
3190 Hir := Hi_Left + Hi_Right;
3191 end if;
3193 -- Division is tricky. The only case we consider is where the right
3194 -- operand is a positive constant, and in this case we simply divide
3195 -- the bounds of the left operand
3197 when N_Op_Divide =>
3198 if OK_Operands then
3199 if Lo_Right = Hi_Right
3200 and then Lo_Right > 0
3201 then
3202 Lor := Lo_Left / Lo_Right;
3203 Hir := Hi_Left / Lo_Right;
3205 else
3206 OK1 := False;
3207 end if;
3208 end if;
3210 -- For binary subtraction, get range of each operand and do the worst
3211 -- case subtraction to get the result range.
3213 when N_Op_Subtract =>
3214 if OK_Operands then
3215 Lor := Lo_Left - Hi_Right;
3216 Hir := Hi_Left - Lo_Right;
3217 end if;
3219 -- For MOD, if right operand is a positive constant, then result must
3220 -- be in the allowable range of mod results.
3222 when N_Op_Mod =>
3223 if OK_Operands then
3224 if Lo_Right = Hi_Right
3225 and then Lo_Right /= 0
3226 then
3227 if Lo_Right > 0 then
3228 Lor := Uint_0;
3229 Hir := Lo_Right - 1;
3231 else -- Lo_Right < 0
3232 Lor := Lo_Right + 1;
3233 Hir := Uint_0;
3234 end if;
3236 else
3237 OK1 := False;
3238 end if;
3239 end if;
3241 -- For REM, if right operand is a positive constant, then result must
3242 -- be in the allowable range of mod results.
3244 when N_Op_Rem =>
3245 if OK_Operands then
3246 if Lo_Right = Hi_Right
3247 and then Lo_Right /= 0
3248 then
3249 declare
3250 Dval : constant Uint := (abs Lo_Right) - 1;
3252 begin
3253 -- The sign of the result depends on the sign of the
3254 -- dividend (but not on the sign of the divisor, hence
3255 -- the abs operation above).
3257 if Lo_Left < 0 then
3258 Lor := -Dval;
3259 else
3260 Lor := Uint_0;
3261 end if;
3263 if Hi_Left < 0 then
3264 Hir := Uint_0;
3265 else
3266 Hir := Dval;
3267 end if;
3268 end;
3270 else
3271 OK1 := False;
3272 end if;
3273 end if;
3275 -- Attribute reference cases
3277 when N_Attribute_Reference =>
3278 case Attribute_Name (N) is
3280 -- For Pos/Val attributes, we can refine the range using the
3281 -- possible range of values of the attribute expression.
3283 when Name_Pos | Name_Val =>
3284 Determine_Range
3285 (First (Expressions (N)), OK1, Lor, Hir, Assume_Valid);
3287 -- For Length attribute, use the bounds of the corresponding
3288 -- index type to refine the range.
3290 when Name_Length =>
3291 declare
3292 Atyp : Entity_Id := Etype (Prefix (N));
3293 Inum : Nat;
3294 Indx : Node_Id;
3296 LL, LU : Uint;
3297 UL, UU : Uint;
3299 begin
3300 if Is_Access_Type (Atyp) then
3301 Atyp := Designated_Type (Atyp);
3302 end if;
3304 -- For string literal, we know exact value
3306 if Ekind (Atyp) = E_String_Literal_Subtype then
3307 OK := True;
3308 Lo := String_Literal_Length (Atyp);
3309 Hi := String_Literal_Length (Atyp);
3310 return;
3311 end if;
3313 -- Otherwise check for expression given
3315 if No (Expressions (N)) then
3316 Inum := 1;
3317 else
3318 Inum :=
3319 UI_To_Int (Expr_Value (First (Expressions (N))));
3320 end if;
3322 Indx := First_Index (Atyp);
3323 for J in 2 .. Inum loop
3324 Indx := Next_Index (Indx);
3325 end loop;
3327 Determine_Range
3328 (Type_Low_Bound (Etype (Indx)), OK1, LL, LU,
3329 Assume_Valid);
3331 if OK1 then
3332 Determine_Range
3333 (Type_High_Bound (Etype (Indx)), OK1, UL, UU,
3334 Assume_Valid);
3336 if OK1 then
3338 -- The maximum value for Length is the biggest
3339 -- possible gap between the values of the bounds.
3340 -- But of course, this value cannot be negative.
3342 Hir := UI_Max (Uint_0, UU - LL + 1);
3344 -- For constrained arrays, the minimum value for
3345 -- Length is taken from the actual value of the
3346 -- bounds, since the index will be exactly of
3347 -- this subtype.
3349 if Is_Constrained (Atyp) then
3350 Lor := UI_Max (Uint_0, UL - LU + 1);
3352 -- For an unconstrained array, the minimum value
3353 -- for length is always zero.
3355 else
3356 Lor := Uint_0;
3357 end if;
3358 end if;
3359 end if;
3360 end;
3362 -- No special handling for other attributes
3363 -- Probably more opportunities exist here ???
3365 when others =>
3366 OK1 := False;
3368 end case;
3370 -- For type conversion from one discrete type to another, we can
3371 -- refine the range using the converted value.
3373 when N_Type_Conversion =>
3374 Determine_Range (Expression (N), OK1, Lor, Hir, Assume_Valid);
3376 -- Nothing special to do for all other expression kinds
3378 when others =>
3379 OK1 := False;
3380 Lor := No_Uint;
3381 Hir := No_Uint;
3382 end case;
3384 -- At this stage, if OK1 is true, then we know that the actual
3385 -- result of the computed expression is in the range Lor .. Hir.
3386 -- We can use this to restrict the possible range of results.
3388 if OK1 then
3390 -- If the refined value of the low bound is greater than the
3391 -- type high bound, then reset it to the more restrictive
3392 -- value. However, we do NOT do this for the case of a modular
3393 -- type where the possible upper bound on the value is above the
3394 -- base type high bound, because that means the result could wrap.
3396 if Lor > Lo
3397 and then not (Is_Modular_Integer_Type (Typ)
3398 and then Hir > Hbound)
3399 then
3400 Lo := Lor;
3401 end if;
3403 -- Similarly, if the refined value of the high bound is less
3404 -- than the value so far, then reset it to the more restrictive
3405 -- value. Again, we do not do this if the refined low bound is
3406 -- negative for a modular type, since this would wrap.
3408 if Hir < Hi
3409 and then not (Is_Modular_Integer_Type (Typ)
3410 and then Lor < Uint_0)
3411 then
3412 Hi := Hir;
3413 end if;
3414 end if;
3416 -- Set cache entry for future call and we are all done
3418 Determine_Range_Cache_N (Cindex) := N;
3419 Determine_Range_Cache_V (Cindex) := Assume_Valid;
3420 Determine_Range_Cache_Lo (Cindex) := Lo;
3421 Determine_Range_Cache_Hi (Cindex) := Hi;
3422 return;
3424 -- If any exception occurs, it means that we have some bug in the compiler
3425 -- possibly triggered by a previous error, or by some unforseen peculiar
3426 -- occurrence. However, this is only an optimization attempt, so there is
3427 -- really no point in crashing the compiler. Instead we just decide, too
3428 -- bad, we can't figure out a range in this case after all.
3430 exception
3431 when others =>
3433 -- Debug flag K disables this behavior (useful for debugging)
3435 if Debug_Flag_K then
3436 raise;
3437 else
3438 OK := False;
3439 Lo := No_Uint;
3440 Hi := No_Uint;
3441 return;
3442 end if;
3443 end Determine_Range;
3445 ------------------------------------
3446 -- Discriminant_Checks_Suppressed --
3447 ------------------------------------
3449 function Discriminant_Checks_Suppressed (E : Entity_Id) return Boolean is
3450 begin
3451 if Present (E) then
3452 if Is_Unchecked_Union (E) then
3453 return True;
3454 elsif Checks_May_Be_Suppressed (E) then
3455 return Is_Check_Suppressed (E, Discriminant_Check);
3456 end if;
3457 end if;
3459 return Scope_Suppress (Discriminant_Check);
3460 end Discriminant_Checks_Suppressed;
3462 --------------------------------
3463 -- Division_Checks_Suppressed --
3464 --------------------------------
3466 function Division_Checks_Suppressed (E : Entity_Id) return Boolean is
3467 begin
3468 if Present (E) and then Checks_May_Be_Suppressed (E) then
3469 return Is_Check_Suppressed (E, Division_Check);
3470 else
3471 return Scope_Suppress (Division_Check);
3472 end if;
3473 end Division_Checks_Suppressed;
3475 -----------------------------------
3476 -- Elaboration_Checks_Suppressed --
3477 -----------------------------------
3479 function Elaboration_Checks_Suppressed (E : Entity_Id) return Boolean is
3480 begin
3481 -- The complication in this routine is that if we are in the dynamic
3482 -- model of elaboration, we also check All_Checks, since All_Checks
3483 -- does not set Elaboration_Check explicitly.
3485 if Present (E) then
3486 if Kill_Elaboration_Checks (E) then
3487 return True;
3489 elsif Checks_May_Be_Suppressed (E) then
3490 if Is_Check_Suppressed (E, Elaboration_Check) then
3491 return True;
3492 elsif Dynamic_Elaboration_Checks then
3493 return Is_Check_Suppressed (E, All_Checks);
3494 else
3495 return False;
3496 end if;
3497 end if;
3498 end if;
3500 if Scope_Suppress (Elaboration_Check) then
3501 return True;
3502 elsif Dynamic_Elaboration_Checks then
3503 return Scope_Suppress (All_Checks);
3504 else
3505 return False;
3506 end if;
3507 end Elaboration_Checks_Suppressed;
3509 ---------------------------
3510 -- Enable_Overflow_Check --
3511 ---------------------------
3513 procedure Enable_Overflow_Check (N : Node_Id) is
3514 Typ : constant Entity_Id := Base_Type (Etype (N));
3515 Chk : Nat;
3516 OK : Boolean;
3517 Ent : Entity_Id;
3518 Ofs : Uint;
3519 Lo : Uint;
3520 Hi : Uint;
3522 begin
3523 if Debug_Flag_CC then
3524 w ("Enable_Overflow_Check for node ", Int (N));
3525 Write_Str (" Source location = ");
3526 wl (Sloc (N));
3527 pg (Union_Id (N));
3528 end if;
3530 -- No check if overflow checks suppressed for type of node
3532 if Present (Etype (N))
3533 and then Overflow_Checks_Suppressed (Etype (N))
3534 then
3535 return;
3537 -- Nothing to do for unsigned integer types, which do not overflow
3539 elsif Is_Modular_Integer_Type (Typ) then
3540 return;
3542 -- Nothing to do if the range of the result is known OK. We skip this
3543 -- for conversions, since the caller already did the check, and in any
3544 -- case the condition for deleting the check for a type conversion is
3545 -- different.
3547 elsif Nkind (N) /= N_Type_Conversion then
3548 Determine_Range (N, OK, Lo, Hi, Assume_Valid => True);
3550 -- Note in the test below that we assume that the range is not OK
3551 -- if a bound of the range is equal to that of the type. That's not
3552 -- quite accurate but we do this for the following reasons:
3554 -- a) The way that Determine_Range works, it will typically report
3555 -- the bounds of the value as being equal to the bounds of the
3556 -- type, because it either can't tell anything more precise, or
3557 -- does not think it is worth the effort to be more precise.
3559 -- b) It is very unusual to have a situation in which this would
3560 -- generate an unnecessary overflow check (an example would be
3561 -- a subtype with a range 0 .. Integer'Last - 1 to which the
3562 -- literal value one is added).
3564 -- c) The alternative is a lot of special casing in this routine
3565 -- which would partially duplicate Determine_Range processing.
3567 if OK
3568 and then Lo > Expr_Value (Type_Low_Bound (Typ))
3569 and then Hi < Expr_Value (Type_High_Bound (Typ))
3570 then
3571 if Debug_Flag_CC then
3572 w ("No overflow check required");
3573 end if;
3575 return;
3576 end if;
3577 end if;
3579 -- If not in optimizing mode, set flag and we are done. We are also done
3580 -- (and just set the flag) if the type is not a discrete type, since it
3581 -- is not worth the effort to eliminate checks for other than discrete
3582 -- types. In addition, we take this same path if we have stored the
3583 -- maximum number of checks possible already (a very unlikely situation,
3584 -- but we do not want to blow up!)
3586 if Optimization_Level = 0
3587 or else not Is_Discrete_Type (Etype (N))
3588 or else Num_Saved_Checks = Saved_Checks'Last
3589 then
3590 Activate_Overflow_Check (N);
3592 if Debug_Flag_CC then
3593 w ("Optimization off");
3594 end if;
3596 return;
3597 end if;
3599 -- Otherwise evaluate and check the expression
3601 Find_Check
3602 (Expr => N,
3603 Check_Type => 'O',
3604 Target_Type => Empty,
3605 Entry_OK => OK,
3606 Check_Num => Chk,
3607 Ent => Ent,
3608 Ofs => Ofs);
3610 if Debug_Flag_CC then
3611 w ("Called Find_Check");
3612 w (" OK = ", OK);
3614 if OK then
3615 w (" Check_Num = ", Chk);
3616 w (" Ent = ", Int (Ent));
3617 Write_Str (" Ofs = ");
3618 pid (Ofs);
3619 end if;
3620 end if;
3622 -- If check is not of form to optimize, then set flag and we are done
3624 if not OK then
3625 Activate_Overflow_Check (N);
3626 return;
3627 end if;
3629 -- If check is already performed, then return without setting flag
3631 if Chk /= 0 then
3632 if Debug_Flag_CC then
3633 w ("Check suppressed!");
3634 end if;
3636 return;
3637 end if;
3639 -- Here we will make a new entry for the new check
3641 Activate_Overflow_Check (N);
3642 Num_Saved_Checks := Num_Saved_Checks + 1;
3643 Saved_Checks (Num_Saved_Checks) :=
3644 (Killed => False,
3645 Entity => Ent,
3646 Offset => Ofs,
3647 Check_Type => 'O',
3648 Target_Type => Empty);
3650 if Debug_Flag_CC then
3651 w ("Make new entry, check number = ", Num_Saved_Checks);
3652 w (" Entity = ", Int (Ent));
3653 Write_Str (" Offset = ");
3654 pid (Ofs);
3655 w (" Check_Type = O");
3656 w (" Target_Type = Empty");
3657 end if;
3659 -- If we get an exception, then something went wrong, probably because of
3660 -- an error in the structure of the tree due to an incorrect program. Or it
3661 -- may be a bug in the optimization circuit. In either case the safest
3662 -- thing is simply to set the check flag unconditionally.
3664 exception
3665 when others =>
3666 Activate_Overflow_Check (N);
3668 if Debug_Flag_CC then
3669 w (" exception occurred, overflow flag set");
3670 end if;
3672 return;
3673 end Enable_Overflow_Check;
3675 ------------------------
3676 -- Enable_Range_Check --
3677 ------------------------
3679 procedure Enable_Range_Check (N : Node_Id) is
3680 Chk : Nat;
3681 OK : Boolean;
3682 Ent : Entity_Id;
3683 Ofs : Uint;
3684 Ttyp : Entity_Id;
3685 P : Node_Id;
3687 begin
3688 -- Return if unchecked type conversion with range check killed. In this
3689 -- case we never set the flag (that's what Kill_Range_Check is about!)
3691 if Nkind (N) = N_Unchecked_Type_Conversion
3692 and then Kill_Range_Check (N)
3693 then
3694 return;
3695 end if;
3697 -- Check for various cases where we should suppress the range check
3699 -- No check if range checks suppressed for type of node
3701 if Present (Etype (N))
3702 and then Range_Checks_Suppressed (Etype (N))
3703 then
3704 return;
3706 -- No check if node is an entity name, and range checks are suppressed
3707 -- for this entity, or for the type of this entity.
3709 elsif Is_Entity_Name (N)
3710 and then (Range_Checks_Suppressed (Entity (N))
3711 or else Range_Checks_Suppressed (Etype (Entity (N))))
3712 then
3713 return;
3715 -- No checks if index of array, and index checks are suppressed for
3716 -- the array object or the type of the array.
3718 elsif Nkind (Parent (N)) = N_Indexed_Component then
3719 declare
3720 Pref : constant Node_Id := Prefix (Parent (N));
3721 begin
3722 if Is_Entity_Name (Pref)
3723 and then Index_Checks_Suppressed (Entity (Pref))
3724 then
3725 return;
3726 elsif Index_Checks_Suppressed (Etype (Pref)) then
3727 return;
3728 end if;
3729 end;
3730 end if;
3732 -- Debug trace output
3734 if Debug_Flag_CC then
3735 w ("Enable_Range_Check for node ", Int (N));
3736 Write_Str (" Source location = ");
3737 wl (Sloc (N));
3738 pg (Union_Id (N));
3739 end if;
3741 -- If not in optimizing mode, set flag and we are done. We are also done
3742 -- (and just set the flag) if the type is not a discrete type, since it
3743 -- is not worth the effort to eliminate checks for other than discrete
3744 -- types. In addition, we take this same path if we have stored the
3745 -- maximum number of checks possible already (a very unlikely situation,
3746 -- but we do not want to blow up!)
3748 if Optimization_Level = 0
3749 or else No (Etype (N))
3750 or else not Is_Discrete_Type (Etype (N))
3751 or else Num_Saved_Checks = Saved_Checks'Last
3752 then
3753 Activate_Range_Check (N);
3755 if Debug_Flag_CC then
3756 w ("Optimization off");
3757 end if;
3759 return;
3760 end if;
3762 -- Otherwise find out the target type
3764 P := Parent (N);
3766 -- For assignment, use left side subtype
3768 if Nkind (P) = N_Assignment_Statement
3769 and then Expression (P) = N
3770 then
3771 Ttyp := Etype (Name (P));
3773 -- For indexed component, use subscript subtype
3775 elsif Nkind (P) = N_Indexed_Component then
3776 declare
3777 Atyp : Entity_Id;
3778 Indx : Node_Id;
3779 Subs : Node_Id;
3781 begin
3782 Atyp := Etype (Prefix (P));
3784 if Is_Access_Type (Atyp) then
3785 Atyp := Designated_Type (Atyp);
3787 -- If the prefix is an access to an unconstrained array,
3788 -- perform check unconditionally: it depends on the bounds of
3789 -- an object and we cannot currently recognize whether the test
3790 -- may be redundant.
3792 if not Is_Constrained (Atyp) then
3793 Activate_Range_Check (N);
3794 return;
3795 end if;
3797 -- Ditto if the prefix is an explicit dereference whose designated
3798 -- type is unconstrained.
3800 elsif Nkind (Prefix (P)) = N_Explicit_Dereference
3801 and then not Is_Constrained (Atyp)
3802 then
3803 Activate_Range_Check (N);
3804 return;
3805 end if;
3807 Indx := First_Index (Atyp);
3808 Subs := First (Expressions (P));
3809 loop
3810 if Subs = N then
3811 Ttyp := Etype (Indx);
3812 exit;
3813 end if;
3815 Next_Index (Indx);
3816 Next (Subs);
3817 end loop;
3818 end;
3820 -- For now, ignore all other cases, they are not so interesting
3822 else
3823 if Debug_Flag_CC then
3824 w (" target type not found, flag set");
3825 end if;
3827 Activate_Range_Check (N);
3828 return;
3829 end if;
3831 -- Evaluate and check the expression
3833 Find_Check
3834 (Expr => N,
3835 Check_Type => 'R',
3836 Target_Type => Ttyp,
3837 Entry_OK => OK,
3838 Check_Num => Chk,
3839 Ent => Ent,
3840 Ofs => Ofs);
3842 if Debug_Flag_CC then
3843 w ("Called Find_Check");
3844 w ("Target_Typ = ", Int (Ttyp));
3845 w (" OK = ", OK);
3847 if OK then
3848 w (" Check_Num = ", Chk);
3849 w (" Ent = ", Int (Ent));
3850 Write_Str (" Ofs = ");
3851 pid (Ofs);
3852 end if;
3853 end if;
3855 -- If check is not of form to optimize, then set flag and we are done
3857 if not OK then
3858 if Debug_Flag_CC then
3859 w (" expression not of optimizable type, flag set");
3860 end if;
3862 Activate_Range_Check (N);
3863 return;
3864 end if;
3866 -- If check is already performed, then return without setting flag
3868 if Chk /= 0 then
3869 if Debug_Flag_CC then
3870 w ("Check suppressed!");
3871 end if;
3873 return;
3874 end if;
3876 -- Here we will make a new entry for the new check
3878 Activate_Range_Check (N);
3879 Num_Saved_Checks := Num_Saved_Checks + 1;
3880 Saved_Checks (Num_Saved_Checks) :=
3881 (Killed => False,
3882 Entity => Ent,
3883 Offset => Ofs,
3884 Check_Type => 'R',
3885 Target_Type => Ttyp);
3887 if Debug_Flag_CC then
3888 w ("Make new entry, check number = ", Num_Saved_Checks);
3889 w (" Entity = ", Int (Ent));
3890 Write_Str (" Offset = ");
3891 pid (Ofs);
3892 w (" Check_Type = R");
3893 w (" Target_Type = ", Int (Ttyp));
3894 pg (Union_Id (Ttyp));
3895 end if;
3897 -- If we get an exception, then something went wrong, probably because of
3898 -- an error in the structure of the tree due to an incorrect program. Or
3899 -- it may be a bug in the optimization circuit. In either case the safest
3900 -- thing is simply to set the check flag unconditionally.
3902 exception
3903 when others =>
3904 Activate_Range_Check (N);
3906 if Debug_Flag_CC then
3907 w (" exception occurred, range flag set");
3908 end if;
3910 return;
3911 end Enable_Range_Check;
3913 ------------------
3914 -- Ensure_Valid --
3915 ------------------
3917 procedure Ensure_Valid (Expr : Node_Id; Holes_OK : Boolean := False) is
3918 Typ : constant Entity_Id := Etype (Expr);
3920 begin
3921 -- Ignore call if we are not doing any validity checking
3923 if not Validity_Checks_On then
3924 return;
3926 -- Ignore call if range or validity checks suppressed on entity or type
3928 elsif Range_Or_Validity_Checks_Suppressed (Expr) then
3929 return;
3931 -- No check required if expression is from the expander, we assume the
3932 -- expander will generate whatever checks are needed. Note that this is
3933 -- not just an optimization, it avoids infinite recursions!
3935 -- Unchecked conversions must be checked, unless they are initialized
3936 -- scalar values, as in a component assignment in an init proc.
3938 -- In addition, we force a check if Force_Validity_Checks is set
3940 elsif not Comes_From_Source (Expr)
3941 and then not Force_Validity_Checks
3942 and then (Nkind (Expr) /= N_Unchecked_Type_Conversion
3943 or else Kill_Range_Check (Expr))
3944 then
3945 return;
3947 -- No check required if expression is known to have valid value
3949 elsif Expr_Known_Valid (Expr) then
3950 return;
3952 -- Ignore case of enumeration with holes where the flag is set not to
3953 -- worry about holes, since no special validity check is needed
3955 elsif Is_Enumeration_Type (Typ)
3956 and then Has_Non_Standard_Rep (Typ)
3957 and then Holes_OK
3958 then
3959 return;
3961 -- No check required on the left-hand side of an assignment
3963 elsif Nkind (Parent (Expr)) = N_Assignment_Statement
3964 and then Expr = Name (Parent (Expr))
3965 then
3966 return;
3968 -- No check on a univeral real constant. The context will eventually
3969 -- convert it to a machine number for some target type, or report an
3970 -- illegality.
3972 elsif Nkind (Expr) = N_Real_Literal
3973 and then Etype (Expr) = Universal_Real
3974 then
3975 return;
3977 -- If the expression denotes a component of a packed boolean arrray,
3978 -- no possible check applies. We ignore the old ACATS chestnuts that
3979 -- involve Boolean range True..True.
3981 -- Note: validity checks are generated for expressions that yield a
3982 -- scalar type, when it is possible to create a value that is outside of
3983 -- the type. If this is a one-bit boolean no such value exists. This is
3984 -- an optimization, and it also prevents compiler blowing up during the
3985 -- elaboration of improperly expanded packed array references.
3987 elsif Nkind (Expr) = N_Indexed_Component
3988 and then Is_Bit_Packed_Array (Etype (Prefix (Expr)))
3989 and then Root_Type (Etype (Expr)) = Standard_Boolean
3990 then
3991 return;
3993 -- An annoying special case. If this is an out parameter of a scalar
3994 -- type, then the value is not going to be accessed, therefore it is
3995 -- inappropriate to do any validity check at the call site.
3997 else
3998 -- Only need to worry about scalar types
4000 if Is_Scalar_Type (Typ) then
4001 declare
4002 P : Node_Id;
4003 N : Node_Id;
4004 E : Entity_Id;
4005 F : Entity_Id;
4006 A : Node_Id;
4007 L : List_Id;
4009 begin
4010 -- Find actual argument (which may be a parameter association)
4011 -- and the parent of the actual argument (the call statement)
4013 N := Expr;
4014 P := Parent (Expr);
4016 if Nkind (P) = N_Parameter_Association then
4017 N := P;
4018 P := Parent (N);
4019 end if;
4021 -- Only need to worry if we are argument of a procedure call
4022 -- since functions don't have out parameters. If this is an
4023 -- indirect or dispatching call, get signature from the
4024 -- subprogram type.
4026 if Nkind (P) = N_Procedure_Call_Statement then
4027 L := Parameter_Associations (P);
4029 if Is_Entity_Name (Name (P)) then
4030 E := Entity (Name (P));
4031 else
4032 pragma Assert (Nkind (Name (P)) = N_Explicit_Dereference);
4033 E := Etype (Name (P));
4034 end if;
4036 -- Only need to worry if there are indeed actuals, and if
4037 -- this could be a procedure call, otherwise we cannot get a
4038 -- match (either we are not an argument, or the mode of the
4039 -- formal is not OUT). This test also filters out the
4040 -- generic case.
4042 if Is_Non_Empty_List (L)
4043 and then Is_Subprogram (E)
4044 then
4045 -- This is the loop through parameters, looking for an
4046 -- OUT parameter for which we are the argument.
4048 F := First_Formal (E);
4049 A := First (L);
4050 while Present (F) loop
4051 if Ekind (F) = E_Out_Parameter and then A = N then
4052 return;
4053 end if;
4055 Next_Formal (F);
4056 Next (A);
4057 end loop;
4058 end if;
4059 end if;
4060 end;
4061 end if;
4062 end if;
4064 -- If we fall through, a validity check is required
4066 Insert_Valid_Check (Expr);
4068 if Is_Entity_Name (Expr)
4069 and then Safe_To_Capture_Value (Expr, Entity (Expr))
4070 then
4071 Set_Is_Known_Valid (Entity (Expr));
4072 end if;
4073 end Ensure_Valid;
4075 ----------------------
4076 -- Expr_Known_Valid --
4077 ----------------------
4079 function Expr_Known_Valid (Expr : Node_Id) return Boolean is
4080 Typ : constant Entity_Id := Etype (Expr);
4082 begin
4083 -- Non-scalar types are always considered valid, since they never give
4084 -- rise to the issues of erroneous or bounded error behavior that are
4085 -- the concern. In formal reference manual terms the notion of validity
4086 -- only applies to scalar types. Note that even when packed arrays are
4087 -- represented using modular types, they are still arrays semantically,
4088 -- so they are also always valid (in particular, the unused bits can be
4089 -- random rubbish without affecting the validity of the array value).
4091 if not Is_Scalar_Type (Typ) or else Is_Packed_Array_Type (Typ) then
4092 return True;
4094 -- If no validity checking, then everything is considered valid
4096 elsif not Validity_Checks_On then
4097 return True;
4099 -- Floating-point types are considered valid unless floating-point
4100 -- validity checks have been specifically turned on.
4102 elsif Is_Floating_Point_Type (Typ)
4103 and then not Validity_Check_Floating_Point
4104 then
4105 return True;
4107 -- If the expression is the value of an object that is known to be
4108 -- valid, then clearly the expression value itself is valid.
4110 elsif Is_Entity_Name (Expr)
4111 and then Is_Known_Valid (Entity (Expr))
4112 then
4113 return True;
4115 -- References to discriminants are always considered valid. The value
4116 -- of a discriminant gets checked when the object is built. Within the
4117 -- record, we consider it valid, and it is important to do so, since
4118 -- otherwise we can try to generate bogus validity checks which
4119 -- reference discriminants out of scope. Discriminants of concurrent
4120 -- types are excluded for the same reason.
4122 elsif Is_Entity_Name (Expr)
4123 and then Denotes_Discriminant (Expr, Check_Concurrent => True)
4124 then
4125 return True;
4127 -- If the type is one for which all values are known valid, then we are
4128 -- sure that the value is valid except in the slightly odd case where
4129 -- the expression is a reference to a variable whose size has been
4130 -- explicitly set to a value greater than the object size.
4132 elsif Is_Known_Valid (Typ) then
4133 if Is_Entity_Name (Expr)
4134 and then Ekind (Entity (Expr)) = E_Variable
4135 and then Esize (Entity (Expr)) > Esize (Typ)
4136 then
4137 return False;
4138 else
4139 return True;
4140 end if;
4142 -- Integer and character literals always have valid values, where
4143 -- appropriate these will be range checked in any case.
4145 elsif Nkind (Expr) = N_Integer_Literal
4146 or else
4147 Nkind (Expr) = N_Character_Literal
4148 then
4149 return True;
4151 -- If we have a type conversion or a qualification of a known valid
4152 -- value, then the result will always be valid.
4154 elsif Nkind (Expr) = N_Type_Conversion
4155 or else
4156 Nkind (Expr) = N_Qualified_Expression
4157 then
4158 return Expr_Known_Valid (Expression (Expr));
4160 -- The result of any operator is always considered valid, since we
4161 -- assume the necessary checks are done by the operator. For operators
4162 -- on floating-point operations, we must also check when the operation
4163 -- is the right-hand side of an assignment, or is an actual in a call.
4165 elsif Nkind (Expr) in N_Op then
4166 if Is_Floating_Point_Type (Typ)
4167 and then Validity_Check_Floating_Point
4168 and then
4169 (Nkind (Parent (Expr)) = N_Assignment_Statement
4170 or else Nkind (Parent (Expr)) = N_Function_Call
4171 or else Nkind (Parent (Expr)) = N_Parameter_Association)
4172 then
4173 return False;
4174 else
4175 return True;
4176 end if;
4178 -- The result of a membership test is always valid, since it is true or
4179 -- false, there are no other possibilities.
4181 elsif Nkind (Expr) in N_Membership_Test then
4182 return True;
4184 -- For all other cases, we do not know the expression is valid
4186 else
4187 return False;
4188 end if;
4189 end Expr_Known_Valid;
4191 ----------------
4192 -- Find_Check --
4193 ----------------
4195 procedure Find_Check
4196 (Expr : Node_Id;
4197 Check_Type : Character;
4198 Target_Type : Entity_Id;
4199 Entry_OK : out Boolean;
4200 Check_Num : out Nat;
4201 Ent : out Entity_Id;
4202 Ofs : out Uint)
4204 function Within_Range_Of
4205 (Target_Type : Entity_Id;
4206 Check_Type : Entity_Id) return Boolean;
4207 -- Given a requirement for checking a range against Target_Type, and
4208 -- and a range Check_Type against which a check has already been made,
4209 -- determines if the check against check type is sufficient to ensure
4210 -- that no check against Target_Type is required.
4212 ---------------------
4213 -- Within_Range_Of --
4214 ---------------------
4216 function Within_Range_Of
4217 (Target_Type : Entity_Id;
4218 Check_Type : Entity_Id) return Boolean
4220 begin
4221 if Target_Type = Check_Type then
4222 return True;
4224 else
4225 declare
4226 Tlo : constant Node_Id := Type_Low_Bound (Target_Type);
4227 Thi : constant Node_Id := Type_High_Bound (Target_Type);
4228 Clo : constant Node_Id := Type_Low_Bound (Check_Type);
4229 Chi : constant Node_Id := Type_High_Bound (Check_Type);
4231 begin
4232 if (Tlo = Clo
4233 or else (Compile_Time_Known_Value (Tlo)
4234 and then
4235 Compile_Time_Known_Value (Clo)
4236 and then
4237 Expr_Value (Clo) >= Expr_Value (Tlo)))
4238 and then
4239 (Thi = Chi
4240 or else (Compile_Time_Known_Value (Thi)
4241 and then
4242 Compile_Time_Known_Value (Chi)
4243 and then
4244 Expr_Value (Chi) <= Expr_Value (Clo)))
4245 then
4246 return True;
4247 else
4248 return False;
4249 end if;
4250 end;
4251 end if;
4252 end Within_Range_Of;
4254 -- Start of processing for Find_Check
4256 begin
4257 -- Establish default, in case no entry is found
4259 Check_Num := 0;
4261 -- Case of expression is simple entity reference
4263 if Is_Entity_Name (Expr) then
4264 Ent := Entity (Expr);
4265 Ofs := Uint_0;
4267 -- Case of expression is entity + known constant
4269 elsif Nkind (Expr) = N_Op_Add
4270 and then Compile_Time_Known_Value (Right_Opnd (Expr))
4271 and then Is_Entity_Name (Left_Opnd (Expr))
4272 then
4273 Ent := Entity (Left_Opnd (Expr));
4274 Ofs := Expr_Value (Right_Opnd (Expr));
4276 -- Case of expression is entity - known constant
4278 elsif Nkind (Expr) = N_Op_Subtract
4279 and then Compile_Time_Known_Value (Right_Opnd (Expr))
4280 and then Is_Entity_Name (Left_Opnd (Expr))
4281 then
4282 Ent := Entity (Left_Opnd (Expr));
4283 Ofs := UI_Negate (Expr_Value (Right_Opnd (Expr)));
4285 -- Any other expression is not of the right form
4287 else
4288 Ent := Empty;
4289 Ofs := Uint_0;
4290 Entry_OK := False;
4291 return;
4292 end if;
4294 -- Come here with expression of appropriate form, check if entity is an
4295 -- appropriate one for our purposes.
4297 if (Ekind (Ent) = E_Variable
4298 or else Is_Constant_Object (Ent))
4299 and then not Is_Library_Level_Entity (Ent)
4300 then
4301 Entry_OK := True;
4302 else
4303 Entry_OK := False;
4304 return;
4305 end if;
4307 -- See if there is matching check already
4309 for J in reverse 1 .. Num_Saved_Checks loop
4310 declare
4311 SC : Saved_Check renames Saved_Checks (J);
4313 begin
4314 if SC.Killed = False
4315 and then SC.Entity = Ent
4316 and then SC.Offset = Ofs
4317 and then SC.Check_Type = Check_Type
4318 and then Within_Range_Of (Target_Type, SC.Target_Type)
4319 then
4320 Check_Num := J;
4321 return;
4322 end if;
4323 end;
4324 end loop;
4326 -- If we fall through entry was not found
4328 return;
4329 end Find_Check;
4331 ---------------------------------
4332 -- Generate_Discriminant_Check --
4333 ---------------------------------
4335 -- Note: the code for this procedure is derived from the
4336 -- Emit_Discriminant_Check Routine in trans.c.
4338 procedure Generate_Discriminant_Check (N : Node_Id) is
4339 Loc : constant Source_Ptr := Sloc (N);
4340 Pref : constant Node_Id := Prefix (N);
4341 Sel : constant Node_Id := Selector_Name (N);
4343 Orig_Comp : constant Entity_Id :=
4344 Original_Record_Component (Entity (Sel));
4345 -- The original component to be checked
4347 Discr_Fct : constant Entity_Id :=
4348 Discriminant_Checking_Func (Orig_Comp);
4349 -- The discriminant checking function
4351 Discr : Entity_Id;
4352 -- One discriminant to be checked in the type
4354 Real_Discr : Entity_Id;
4355 -- Actual discriminant in the call
4357 Pref_Type : Entity_Id;
4358 -- Type of relevant prefix (ignoring private/access stuff)
4360 Args : List_Id;
4361 -- List of arguments for function call
4363 Formal : Entity_Id;
4364 -- Keep track of the formal corresponding to the actual we build for
4365 -- each discriminant, in order to be able to perform the necessary type
4366 -- conversions.
4368 Scomp : Node_Id;
4369 -- Selected component reference for checking function argument
4371 begin
4372 Pref_Type := Etype (Pref);
4374 -- Force evaluation of the prefix, so that it does not get evaluated
4375 -- twice (once for the check, once for the actual reference). Such a
4376 -- double evaluation is always a potential source of inefficiency,
4377 -- and is functionally incorrect in the volatile case, or when the
4378 -- prefix may have side-effects. An entity or a component of an
4379 -- entity requires no evaluation.
4381 if Is_Entity_Name (Pref) then
4382 if Treat_As_Volatile (Entity (Pref)) then
4383 Force_Evaluation (Pref, Name_Req => True);
4384 end if;
4386 elsif Treat_As_Volatile (Etype (Pref)) then
4387 Force_Evaluation (Pref, Name_Req => True);
4389 elsif Nkind (Pref) = N_Selected_Component
4390 and then Is_Entity_Name (Prefix (Pref))
4391 then
4392 null;
4394 else
4395 Force_Evaluation (Pref, Name_Req => True);
4396 end if;
4398 -- For a tagged type, use the scope of the original component to
4399 -- obtain the type, because ???
4401 if Is_Tagged_Type (Scope (Orig_Comp)) then
4402 Pref_Type := Scope (Orig_Comp);
4404 -- For an untagged derived type, use the discriminants of the parent
4405 -- which have been renamed in the derivation, possibly by a one-to-many
4406 -- discriminant constraint. For non-tagged type, initially get the Etype
4407 -- of the prefix
4409 else
4410 if Is_Derived_Type (Pref_Type)
4411 and then Number_Discriminants (Pref_Type) /=
4412 Number_Discriminants (Etype (Base_Type (Pref_Type)))
4413 then
4414 Pref_Type := Etype (Base_Type (Pref_Type));
4415 end if;
4416 end if;
4418 -- We definitely should have a checking function, This routine should
4419 -- not be called if no discriminant checking function is present.
4421 pragma Assert (Present (Discr_Fct));
4423 -- Create the list of the actual parameters for the call. This list
4424 -- is the list of the discriminant fields of the record expression to
4425 -- be discriminant checked.
4427 Args := New_List;
4428 Formal := First_Formal (Discr_Fct);
4429 Discr := First_Discriminant (Pref_Type);
4430 while Present (Discr) loop
4432 -- If we have a corresponding discriminant field, and a parent
4433 -- subtype is present, then we want to use the corresponding
4434 -- discriminant since this is the one with the useful value.
4436 if Present (Corresponding_Discriminant (Discr))
4437 and then Ekind (Pref_Type) = E_Record_Type
4438 and then Present (Parent_Subtype (Pref_Type))
4439 then
4440 Real_Discr := Corresponding_Discriminant (Discr);
4441 else
4442 Real_Discr := Discr;
4443 end if;
4445 -- Construct the reference to the discriminant
4447 Scomp :=
4448 Make_Selected_Component (Loc,
4449 Prefix =>
4450 Unchecked_Convert_To (Pref_Type,
4451 Duplicate_Subexpr (Pref)),
4452 Selector_Name => New_Occurrence_Of (Real_Discr, Loc));
4454 -- Manually analyze and resolve this selected component. We really
4455 -- want it just as it appears above, and do not want the expander
4456 -- playing discriminal games etc with this reference. Then we append
4457 -- the argument to the list we are gathering.
4459 Set_Etype (Scomp, Etype (Real_Discr));
4460 Set_Analyzed (Scomp, True);
4461 Append_To (Args, Convert_To (Etype (Formal), Scomp));
4463 Next_Formal_With_Extras (Formal);
4464 Next_Discriminant (Discr);
4465 end loop;
4467 -- Now build and insert the call
4469 Insert_Action (N,
4470 Make_Raise_Constraint_Error (Loc,
4471 Condition =>
4472 Make_Function_Call (Loc,
4473 Name => New_Occurrence_Of (Discr_Fct, Loc),
4474 Parameter_Associations => Args),
4475 Reason => CE_Discriminant_Check_Failed));
4476 end Generate_Discriminant_Check;
4478 ---------------------------
4479 -- Generate_Index_Checks --
4480 ---------------------------
4482 procedure Generate_Index_Checks (N : Node_Id) is
4483 Loc : constant Source_Ptr := Sloc (N);
4484 A : constant Node_Id := Prefix (N);
4485 Sub : Node_Id;
4486 Ind : Nat;
4487 Num : List_Id;
4489 begin
4490 -- Ignore call if index checks suppressed for array object or type
4492 if (Is_Entity_Name (A) and then Index_Checks_Suppressed (Entity (A)))
4493 or else Index_Checks_Suppressed (Etype (A))
4494 then
4495 return;
4496 end if;
4498 -- Generate the checks
4500 Sub := First (Expressions (N));
4501 Ind := 1;
4502 while Present (Sub) loop
4503 if Do_Range_Check (Sub) then
4504 Set_Do_Range_Check (Sub, False);
4506 -- Force evaluation except for the case of a simple name of a
4507 -- non-volatile entity.
4509 if not Is_Entity_Name (Sub)
4510 or else Treat_As_Volatile (Entity (Sub))
4511 then
4512 Force_Evaluation (Sub);
4513 end if;
4515 -- Generate a raise of constraint error with the appropriate
4516 -- reason and a condition of the form:
4518 -- Base_Type(Sub) not in array'range (subscript)
4520 -- Note that the reason we generate the conversion to the base
4521 -- type here is that we definitely want the range check to take
4522 -- place, even if it looks like the subtype is OK. Optimization
4523 -- considerations that allow us to omit the check have already
4524 -- been taken into account in the setting of the Do_Range_Check
4525 -- flag earlier on.
4527 if Ind = 1 then
4528 Num := No_List;
4529 else
4530 Num := New_List (Make_Integer_Literal (Loc, Ind));
4531 end if;
4533 Insert_Action (N,
4534 Make_Raise_Constraint_Error (Loc,
4535 Condition =>
4536 Make_Not_In (Loc,
4537 Left_Opnd =>
4538 Convert_To (Base_Type (Etype (Sub)),
4539 Duplicate_Subexpr_Move_Checks (Sub)),
4540 Right_Opnd =>
4541 Make_Attribute_Reference (Loc,
4542 Prefix =>
4543 Duplicate_Subexpr_Move_Checks (A, Name_Req => True),
4544 Attribute_Name => Name_Range,
4545 Expressions => Num)),
4546 Reason => CE_Index_Check_Failed));
4547 end if;
4549 Ind := Ind + 1;
4550 Next (Sub);
4551 end loop;
4552 end Generate_Index_Checks;
4554 --------------------------
4555 -- Generate_Range_Check --
4556 --------------------------
4558 procedure Generate_Range_Check
4559 (N : Node_Id;
4560 Target_Type : Entity_Id;
4561 Reason : RT_Exception_Code)
4563 Loc : constant Source_Ptr := Sloc (N);
4564 Source_Type : constant Entity_Id := Etype (N);
4565 Source_Base_Type : constant Entity_Id := Base_Type (Source_Type);
4566 Target_Base_Type : constant Entity_Id := Base_Type (Target_Type);
4568 begin
4569 -- First special case, if the source type is already within the range
4570 -- of the target type, then no check is needed (probably we should have
4571 -- stopped Do_Range_Check from being set in the first place, but better
4572 -- late than later in preventing junk code!
4574 -- We do NOT apply this if the source node is a literal, since in this
4575 -- case the literal has already been labeled as having the subtype of
4576 -- the target.
4578 if In_Subrange_Of (Source_Type, Target_Type)
4579 and then not
4580 (Nkind (N) = N_Integer_Literal
4581 or else
4582 Nkind (N) = N_Real_Literal
4583 or else
4584 Nkind (N) = N_Character_Literal
4585 or else
4586 (Is_Entity_Name (N)
4587 and then Ekind (Entity (N)) = E_Enumeration_Literal))
4588 then
4589 return;
4590 end if;
4592 -- We need a check, so force evaluation of the node, so that it does
4593 -- not get evaluated twice (once for the check, once for the actual
4594 -- reference). Such a double evaluation is always a potential source
4595 -- of inefficiency, and is functionally incorrect in the volatile case.
4597 if not Is_Entity_Name (N)
4598 or else Treat_As_Volatile (Entity (N))
4599 then
4600 Force_Evaluation (N);
4601 end if;
4603 -- The easiest case is when Source_Base_Type and Target_Base_Type are
4604 -- the same since in this case we can simply do a direct check of the
4605 -- value of N against the bounds of Target_Type.
4607 -- [constraint_error when N not in Target_Type]
4609 -- Note: this is by far the most common case, for example all cases of
4610 -- checks on the RHS of assignments are in this category, but not all
4611 -- cases are like this. Notably conversions can involve two types.
4613 if Source_Base_Type = Target_Base_Type then
4614 Insert_Action (N,
4615 Make_Raise_Constraint_Error (Loc,
4616 Condition =>
4617 Make_Not_In (Loc,
4618 Left_Opnd => Duplicate_Subexpr (N),
4619 Right_Opnd => New_Occurrence_Of (Target_Type, Loc)),
4620 Reason => Reason));
4622 -- Next test for the case where the target type is within the bounds
4623 -- of the base type of the source type, since in this case we can
4624 -- simply convert these bounds to the base type of T to do the test.
4626 -- [constraint_error when N not in
4627 -- Source_Base_Type (Target_Type'First)
4628 -- ..
4629 -- Source_Base_Type(Target_Type'Last))]
4631 -- The conversions will always work and need no check
4633 -- Unchecked_Convert_To is used instead of Convert_To to handle the case
4634 -- of converting from an enumeration value to an integer type, such as
4635 -- occurs for the case of generating a range check on Enum'Val(Exp)
4636 -- (which used to be handled by gigi). This is OK, since the conversion
4637 -- itself does not require a check.
4639 elsif In_Subrange_Of (Target_Type, Source_Base_Type) then
4640 Insert_Action (N,
4641 Make_Raise_Constraint_Error (Loc,
4642 Condition =>
4643 Make_Not_In (Loc,
4644 Left_Opnd => Duplicate_Subexpr (N),
4646 Right_Opnd =>
4647 Make_Range (Loc,
4648 Low_Bound =>
4649 Unchecked_Convert_To (Source_Base_Type,
4650 Make_Attribute_Reference (Loc,
4651 Prefix =>
4652 New_Occurrence_Of (Target_Type, Loc),
4653 Attribute_Name => Name_First)),
4655 High_Bound =>
4656 Unchecked_Convert_To (Source_Base_Type,
4657 Make_Attribute_Reference (Loc,
4658 Prefix =>
4659 New_Occurrence_Of (Target_Type, Loc),
4660 Attribute_Name => Name_Last)))),
4661 Reason => Reason));
4663 -- Note that at this stage we now that the Target_Base_Type is not in
4664 -- the range of the Source_Base_Type (since even the Target_Type itself
4665 -- is not in this range). It could still be the case that Source_Type is
4666 -- in range of the target base type since we have not checked that case.
4668 -- If that is the case, we can freely convert the source to the target,
4669 -- and then test the target result against the bounds.
4671 elsif In_Subrange_Of (Source_Type, Target_Base_Type) then
4673 -- We make a temporary to hold the value of the converted value
4674 -- (converted to the base type), and then we will do the test against
4675 -- this temporary.
4677 -- Tnn : constant Target_Base_Type := Target_Base_Type (N);
4678 -- [constraint_error when Tnn not in Target_Type]
4680 -- Then the conversion itself is replaced by an occurrence of Tnn
4682 declare
4683 Tnn : constant Entity_Id :=
4684 Make_Defining_Identifier (Loc,
4685 Chars => New_Internal_Name ('T'));
4687 begin
4688 Insert_Actions (N, New_List (
4689 Make_Object_Declaration (Loc,
4690 Defining_Identifier => Tnn,
4691 Object_Definition =>
4692 New_Occurrence_Of (Target_Base_Type, Loc),
4693 Constant_Present => True,
4694 Expression =>
4695 Make_Type_Conversion (Loc,
4696 Subtype_Mark => New_Occurrence_Of (Target_Base_Type, Loc),
4697 Expression => Duplicate_Subexpr (N))),
4699 Make_Raise_Constraint_Error (Loc,
4700 Condition =>
4701 Make_Not_In (Loc,
4702 Left_Opnd => New_Occurrence_Of (Tnn, Loc),
4703 Right_Opnd => New_Occurrence_Of (Target_Type, Loc)),
4705 Reason => Reason)));
4707 Rewrite (N, New_Occurrence_Of (Tnn, Loc));
4709 -- Set the type of N, because the declaration for Tnn might not
4710 -- be analyzed yet, as is the case if N appears within a record
4711 -- declaration, as a discriminant constraint or expression.
4713 Set_Etype (N, Target_Base_Type);
4714 end;
4716 -- At this stage, we know that we have two scalar types, which are
4717 -- directly convertible, and where neither scalar type has a base
4718 -- range that is in the range of the other scalar type.
4720 -- The only way this can happen is with a signed and unsigned type.
4721 -- So test for these two cases:
4723 else
4724 -- Case of the source is unsigned and the target is signed
4726 if Is_Unsigned_Type (Source_Base_Type)
4727 and then not Is_Unsigned_Type (Target_Base_Type)
4728 then
4729 -- If the source is unsigned and the target is signed, then we
4730 -- know that the source is not shorter than the target (otherwise
4731 -- the source base type would be in the target base type range).
4733 -- In other words, the unsigned type is either the same size as
4734 -- the target, or it is larger. It cannot be smaller.
4736 pragma Assert
4737 (Esize (Source_Base_Type) >= Esize (Target_Base_Type));
4739 -- We only need to check the low bound if the low bound of the
4740 -- target type is non-negative. If the low bound of the target
4741 -- type is negative, then we know that we will fit fine.
4743 -- If the high bound of the target type is negative, then we
4744 -- know we have a constraint error, since we can't possibly
4745 -- have a negative source.
4747 -- With these two checks out of the way, we can do the check
4748 -- using the source type safely
4750 -- This is definitely the most annoying case!
4752 -- [constraint_error
4753 -- when (Target_Type'First >= 0
4754 -- and then
4755 -- N < Source_Base_Type (Target_Type'First))
4756 -- or else Target_Type'Last < 0
4757 -- or else N > Source_Base_Type (Target_Type'Last)];
4759 -- We turn off all checks since we know that the conversions
4760 -- will work fine, given the guards for negative values.
4762 Insert_Action (N,
4763 Make_Raise_Constraint_Error (Loc,
4764 Condition =>
4765 Make_Or_Else (Loc,
4766 Make_Or_Else (Loc,
4767 Left_Opnd =>
4768 Make_And_Then (Loc,
4769 Left_Opnd => Make_Op_Ge (Loc,
4770 Left_Opnd =>
4771 Make_Attribute_Reference (Loc,
4772 Prefix =>
4773 New_Occurrence_Of (Target_Type, Loc),
4774 Attribute_Name => Name_First),
4775 Right_Opnd => Make_Integer_Literal (Loc, Uint_0)),
4777 Right_Opnd =>
4778 Make_Op_Lt (Loc,
4779 Left_Opnd => Duplicate_Subexpr (N),
4780 Right_Opnd =>
4781 Convert_To (Source_Base_Type,
4782 Make_Attribute_Reference (Loc,
4783 Prefix =>
4784 New_Occurrence_Of (Target_Type, Loc),
4785 Attribute_Name => Name_First)))),
4787 Right_Opnd =>
4788 Make_Op_Lt (Loc,
4789 Left_Opnd =>
4790 Make_Attribute_Reference (Loc,
4791 Prefix => New_Occurrence_Of (Target_Type, Loc),
4792 Attribute_Name => Name_Last),
4793 Right_Opnd => Make_Integer_Literal (Loc, Uint_0))),
4795 Right_Opnd =>
4796 Make_Op_Gt (Loc,
4797 Left_Opnd => Duplicate_Subexpr (N),
4798 Right_Opnd =>
4799 Convert_To (Source_Base_Type,
4800 Make_Attribute_Reference (Loc,
4801 Prefix => New_Occurrence_Of (Target_Type, Loc),
4802 Attribute_Name => Name_Last)))),
4804 Reason => Reason),
4805 Suppress => All_Checks);
4807 -- Only remaining possibility is that the source is signed and
4808 -- the target is unsigned.
4810 else
4811 pragma Assert (not Is_Unsigned_Type (Source_Base_Type)
4812 and then Is_Unsigned_Type (Target_Base_Type));
4814 -- If the source is signed and the target is unsigned, then we
4815 -- know that the target is not shorter than the source (otherwise
4816 -- the target base type would be in the source base type range).
4818 -- In other words, the unsigned type is either the same size as
4819 -- the target, or it is larger. It cannot be smaller.
4821 -- Clearly we have an error if the source value is negative since
4822 -- no unsigned type can have negative values. If the source type
4823 -- is non-negative, then the check can be done using the target
4824 -- type.
4826 -- Tnn : constant Target_Base_Type (N) := Target_Type;
4828 -- [constraint_error
4829 -- when N < 0 or else Tnn not in Target_Type];
4831 -- We turn off all checks for the conversion of N to the target
4832 -- base type, since we generate the explicit check to ensure that
4833 -- the value is non-negative
4835 declare
4836 Tnn : constant Entity_Id :=
4837 Make_Defining_Identifier (Loc,
4838 Chars => New_Internal_Name ('T'));
4840 begin
4841 Insert_Actions (N, New_List (
4842 Make_Object_Declaration (Loc,
4843 Defining_Identifier => Tnn,
4844 Object_Definition =>
4845 New_Occurrence_Of (Target_Base_Type, Loc),
4846 Constant_Present => True,
4847 Expression =>
4848 Make_Unchecked_Type_Conversion (Loc,
4849 Subtype_Mark =>
4850 New_Occurrence_Of (Target_Base_Type, Loc),
4851 Expression => Duplicate_Subexpr (N))),
4853 Make_Raise_Constraint_Error (Loc,
4854 Condition =>
4855 Make_Or_Else (Loc,
4856 Left_Opnd =>
4857 Make_Op_Lt (Loc,
4858 Left_Opnd => Duplicate_Subexpr (N),
4859 Right_Opnd => Make_Integer_Literal (Loc, Uint_0)),
4861 Right_Opnd =>
4862 Make_Not_In (Loc,
4863 Left_Opnd => New_Occurrence_Of (Tnn, Loc),
4864 Right_Opnd =>
4865 New_Occurrence_Of (Target_Type, Loc))),
4867 Reason => Reason)),
4868 Suppress => All_Checks);
4870 -- Set the Etype explicitly, because Insert_Actions may have
4871 -- placed the declaration in the freeze list for an enclosing
4872 -- construct, and thus it is not analyzed yet.
4874 Set_Etype (Tnn, Target_Base_Type);
4875 Rewrite (N, New_Occurrence_Of (Tnn, Loc));
4876 end;
4877 end if;
4878 end if;
4879 end Generate_Range_Check;
4881 ------------------
4882 -- Get_Check_Id --
4883 ------------------
4885 function Get_Check_Id (N : Name_Id) return Check_Id is
4886 begin
4887 -- For standard check name, we can do a direct computation
4889 if N in First_Check_Name .. Last_Check_Name then
4890 return Check_Id (N - (First_Check_Name - 1));
4892 -- For non-standard names added by pragma Check_Name, search table
4894 else
4895 for J in All_Checks + 1 .. Check_Names.Last loop
4896 if Check_Names.Table (J) = N then
4897 return J;
4898 end if;
4899 end loop;
4900 end if;
4902 -- No matching name found
4904 return No_Check_Id;
4905 end Get_Check_Id;
4907 ---------------------
4908 -- Get_Discriminal --
4909 ---------------------
4911 function Get_Discriminal (E : Entity_Id; Bound : Node_Id) return Node_Id is
4912 Loc : constant Source_Ptr := Sloc (E);
4913 D : Entity_Id;
4914 Sc : Entity_Id;
4916 begin
4917 -- The bound can be a bona fide parameter of a protected operation,
4918 -- rather than a prival encoded as an in-parameter.
4920 if No (Discriminal_Link (Entity (Bound))) then
4921 return Bound;
4922 end if;
4924 -- Climb the scope stack looking for an enclosing protected type. If
4925 -- we run out of scopes, return the bound itself.
4927 Sc := Scope (E);
4928 while Present (Sc) loop
4929 if Sc = Standard_Standard then
4930 return Bound;
4932 elsif Ekind (Sc) = E_Protected_Type then
4933 exit;
4934 end if;
4936 Sc := Scope (Sc);
4937 end loop;
4939 D := First_Discriminant (Sc);
4940 while Present (D) loop
4941 if Chars (D) = Chars (Bound) then
4942 return New_Occurrence_Of (Discriminal (D), Loc);
4943 end if;
4945 Next_Discriminant (D);
4946 end loop;
4948 return Bound;
4949 end Get_Discriminal;
4951 ----------------------
4952 -- Get_Range_Checks --
4953 ----------------------
4955 function Get_Range_Checks
4956 (Ck_Node : Node_Id;
4957 Target_Typ : Entity_Id;
4958 Source_Typ : Entity_Id := Empty;
4959 Warn_Node : Node_Id := Empty) return Check_Result
4961 begin
4962 return Selected_Range_Checks
4963 (Ck_Node, Target_Typ, Source_Typ, Warn_Node);
4964 end Get_Range_Checks;
4966 ------------------
4967 -- Guard_Access --
4968 ------------------
4970 function Guard_Access
4971 (Cond : Node_Id;
4972 Loc : Source_Ptr;
4973 Ck_Node : Node_Id) return Node_Id
4975 begin
4976 if Nkind (Cond) = N_Or_Else then
4977 Set_Paren_Count (Cond, 1);
4978 end if;
4980 if Nkind (Ck_Node) = N_Allocator then
4981 return Cond;
4982 else
4983 return
4984 Make_And_Then (Loc,
4985 Left_Opnd =>
4986 Make_Op_Ne (Loc,
4987 Left_Opnd => Duplicate_Subexpr_No_Checks (Ck_Node),
4988 Right_Opnd => Make_Null (Loc)),
4989 Right_Opnd => Cond);
4990 end if;
4991 end Guard_Access;
4993 -----------------------------
4994 -- Index_Checks_Suppressed --
4995 -----------------------------
4997 function Index_Checks_Suppressed (E : Entity_Id) return Boolean is
4998 begin
4999 if Present (E) and then Checks_May_Be_Suppressed (E) then
5000 return Is_Check_Suppressed (E, Index_Check);
5001 else
5002 return Scope_Suppress (Index_Check);
5003 end if;
5004 end Index_Checks_Suppressed;
5006 ----------------
5007 -- Initialize --
5008 ----------------
5010 procedure Initialize is
5011 begin
5012 for J in Determine_Range_Cache_N'Range loop
5013 Determine_Range_Cache_N (J) := Empty;
5014 end loop;
5016 Check_Names.Init;
5018 for J in Int range 1 .. All_Checks loop
5019 Check_Names.Append (Name_Id (Int (First_Check_Name) + J - 1));
5020 end loop;
5021 end Initialize;
5023 -------------------------
5024 -- Insert_Range_Checks --
5025 -------------------------
5027 procedure Insert_Range_Checks
5028 (Checks : Check_Result;
5029 Node : Node_Id;
5030 Suppress_Typ : Entity_Id;
5031 Static_Sloc : Source_Ptr := No_Location;
5032 Flag_Node : Node_Id := Empty;
5033 Do_Before : Boolean := False)
5035 Internal_Flag_Node : Node_Id := Flag_Node;
5036 Internal_Static_Sloc : Source_Ptr := Static_Sloc;
5038 Check_Node : Node_Id;
5039 Checks_On : constant Boolean :=
5040 (not Index_Checks_Suppressed (Suppress_Typ))
5041 or else
5042 (not Range_Checks_Suppressed (Suppress_Typ));
5044 begin
5045 -- For now we just return if Checks_On is false, however this should be
5046 -- enhanced to check for an always True value in the condition and to
5047 -- generate a compilation warning???
5049 if not Expander_Active or else not Checks_On then
5050 return;
5051 end if;
5053 if Static_Sloc = No_Location then
5054 Internal_Static_Sloc := Sloc (Node);
5055 end if;
5057 if No (Flag_Node) then
5058 Internal_Flag_Node := Node;
5059 end if;
5061 for J in 1 .. 2 loop
5062 exit when No (Checks (J));
5064 if Nkind (Checks (J)) = N_Raise_Constraint_Error
5065 and then Present (Condition (Checks (J)))
5066 then
5067 if not Has_Dynamic_Range_Check (Internal_Flag_Node) then
5068 Check_Node := Checks (J);
5069 Mark_Rewrite_Insertion (Check_Node);
5071 if Do_Before then
5072 Insert_Before_And_Analyze (Node, Check_Node);
5073 else
5074 Insert_After_And_Analyze (Node, Check_Node);
5075 end if;
5077 Set_Has_Dynamic_Range_Check (Internal_Flag_Node);
5078 end if;
5080 else
5081 Check_Node :=
5082 Make_Raise_Constraint_Error (Internal_Static_Sloc,
5083 Reason => CE_Range_Check_Failed);
5084 Mark_Rewrite_Insertion (Check_Node);
5086 if Do_Before then
5087 Insert_Before_And_Analyze (Node, Check_Node);
5088 else
5089 Insert_After_And_Analyze (Node, Check_Node);
5090 end if;
5091 end if;
5092 end loop;
5093 end Insert_Range_Checks;
5095 ------------------------
5096 -- Insert_Valid_Check --
5097 ------------------------
5099 procedure Insert_Valid_Check (Expr : Node_Id) is
5100 Loc : constant Source_Ptr := Sloc (Expr);
5101 Exp : Node_Id;
5103 begin
5104 -- Do not insert if checks off, or if not checking validity or
5105 -- if expression is known to be valid
5107 if not Validity_Checks_On
5108 or else Range_Or_Validity_Checks_Suppressed (Expr)
5109 or else Expr_Known_Valid (Expr)
5110 then
5111 return;
5112 end if;
5114 -- If we have a checked conversion, then validity check applies to
5115 -- the expression inside the conversion, not the result, since if
5116 -- the expression inside is valid, then so is the conversion result.
5118 Exp := Expr;
5119 while Nkind (Exp) = N_Type_Conversion loop
5120 Exp := Expression (Exp);
5121 end loop;
5123 -- We are about to insert the validity check for Exp. We save and
5124 -- reset the Do_Range_Check flag over this validity check, and then
5125 -- put it back for the final original reference (Exp may be rewritten).
5127 declare
5128 DRC : constant Boolean := Do_Range_Check (Exp);
5130 begin
5131 Set_Do_Range_Check (Exp, False);
5133 -- Force evaluation to avoid multiple reads for atomic/volatile
5135 if Is_Entity_Name (Exp)
5136 and then Is_Volatile (Entity (Exp))
5137 then
5138 Force_Evaluation (Exp, Name_Req => True);
5139 end if;
5141 -- Insert the validity check. Note that we do this with validity
5142 -- checks turned off, to avoid recursion, we do not want validity
5143 -- checks on the validity checking code itself!
5145 Insert_Action
5146 (Expr,
5147 Make_Raise_Constraint_Error (Loc,
5148 Condition =>
5149 Make_Op_Not (Loc,
5150 Right_Opnd =>
5151 Make_Attribute_Reference (Loc,
5152 Prefix =>
5153 Duplicate_Subexpr_No_Checks (Exp, Name_Req => True),
5154 Attribute_Name => Name_Valid)),
5155 Reason => CE_Invalid_Data),
5156 Suppress => Validity_Check);
5158 -- If the expression is a a reference to an element of a bit-packed
5159 -- array, then it is rewritten as a renaming declaration. If the
5160 -- expression is an actual in a call, it has not been expanded,
5161 -- waiting for the proper point at which to do it. The same happens
5162 -- with renamings, so that we have to force the expansion now. This
5163 -- non-local complication is due to code in exp_ch2,adb, exp_ch4.adb
5164 -- and exp_ch6.adb.
5166 if Is_Entity_Name (Exp)
5167 and then Nkind (Parent (Entity (Exp))) =
5168 N_Object_Renaming_Declaration
5169 then
5170 declare
5171 Old_Exp : constant Node_Id := Name (Parent (Entity (Exp)));
5172 begin
5173 if Nkind (Old_Exp) = N_Indexed_Component
5174 and then Is_Bit_Packed_Array (Etype (Prefix (Old_Exp)))
5175 then
5176 Expand_Packed_Element_Reference (Old_Exp);
5177 end if;
5178 end;
5179 end if;
5181 -- Put back the Do_Range_Check flag on the resulting (possibly
5182 -- rewritten) expression.
5184 -- Note: it might be thought that a validity check is not required
5185 -- when a range check is present, but that's not the case, because
5186 -- the back end is allowed to assume for the range check that the
5187 -- operand is within its declared range (an assumption that validity
5188 -- checking is all about NOT assuming!)
5190 -- Note: no need to worry about Possible_Local_Raise here, it will
5191 -- already have been called if original node has Do_Range_Check set.
5193 Set_Do_Range_Check (Exp, DRC);
5194 end;
5195 end Insert_Valid_Check;
5197 ----------------------------------
5198 -- Install_Null_Excluding_Check --
5199 ----------------------------------
5201 procedure Install_Null_Excluding_Check (N : Node_Id) is
5202 Loc : constant Source_Ptr := Sloc (N);
5203 Typ : constant Entity_Id := Etype (N);
5205 function Safe_To_Capture_In_Parameter_Value return Boolean;
5206 -- Determines if it is safe to capture Known_Non_Null status for an
5207 -- the entity referenced by node N. The caller ensures that N is indeed
5208 -- an entity name. It is safe to capture the non-null status for an IN
5209 -- parameter when the reference occurs within a declaration that is sure
5210 -- to be executed as part of the declarative region.
5212 procedure Mark_Non_Null;
5213 -- After installation of check, if the node in question is an entity
5214 -- name, then mark this entity as non-null if possible.
5216 function Safe_To_Capture_In_Parameter_Value return Boolean is
5217 E : constant Entity_Id := Entity (N);
5218 S : constant Entity_Id := Current_Scope;
5219 S_Par : Node_Id;
5221 begin
5222 if Ekind (E) /= E_In_Parameter then
5223 return False;
5224 end if;
5226 -- Two initial context checks. We must be inside a subprogram body
5227 -- with declarations and reference must not appear in nested scopes.
5229 if (Ekind (S) /= E_Function and then Ekind (S) /= E_Procedure)
5230 or else Scope (E) /= S
5231 then
5232 return False;
5233 end if;
5235 S_Par := Parent (Parent (S));
5237 if Nkind (S_Par) /= N_Subprogram_Body
5238 or else No (Declarations (S_Par))
5239 then
5240 return False;
5241 end if;
5243 declare
5244 N_Decl : Node_Id;
5245 P : Node_Id;
5247 begin
5248 -- Retrieve the declaration node of N (if any). Note that N
5249 -- may be a part of a complex initialization expression.
5251 P := Parent (N);
5252 N_Decl := Empty;
5253 while Present (P) loop
5255 -- If we have a short circuit form, and we are within the right
5256 -- hand expression, we return false, since the right hand side
5257 -- is not guaranteed to be elaborated.
5259 if Nkind (P) in N_Short_Circuit
5260 and then N = Right_Opnd (P)
5261 then
5262 return False;
5263 end if;
5265 -- Similarly, if we are in a conditional expression and not
5266 -- part of the condition, then we return False, since neither
5267 -- the THEN or ELSE expressions will always be elaborated.
5269 if Nkind (P) = N_Conditional_Expression
5270 and then N /= First (Expressions (P))
5271 then
5272 return False;
5273 end if;
5275 -- While traversing the parent chain, we find that N
5276 -- belongs to a statement, thus it may never appear in
5277 -- a declarative region.
5279 if Nkind (P) in N_Statement_Other_Than_Procedure_Call
5280 or else Nkind (P) = N_Procedure_Call_Statement
5281 then
5282 return False;
5283 end if;
5285 -- If we are at a declaration, record it and exit
5287 if Nkind (P) in N_Declaration
5288 and then Nkind (P) not in N_Subprogram_Specification
5289 then
5290 N_Decl := P;
5291 exit;
5292 end if;
5294 P := Parent (P);
5295 end loop;
5297 if No (N_Decl) then
5298 return False;
5299 end if;
5301 return List_Containing (N_Decl) = Declarations (S_Par);
5302 end;
5303 end Safe_To_Capture_In_Parameter_Value;
5305 -------------------
5306 -- Mark_Non_Null --
5307 -------------------
5309 procedure Mark_Non_Null is
5310 begin
5311 -- Only case of interest is if node N is an entity name
5313 if Is_Entity_Name (N) then
5315 -- For sure, we want to clear an indication that this is known to
5316 -- be null, since if we get past this check, it definitely is not!
5318 Set_Is_Known_Null (Entity (N), False);
5320 -- We can mark the entity as known to be non-null if either it is
5321 -- safe to capture the value, or in the case of an IN parameter,
5322 -- which is a constant, if the check we just installed is in the
5323 -- declarative region of the subprogram body. In this latter case,
5324 -- a check is decisive for the rest of the body if the expression
5325 -- is sure to be elaborated, since we know we have to elaborate
5326 -- all declarations before executing the body.
5328 -- Couldn't this always be part of Safe_To_Capture_Value ???
5330 if Safe_To_Capture_Value (N, Entity (N))
5331 or else Safe_To_Capture_In_Parameter_Value
5332 then
5333 Set_Is_Known_Non_Null (Entity (N));
5334 end if;
5335 end if;
5336 end Mark_Non_Null;
5338 -- Start of processing for Install_Null_Excluding_Check
5340 begin
5341 pragma Assert (Is_Access_Type (Typ));
5343 -- No check inside a generic (why not???)
5345 if Inside_A_Generic then
5346 return;
5347 end if;
5349 -- No check needed if known to be non-null
5351 if Known_Non_Null (N) then
5352 return;
5353 end if;
5355 -- If known to be null, here is where we generate a compile time check
5357 if Known_Null (N) then
5359 -- Avoid generating warning message inside init procs
5361 if not Inside_Init_Proc then
5362 Apply_Compile_Time_Constraint_Error
5364 "null value not allowed here?",
5365 CE_Access_Check_Failed);
5366 else
5367 Insert_Action (N,
5368 Make_Raise_Constraint_Error (Loc,
5369 Reason => CE_Access_Check_Failed));
5370 end if;
5372 Mark_Non_Null;
5373 return;
5374 end if;
5376 -- If entity is never assigned, for sure a warning is appropriate
5378 if Is_Entity_Name (N) then
5379 Check_Unset_Reference (N);
5380 end if;
5382 -- No check needed if checks are suppressed on the range. Note that we
5383 -- don't set Is_Known_Non_Null in this case (we could legitimately do
5384 -- so, since the program is erroneous, but we don't like to casually
5385 -- propagate such conclusions from erroneosity).
5387 if Access_Checks_Suppressed (Typ) then
5388 return;
5389 end if;
5391 -- No check needed for access to concurrent record types generated by
5392 -- the expander. This is not just an optimization (though it does indeed
5393 -- remove junk checks). It also avoids generation of junk warnings.
5395 if Nkind (N) in N_Has_Chars
5396 and then Chars (N) = Name_uObject
5397 and then Is_Concurrent_Record_Type
5398 (Directly_Designated_Type (Etype (N)))
5399 then
5400 return;
5401 end if;
5403 -- Otherwise install access check
5405 Insert_Action (N,
5406 Make_Raise_Constraint_Error (Loc,
5407 Condition =>
5408 Make_Op_Eq (Loc,
5409 Left_Opnd => Duplicate_Subexpr_Move_Checks (N),
5410 Right_Opnd => Make_Null (Loc)),
5411 Reason => CE_Access_Check_Failed));
5413 Mark_Non_Null;
5414 end Install_Null_Excluding_Check;
5416 --------------------------
5417 -- Install_Static_Check --
5418 --------------------------
5420 procedure Install_Static_Check (R_Cno : Node_Id; Loc : Source_Ptr) is
5421 Stat : constant Boolean := Is_Static_Expression (R_Cno);
5422 Typ : constant Entity_Id := Etype (R_Cno);
5424 begin
5425 Rewrite (R_Cno,
5426 Make_Raise_Constraint_Error (Loc,
5427 Reason => CE_Range_Check_Failed));
5428 Set_Analyzed (R_Cno);
5429 Set_Etype (R_Cno, Typ);
5430 Set_Raises_Constraint_Error (R_Cno);
5431 Set_Is_Static_Expression (R_Cno, Stat);
5433 -- Now deal with possible local raise handling
5435 Possible_Local_Raise (R_Cno, Standard_Constraint_Error);
5436 end Install_Static_Check;
5438 ---------------------
5439 -- Kill_All_Checks --
5440 ---------------------
5442 procedure Kill_All_Checks is
5443 begin
5444 if Debug_Flag_CC then
5445 w ("Kill_All_Checks");
5446 end if;
5448 -- We reset the number of saved checks to zero, and also modify all
5449 -- stack entries for statement ranges to indicate that the number of
5450 -- checks at each level is now zero.
5452 Num_Saved_Checks := 0;
5454 -- Note: the Int'Min here avoids any possibility of J being out of
5455 -- range when called from e.g. Conditional_Statements_Begin.
5457 for J in 1 .. Int'Min (Saved_Checks_TOS, Saved_Checks_Stack'Last) loop
5458 Saved_Checks_Stack (J) := 0;
5459 end loop;
5460 end Kill_All_Checks;
5462 -----------------
5463 -- Kill_Checks --
5464 -----------------
5466 procedure Kill_Checks (V : Entity_Id) is
5467 begin
5468 if Debug_Flag_CC then
5469 w ("Kill_Checks for entity", Int (V));
5470 end if;
5472 for J in 1 .. Num_Saved_Checks loop
5473 if Saved_Checks (J).Entity = V then
5474 if Debug_Flag_CC then
5475 w (" Checks killed for saved check ", J);
5476 end if;
5478 Saved_Checks (J).Killed := True;
5479 end if;
5480 end loop;
5481 end Kill_Checks;
5483 ------------------------------
5484 -- Length_Checks_Suppressed --
5485 ------------------------------
5487 function Length_Checks_Suppressed (E : Entity_Id) return Boolean is
5488 begin
5489 if Present (E) and then Checks_May_Be_Suppressed (E) then
5490 return Is_Check_Suppressed (E, Length_Check);
5491 else
5492 return Scope_Suppress (Length_Check);
5493 end if;
5494 end Length_Checks_Suppressed;
5496 --------------------------------
5497 -- Overflow_Checks_Suppressed --
5498 --------------------------------
5500 function Overflow_Checks_Suppressed (E : Entity_Id) return Boolean is
5501 begin
5502 if Present (E) and then Checks_May_Be_Suppressed (E) then
5503 return Is_Check_Suppressed (E, Overflow_Check);
5504 else
5505 return Scope_Suppress (Overflow_Check);
5506 end if;
5507 end Overflow_Checks_Suppressed;
5509 -----------------------------
5510 -- Range_Checks_Suppressed --
5511 -----------------------------
5513 function Range_Checks_Suppressed (E : Entity_Id) return Boolean is
5514 begin
5515 if Present (E) then
5517 -- Note: for now we always suppress range checks on Vax float types,
5518 -- since Gigi does not know how to generate these checks.
5520 if Vax_Float (E) then
5521 return True;
5522 elsif Kill_Range_Checks (E) then
5523 return True;
5524 elsif Checks_May_Be_Suppressed (E) then
5525 return Is_Check_Suppressed (E, Range_Check);
5526 end if;
5527 end if;
5529 return Scope_Suppress (Range_Check);
5530 end Range_Checks_Suppressed;
5532 -----------------------------------------
5533 -- Range_Or_Validity_Checks_Suppressed --
5534 -----------------------------------------
5536 -- Note: the coding would be simpler here if we simply made appropriate
5537 -- calls to Range/Validity_Checks_Suppressed, but that would result in
5538 -- duplicated checks which we prefer to avoid.
5540 function Range_Or_Validity_Checks_Suppressed
5541 (Expr : Node_Id) return Boolean
5543 begin
5544 -- Immediate return if scope checks suppressed for either check
5546 if Scope_Suppress (Range_Check) or Scope_Suppress (Validity_Check) then
5547 return True;
5548 end if;
5550 -- If no expression, that's odd, decide that checks are suppressed,
5551 -- since we don't want anyone trying to do checks in this case, which
5552 -- is most likely the result of some other error.
5554 if No (Expr) then
5555 return True;
5556 end if;
5558 -- Expression is present, so perform suppress checks on type
5560 declare
5561 Typ : constant Entity_Id := Etype (Expr);
5562 begin
5563 if Vax_Float (Typ) then
5564 return True;
5565 elsif Checks_May_Be_Suppressed (Typ)
5566 and then (Is_Check_Suppressed (Typ, Range_Check)
5567 or else
5568 Is_Check_Suppressed (Typ, Validity_Check))
5569 then
5570 return True;
5571 end if;
5572 end;
5574 -- If expression is an entity name, perform checks on this entity
5576 if Is_Entity_Name (Expr) then
5577 declare
5578 Ent : constant Entity_Id := Entity (Expr);
5579 begin
5580 if Checks_May_Be_Suppressed (Ent) then
5581 return Is_Check_Suppressed (Ent, Range_Check)
5582 or else Is_Check_Suppressed (Ent, Validity_Check);
5583 end if;
5584 end;
5585 end if;
5587 -- If we fall through, no checks suppressed
5589 return False;
5590 end Range_Or_Validity_Checks_Suppressed;
5592 -------------------
5593 -- Remove_Checks --
5594 -------------------
5596 procedure Remove_Checks (Expr : Node_Id) is
5597 function Process (N : Node_Id) return Traverse_Result;
5598 -- Process a single node during the traversal
5600 procedure Traverse is new Traverse_Proc (Process);
5601 -- The traversal procedure itself
5603 -------------
5604 -- Process --
5605 -------------
5607 function Process (N : Node_Id) return Traverse_Result is
5608 begin
5609 if Nkind (N) not in N_Subexpr then
5610 return Skip;
5611 end if;
5613 Set_Do_Range_Check (N, False);
5615 case Nkind (N) is
5616 when N_And_Then =>
5617 Traverse (Left_Opnd (N));
5618 return Skip;
5620 when N_Attribute_Reference =>
5621 Set_Do_Overflow_Check (N, False);
5623 when N_Function_Call =>
5624 Set_Do_Tag_Check (N, False);
5626 when N_Op =>
5627 Set_Do_Overflow_Check (N, False);
5629 case Nkind (N) is
5630 when N_Op_Divide =>
5631 Set_Do_Division_Check (N, False);
5633 when N_Op_And =>
5634 Set_Do_Length_Check (N, False);
5636 when N_Op_Mod =>
5637 Set_Do_Division_Check (N, False);
5639 when N_Op_Or =>
5640 Set_Do_Length_Check (N, False);
5642 when N_Op_Rem =>
5643 Set_Do_Division_Check (N, False);
5645 when N_Op_Xor =>
5646 Set_Do_Length_Check (N, False);
5648 when others =>
5649 null;
5650 end case;
5652 when N_Or_Else =>
5653 Traverse (Left_Opnd (N));
5654 return Skip;
5656 when N_Selected_Component =>
5657 Set_Do_Discriminant_Check (N, False);
5659 when N_Type_Conversion =>
5660 Set_Do_Length_Check (N, False);
5661 Set_Do_Tag_Check (N, False);
5662 Set_Do_Overflow_Check (N, False);
5664 when others =>
5665 null;
5666 end case;
5668 return OK;
5669 end Process;
5671 -- Start of processing for Remove_Checks
5673 begin
5674 Traverse (Expr);
5675 end Remove_Checks;
5677 ----------------------------
5678 -- Selected_Length_Checks --
5679 ----------------------------
5681 function Selected_Length_Checks
5682 (Ck_Node : Node_Id;
5683 Target_Typ : Entity_Id;
5684 Source_Typ : Entity_Id;
5685 Warn_Node : Node_Id) return Check_Result
5687 Loc : constant Source_Ptr := Sloc (Ck_Node);
5688 S_Typ : Entity_Id;
5689 T_Typ : Entity_Id;
5690 Expr_Actual : Node_Id;
5691 Exptyp : Entity_Id;
5692 Cond : Node_Id := Empty;
5693 Do_Access : Boolean := False;
5694 Wnode : Node_Id := Warn_Node;
5695 Ret_Result : Check_Result := (Empty, Empty);
5696 Num_Checks : Natural := 0;
5698 procedure Add_Check (N : Node_Id);
5699 -- Adds the action given to Ret_Result if N is non-Empty
5701 function Get_E_Length (E : Entity_Id; Indx : Nat) return Node_Id;
5702 function Get_N_Length (N : Node_Id; Indx : Nat) return Node_Id;
5703 -- Comments required ???
5705 function Same_Bounds (L : Node_Id; R : Node_Id) return Boolean;
5706 -- True for equal literals and for nodes that denote the same constant
5707 -- entity, even if its value is not a static constant. This includes the
5708 -- case of a discriminal reference within an init proc. Removes some
5709 -- obviously superfluous checks.
5711 function Length_E_Cond
5712 (Exptyp : Entity_Id;
5713 Typ : Entity_Id;
5714 Indx : Nat) return Node_Id;
5715 -- Returns expression to compute:
5716 -- Typ'Length /= Exptyp'Length
5718 function Length_N_Cond
5719 (Expr : Node_Id;
5720 Typ : Entity_Id;
5721 Indx : Nat) return Node_Id;
5722 -- Returns expression to compute:
5723 -- Typ'Length /= Expr'Length
5725 ---------------
5726 -- Add_Check --
5727 ---------------
5729 procedure Add_Check (N : Node_Id) is
5730 begin
5731 if Present (N) then
5733 -- For now, ignore attempt to place more than 2 checks ???
5735 if Num_Checks = 2 then
5736 return;
5737 end if;
5739 pragma Assert (Num_Checks <= 1);
5740 Num_Checks := Num_Checks + 1;
5741 Ret_Result (Num_Checks) := N;
5742 end if;
5743 end Add_Check;
5745 ------------------
5746 -- Get_E_Length --
5747 ------------------
5749 function Get_E_Length (E : Entity_Id; Indx : Nat) return Node_Id is
5750 SE : constant Entity_Id := Scope (E);
5751 N : Node_Id;
5752 E1 : Entity_Id := E;
5754 begin
5755 if Ekind (Scope (E)) = E_Record_Type
5756 and then Has_Discriminants (Scope (E))
5757 then
5758 N := Build_Discriminal_Subtype_Of_Component (E);
5760 if Present (N) then
5761 Insert_Action (Ck_Node, N);
5762 E1 := Defining_Identifier (N);
5763 end if;
5764 end if;
5766 if Ekind (E1) = E_String_Literal_Subtype then
5767 return
5768 Make_Integer_Literal (Loc,
5769 Intval => String_Literal_Length (E1));
5771 elsif SE /= Standard_Standard
5772 and then Ekind (Scope (SE)) = E_Protected_Type
5773 and then Has_Discriminants (Scope (SE))
5774 and then Has_Completion (Scope (SE))
5775 and then not Inside_Init_Proc
5776 then
5777 -- If the type whose length is needed is a private component
5778 -- constrained by a discriminant, we must expand the 'Length
5779 -- attribute into an explicit computation, using the discriminal
5780 -- of the current protected operation. This is because the actual
5781 -- type of the prival is constructed after the protected opera-
5782 -- tion has been fully expanded.
5784 declare
5785 Indx_Type : Node_Id;
5786 Lo : Node_Id;
5787 Hi : Node_Id;
5788 Do_Expand : Boolean := False;
5790 begin
5791 Indx_Type := First_Index (E);
5793 for J in 1 .. Indx - 1 loop
5794 Next_Index (Indx_Type);
5795 end loop;
5797 Get_Index_Bounds (Indx_Type, Lo, Hi);
5799 if Nkind (Lo) = N_Identifier
5800 and then Ekind (Entity (Lo)) = E_In_Parameter
5801 then
5802 Lo := Get_Discriminal (E, Lo);
5803 Do_Expand := True;
5804 end if;
5806 if Nkind (Hi) = N_Identifier
5807 and then Ekind (Entity (Hi)) = E_In_Parameter
5808 then
5809 Hi := Get_Discriminal (E, Hi);
5810 Do_Expand := True;
5811 end if;
5813 if Do_Expand then
5814 if not Is_Entity_Name (Lo) then
5815 Lo := Duplicate_Subexpr_No_Checks (Lo);
5816 end if;
5818 if not Is_Entity_Name (Hi) then
5819 Lo := Duplicate_Subexpr_No_Checks (Hi);
5820 end if;
5822 N :=
5823 Make_Op_Add (Loc,
5824 Left_Opnd =>
5825 Make_Op_Subtract (Loc,
5826 Left_Opnd => Hi,
5827 Right_Opnd => Lo),
5829 Right_Opnd => Make_Integer_Literal (Loc, 1));
5830 return N;
5832 else
5833 N :=
5834 Make_Attribute_Reference (Loc,
5835 Attribute_Name => Name_Length,
5836 Prefix =>
5837 New_Occurrence_Of (E1, Loc));
5839 if Indx > 1 then
5840 Set_Expressions (N, New_List (
5841 Make_Integer_Literal (Loc, Indx)));
5842 end if;
5844 return N;
5845 end if;
5846 end;
5848 else
5849 N :=
5850 Make_Attribute_Reference (Loc,
5851 Attribute_Name => Name_Length,
5852 Prefix =>
5853 New_Occurrence_Of (E1, Loc));
5855 if Indx > 1 then
5856 Set_Expressions (N, New_List (
5857 Make_Integer_Literal (Loc, Indx)));
5858 end if;
5860 return N;
5861 end if;
5862 end Get_E_Length;
5864 ------------------
5865 -- Get_N_Length --
5866 ------------------
5868 function Get_N_Length (N : Node_Id; Indx : Nat) return Node_Id is
5869 begin
5870 return
5871 Make_Attribute_Reference (Loc,
5872 Attribute_Name => Name_Length,
5873 Prefix =>
5874 Duplicate_Subexpr_No_Checks (N, Name_Req => True),
5875 Expressions => New_List (
5876 Make_Integer_Literal (Loc, Indx)));
5877 end Get_N_Length;
5879 -------------------
5880 -- Length_E_Cond --
5881 -------------------
5883 function Length_E_Cond
5884 (Exptyp : Entity_Id;
5885 Typ : Entity_Id;
5886 Indx : Nat) return Node_Id
5888 begin
5889 return
5890 Make_Op_Ne (Loc,
5891 Left_Opnd => Get_E_Length (Typ, Indx),
5892 Right_Opnd => Get_E_Length (Exptyp, Indx));
5893 end Length_E_Cond;
5895 -------------------
5896 -- Length_N_Cond --
5897 -------------------
5899 function Length_N_Cond
5900 (Expr : Node_Id;
5901 Typ : Entity_Id;
5902 Indx : Nat) return Node_Id
5904 begin
5905 return
5906 Make_Op_Ne (Loc,
5907 Left_Opnd => Get_E_Length (Typ, Indx),
5908 Right_Opnd => Get_N_Length (Expr, Indx));
5909 end Length_N_Cond;
5911 -----------------
5912 -- Same_Bounds --
5913 -----------------
5915 function Same_Bounds (L : Node_Id; R : Node_Id) return Boolean is
5916 begin
5917 return
5918 (Nkind (L) = N_Integer_Literal
5919 and then Nkind (R) = N_Integer_Literal
5920 and then Intval (L) = Intval (R))
5922 or else
5923 (Is_Entity_Name (L)
5924 and then Ekind (Entity (L)) = E_Constant
5925 and then ((Is_Entity_Name (R)
5926 and then Entity (L) = Entity (R))
5927 or else
5928 (Nkind (R) = N_Type_Conversion
5929 and then Is_Entity_Name (Expression (R))
5930 and then Entity (L) = Entity (Expression (R)))))
5932 or else
5933 (Is_Entity_Name (R)
5934 and then Ekind (Entity (R)) = E_Constant
5935 and then Nkind (L) = N_Type_Conversion
5936 and then Is_Entity_Name (Expression (L))
5937 and then Entity (R) = Entity (Expression (L)))
5939 or else
5940 (Is_Entity_Name (L)
5941 and then Is_Entity_Name (R)
5942 and then Entity (L) = Entity (R)
5943 and then Ekind (Entity (L)) = E_In_Parameter
5944 and then Inside_Init_Proc);
5945 end Same_Bounds;
5947 -- Start of processing for Selected_Length_Checks
5949 begin
5950 if not Expander_Active then
5951 return Ret_Result;
5952 end if;
5954 if Target_Typ = Any_Type
5955 or else Target_Typ = Any_Composite
5956 or else Raises_Constraint_Error (Ck_Node)
5957 then
5958 return Ret_Result;
5959 end if;
5961 if No (Wnode) then
5962 Wnode := Ck_Node;
5963 end if;
5965 T_Typ := Target_Typ;
5967 if No (Source_Typ) then
5968 S_Typ := Etype (Ck_Node);
5969 else
5970 S_Typ := Source_Typ;
5971 end if;
5973 if S_Typ = Any_Type or else S_Typ = Any_Composite then
5974 return Ret_Result;
5975 end if;
5977 if Is_Access_Type (T_Typ) and then Is_Access_Type (S_Typ) then
5978 S_Typ := Designated_Type (S_Typ);
5979 T_Typ := Designated_Type (T_Typ);
5980 Do_Access := True;
5982 -- A simple optimization for the null case
5984 if Known_Null (Ck_Node) then
5985 return Ret_Result;
5986 end if;
5987 end if;
5989 if Is_Array_Type (T_Typ) and then Is_Array_Type (S_Typ) then
5990 if Is_Constrained (T_Typ) then
5992 -- The checking code to be generated will freeze the
5993 -- corresponding array type. However, we must freeze the
5994 -- type now, so that the freeze node does not appear within
5995 -- the generated condional expression, but ahead of it.
5997 Freeze_Before (Ck_Node, T_Typ);
5999 Expr_Actual := Get_Referenced_Object (Ck_Node);
6000 Exptyp := Get_Actual_Subtype (Ck_Node);
6002 if Is_Access_Type (Exptyp) then
6003 Exptyp := Designated_Type (Exptyp);
6004 end if;
6006 -- String_Literal case. This needs to be handled specially be-
6007 -- cause no index types are available for string literals. The
6008 -- condition is simply:
6010 -- T_Typ'Length = string-literal-length
6012 if Nkind (Expr_Actual) = N_String_Literal
6013 and then Ekind (Etype (Expr_Actual)) = E_String_Literal_Subtype
6014 then
6015 Cond :=
6016 Make_Op_Ne (Loc,
6017 Left_Opnd => Get_E_Length (T_Typ, 1),
6018 Right_Opnd =>
6019 Make_Integer_Literal (Loc,
6020 Intval =>
6021 String_Literal_Length (Etype (Expr_Actual))));
6023 -- General array case. Here we have a usable actual subtype for
6024 -- the expression, and the condition is built from the two types
6025 -- (Do_Length):
6027 -- T_Typ'Length /= Exptyp'Length or else
6028 -- T_Typ'Length (2) /= Exptyp'Length (2) or else
6029 -- T_Typ'Length (3) /= Exptyp'Length (3) or else
6030 -- ...
6032 elsif Is_Constrained (Exptyp) then
6033 declare
6034 Ndims : constant Nat := Number_Dimensions (T_Typ);
6036 L_Index : Node_Id;
6037 R_Index : Node_Id;
6038 L_Low : Node_Id;
6039 L_High : Node_Id;
6040 R_Low : Node_Id;
6041 R_High : Node_Id;
6042 L_Length : Uint;
6043 R_Length : Uint;
6044 Ref_Node : Node_Id;
6046 begin
6047 -- At the library level, we need to ensure that the type of
6048 -- the object is elaborated before the check itself is
6049 -- emitted. This is only done if the object is in the
6050 -- current compilation unit, otherwise the type is frozen
6051 -- and elaborated in its unit.
6053 if Is_Itype (Exptyp)
6054 and then
6055 Ekind (Cunit_Entity (Current_Sem_Unit)) = E_Package
6056 and then
6057 not In_Package_Body (Cunit_Entity (Current_Sem_Unit))
6058 and then In_Open_Scopes (Scope (Exptyp))
6059 then
6060 Ref_Node := Make_Itype_Reference (Sloc (Ck_Node));
6061 Set_Itype (Ref_Node, Exptyp);
6062 Insert_Action (Ck_Node, Ref_Node);
6063 end if;
6065 L_Index := First_Index (T_Typ);
6066 R_Index := First_Index (Exptyp);
6068 for Indx in 1 .. Ndims loop
6069 if not (Nkind (L_Index) = N_Raise_Constraint_Error
6070 or else
6071 Nkind (R_Index) = N_Raise_Constraint_Error)
6072 then
6073 Get_Index_Bounds (L_Index, L_Low, L_High);
6074 Get_Index_Bounds (R_Index, R_Low, R_High);
6076 -- Deal with compile time length check. Note that we
6077 -- skip this in the access case, because the access
6078 -- value may be null, so we cannot know statically.
6080 if not Do_Access
6081 and then Compile_Time_Known_Value (L_Low)
6082 and then Compile_Time_Known_Value (L_High)
6083 and then Compile_Time_Known_Value (R_Low)
6084 and then Compile_Time_Known_Value (R_High)
6085 then
6086 if Expr_Value (L_High) >= Expr_Value (L_Low) then
6087 L_Length := Expr_Value (L_High) -
6088 Expr_Value (L_Low) + 1;
6089 else
6090 L_Length := UI_From_Int (0);
6091 end if;
6093 if Expr_Value (R_High) >= Expr_Value (R_Low) then
6094 R_Length := Expr_Value (R_High) -
6095 Expr_Value (R_Low) + 1;
6096 else
6097 R_Length := UI_From_Int (0);
6098 end if;
6100 if L_Length > R_Length then
6101 Add_Check
6102 (Compile_Time_Constraint_Error
6103 (Wnode, "too few elements for}?", T_Typ));
6105 elsif L_Length < R_Length then
6106 Add_Check
6107 (Compile_Time_Constraint_Error
6108 (Wnode, "too many elements for}?", T_Typ));
6109 end if;
6111 -- The comparison for an individual index subtype
6112 -- is omitted if the corresponding index subtypes
6113 -- statically match, since the result is known to
6114 -- be true. Note that this test is worth while even
6115 -- though we do static evaluation, because non-static
6116 -- subtypes can statically match.
6118 elsif not
6119 Subtypes_Statically_Match
6120 (Etype (L_Index), Etype (R_Index))
6122 and then not
6123 (Same_Bounds (L_Low, R_Low)
6124 and then Same_Bounds (L_High, R_High))
6125 then
6126 Evolve_Or_Else
6127 (Cond, Length_E_Cond (Exptyp, T_Typ, Indx));
6128 end if;
6130 Next (L_Index);
6131 Next (R_Index);
6132 end if;
6133 end loop;
6134 end;
6136 -- Handle cases where we do not get a usable actual subtype that
6137 -- is constrained. This happens for example in the function call
6138 -- and explicit dereference cases. In these cases, we have to get
6139 -- the length or range from the expression itself, making sure we
6140 -- do not evaluate it more than once.
6142 -- Here Ck_Node is the original expression, or more properly the
6143 -- result of applying Duplicate_Expr to the original tree, forcing
6144 -- the result to be a name.
6146 else
6147 declare
6148 Ndims : constant Nat := Number_Dimensions (T_Typ);
6150 begin
6151 -- Build the condition for the explicit dereference case
6153 for Indx in 1 .. Ndims loop
6154 Evolve_Or_Else
6155 (Cond, Length_N_Cond (Ck_Node, T_Typ, Indx));
6156 end loop;
6157 end;
6158 end if;
6159 end if;
6160 end if;
6162 -- Construct the test and insert into the tree
6164 if Present (Cond) then
6165 if Do_Access then
6166 Cond := Guard_Access (Cond, Loc, Ck_Node);
6167 end if;
6169 Add_Check
6170 (Make_Raise_Constraint_Error (Loc,
6171 Condition => Cond,
6172 Reason => CE_Length_Check_Failed));
6173 end if;
6175 return Ret_Result;
6176 end Selected_Length_Checks;
6178 ---------------------------
6179 -- Selected_Range_Checks --
6180 ---------------------------
6182 function Selected_Range_Checks
6183 (Ck_Node : Node_Id;
6184 Target_Typ : Entity_Id;
6185 Source_Typ : Entity_Id;
6186 Warn_Node : Node_Id) return Check_Result
6188 Loc : constant Source_Ptr := Sloc (Ck_Node);
6189 S_Typ : Entity_Id;
6190 T_Typ : Entity_Id;
6191 Expr_Actual : Node_Id;
6192 Exptyp : Entity_Id;
6193 Cond : Node_Id := Empty;
6194 Do_Access : Boolean := False;
6195 Wnode : Node_Id := Warn_Node;
6196 Ret_Result : Check_Result := (Empty, Empty);
6197 Num_Checks : Integer := 0;
6199 procedure Add_Check (N : Node_Id);
6200 -- Adds the action given to Ret_Result if N is non-Empty
6202 function Discrete_Range_Cond
6203 (Expr : Node_Id;
6204 Typ : Entity_Id) return Node_Id;
6205 -- Returns expression to compute:
6206 -- Low_Bound (Expr) < Typ'First
6207 -- or else
6208 -- High_Bound (Expr) > Typ'Last
6210 function Discrete_Expr_Cond
6211 (Expr : Node_Id;
6212 Typ : Entity_Id) return Node_Id;
6213 -- Returns expression to compute:
6214 -- Expr < Typ'First
6215 -- or else
6216 -- Expr > Typ'Last
6218 function Get_E_First_Or_Last
6219 (E : Entity_Id;
6220 Indx : Nat;
6221 Nam : Name_Id) return Node_Id;
6222 -- Returns expression to compute:
6223 -- E'First or E'Last
6225 function Get_N_First (N : Node_Id; Indx : Nat) return Node_Id;
6226 function Get_N_Last (N : Node_Id; Indx : Nat) return Node_Id;
6227 -- Returns expression to compute:
6228 -- N'First or N'Last using Duplicate_Subexpr_No_Checks
6230 function Range_E_Cond
6231 (Exptyp : Entity_Id;
6232 Typ : Entity_Id;
6233 Indx : Nat)
6234 return Node_Id;
6235 -- Returns expression to compute:
6236 -- Exptyp'First < Typ'First or else Exptyp'Last > Typ'Last
6238 function Range_Equal_E_Cond
6239 (Exptyp : Entity_Id;
6240 Typ : Entity_Id;
6241 Indx : Nat) return Node_Id;
6242 -- Returns expression to compute:
6243 -- Exptyp'First /= Typ'First or else Exptyp'Last /= Typ'Last
6245 function Range_N_Cond
6246 (Expr : Node_Id;
6247 Typ : Entity_Id;
6248 Indx : Nat) return Node_Id;
6249 -- Return expression to compute:
6250 -- Expr'First < Typ'First or else Expr'Last > Typ'Last
6252 ---------------
6253 -- Add_Check --
6254 ---------------
6256 procedure Add_Check (N : Node_Id) is
6257 begin
6258 if Present (N) then
6260 -- For now, ignore attempt to place more than 2 checks ???
6262 if Num_Checks = 2 then
6263 return;
6264 end if;
6266 pragma Assert (Num_Checks <= 1);
6267 Num_Checks := Num_Checks + 1;
6268 Ret_Result (Num_Checks) := N;
6269 end if;
6270 end Add_Check;
6272 -------------------------
6273 -- Discrete_Expr_Cond --
6274 -------------------------
6276 function Discrete_Expr_Cond
6277 (Expr : Node_Id;
6278 Typ : Entity_Id) return Node_Id
6280 begin
6281 return
6282 Make_Or_Else (Loc,
6283 Left_Opnd =>
6284 Make_Op_Lt (Loc,
6285 Left_Opnd =>
6286 Convert_To (Base_Type (Typ),
6287 Duplicate_Subexpr_No_Checks (Expr)),
6288 Right_Opnd =>
6289 Convert_To (Base_Type (Typ),
6290 Get_E_First_Or_Last (Typ, 0, Name_First))),
6292 Right_Opnd =>
6293 Make_Op_Gt (Loc,
6294 Left_Opnd =>
6295 Convert_To (Base_Type (Typ),
6296 Duplicate_Subexpr_No_Checks (Expr)),
6297 Right_Opnd =>
6298 Convert_To
6299 (Base_Type (Typ),
6300 Get_E_First_Or_Last (Typ, 0, Name_Last))));
6301 end Discrete_Expr_Cond;
6303 -------------------------
6304 -- Discrete_Range_Cond --
6305 -------------------------
6307 function Discrete_Range_Cond
6308 (Expr : Node_Id;
6309 Typ : Entity_Id) return Node_Id
6311 LB : Node_Id := Low_Bound (Expr);
6312 HB : Node_Id := High_Bound (Expr);
6314 Left_Opnd : Node_Id;
6315 Right_Opnd : Node_Id;
6317 begin
6318 if Nkind (LB) = N_Identifier
6319 and then Ekind (Entity (LB)) = E_Discriminant
6320 then
6321 LB := New_Occurrence_Of (Discriminal (Entity (LB)), Loc);
6322 end if;
6324 if Nkind (HB) = N_Identifier
6325 and then Ekind (Entity (HB)) = E_Discriminant
6326 then
6327 HB := New_Occurrence_Of (Discriminal (Entity (HB)), Loc);
6328 end if;
6330 Left_Opnd :=
6331 Make_Op_Lt (Loc,
6332 Left_Opnd =>
6333 Convert_To
6334 (Base_Type (Typ), Duplicate_Subexpr_No_Checks (LB)),
6336 Right_Opnd =>
6337 Convert_To
6338 (Base_Type (Typ), Get_E_First_Or_Last (Typ, 0, Name_First)));
6340 if Base_Type (Typ) = Typ then
6341 return Left_Opnd;
6343 elsif Compile_Time_Known_Value (High_Bound (Scalar_Range (Typ)))
6344 and then
6345 Compile_Time_Known_Value (High_Bound (Scalar_Range
6346 (Base_Type (Typ))))
6347 then
6348 if Is_Floating_Point_Type (Typ) then
6349 if Expr_Value_R (High_Bound (Scalar_Range (Typ))) =
6350 Expr_Value_R (High_Bound (Scalar_Range (Base_Type (Typ))))
6351 then
6352 return Left_Opnd;
6353 end if;
6355 else
6356 if Expr_Value (High_Bound (Scalar_Range (Typ))) =
6357 Expr_Value (High_Bound (Scalar_Range (Base_Type (Typ))))
6358 then
6359 return Left_Opnd;
6360 end if;
6361 end if;
6362 end if;
6364 Right_Opnd :=
6365 Make_Op_Gt (Loc,
6366 Left_Opnd =>
6367 Convert_To
6368 (Base_Type (Typ), Duplicate_Subexpr_No_Checks (HB)),
6370 Right_Opnd =>
6371 Convert_To
6372 (Base_Type (Typ),
6373 Get_E_First_Or_Last (Typ, 0, Name_Last)));
6375 return Make_Or_Else (Loc, Left_Opnd, Right_Opnd);
6376 end Discrete_Range_Cond;
6378 -------------------------
6379 -- Get_E_First_Or_Last --
6380 -------------------------
6382 function Get_E_First_Or_Last
6383 (E : Entity_Id;
6384 Indx : Nat;
6385 Nam : Name_Id) return Node_Id
6387 N : Node_Id;
6388 LB : Node_Id;
6389 HB : Node_Id;
6390 Bound : Node_Id;
6392 begin
6393 if Is_Array_Type (E) then
6394 N := First_Index (E);
6396 for J in 2 .. Indx loop
6397 Next_Index (N);
6398 end loop;
6400 else
6401 N := Scalar_Range (E);
6402 end if;
6404 if Nkind (N) = N_Subtype_Indication then
6405 LB := Low_Bound (Range_Expression (Constraint (N)));
6406 HB := High_Bound (Range_Expression (Constraint (N)));
6408 elsif Is_Entity_Name (N) then
6409 LB := Type_Low_Bound (Etype (N));
6410 HB := Type_High_Bound (Etype (N));
6412 else
6413 LB := Low_Bound (N);
6414 HB := High_Bound (N);
6415 end if;
6417 if Nam = Name_First then
6418 Bound := LB;
6419 else
6420 Bound := HB;
6421 end if;
6423 if Nkind (Bound) = N_Identifier
6424 and then Ekind (Entity (Bound)) = E_Discriminant
6425 then
6426 -- If this is a task discriminant, and we are the body, we must
6427 -- retrieve the corresponding body discriminal. This is another
6428 -- consequence of the early creation of discriminals, and the
6429 -- need to generate constraint checks before their declarations
6430 -- are made visible.
6432 if Is_Concurrent_Record_Type (Scope (Entity (Bound))) then
6433 declare
6434 Tsk : constant Entity_Id :=
6435 Corresponding_Concurrent_Type
6436 (Scope (Entity (Bound)));
6437 Disc : Entity_Id;
6439 begin
6440 if In_Open_Scopes (Tsk)
6441 and then Has_Completion (Tsk)
6442 then
6443 -- Find discriminant of original task, and use its
6444 -- current discriminal, which is the renaming within
6445 -- the task body.
6447 Disc := First_Discriminant (Tsk);
6448 while Present (Disc) loop
6449 if Chars (Disc) = Chars (Entity (Bound)) then
6450 Set_Scope (Discriminal (Disc), Tsk);
6451 return New_Occurrence_Of (Discriminal (Disc), Loc);
6452 end if;
6454 Next_Discriminant (Disc);
6455 end loop;
6457 -- That loop should always succeed in finding a matching
6458 -- entry and returning. Fatal error if not.
6460 raise Program_Error;
6462 else
6463 return
6464 New_Occurrence_Of (Discriminal (Entity (Bound)), Loc);
6465 end if;
6466 end;
6467 else
6468 return New_Occurrence_Of (Discriminal (Entity (Bound)), Loc);
6469 end if;
6471 elsif Nkind (Bound) = N_Identifier
6472 and then Ekind (Entity (Bound)) = E_In_Parameter
6473 and then not Inside_Init_Proc
6474 then
6475 return Get_Discriminal (E, Bound);
6477 elsif Nkind (Bound) = N_Integer_Literal then
6478 return Make_Integer_Literal (Loc, Intval (Bound));
6480 -- Case of a bound rewritten to an N_Raise_Constraint_Error node
6481 -- because it is an out-of-range value. Duplicate_Subexpr cannot be
6482 -- called on this node because an N_Raise_Constraint_Error is not
6483 -- side effect free, and we may not assume that we are in the proper
6484 -- context to remove side effects on it at the point of reference.
6486 elsif Nkind (Bound) = N_Raise_Constraint_Error then
6487 return New_Copy_Tree (Bound);
6489 else
6490 return Duplicate_Subexpr_No_Checks (Bound);
6491 end if;
6492 end Get_E_First_Or_Last;
6494 -----------------
6495 -- Get_N_First --
6496 -----------------
6498 function Get_N_First (N : Node_Id; Indx : Nat) return Node_Id is
6499 begin
6500 return
6501 Make_Attribute_Reference (Loc,
6502 Attribute_Name => Name_First,
6503 Prefix =>
6504 Duplicate_Subexpr_No_Checks (N, Name_Req => True),
6505 Expressions => New_List (
6506 Make_Integer_Literal (Loc, Indx)));
6507 end Get_N_First;
6509 ----------------
6510 -- Get_N_Last --
6511 ----------------
6513 function Get_N_Last (N : Node_Id; Indx : Nat) return Node_Id is
6514 begin
6515 return
6516 Make_Attribute_Reference (Loc,
6517 Attribute_Name => Name_Last,
6518 Prefix =>
6519 Duplicate_Subexpr_No_Checks (N, Name_Req => True),
6520 Expressions => New_List (
6521 Make_Integer_Literal (Loc, Indx)));
6522 end Get_N_Last;
6524 ------------------
6525 -- Range_E_Cond --
6526 ------------------
6528 function Range_E_Cond
6529 (Exptyp : Entity_Id;
6530 Typ : Entity_Id;
6531 Indx : Nat) return Node_Id
6533 begin
6534 return
6535 Make_Or_Else (Loc,
6536 Left_Opnd =>
6537 Make_Op_Lt (Loc,
6538 Left_Opnd => Get_E_First_Or_Last (Exptyp, Indx, Name_First),
6539 Right_Opnd => Get_E_First_Or_Last (Typ, Indx, Name_First)),
6541 Right_Opnd =>
6542 Make_Op_Gt (Loc,
6543 Left_Opnd => Get_E_First_Or_Last (Exptyp, Indx, Name_Last),
6544 Right_Opnd => Get_E_First_Or_Last (Typ, Indx, Name_Last)));
6545 end Range_E_Cond;
6547 ------------------------
6548 -- Range_Equal_E_Cond --
6549 ------------------------
6551 function Range_Equal_E_Cond
6552 (Exptyp : Entity_Id;
6553 Typ : Entity_Id;
6554 Indx : Nat) return Node_Id
6556 begin
6557 return
6558 Make_Or_Else (Loc,
6559 Left_Opnd =>
6560 Make_Op_Ne (Loc,
6561 Left_Opnd => Get_E_First_Or_Last (Exptyp, Indx, Name_First),
6562 Right_Opnd => Get_E_First_Or_Last (Typ, Indx, Name_First)),
6563 Right_Opnd =>
6564 Make_Op_Ne (Loc,
6565 Left_Opnd => Get_E_First_Or_Last (Exptyp, Indx, Name_Last),
6566 Right_Opnd => Get_E_First_Or_Last (Typ, Indx, Name_Last)));
6567 end Range_Equal_E_Cond;
6569 ------------------
6570 -- Range_N_Cond --
6571 ------------------
6573 function Range_N_Cond
6574 (Expr : Node_Id;
6575 Typ : Entity_Id;
6576 Indx : Nat) return Node_Id
6578 begin
6579 return
6580 Make_Or_Else (Loc,
6581 Left_Opnd =>
6582 Make_Op_Lt (Loc,
6583 Left_Opnd => Get_N_First (Expr, Indx),
6584 Right_Opnd => Get_E_First_Or_Last (Typ, Indx, Name_First)),
6586 Right_Opnd =>
6587 Make_Op_Gt (Loc,
6588 Left_Opnd => Get_N_Last (Expr, Indx),
6589 Right_Opnd => Get_E_First_Or_Last (Typ, Indx, Name_Last)));
6590 end Range_N_Cond;
6592 -- Start of processing for Selected_Range_Checks
6594 begin
6595 if not Expander_Active then
6596 return Ret_Result;
6597 end if;
6599 if Target_Typ = Any_Type
6600 or else Target_Typ = Any_Composite
6601 or else Raises_Constraint_Error (Ck_Node)
6602 then
6603 return Ret_Result;
6604 end if;
6606 if No (Wnode) then
6607 Wnode := Ck_Node;
6608 end if;
6610 T_Typ := Target_Typ;
6612 if No (Source_Typ) then
6613 S_Typ := Etype (Ck_Node);
6614 else
6615 S_Typ := Source_Typ;
6616 end if;
6618 if S_Typ = Any_Type or else S_Typ = Any_Composite then
6619 return Ret_Result;
6620 end if;
6622 -- The order of evaluating T_Typ before S_Typ seems to be critical
6623 -- because S_Typ can be derived from Etype (Ck_Node), if it's not passed
6624 -- in, and since Node can be an N_Range node, it might be invalid.
6625 -- Should there be an assert check somewhere for taking the Etype of
6626 -- an N_Range node ???
6628 if Is_Access_Type (T_Typ) and then Is_Access_Type (S_Typ) then
6629 S_Typ := Designated_Type (S_Typ);
6630 T_Typ := Designated_Type (T_Typ);
6631 Do_Access := True;
6633 -- A simple optimization for the null case
6635 if Known_Null (Ck_Node) then
6636 return Ret_Result;
6637 end if;
6638 end if;
6640 -- For an N_Range Node, check for a null range and then if not
6641 -- null generate a range check action.
6643 if Nkind (Ck_Node) = N_Range then
6645 -- There's no point in checking a range against itself
6647 if Ck_Node = Scalar_Range (T_Typ) then
6648 return Ret_Result;
6649 end if;
6651 declare
6652 T_LB : constant Node_Id := Type_Low_Bound (T_Typ);
6653 T_HB : constant Node_Id := Type_High_Bound (T_Typ);
6654 Known_T_LB : constant Boolean := Compile_Time_Known_Value (T_LB);
6655 Known_T_HB : constant Boolean := Compile_Time_Known_Value (T_HB);
6657 LB : Node_Id := Low_Bound (Ck_Node);
6658 HB : Node_Id := High_Bound (Ck_Node);
6659 Known_LB : Boolean;
6660 Known_HB : Boolean;
6662 Null_Range : Boolean;
6663 Out_Of_Range_L : Boolean;
6664 Out_Of_Range_H : Boolean;
6666 begin
6667 -- Compute what is known at compile time
6669 if Known_T_LB and Known_T_HB then
6670 if Compile_Time_Known_Value (LB) then
6671 Known_LB := True;
6673 -- There's no point in checking that a bound is within its
6674 -- own range so pretend that it is known in this case. First
6675 -- deal with low bound.
6677 elsif Ekind (Etype (LB)) = E_Signed_Integer_Subtype
6678 and then Scalar_Range (Etype (LB)) = Scalar_Range (T_Typ)
6679 then
6680 LB := T_LB;
6681 Known_LB := True;
6683 else
6684 Known_LB := False;
6685 end if;
6687 -- Likewise for the high bound
6689 if Compile_Time_Known_Value (HB) then
6690 Known_HB := True;
6692 elsif Ekind (Etype (HB)) = E_Signed_Integer_Subtype
6693 and then Scalar_Range (Etype (HB)) = Scalar_Range (T_Typ)
6694 then
6695 HB := T_HB;
6696 Known_HB := True;
6698 else
6699 Known_HB := False;
6700 end if;
6701 end if;
6703 -- Check for case where everything is static and we can do the
6704 -- check at compile time. This is skipped if we have an access
6705 -- type, since the access value may be null.
6707 -- ??? This code can be improved since you only need to know that
6708 -- the two respective bounds (LB & T_LB or HB & T_HB) are known at
6709 -- compile time to emit pertinent messages.
6711 if Known_T_LB and Known_T_HB and Known_LB and Known_HB
6712 and not Do_Access
6713 then
6714 -- Floating-point case
6716 if Is_Floating_Point_Type (S_Typ) then
6717 Null_Range := Expr_Value_R (HB) < Expr_Value_R (LB);
6718 Out_Of_Range_L :=
6719 (Expr_Value_R (LB) < Expr_Value_R (T_LB))
6720 or else
6721 (Expr_Value_R (LB) > Expr_Value_R (T_HB));
6723 Out_Of_Range_H :=
6724 (Expr_Value_R (HB) > Expr_Value_R (T_HB))
6725 or else
6726 (Expr_Value_R (HB) < Expr_Value_R (T_LB));
6728 -- Fixed or discrete type case
6730 else
6731 Null_Range := Expr_Value (HB) < Expr_Value (LB);
6732 Out_Of_Range_L :=
6733 (Expr_Value (LB) < Expr_Value (T_LB))
6734 or else
6735 (Expr_Value (LB) > Expr_Value (T_HB));
6737 Out_Of_Range_H :=
6738 (Expr_Value (HB) > Expr_Value (T_HB))
6739 or else
6740 (Expr_Value (HB) < Expr_Value (T_LB));
6741 end if;
6743 if not Null_Range then
6744 if Out_Of_Range_L then
6745 if No (Warn_Node) then
6746 Add_Check
6747 (Compile_Time_Constraint_Error
6748 (Low_Bound (Ck_Node),
6749 "static value out of range of}?", T_Typ));
6751 else
6752 Add_Check
6753 (Compile_Time_Constraint_Error
6754 (Wnode,
6755 "static range out of bounds of}?", T_Typ));
6756 end if;
6757 end if;
6759 if Out_Of_Range_H then
6760 if No (Warn_Node) then
6761 Add_Check
6762 (Compile_Time_Constraint_Error
6763 (High_Bound (Ck_Node),
6764 "static value out of range of}?", T_Typ));
6766 else
6767 Add_Check
6768 (Compile_Time_Constraint_Error
6769 (Wnode,
6770 "static range out of bounds of}?", T_Typ));
6771 end if;
6772 end if;
6773 end if;
6775 else
6776 declare
6777 LB : Node_Id := Low_Bound (Ck_Node);
6778 HB : Node_Id := High_Bound (Ck_Node);
6780 begin
6781 -- If either bound is a discriminant and we are within the
6782 -- record declaration, it is a use of the discriminant in a
6783 -- constraint of a component, and nothing can be checked
6784 -- here. The check will be emitted within the init proc.
6785 -- Before then, the discriminal has no real meaning.
6786 -- Similarly, if the entity is a discriminal, there is no
6787 -- check to perform yet.
6789 -- The same holds within a discriminated synchronized type,
6790 -- where the discriminant may constrain a component or an
6791 -- entry family.
6793 if Nkind (LB) = N_Identifier
6794 and then Denotes_Discriminant (LB, True)
6795 then
6796 if Current_Scope = Scope (Entity (LB))
6797 or else Is_Concurrent_Type (Current_Scope)
6798 or else Ekind (Entity (LB)) /= E_Discriminant
6799 then
6800 return Ret_Result;
6801 else
6802 LB :=
6803 New_Occurrence_Of (Discriminal (Entity (LB)), Loc);
6804 end if;
6805 end if;
6807 if Nkind (HB) = N_Identifier
6808 and then Denotes_Discriminant (HB, True)
6809 then
6810 if Current_Scope = Scope (Entity (HB))
6811 or else Is_Concurrent_Type (Current_Scope)
6812 or else Ekind (Entity (HB)) /= E_Discriminant
6813 then
6814 return Ret_Result;
6815 else
6816 HB :=
6817 New_Occurrence_Of (Discriminal (Entity (HB)), Loc);
6818 end if;
6819 end if;
6821 Cond := Discrete_Range_Cond (Ck_Node, T_Typ);
6822 Set_Paren_Count (Cond, 1);
6824 Cond :=
6825 Make_And_Then (Loc,
6826 Left_Opnd =>
6827 Make_Op_Ge (Loc,
6828 Left_Opnd => Duplicate_Subexpr_No_Checks (HB),
6829 Right_Opnd => Duplicate_Subexpr_No_Checks (LB)),
6830 Right_Opnd => Cond);
6831 end;
6832 end if;
6833 end;
6835 elsif Is_Scalar_Type (S_Typ) then
6837 -- This somewhat duplicates what Apply_Scalar_Range_Check does,
6838 -- except the above simply sets a flag in the node and lets
6839 -- gigi generate the check base on the Etype of the expression.
6840 -- Sometimes, however we want to do a dynamic check against an
6841 -- arbitrary target type, so we do that here.
6843 if Ekind (Base_Type (S_Typ)) /= Ekind (Base_Type (T_Typ)) then
6844 Cond := Discrete_Expr_Cond (Ck_Node, T_Typ);
6846 -- For literals, we can tell if the constraint error will be
6847 -- raised at compile time, so we never need a dynamic check, but
6848 -- if the exception will be raised, then post the usual warning,
6849 -- and replace the literal with a raise constraint error
6850 -- expression. As usual, skip this for access types
6852 elsif Compile_Time_Known_Value (Ck_Node)
6853 and then not Do_Access
6854 then
6855 declare
6856 LB : constant Node_Id := Type_Low_Bound (T_Typ);
6857 UB : constant Node_Id := Type_High_Bound (T_Typ);
6859 Out_Of_Range : Boolean;
6860 Static_Bounds : constant Boolean :=
6861 Compile_Time_Known_Value (LB)
6862 and Compile_Time_Known_Value (UB);
6864 begin
6865 -- Following range tests should use Sem_Eval routine ???
6867 if Static_Bounds then
6868 if Is_Floating_Point_Type (S_Typ) then
6869 Out_Of_Range :=
6870 (Expr_Value_R (Ck_Node) < Expr_Value_R (LB))
6871 or else
6872 (Expr_Value_R (Ck_Node) > Expr_Value_R (UB));
6874 -- Fixed or discrete type
6876 else
6877 Out_Of_Range :=
6878 Expr_Value (Ck_Node) < Expr_Value (LB)
6879 or else
6880 Expr_Value (Ck_Node) > Expr_Value (UB);
6881 end if;
6883 -- Bounds of the type are static and the literal is out of
6884 -- range so output a warning message.
6886 if Out_Of_Range then
6887 if No (Warn_Node) then
6888 Add_Check
6889 (Compile_Time_Constraint_Error
6890 (Ck_Node,
6891 "static value out of range of}?", T_Typ));
6893 else
6894 Add_Check
6895 (Compile_Time_Constraint_Error
6896 (Wnode,
6897 "static value out of range of}?", T_Typ));
6898 end if;
6899 end if;
6901 else
6902 Cond := Discrete_Expr_Cond (Ck_Node, T_Typ);
6903 end if;
6904 end;
6906 -- Here for the case of a non-static expression, we need a runtime
6907 -- check unless the source type range is guaranteed to be in the
6908 -- range of the target type.
6910 else
6911 if not In_Subrange_Of (S_Typ, T_Typ) then
6912 Cond := Discrete_Expr_Cond (Ck_Node, T_Typ);
6913 end if;
6914 end if;
6915 end if;
6917 if Is_Array_Type (T_Typ) and then Is_Array_Type (S_Typ) then
6918 if Is_Constrained (T_Typ) then
6920 Expr_Actual := Get_Referenced_Object (Ck_Node);
6921 Exptyp := Get_Actual_Subtype (Expr_Actual);
6923 if Is_Access_Type (Exptyp) then
6924 Exptyp := Designated_Type (Exptyp);
6925 end if;
6927 -- String_Literal case. This needs to be handled specially be-
6928 -- cause no index types are available for string literals. The
6929 -- condition is simply:
6931 -- T_Typ'Length = string-literal-length
6933 if Nkind (Expr_Actual) = N_String_Literal then
6934 null;
6936 -- General array case. Here we have a usable actual subtype for
6937 -- the expression, and the condition is built from the two types
6939 -- T_Typ'First < Exptyp'First or else
6940 -- T_Typ'Last > Exptyp'Last or else
6941 -- T_Typ'First(1) < Exptyp'First(1) or else
6942 -- T_Typ'Last(1) > Exptyp'Last(1) or else
6943 -- ...
6945 elsif Is_Constrained (Exptyp) then
6946 declare
6947 Ndims : constant Nat := Number_Dimensions (T_Typ);
6949 L_Index : Node_Id;
6950 R_Index : Node_Id;
6952 begin
6953 L_Index := First_Index (T_Typ);
6954 R_Index := First_Index (Exptyp);
6956 for Indx in 1 .. Ndims loop
6957 if not (Nkind (L_Index) = N_Raise_Constraint_Error
6958 or else
6959 Nkind (R_Index) = N_Raise_Constraint_Error)
6960 then
6961 -- Deal with compile time length check. Note that we
6962 -- skip this in the access case, because the access
6963 -- value may be null, so we cannot know statically.
6965 if not
6966 Subtypes_Statically_Match
6967 (Etype (L_Index), Etype (R_Index))
6968 then
6969 -- If the target type is constrained then we
6970 -- have to check for exact equality of bounds
6971 -- (required for qualified expressions).
6973 if Is_Constrained (T_Typ) then
6974 Evolve_Or_Else
6975 (Cond,
6976 Range_Equal_E_Cond (Exptyp, T_Typ, Indx));
6977 else
6978 Evolve_Or_Else
6979 (Cond, Range_E_Cond (Exptyp, T_Typ, Indx));
6980 end if;
6981 end if;
6983 Next (L_Index);
6984 Next (R_Index);
6985 end if;
6986 end loop;
6987 end;
6989 -- Handle cases where we do not get a usable actual subtype that
6990 -- is constrained. This happens for example in the function call
6991 -- and explicit dereference cases. In these cases, we have to get
6992 -- the length or range from the expression itself, making sure we
6993 -- do not evaluate it more than once.
6995 -- Here Ck_Node is the original expression, or more properly the
6996 -- result of applying Duplicate_Expr to the original tree,
6997 -- forcing the result to be a name.
6999 else
7000 declare
7001 Ndims : constant Nat := Number_Dimensions (T_Typ);
7003 begin
7004 -- Build the condition for the explicit dereference case
7006 for Indx in 1 .. Ndims loop
7007 Evolve_Or_Else
7008 (Cond, Range_N_Cond (Ck_Node, T_Typ, Indx));
7009 end loop;
7010 end;
7011 end if;
7013 else
7014 -- For a conversion to an unconstrained array type, generate an
7015 -- Action to check that the bounds of the source value are within
7016 -- the constraints imposed by the target type (RM 4.6(38)). No
7017 -- check is needed for a conversion to an access to unconstrained
7018 -- array type, as 4.6(24.15/2) requires the designated subtypes
7019 -- of the two access types to statically match.
7021 if Nkind (Parent (Ck_Node)) = N_Type_Conversion
7022 and then not Do_Access
7023 then
7024 declare
7025 Opnd_Index : Node_Id;
7026 Targ_Index : Node_Id;
7027 Opnd_Range : Node_Id;
7029 begin
7030 Opnd_Index := First_Index (Get_Actual_Subtype (Ck_Node));
7031 Targ_Index := First_Index (T_Typ);
7032 while Present (Opnd_Index) loop
7034 -- If the index is a range, use its bounds. If it is an
7035 -- entity (as will be the case if it is a named subtype
7036 -- or an itype created for a slice) retrieve its range.
7038 if Is_Entity_Name (Opnd_Index)
7039 and then Is_Type (Entity (Opnd_Index))
7040 then
7041 Opnd_Range := Scalar_Range (Entity (Opnd_Index));
7042 else
7043 Opnd_Range := Opnd_Index;
7044 end if;
7046 if Nkind (Opnd_Range) = N_Range then
7047 if Is_In_Range
7048 (Low_Bound (Opnd_Range), Etype (Targ_Index),
7049 Assume_Valid => True)
7050 and then
7051 Is_In_Range
7052 (High_Bound (Opnd_Range), Etype (Targ_Index),
7053 Assume_Valid => True)
7054 then
7055 null;
7057 -- If null range, no check needed
7059 elsif
7060 Compile_Time_Known_Value (High_Bound (Opnd_Range))
7061 and then
7062 Compile_Time_Known_Value (Low_Bound (Opnd_Range))
7063 and then
7064 Expr_Value (High_Bound (Opnd_Range)) <
7065 Expr_Value (Low_Bound (Opnd_Range))
7066 then
7067 null;
7069 elsif Is_Out_Of_Range
7070 (Low_Bound (Opnd_Range), Etype (Targ_Index),
7071 Assume_Valid => True)
7072 or else
7073 Is_Out_Of_Range
7074 (High_Bound (Opnd_Range), Etype (Targ_Index),
7075 Assume_Valid => True)
7076 then
7077 Add_Check
7078 (Compile_Time_Constraint_Error
7079 (Wnode, "value out of range of}?", T_Typ));
7081 else
7082 Evolve_Or_Else
7083 (Cond,
7084 Discrete_Range_Cond
7085 (Opnd_Range, Etype (Targ_Index)));
7086 end if;
7087 end if;
7089 Next_Index (Opnd_Index);
7090 Next_Index (Targ_Index);
7091 end loop;
7092 end;
7093 end if;
7094 end if;
7095 end if;
7097 -- Construct the test and insert into the tree
7099 if Present (Cond) then
7100 if Do_Access then
7101 Cond := Guard_Access (Cond, Loc, Ck_Node);
7102 end if;
7104 Add_Check
7105 (Make_Raise_Constraint_Error (Loc,
7106 Condition => Cond,
7107 Reason => CE_Range_Check_Failed));
7108 end if;
7110 return Ret_Result;
7111 end Selected_Range_Checks;
7113 -------------------------------
7114 -- Storage_Checks_Suppressed --
7115 -------------------------------
7117 function Storage_Checks_Suppressed (E : Entity_Id) return Boolean is
7118 begin
7119 if Present (E) and then Checks_May_Be_Suppressed (E) then
7120 return Is_Check_Suppressed (E, Storage_Check);
7121 else
7122 return Scope_Suppress (Storage_Check);
7123 end if;
7124 end Storage_Checks_Suppressed;
7126 ---------------------------
7127 -- Tag_Checks_Suppressed --
7128 ---------------------------
7130 function Tag_Checks_Suppressed (E : Entity_Id) return Boolean is
7131 begin
7132 if Present (E) then
7133 if Kill_Tag_Checks (E) then
7134 return True;
7135 elsif Checks_May_Be_Suppressed (E) then
7136 return Is_Check_Suppressed (E, Tag_Check);
7137 end if;
7138 end if;
7140 return Scope_Suppress (Tag_Check);
7141 end Tag_Checks_Suppressed;
7143 --------------------------
7144 -- Validity_Check_Range --
7145 --------------------------
7147 procedure Validity_Check_Range (N : Node_Id) is
7148 begin
7149 if Validity_Checks_On and Validity_Check_Operands then
7150 if Nkind (N) = N_Range then
7151 Ensure_Valid (Low_Bound (N));
7152 Ensure_Valid (High_Bound (N));
7153 end if;
7154 end if;
7155 end Validity_Check_Range;
7157 --------------------------------
7158 -- Validity_Checks_Suppressed --
7159 --------------------------------
7161 function Validity_Checks_Suppressed (E : Entity_Id) return Boolean is
7162 begin
7163 if Present (E) and then Checks_May_Be_Suppressed (E) then
7164 return Is_Check_Suppressed (E, Validity_Check);
7165 else
7166 return Scope_Suppress (Validity_Check);
7167 end if;
7168 end Validity_Checks_Suppressed;
7170 end Checks;