1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 1992-2009, Free Software Foundation, Inc. --
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. --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
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_Ch4
; use Exp_Ch4
;
32 with Exp_Ch11
; use Exp_Ch11
;
33 with Exp_Pakd
; use Exp_Pakd
;
34 with Exp_Util
; use Exp_Util
;
35 with Elists
; use Elists
;
36 with Eval_Fat
; use Eval_Fat
;
37 with Freeze
; use Freeze
;
39 with Nlists
; use Nlists
;
40 with Nmake
; use Nmake
;
42 with Output
; use Output
;
43 with Restrict
; use Restrict
;
44 with Rident
; use Rident
;
45 with Rtsfind
; use Rtsfind
;
47 with Sem_Aux
; use Sem_Aux
;
48 with Sem_Eval
; use Sem_Eval
;
49 with Sem_Ch3
; use Sem_Ch3
;
50 with Sem_Ch8
; use Sem_Ch8
;
51 with Sem_Res
; use Sem_Res
;
52 with Sem_Util
; use Sem_Util
;
53 with Sem_Warn
; use Sem_Warn
;
54 with Sinfo
; use Sinfo
;
55 with Sinput
; use Sinput
;
56 with Snames
; use Snames
;
57 with Sprint
; use Sprint
;
58 with Stand
; use Stand
;
59 with Targparm
; use Targparm
;
60 with Tbuild
; use Tbuild
;
61 with Ttypes
; use Ttypes
;
62 with Urealp
; use Urealp
;
63 with Validsw
; use Validsw
;
65 package body Checks
is
67 -- General note: many of these routines are concerned with generating
68 -- checking code to make sure that constraint error is raised at runtime.
69 -- Clearly this code is only needed if the expander is active, since
70 -- otherwise we will not be generating code or going into the runtime
73 -- We therefore disconnect most of these checks if the expander is
74 -- inactive. This has the additional benefit that we do not need to
75 -- worry about the tree being messed up by previous errors (since errors
76 -- turn off expansion anyway).
78 -- There are a few exceptions to the above rule. For instance routines
79 -- such as Apply_Scalar_Range_Check that do not insert any code can be
80 -- safely called even when the Expander is inactive (but Errors_Detected
81 -- is 0). The benefit of executing this code when expansion is off, is
82 -- the ability to emit constraint error warning for static expressions
83 -- even when we are not generating code.
85 -------------------------------------
86 -- Suppression of Redundant Checks --
87 -------------------------------------
89 -- This unit implements a limited circuit for removal of redundant
90 -- checks. The processing is based on a tracing of simple sequential
91 -- flow. For any sequence of statements, we save expressions that are
92 -- marked to be checked, and then if the same expression appears later
93 -- with the same check, then under certain circumstances, the second
94 -- check can be suppressed.
96 -- Basically, we can suppress the check if we know for certain that
97 -- the previous expression has been elaborated (together with its
98 -- check), and we know that the exception frame is the same, and that
99 -- nothing has happened to change the result of the exception.
101 -- Let us examine each of these three conditions in turn to describe
102 -- how we ensure that this condition is met.
104 -- First, we need to know for certain that the previous expression has
105 -- been executed. This is done principly by the mechanism of calling
106 -- Conditional_Statements_Begin at the start of any statement sequence
107 -- and Conditional_Statements_End at the end. The End call causes all
108 -- checks remembered since the Begin call to be discarded. This does
109 -- miss a few cases, notably the case of a nested BEGIN-END block with
110 -- no exception handlers. But the important thing is to be conservative.
111 -- The other protection is that all checks are discarded if a label
112 -- is encountered, since then the assumption of sequential execution
113 -- is violated, and we don't know enough about the flow.
115 -- Second, we need to know that the exception frame is the same. We
116 -- do this by killing all remembered checks when we enter a new frame.
117 -- Again, that's over-conservative, but generally the cases we can help
118 -- with are pretty local anyway (like the body of a loop for example).
120 -- Third, we must be sure to forget any checks which are no longer valid.
121 -- This is done by two mechanisms, first the Kill_Checks_Variable call is
122 -- used to note any changes to local variables. We only attempt to deal
123 -- with checks involving local variables, so we do not need to worry
124 -- about global variables. Second, a call to any non-global procedure
125 -- causes us to abandon all stored checks, since such a all may affect
126 -- the values of any local variables.
128 -- The following define the data structures used to deal with remembering
129 -- checks so that redundant checks can be eliminated as described above.
131 -- Right now, the only expressions that we deal with are of the form of
132 -- simple local objects (either declared locally, or IN parameters) or
133 -- such objects plus/minus a compile time known constant. We can do
134 -- more later on if it seems worthwhile, but this catches many simple
135 -- cases in practice.
137 -- The following record type reflects a single saved check. An entry
138 -- is made in the stack of saved checks if and only if the expression
139 -- has been elaborated with the indicated checks.
141 type Saved_Check
is record
143 -- Set True if entry is killed by Kill_Checks
146 -- The entity involved in the expression that is checked
149 -- A compile time value indicating the result of adding or
150 -- subtracting a compile time value. This value is to be
151 -- added to the value of the Entity. A value of zero is
152 -- used for the case of a simple entity reference.
154 Check_Type
: Character;
155 -- This is set to 'R' for a range check (in which case Target_Type
156 -- is set to the target type for the range check) or to 'O' for an
157 -- overflow check (in which case Target_Type is set to Empty).
159 Target_Type
: Entity_Id
;
160 -- Used only if Do_Range_Check is set. Records the target type for
161 -- the check. We need this, because a check is a duplicate only if
162 -- it has a the same target type (or more accurately one with a
163 -- range that is smaller or equal to the stored target type of a
167 -- The following table keeps track of saved checks. Rather than use an
168 -- extensible table. We just use a table of fixed size, and we discard
169 -- any saved checks that do not fit. That's very unlikely to happen and
170 -- this is only an optimization in any case.
172 Saved_Checks
: array (Int
range 1 .. 200) of Saved_Check
;
173 -- Array of saved checks
175 Num_Saved_Checks
: Nat
:= 0;
176 -- Number of saved checks
178 -- The following stack keeps track of statement ranges. It is treated
179 -- as a stack. When Conditional_Statements_Begin is called, an entry
180 -- is pushed onto this stack containing the value of Num_Saved_Checks
181 -- at the time of the call. Then when Conditional_Statements_End is
182 -- called, this value is popped off and used to reset Num_Saved_Checks.
184 -- Note: again, this is a fixed length stack with a size that should
185 -- always be fine. If the value of the stack pointer goes above the
186 -- limit, then we just forget all saved checks.
188 Saved_Checks_Stack
: array (Int
range 1 .. 100) of Nat
;
189 Saved_Checks_TOS
: Nat
:= 0;
191 -----------------------
192 -- Local Subprograms --
193 -----------------------
195 procedure Apply_Float_Conversion_Check
197 Target_Typ
: Entity_Id
);
198 -- The checks on a conversion from a floating-point type to an integer
199 -- type are delicate. They have to be performed before conversion, they
200 -- have to raise an exception when the operand is a NaN, and rounding must
201 -- be taken into account to determine the safe bounds of the operand.
203 procedure Apply_Selected_Length_Checks
205 Target_Typ
: Entity_Id
;
206 Source_Typ
: Entity_Id
;
207 Do_Static
: Boolean);
208 -- This is the subprogram that does all the work for Apply_Length_Check
209 -- and Apply_Static_Length_Check. Expr, Target_Typ and Source_Typ are as
210 -- described for the above routines. The Do_Static flag indicates that
211 -- only a static check is to be done.
213 procedure Apply_Selected_Range_Checks
215 Target_Typ
: Entity_Id
;
216 Source_Typ
: Entity_Id
;
217 Do_Static
: Boolean);
218 -- This is the subprogram that does all the work for Apply_Range_Check.
219 -- Expr, Target_Typ and Source_Typ are as described for the above
220 -- routine. The Do_Static flag indicates that only a static check is
223 type Check_Type
is new Check_Id
range Access_Check
.. Division_Check
;
224 function Check_Needed
(Nod
: Node_Id
; Check
: Check_Type
) return Boolean;
225 -- This function is used to see if an access or division by zero check is
226 -- needed. The check is to be applied to a single variable appearing in the
227 -- source, and N is the node for the reference. If N is not of this form,
228 -- True is returned with no further processing. If N is of the right form,
229 -- then further processing determines if the given Check is needed.
231 -- The particular circuit is to see if we have the case of a check that is
232 -- not needed because it appears in the right operand of a short circuited
233 -- conditional where the left operand guards the check. For example:
235 -- if Var = 0 or else Q / Var > 12 then
239 -- In this example, the division check is not required. At the same time
240 -- we can issue warnings for suspicious use of non-short-circuited forms,
243 -- if Var = 0 or Q / Var > 12 then
249 Check_Type
: Character;
250 Target_Type
: Entity_Id
;
251 Entry_OK
: out Boolean;
255 -- This routine is used by Enable_Range_Check and Enable_Overflow_Check
256 -- to see if a check is of the form for optimization, and if so, to see
257 -- if it has already been performed. Expr is the expression to check,
258 -- and Check_Type is 'R' for a range check, 'O' for an overflow check.
259 -- Target_Type is the target type for a range check, and Empty for an
260 -- overflow check. If the entry is not of the form for optimization,
261 -- then Entry_OK is set to False, and the remaining out parameters
262 -- are undefined. If the entry is OK, then Ent/Ofs are set to the
263 -- entity and offset from the expression. Check_Num is the number of
264 -- a matching saved entry in Saved_Checks, or zero if no such entry
267 function Get_Discriminal
(E
: Entity_Id
; Bound
: Node_Id
) return Node_Id
;
268 -- If a discriminal is used in constraining a prival, Return reference
269 -- to the discriminal of the protected body (which renames the parameter
270 -- of the enclosing protected operation). This clumsy transformation is
271 -- needed because privals are created too late and their actual subtypes
272 -- are not available when analysing the bodies of the protected operations.
273 -- This function is called whenever the bound is an entity and the scope
274 -- indicates a protected operation. If the bound is an in-parameter of
275 -- a protected operation that is not a prival, the function returns the
277 -- To be cleaned up???
279 function Guard_Access
282 Ck_Node
: Node_Id
) return Node_Id
;
283 -- In the access type case, guard the test with a test to ensure
284 -- that the access value is non-null, since the checks do not
285 -- not apply to null access values.
287 procedure Install_Static_Check
(R_Cno
: Node_Id
; Loc
: Source_Ptr
);
288 -- Called by Apply_{Length,Range}_Checks to rewrite the tree with the
289 -- Constraint_Error node.
291 function Range_Or_Validity_Checks_Suppressed
292 (Expr
: Node_Id
) return Boolean;
293 -- Returns True if either range or validity checks or both are suppressed
294 -- for the type of the given expression, or, if the expression is the name
295 -- of an entity, if these checks are suppressed for the entity.
297 function Selected_Length_Checks
299 Target_Typ
: Entity_Id
;
300 Source_Typ
: Entity_Id
;
301 Warn_Node
: Node_Id
) return Check_Result
;
302 -- Like Apply_Selected_Length_Checks, except it doesn't modify
303 -- anything, just returns a list of nodes as described in the spec of
304 -- this package for the Range_Check function.
306 function Selected_Range_Checks
308 Target_Typ
: Entity_Id
;
309 Source_Typ
: Entity_Id
;
310 Warn_Node
: Node_Id
) return Check_Result
;
311 -- Like Apply_Selected_Range_Checks, except it doesn't modify anything,
312 -- just returns a list of nodes as described in the spec of this package
313 -- for the Range_Check function.
315 ------------------------------
316 -- Access_Checks_Suppressed --
317 ------------------------------
319 function Access_Checks_Suppressed
(E
: Entity_Id
) return Boolean is
321 if Present
(E
) and then Checks_May_Be_Suppressed
(E
) then
322 return Is_Check_Suppressed
(E
, Access_Check
);
324 return Scope_Suppress
(Access_Check
);
326 end Access_Checks_Suppressed
;
328 -------------------------------------
329 -- Accessibility_Checks_Suppressed --
330 -------------------------------------
332 function Accessibility_Checks_Suppressed
(E
: Entity_Id
) return Boolean is
334 if Present
(E
) and then Checks_May_Be_Suppressed
(E
) then
335 return Is_Check_Suppressed
(E
, Accessibility_Check
);
337 return Scope_Suppress
(Accessibility_Check
);
339 end Accessibility_Checks_Suppressed
;
341 -----------------------------
342 -- Activate_Division_Check --
343 -----------------------------
345 procedure Activate_Division_Check
(N
: Node_Id
) is
347 Set_Do_Division_Check
(N
, True);
348 Possible_Local_Raise
(N
, Standard_Constraint_Error
);
349 end Activate_Division_Check
;
351 -----------------------------
352 -- Activate_Overflow_Check --
353 -----------------------------
355 procedure Activate_Overflow_Check
(N
: Node_Id
) is
357 Set_Do_Overflow_Check
(N
, True);
358 Possible_Local_Raise
(N
, Standard_Constraint_Error
);
359 end Activate_Overflow_Check
;
361 --------------------------
362 -- Activate_Range_Check --
363 --------------------------
365 procedure Activate_Range_Check
(N
: Node_Id
) is
367 Set_Do_Range_Check
(N
, True);
368 Possible_Local_Raise
(N
, Standard_Constraint_Error
);
369 end Activate_Range_Check
;
371 ---------------------------------
372 -- Alignment_Checks_Suppressed --
373 ---------------------------------
375 function Alignment_Checks_Suppressed
(E
: Entity_Id
) return Boolean is
377 if Present
(E
) and then Checks_May_Be_Suppressed
(E
) then
378 return Is_Check_Suppressed
(E
, Alignment_Check
);
380 return Scope_Suppress
(Alignment_Check
);
382 end Alignment_Checks_Suppressed
;
384 -------------------------
385 -- Append_Range_Checks --
386 -------------------------
388 procedure Append_Range_Checks
389 (Checks
: Check_Result
;
391 Suppress_Typ
: Entity_Id
;
392 Static_Sloc
: Source_Ptr
;
395 Internal_Flag_Node
: constant Node_Id
:= Flag_Node
;
396 Internal_Static_Sloc
: constant Source_Ptr
:= Static_Sloc
;
398 Checks_On
: constant Boolean :=
399 (not Index_Checks_Suppressed
(Suppress_Typ
))
401 (not Range_Checks_Suppressed
(Suppress_Typ
));
404 -- For now we just return if Checks_On is false, however this should
405 -- be enhanced to check for an always True value in the condition
406 -- and to generate a compilation warning???
408 if not Checks_On
then
413 exit when No
(Checks
(J
));
415 if Nkind
(Checks
(J
)) = N_Raise_Constraint_Error
416 and then Present
(Condition
(Checks
(J
)))
418 if not Has_Dynamic_Range_Check
(Internal_Flag_Node
) then
419 Append_To
(Stmts
, Checks
(J
));
420 Set_Has_Dynamic_Range_Check
(Internal_Flag_Node
);
426 Make_Raise_Constraint_Error
(Internal_Static_Sloc
,
427 Reason
=> CE_Range_Check_Failed
));
430 end Append_Range_Checks
;
432 ------------------------
433 -- Apply_Access_Check --
434 ------------------------
436 procedure Apply_Access_Check
(N
: Node_Id
) is
437 P
: constant Node_Id
:= Prefix
(N
);
440 -- We do not need checks if we are not generating code (i.e. the
441 -- expander is not active). This is not just an optimization, there
442 -- are cases (e.g. with pragma Debug) where generating the checks
443 -- can cause real trouble).
445 if not Expander_Active
then
449 -- No check if short circuiting makes check unnecessary
451 if not Check_Needed
(P
, Access_Check
) then
455 -- No check if accessing the Offset_To_Top component of a dispatch
456 -- table. They are safe by construction.
458 if Tagged_Type_Expansion
459 and then Present
(Etype
(P
))
460 and then RTU_Loaded
(Ada_Tags
)
461 and then RTE_Available
(RE_Offset_To_Top_Ptr
)
462 and then Etype
(P
) = RTE
(RE_Offset_To_Top_Ptr
)
467 -- Otherwise go ahead and install the check
469 Install_Null_Excluding_Check
(P
);
470 end Apply_Access_Check
;
472 -------------------------------
473 -- Apply_Accessibility_Check --
474 -------------------------------
476 procedure Apply_Accessibility_Check
479 Insert_Node
: Node_Id
)
481 Loc
: constant Source_Ptr
:= Sloc
(N
);
482 Param_Ent
: constant Entity_Id
:= Param_Entity
(N
);
483 Param_Level
: Node_Id
;
484 Type_Level
: Node_Id
;
487 if Inside_A_Generic
then
490 -- Only apply the run-time check if the access parameter has an
491 -- associated extra access level parameter and when the level of the
492 -- type is less deep than the level of the access parameter, and
493 -- accessibility checks are not suppressed.
495 elsif Present
(Param_Ent
)
496 and then Present
(Extra_Accessibility
(Param_Ent
))
497 and then UI_Gt
(Object_Access_Level
(N
), Type_Access_Level
(Typ
))
498 and then not Accessibility_Checks_Suppressed
(Param_Ent
)
499 and then not Accessibility_Checks_Suppressed
(Typ
)
502 New_Occurrence_Of
(Extra_Accessibility
(Param_Ent
), Loc
);
505 Make_Integer_Literal
(Loc
, Type_Access_Level
(Typ
));
507 -- Raise Program_Error if the accessibility level of the access
508 -- parameter is deeper than the level of the target access type.
510 Insert_Action
(Insert_Node
,
511 Make_Raise_Program_Error
(Loc
,
514 Left_Opnd
=> Param_Level
,
515 Right_Opnd
=> Type_Level
),
516 Reason
=> PE_Accessibility_Check_Failed
));
518 Analyze_And_Resolve
(N
);
520 end Apply_Accessibility_Check
;
522 --------------------------------
523 -- Apply_Address_Clause_Check --
524 --------------------------------
526 procedure Apply_Address_Clause_Check
(E
: Entity_Id
; N
: Node_Id
) is
527 AC
: constant Node_Id
:= Address_Clause
(E
);
528 Loc
: constant Source_Ptr
:= Sloc
(AC
);
529 Typ
: constant Entity_Id
:= Etype
(E
);
530 Aexp
: constant Node_Id
:= Expression
(AC
);
533 -- Address expression (not necessarily the same as Aexp, for example
534 -- when Aexp is a reference to a constant, in which case Expr gets
535 -- reset to reference the value expression of the constant.
537 procedure Compile_Time_Bad_Alignment
;
538 -- Post error warnings when alignment is known to be incompatible. Note
539 -- that we do not go as far as inserting a raise of Program_Error since
540 -- this is an erroneous case, and it may happen that we are lucky and an
541 -- underaligned address turns out to be OK after all.
543 --------------------------------
544 -- Compile_Time_Bad_Alignment --
545 --------------------------------
547 procedure Compile_Time_Bad_Alignment
is
549 if Address_Clause_Overlay_Warnings
then
551 ("?specified address for& may be inconsistent with alignment ",
554 ("\?program execution may be erroneous (RM 13.3(27))",
556 Set_Address_Warning_Posted
(AC
);
558 end Compile_Time_Bad_Alignment
;
560 -- Start of processing for Apply_Address_Clause_Check
563 -- See if alignment check needed. Note that we never need a check if the
564 -- maximum alignment is one, since the check will always succeed.
566 -- Note: we do not check for checks suppressed here, since that check
567 -- was done in Sem_Ch13 when the address clause was processed. We are
568 -- only called if checks were not suppressed. The reason for this is
569 -- that we have to delay the call to Apply_Alignment_Check till freeze
570 -- time (so that all types etc are elaborated), but we have to check
571 -- the status of check suppressing at the point of the address clause.
574 or else not Check_Address_Alignment
(AC
)
575 or else Maximum_Alignment
= 1
580 -- Obtain expression from address clause
582 Expr
:= Expression
(AC
);
584 -- The following loop digs for the real expression to use in the check
587 -- For constant, get constant expression
589 if Is_Entity_Name
(Expr
)
590 and then Ekind
(Entity
(Expr
)) = E_Constant
592 Expr
:= Constant_Value
(Entity
(Expr
));
594 -- For unchecked conversion, get result to convert
596 elsif Nkind
(Expr
) = N_Unchecked_Type_Conversion
then
597 Expr
:= Expression
(Expr
);
599 -- For (common case) of To_Address call, get argument
601 elsif Nkind
(Expr
) = N_Function_Call
602 and then Is_Entity_Name
(Name
(Expr
))
603 and then Is_RTE
(Entity
(Name
(Expr
)), RE_To_Address
)
605 Expr
:= First
(Parameter_Associations
(Expr
));
607 if Nkind
(Expr
) = N_Parameter_Association
then
608 Expr
:= Explicit_Actual_Parameter
(Expr
);
611 -- We finally have the real expression
618 -- See if we know that Expr has a bad alignment at compile time
620 if Compile_Time_Known_Value
(Expr
)
621 and then (Known_Alignment
(E
) or else Known_Alignment
(Typ
))
624 AL
: Uint
:= Alignment
(Typ
);
627 -- The object alignment might be more restrictive than the
630 if Known_Alignment
(E
) then
634 if Expr_Value
(Expr
) mod AL
/= 0 then
635 Compile_Time_Bad_Alignment
;
641 -- If the expression has the form X'Address, then we can find out if
642 -- the object X has an alignment that is compatible with the object E.
643 -- If it hasn't or we don't know, we defer issuing the warning until
644 -- the end of the compilation to take into account back end annotations.
646 elsif Nkind
(Expr
) = N_Attribute_Reference
647 and then Attribute_Name
(Expr
) = Name_Address
648 and then Has_Compatible_Alignment
(E
, Prefix
(Expr
)) = Known_Compatible
653 -- Here we do not know if the value is acceptable. Stricly we don't have
654 -- to do anything, since if the alignment is bad, we have an erroneous
655 -- program. However we are allowed to check for erroneous conditions and
656 -- we decide to do this by default if the check is not suppressed.
658 -- However, don't do the check if elaboration code is unwanted
660 if Restriction_Active
(No_Elaboration_Code
) then
663 -- Generate a check to raise PE if alignment may be inappropriate
666 -- If the original expression is a non-static constant, use the
667 -- name of the constant itself rather than duplicating its
668 -- defining expression, which was extracted above.
670 -- Note: Expr is empty if the address-clause is applied to in-mode
671 -- actuals (allowed by 13.1(22)).
673 if not Present
(Expr
)
675 (Is_Entity_Name
(Expression
(AC
))
676 and then Ekind
(Entity
(Expression
(AC
))) = E_Constant
677 and then Nkind
(Parent
(Entity
(Expression
(AC
))))
678 = N_Object_Declaration
)
680 Expr
:= New_Copy_Tree
(Expression
(AC
));
682 Remove_Side_Effects
(Expr
);
685 Insert_After_And_Analyze
(N
,
686 Make_Raise_Program_Error
(Loc
,
693 (RTE
(RE_Integer_Address
), Expr
),
695 Make_Attribute_Reference
(Loc
,
696 Prefix
=> New_Occurrence_Of
(E
, Loc
),
697 Attribute_Name
=> Name_Alignment
)),
698 Right_Opnd
=> Make_Integer_Literal
(Loc
, Uint_0
)),
699 Reason
=> PE_Misaligned_Address_Value
),
700 Suppress
=> All_Checks
);
705 -- If we have some missing run time component in configurable run time
706 -- mode then just skip the check (it is not required in any case).
708 when RE_Not_Available
=>
710 end Apply_Address_Clause_Check
;
712 -------------------------------------
713 -- Apply_Arithmetic_Overflow_Check --
714 -------------------------------------
716 -- This routine is called only if the type is an integer type, and a
717 -- software arithmetic overflow check may be needed for op (add, subtract,
718 -- or multiply). This check is performed only if Software_Overflow_Checking
719 -- is enabled and Do_Overflow_Check is set. In this case we expand the
720 -- operation into a more complex sequence of tests that ensures that
721 -- overflow is properly caught.
723 procedure Apply_Arithmetic_Overflow_Check
(N
: Node_Id
) is
724 Loc
: constant Source_Ptr
:= Sloc
(N
);
725 Typ
: Entity_Id
:= Etype
(N
);
726 Rtyp
: Entity_Id
:= Root_Type
(Typ
);
729 -- An interesting special case. If the arithmetic operation appears as
730 -- the operand of a type conversion:
734 -- and all the following conditions apply:
736 -- arithmetic operation is for a signed integer type
737 -- target type type1 is a static integer subtype
738 -- range of x and y are both included in the range of type1
739 -- range of x op y is included in the range of type1
740 -- size of type1 is at least twice the result size of op
742 -- then we don't do an overflow check in any case, instead we transform
743 -- the operation so that we end up with:
745 -- type1 (type1 (x) op type1 (y))
747 -- This avoids intermediate overflow before the conversion. It is
748 -- explicitly permitted by RM 3.5.4(24):
750 -- For the execution of a predefined operation of a signed integer
751 -- type, the implementation need not raise Constraint_Error if the
752 -- result is outside the base range of the type, so long as the
753 -- correct result is produced.
755 -- It's hard to imagine that any programmer counts on the exception
756 -- being raised in this case, and in any case it's wrong coding to
757 -- have this expectation, given the RM permission. Furthermore, other
758 -- Ada compilers do allow such out of range results.
760 -- Note that we do this transformation even if overflow checking is
761 -- off, since this is precisely about giving the "right" result and
762 -- avoiding the need for an overflow check.
764 -- Note: this circuit is partially redundant with respect to the similar
765 -- processing in Exp_Ch4.Expand_N_Type_Conversion, but the latter deals
766 -- with cases that do not come through here. We still need the following
767 -- processing even with the Exp_Ch4 code in place, since we want to be
768 -- sure not to generate the arithmetic overflow check in these cases
769 -- (Exp_Ch4 would have a hard time removing them once generated).
771 if Is_Signed_Integer_Type
(Typ
)
772 and then Nkind
(Parent
(N
)) = N_Type_Conversion
775 Target_Type
: constant Entity_Id
:=
776 Base_Type
(Entity
(Subtype_Mark
(Parent
(N
))));
790 if Is_Integer_Type
(Target_Type
)
791 and then RM_Size
(Root_Type
(Target_Type
)) >= 2 * RM_Size
(Rtyp
)
793 Tlo
:= Expr_Value
(Type_Low_Bound
(Target_Type
));
794 Thi
:= Expr_Value
(Type_High_Bound
(Target_Type
));
797 (Left_Opnd
(N
), LOK
, Llo
, Lhi
, Assume_Valid
=> True);
799 (Right_Opnd
(N
), ROK
, Rlo
, Rhi
, Assume_Valid
=> True);
802 and then Tlo
<= Llo
and then Lhi
<= Thi
803 and then Tlo
<= Rlo
and then Rhi
<= Thi
805 Determine_Range
(N
, VOK
, Vlo
, Vhi
, Assume_Valid
=> True);
807 if VOK
and then Tlo
<= Vlo
and then Vhi
<= Thi
then
808 Rewrite
(Left_Opnd
(N
),
809 Make_Type_Conversion
(Loc
,
810 Subtype_Mark
=> New_Occurrence_Of
(Target_Type
, Loc
),
811 Expression
=> Relocate_Node
(Left_Opnd
(N
))));
813 Rewrite
(Right_Opnd
(N
),
814 Make_Type_Conversion
(Loc
,
815 Subtype_Mark
=> New_Occurrence_Of
(Target_Type
, Loc
),
816 Expression
=> Relocate_Node
(Right_Opnd
(N
))));
818 Set_Etype
(N
, Target_Type
);
820 Rtyp
:= Root_Type
(Typ
);
821 Analyze_And_Resolve
(Left_Opnd
(N
), Target_Type
);
822 Analyze_And_Resolve
(Right_Opnd
(N
), Target_Type
);
824 -- Given that the target type is twice the size of the
825 -- source type, overflow is now impossible, so we can
826 -- safely kill the overflow check and return.
828 Set_Do_Overflow_Check
(N
, False);
836 -- Now see if an overflow check is required
839 Siz
: constant Int
:= UI_To_Int
(Esize
(Rtyp
));
840 Dsiz
: constant Int
:= Siz
* 2;
847 -- Skip check if back end does overflow checks, or the overflow flag
848 -- is not set anyway, or we are not doing code expansion, or the
849 -- parent node is a type conversion whose operand is an arithmetic
850 -- operation on signed integers on which the expander can promote
851 -- later the operands to type Integer (see Expand_N_Type_Conversion).
853 -- Special case CLI target, where arithmetic overflow checks can be
854 -- performed for integer and long_integer
856 if Backend_Overflow_Checks_On_Target
857 or else not Do_Overflow_Check
(N
)
858 or else not Expander_Active
859 or else (Present
(Parent
(N
))
860 and then Nkind
(Parent
(N
)) = N_Type_Conversion
861 and then Integer_Promotion_Possible
(Parent
(N
)))
863 (VM_Target
= CLI_Target
and then Siz
>= Standard_Integer_Size
)
868 -- Otherwise, generate the full general code for front end overflow
869 -- detection, which works by doing arithmetic in a larger type:
875 -- Typ (Checktyp (x) op Checktyp (y));
877 -- where Typ is the type of the original expression, and Checktyp is
878 -- an integer type of sufficient length to hold the largest possible
881 -- If the size of check type exceeds the size of Long_Long_Integer,
882 -- we use a different approach, expanding to:
884 -- typ (xxx_With_Ovflo_Check (Integer_64 (x), Integer (y)))
886 -- where xxx is Add, Multiply or Subtract as appropriate
888 -- Find check type if one exists
890 if Dsiz
<= Standard_Integer_Size
then
891 Ctyp
:= Standard_Integer
;
893 elsif Dsiz
<= Standard_Long_Long_Integer_Size
then
894 Ctyp
:= Standard_Long_Long_Integer
;
896 -- No check type exists, use runtime call
899 if Nkind
(N
) = N_Op_Add
then
900 Cent
:= RE_Add_With_Ovflo_Check
;
902 elsif Nkind
(N
) = N_Op_Multiply
then
903 Cent
:= RE_Multiply_With_Ovflo_Check
;
906 pragma Assert
(Nkind
(N
) = N_Op_Subtract
);
907 Cent
:= RE_Subtract_With_Ovflo_Check
;
912 Make_Function_Call
(Loc
,
913 Name
=> New_Reference_To
(RTE
(Cent
), Loc
),
914 Parameter_Associations
=> New_List
(
915 OK_Convert_To
(RTE
(RE_Integer_64
), Left_Opnd
(N
)),
916 OK_Convert_To
(RTE
(RE_Integer_64
), Right_Opnd
(N
))))));
918 Analyze_And_Resolve
(N
, Typ
);
922 -- If we fall through, we have the case where we do the arithmetic
923 -- in the next higher type and get the check by conversion. In these
924 -- cases Ctyp is set to the type to be used as the check type.
926 Opnod
:= Relocate_Node
(N
);
928 Opnd
:= OK_Convert_To
(Ctyp
, Left_Opnd
(Opnod
));
931 Set_Etype
(Opnd
, Ctyp
);
932 Set_Analyzed
(Opnd
, True);
933 Set_Left_Opnd
(Opnod
, Opnd
);
935 Opnd
:= OK_Convert_To
(Ctyp
, Right_Opnd
(Opnod
));
938 Set_Etype
(Opnd
, Ctyp
);
939 Set_Analyzed
(Opnd
, True);
940 Set_Right_Opnd
(Opnod
, Opnd
);
942 -- The type of the operation changes to the base type of the check
943 -- type, and we reset the overflow check indication, since clearly no
944 -- overflow is possible now that we are using a double length type.
945 -- We also set the Analyzed flag to avoid a recursive attempt to
948 Set_Etype
(Opnod
, Base_Type
(Ctyp
));
949 Set_Do_Overflow_Check
(Opnod
, False);
950 Set_Analyzed
(Opnod
, True);
952 -- Now build the outer conversion
954 Opnd
:= OK_Convert_To
(Typ
, Opnod
);
956 Set_Etype
(Opnd
, Typ
);
958 -- In the discrete type case, we directly generate the range check
959 -- for the outer operand. This range check will implement the
960 -- required overflow check.
962 if Is_Discrete_Type
(Typ
) then
965 (Expression
(N
), Typ
, CE_Overflow_Check_Failed
);
967 -- For other types, we enable overflow checking on the conversion,
968 -- after setting the node as analyzed to prevent recursive attempts
969 -- to expand the conversion node.
972 Set_Analyzed
(Opnd
, True);
973 Enable_Overflow_Check
(Opnd
);
978 when RE_Not_Available
=>
981 end Apply_Arithmetic_Overflow_Check
;
983 ----------------------------
984 -- Apply_Constraint_Check --
985 ----------------------------
987 procedure Apply_Constraint_Check
990 No_Sliding
: Boolean := False)
992 Desig_Typ
: Entity_Id
;
995 if Inside_A_Generic
then
998 elsif Is_Scalar_Type
(Typ
) then
999 Apply_Scalar_Range_Check
(N
, Typ
);
1001 elsif Is_Array_Type
(Typ
) then
1003 -- A useful optimization: an aggregate with only an others clause
1004 -- always has the right bounds.
1006 if Nkind
(N
) = N_Aggregate
1007 and then No
(Expressions
(N
))
1009 (First
(Choices
(First
(Component_Associations
(N
)))))
1015 if Is_Constrained
(Typ
) then
1016 Apply_Length_Check
(N
, Typ
);
1019 Apply_Range_Check
(N
, Typ
);
1022 Apply_Range_Check
(N
, Typ
);
1025 elsif (Is_Record_Type
(Typ
)
1026 or else Is_Private_Type
(Typ
))
1027 and then Has_Discriminants
(Base_Type
(Typ
))
1028 and then Is_Constrained
(Typ
)
1030 Apply_Discriminant_Check
(N
, Typ
);
1032 elsif Is_Access_Type
(Typ
) then
1034 Desig_Typ
:= Designated_Type
(Typ
);
1036 -- No checks necessary if expression statically null
1038 if Known_Null
(N
) then
1039 if Can_Never_Be_Null
(Typ
) then
1040 Install_Null_Excluding_Check
(N
);
1043 -- No sliding possible on access to arrays
1045 elsif Is_Array_Type
(Desig_Typ
) then
1046 if Is_Constrained
(Desig_Typ
) then
1047 Apply_Length_Check
(N
, Typ
);
1050 Apply_Range_Check
(N
, Typ
);
1052 elsif Has_Discriminants
(Base_Type
(Desig_Typ
))
1053 and then Is_Constrained
(Desig_Typ
)
1055 Apply_Discriminant_Check
(N
, Typ
);
1058 -- Apply the 2005 Null_Excluding check. Note that we do not apply
1059 -- this check if the constraint node is illegal, as shown by having
1060 -- an error posted. This additional guard prevents cascaded errors
1061 -- and compiler aborts on illegal programs involving Ada 2005 checks.
1063 if Can_Never_Be_Null
(Typ
)
1064 and then not Can_Never_Be_Null
(Etype
(N
))
1065 and then not Error_Posted
(N
)
1067 Install_Null_Excluding_Check
(N
);
1070 end Apply_Constraint_Check
;
1072 ------------------------------
1073 -- Apply_Discriminant_Check --
1074 ------------------------------
1076 procedure Apply_Discriminant_Check
1079 Lhs
: Node_Id
:= Empty
)
1081 Loc
: constant Source_Ptr
:= Sloc
(N
);
1082 Do_Access
: constant Boolean := Is_Access_Type
(Typ
);
1083 S_Typ
: Entity_Id
:= Etype
(N
);
1087 function Is_Aliased_Unconstrained_Component
return Boolean;
1088 -- It is possible for an aliased component to have a nominal
1089 -- unconstrained subtype (through instantiation). If this is a
1090 -- discriminated component assigned in the expansion of an aggregate
1091 -- in an initialization, the check must be suppressed. This unusual
1092 -- situation requires a predicate of its own.
1094 ----------------------------------------
1095 -- Is_Aliased_Unconstrained_Component --
1096 ----------------------------------------
1098 function Is_Aliased_Unconstrained_Component
return Boolean is
1103 if Nkind
(Lhs
) /= N_Selected_Component
then
1106 Comp
:= Entity
(Selector_Name
(Lhs
));
1107 Pref
:= Prefix
(Lhs
);
1110 if Ekind
(Comp
) /= E_Component
1111 or else not Is_Aliased
(Comp
)
1116 return not Comes_From_Source
(Pref
)
1117 and then In_Instance
1118 and then not Is_Constrained
(Etype
(Comp
));
1119 end Is_Aliased_Unconstrained_Component
;
1121 -- Start of processing for Apply_Discriminant_Check
1125 T_Typ
:= Designated_Type
(Typ
);
1130 -- Nothing to do if discriminant checks are suppressed or else no code
1131 -- is to be generated
1133 if not Expander_Active
1134 or else Discriminant_Checks_Suppressed
(T_Typ
)
1139 -- No discriminant checks necessary for an access when expression is
1140 -- statically Null. This is not only an optimization, it is fundamental
1141 -- because otherwise discriminant checks may be generated in init procs
1142 -- for types containing an access to a not-yet-frozen record, causing a
1143 -- deadly forward reference.
1145 -- Also, if the expression is of an access type whose designated type is
1146 -- incomplete, then the access value must be null and we suppress the
1149 if Known_Null
(N
) then
1152 elsif Is_Access_Type
(S_Typ
) then
1153 S_Typ
:= Designated_Type
(S_Typ
);
1155 if Ekind
(S_Typ
) = E_Incomplete_Type
then
1160 -- If an assignment target is present, then we need to generate the
1161 -- actual subtype if the target is a parameter or aliased object with
1162 -- an unconstrained nominal subtype.
1164 -- Ada 2005 (AI-363): For Ada 2005, we limit the building of the actual
1165 -- subtype to the parameter and dereference cases, since other aliased
1166 -- objects are unconstrained (unless the nominal subtype is explicitly
1167 -- constrained). (But we also need to test for renamings???)
1170 and then (Present
(Param_Entity
(Lhs
))
1171 or else (Ada_Version
< Ada_05
1172 and then not Is_Constrained
(T_Typ
)
1173 and then Is_Aliased_View
(Lhs
)
1174 and then not Is_Aliased_Unconstrained_Component
)
1175 or else (Ada_Version
>= Ada_05
1176 and then not Is_Constrained
(T_Typ
)
1177 and then Nkind
(Lhs
) = N_Explicit_Dereference
1178 and then Nkind
(Original_Node
(Lhs
)) /=
1181 T_Typ
:= Get_Actual_Subtype
(Lhs
);
1184 -- Nothing to do if the type is unconstrained (this is the case where
1185 -- the actual subtype in the RM sense of N is unconstrained and no check
1188 if not Is_Constrained
(T_Typ
) then
1191 -- Ada 2005: nothing to do if the type is one for which there is a
1192 -- partial view that is constrained.
1194 elsif Ada_Version
>= Ada_05
1195 and then Has_Constrained_Partial_View
(Base_Type
(T_Typ
))
1200 -- Nothing to do if the type is an Unchecked_Union
1202 if Is_Unchecked_Union
(Base_Type
(T_Typ
)) then
1206 -- Suppress checks if the subtypes are the same. the check must be
1207 -- preserved in an assignment to a formal, because the constraint is
1208 -- given by the actual.
1210 if Nkind
(Original_Node
(N
)) /= N_Allocator
1212 or else not Is_Entity_Name
(Lhs
)
1213 or else No
(Param_Entity
(Lhs
)))
1216 or else (Do_Access
and then Designated_Type
(Typ
) = S_Typ
))
1217 and then not Is_Aliased_View
(Lhs
)
1222 -- We can also eliminate checks on allocators with a subtype mark that
1223 -- coincides with the context type. The context type may be a subtype
1224 -- without a constraint (common case, a generic actual).
1226 elsif Nkind
(Original_Node
(N
)) = N_Allocator
1227 and then Is_Entity_Name
(Expression
(Original_Node
(N
)))
1230 Alloc_Typ
: constant Entity_Id
:=
1231 Entity
(Expression
(Original_Node
(N
)));
1234 if Alloc_Typ
= T_Typ
1235 or else (Nkind
(Parent
(T_Typ
)) = N_Subtype_Declaration
1236 and then Is_Entity_Name
(
1237 Subtype_Indication
(Parent
(T_Typ
)))
1238 and then Alloc_Typ
= Base_Type
(T_Typ
))
1246 -- See if we have a case where the types are both constrained, and all
1247 -- the constraints are constants. In this case, we can do the check
1248 -- successfully at compile time.
1250 -- We skip this check for the case where the node is a rewritten`
1251 -- allocator, because it already carries the context subtype, and
1252 -- extracting the discriminants from the aggregate is messy.
1254 if Is_Constrained
(S_Typ
)
1255 and then Nkind
(Original_Node
(N
)) /= N_Allocator
1265 -- S_Typ may not have discriminants in the case where it is a
1266 -- private type completed by a default discriminated type. In that
1267 -- case, we need to get the constraints from the underlying_type.
1268 -- If the underlying type is unconstrained (i.e. has no default
1269 -- discriminants) no check is needed.
1271 if Has_Discriminants
(S_Typ
) then
1272 Discr
:= First_Discriminant
(S_Typ
);
1273 DconS
:= First_Elmt
(Discriminant_Constraint
(S_Typ
));
1276 Discr
:= First_Discriminant
(Underlying_Type
(S_Typ
));
1279 (Discriminant_Constraint
(Underlying_Type
(S_Typ
)));
1285 -- A further optimization: if T_Typ is derived from S_Typ
1286 -- without imposing a constraint, no check is needed.
1288 if Nkind
(Original_Node
(Parent
(T_Typ
))) =
1289 N_Full_Type_Declaration
1292 Type_Def
: constant Node_Id
:=
1294 (Original_Node
(Parent
(T_Typ
)));
1296 if Nkind
(Type_Def
) = N_Derived_Type_Definition
1297 and then Is_Entity_Name
(Subtype_Indication
(Type_Def
))
1298 and then Entity
(Subtype_Indication
(Type_Def
)) = S_Typ
1306 DconT
:= First_Elmt
(Discriminant_Constraint
(T_Typ
));
1308 while Present
(Discr
) loop
1309 ItemS
:= Node
(DconS
);
1310 ItemT
:= Node
(DconT
);
1312 -- For a discriminated component type constrained by the
1313 -- current instance of an enclosing type, there is no
1314 -- applicable discriminant check.
1316 if Nkind
(ItemT
) = N_Attribute_Reference
1317 and then Is_Access_Type
(Etype
(ItemT
))
1318 and then Is_Entity_Name
(Prefix
(ItemT
))
1319 and then Is_Type
(Entity
(Prefix
(ItemT
)))
1324 -- If the expressions for the discriminants are identical
1325 -- and it is side-effect free (for now just an entity),
1326 -- this may be a shared constraint, e.g. from a subtype
1327 -- without a constraint introduced as a generic actual.
1328 -- Examine other discriminants if any.
1331 and then Is_Entity_Name
(ItemS
)
1335 elsif not Is_OK_Static_Expression
(ItemS
)
1336 or else not Is_OK_Static_Expression
(ItemT
)
1340 elsif Expr_Value
(ItemS
) /= Expr_Value
(ItemT
) then
1341 if Do_Access
then -- needs run-time check.
1344 Apply_Compile_Time_Constraint_Error
1345 (N
, "incorrect value for discriminant&?",
1346 CE_Discriminant_Check_Failed
, Ent
=> Discr
);
1353 Next_Discriminant
(Discr
);
1362 -- Here we need a discriminant check. First build the expression
1363 -- for the comparisons of the discriminants:
1365 -- (n.disc1 /= typ.disc1) or else
1366 -- (n.disc2 /= typ.disc2) or else
1368 -- (n.discn /= typ.discn)
1370 Cond
:= Build_Discriminant_Checks
(N
, T_Typ
);
1372 -- If Lhs is set and is a parameter, then the condition is
1373 -- guarded by: lhs'constrained and then (condition built above)
1375 if Present
(Param_Entity
(Lhs
)) then
1379 Make_Attribute_Reference
(Loc
,
1380 Prefix
=> New_Occurrence_Of
(Param_Entity
(Lhs
), Loc
),
1381 Attribute_Name
=> Name_Constrained
),
1382 Right_Opnd
=> Cond
);
1386 Cond
:= Guard_Access
(Cond
, Loc
, N
);
1390 Make_Raise_Constraint_Error
(Loc
,
1392 Reason
=> CE_Discriminant_Check_Failed
));
1393 end Apply_Discriminant_Check
;
1395 ------------------------
1396 -- Apply_Divide_Check --
1397 ------------------------
1399 procedure Apply_Divide_Check
(N
: Node_Id
) is
1400 Loc
: constant Source_Ptr
:= Sloc
(N
);
1401 Typ
: constant Entity_Id
:= Etype
(N
);
1402 Left
: constant Node_Id
:= Left_Opnd
(N
);
1403 Right
: constant Node_Id
:= Right_Opnd
(N
);
1413 pragma Warnings
(Off
, Lhi
);
1414 -- Don't actually use this value
1418 and then not Backend_Divide_Checks_On_Target
1419 and then Check_Needed
(Right
, Division_Check
)
1421 Determine_Range
(Right
, ROK
, Rlo
, Rhi
, Assume_Valid
=> True);
1423 -- See if division by zero possible, and if so generate test. This
1424 -- part of the test is not controlled by the -gnato switch.
1426 if Do_Division_Check
(N
) then
1427 if (not ROK
) or else (Rlo
<= 0 and then 0 <= Rhi
) then
1429 Make_Raise_Constraint_Error
(Loc
,
1432 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Right
),
1433 Right_Opnd
=> Make_Integer_Literal
(Loc
, 0)),
1434 Reason
=> CE_Divide_By_Zero
));
1438 -- Test for extremely annoying case of xxx'First divided by -1
1440 if Do_Overflow_Check
(N
) then
1441 if Nkind
(N
) = N_Op_Divide
1442 and then Is_Signed_Integer_Type
(Typ
)
1444 Determine_Range
(Left
, LOK
, Llo
, Lhi
, Assume_Valid
=> True);
1445 LLB
:= Expr_Value
(Type_Low_Bound
(Base_Type
(Typ
)));
1447 if ((not ROK
) or else (Rlo
<= (-1) and then (-1) <= Rhi
))
1449 ((not LOK
) or else (Llo
= LLB
))
1452 Make_Raise_Constraint_Error
(Loc
,
1458 Duplicate_Subexpr_Move_Checks
(Left
),
1459 Right_Opnd
=> Make_Integer_Literal
(Loc
, LLB
)),
1463 Duplicate_Subexpr
(Right
),
1465 Make_Integer_Literal
(Loc
, -1))),
1466 Reason
=> CE_Overflow_Check_Failed
));
1471 end Apply_Divide_Check
;
1473 ----------------------------------
1474 -- Apply_Float_Conversion_Check --
1475 ----------------------------------
1477 -- Let F and I be the source and target types of the conversion. The RM
1478 -- specifies that a floating-point value X is rounded to the nearest
1479 -- integer, with halfway cases being rounded away from zero. The rounded
1480 -- value of X is checked against I'Range.
1482 -- The catch in the above paragraph is that there is no good way to know
1483 -- whether the round-to-integer operation resulted in overflow. A remedy is
1484 -- to perform a range check in the floating-point domain instead, however:
1486 -- (1) The bounds may not be known at compile time
1487 -- (2) The check must take into account rounding or truncation.
1488 -- (3) The range of type I may not be exactly representable in F.
1489 -- (4) For the rounding case, The end-points I'First - 0.5 and
1490 -- I'Last + 0.5 may or may not be in range, depending on the
1491 -- sign of I'First and I'Last.
1492 -- (5) X may be a NaN, which will fail any comparison
1494 -- The following steps correctly convert X with rounding:
1496 -- (1) If either I'First or I'Last is not known at compile time, use
1497 -- I'Base instead of I in the next three steps and perform a
1498 -- regular range check against I'Range after conversion.
1499 -- (2) If I'First - 0.5 is representable in F then let Lo be that
1500 -- value and define Lo_OK as (I'First > 0). Otherwise, let Lo be
1501 -- F'Machine (I'First) and let Lo_OK be (Lo >= I'First).
1502 -- In other words, take one of the closest floating-point numbers
1503 -- (which is an integer value) to I'First, and see if it is in
1505 -- (3) If I'Last + 0.5 is representable in F then let Hi be that value
1506 -- and define Hi_OK as (I'Last < 0). Otherwise, let Hi be
1507 -- F'Machine (I'Last) and let Hi_OK be (Hi <= I'Last).
1508 -- (4) Raise CE when (Lo_OK and X < Lo) or (not Lo_OK and X <= Lo)
1509 -- or (Hi_OK and X > Hi) or (not Hi_OK and X >= Hi)
1511 -- For the truncating case, replace steps (2) and (3) as follows:
1512 -- (2) If I'First > 0, then let Lo be F'Pred (I'First) and let Lo_OK
1513 -- be False. Otherwise, let Lo be F'Succ (I'First - 1) and let
1515 -- (3) If I'Last < 0, then let Hi be F'Succ (I'Last) and let Hi_OK
1516 -- be False. Otherwise let Hi be F'Pred (I'Last + 1) and let
1519 procedure Apply_Float_Conversion_Check
1521 Target_Typ
: Entity_Id
)
1523 LB
: constant Node_Id
:= Type_Low_Bound
(Target_Typ
);
1524 HB
: constant Node_Id
:= Type_High_Bound
(Target_Typ
);
1525 Loc
: constant Source_Ptr
:= Sloc
(Ck_Node
);
1526 Expr_Type
: constant Entity_Id
:= Base_Type
(Etype
(Ck_Node
));
1527 Target_Base
: constant Entity_Id
:=
1528 Implementation_Base_Type
(Target_Typ
);
1530 Par
: constant Node_Id
:= Parent
(Ck_Node
);
1531 pragma Assert
(Nkind
(Par
) = N_Type_Conversion
);
1532 -- Parent of check node, must be a type conversion
1534 Truncate
: constant Boolean := Float_Truncate
(Par
);
1535 Max_Bound
: constant Uint
:=
1537 (Machine_Radix
(Expr_Type
),
1538 Machine_Mantissa
(Expr_Type
) - 1) - 1;
1540 -- Largest bound, so bound plus or minus half is a machine number of F
1542 Ifirst
, Ilast
: Uint
;
1543 -- Bounds of integer type
1546 -- Bounds to check in floating-point domain
1548 Lo_OK
, Hi_OK
: Boolean;
1549 -- True iff Lo resp. Hi belongs to I'Range
1551 Lo_Chk
, Hi_Chk
: Node_Id
;
1552 -- Expressions that are False iff check fails
1554 Reason
: RT_Exception_Code
;
1557 if not Compile_Time_Known_Value
(LB
)
1558 or not Compile_Time_Known_Value
(HB
)
1561 -- First check that the value falls in the range of the base type,
1562 -- to prevent overflow during conversion and then perform a
1563 -- regular range check against the (dynamic) bounds.
1565 pragma Assert
(Target_Base
/= Target_Typ
);
1567 Temp
: constant Entity_Id
:=
1568 Make_Defining_Identifier
(Loc
,
1569 Chars
=> New_Internal_Name
('T'));
1572 Apply_Float_Conversion_Check
(Ck_Node
, Target_Base
);
1573 Set_Etype
(Temp
, Target_Base
);
1575 Insert_Action
(Parent
(Par
),
1576 Make_Object_Declaration
(Loc
,
1577 Defining_Identifier
=> Temp
,
1578 Object_Definition
=> New_Occurrence_Of
(Target_Typ
, Loc
),
1579 Expression
=> New_Copy_Tree
(Par
)),
1580 Suppress
=> All_Checks
);
1583 Make_Raise_Constraint_Error
(Loc
,
1586 Left_Opnd
=> New_Occurrence_Of
(Temp
, Loc
),
1587 Right_Opnd
=> New_Occurrence_Of
(Target_Typ
, Loc
)),
1588 Reason
=> CE_Range_Check_Failed
));
1589 Rewrite
(Par
, New_Occurrence_Of
(Temp
, Loc
));
1595 -- Get the (static) bounds of the target type
1597 Ifirst
:= Expr_Value
(LB
);
1598 Ilast
:= Expr_Value
(HB
);
1600 -- A simple optimization: if the expression is a universal literal,
1601 -- we can do the comparison with the bounds and the conversion to
1602 -- an integer type statically. The range checks are unchanged.
1604 if Nkind
(Ck_Node
) = N_Real_Literal
1605 and then Etype
(Ck_Node
) = Universal_Real
1606 and then Is_Integer_Type
(Target_Typ
)
1607 and then Nkind
(Parent
(Ck_Node
)) = N_Type_Conversion
1610 Int_Val
: constant Uint
:= UR_To_Uint
(Realval
(Ck_Node
));
1613 if Int_Val
<= Ilast
and then Int_Val
>= Ifirst
then
1615 -- Conversion is safe
1617 Rewrite
(Parent
(Ck_Node
),
1618 Make_Integer_Literal
(Loc
, UI_To_Int
(Int_Val
)));
1619 Analyze_And_Resolve
(Parent
(Ck_Node
), Target_Typ
);
1625 -- Check against lower bound
1627 if Truncate
and then Ifirst
> 0 then
1628 Lo
:= Pred
(Expr_Type
, UR_From_Uint
(Ifirst
));
1632 Lo
:= Succ
(Expr_Type
, UR_From_Uint
(Ifirst
- 1));
1635 elsif abs (Ifirst
) < Max_Bound
then
1636 Lo
:= UR_From_Uint
(Ifirst
) - Ureal_Half
;
1637 Lo_OK
:= (Ifirst
> 0);
1640 Lo
:= Machine
(Expr_Type
, UR_From_Uint
(Ifirst
), Round_Even
, Ck_Node
);
1641 Lo_OK
:= (Lo
>= UR_From_Uint
(Ifirst
));
1646 -- Lo_Chk := (X >= Lo)
1648 Lo_Chk
:= Make_Op_Ge
(Loc
,
1649 Left_Opnd
=> Duplicate_Subexpr_No_Checks
(Ck_Node
),
1650 Right_Opnd
=> Make_Real_Literal
(Loc
, Lo
));
1653 -- Lo_Chk := (X > Lo)
1655 Lo_Chk
:= Make_Op_Gt
(Loc
,
1656 Left_Opnd
=> Duplicate_Subexpr_No_Checks
(Ck_Node
),
1657 Right_Opnd
=> Make_Real_Literal
(Loc
, Lo
));
1660 -- Check against higher bound
1662 if Truncate
and then Ilast
< 0 then
1663 Hi
:= Succ
(Expr_Type
, UR_From_Uint
(Ilast
));
1667 Hi
:= Pred
(Expr_Type
, UR_From_Uint
(Ilast
+ 1));
1670 elsif abs (Ilast
) < Max_Bound
then
1671 Hi
:= UR_From_Uint
(Ilast
) + Ureal_Half
;
1672 Hi_OK
:= (Ilast
< 0);
1674 Hi
:= Machine
(Expr_Type
, UR_From_Uint
(Ilast
), Round_Even
, Ck_Node
);
1675 Hi_OK
:= (Hi
<= UR_From_Uint
(Ilast
));
1680 -- Hi_Chk := (X <= Hi)
1682 Hi_Chk
:= Make_Op_Le
(Loc
,
1683 Left_Opnd
=> Duplicate_Subexpr_No_Checks
(Ck_Node
),
1684 Right_Opnd
=> Make_Real_Literal
(Loc
, Hi
));
1687 -- Hi_Chk := (X < Hi)
1689 Hi_Chk
:= Make_Op_Lt
(Loc
,
1690 Left_Opnd
=> Duplicate_Subexpr_No_Checks
(Ck_Node
),
1691 Right_Opnd
=> Make_Real_Literal
(Loc
, Hi
));
1694 -- If the bounds of the target type are the same as those of the base
1695 -- type, the check is an overflow check as a range check is not
1696 -- performed in these cases.
1698 if Expr_Value
(Type_Low_Bound
(Target_Base
)) = Ifirst
1699 and then Expr_Value
(Type_High_Bound
(Target_Base
)) = Ilast
1701 Reason
:= CE_Overflow_Check_Failed
;
1703 Reason
:= CE_Range_Check_Failed
;
1706 -- Raise CE if either conditions does not hold
1708 Insert_Action
(Ck_Node
,
1709 Make_Raise_Constraint_Error
(Loc
,
1710 Condition
=> Make_Op_Not
(Loc
, Make_And_Then
(Loc
, Lo_Chk
, Hi_Chk
)),
1712 end Apply_Float_Conversion_Check
;
1714 ------------------------
1715 -- Apply_Length_Check --
1716 ------------------------
1718 procedure Apply_Length_Check
1720 Target_Typ
: Entity_Id
;
1721 Source_Typ
: Entity_Id
:= Empty
)
1724 Apply_Selected_Length_Checks
1725 (Ck_Node
, Target_Typ
, Source_Typ
, Do_Static
=> False);
1726 end Apply_Length_Check
;
1728 -----------------------
1729 -- Apply_Range_Check --
1730 -----------------------
1732 procedure Apply_Range_Check
1734 Target_Typ
: Entity_Id
;
1735 Source_Typ
: Entity_Id
:= Empty
)
1738 Apply_Selected_Range_Checks
1739 (Ck_Node
, Target_Typ
, Source_Typ
, Do_Static
=> False);
1740 end Apply_Range_Check
;
1742 ------------------------------
1743 -- Apply_Scalar_Range_Check --
1744 ------------------------------
1746 -- Note that Apply_Scalar_Range_Check never turns the Do_Range_Check flag
1747 -- off if it is already set on.
1749 procedure Apply_Scalar_Range_Check
1751 Target_Typ
: Entity_Id
;
1752 Source_Typ
: Entity_Id
:= Empty
;
1753 Fixed_Int
: Boolean := False)
1755 Parnt
: constant Node_Id
:= Parent
(Expr
);
1757 Arr
: Node_Id
:= Empty
; -- initialize to prevent warning
1758 Arr_Typ
: Entity_Id
:= Empty
; -- initialize to prevent warning
1761 Is_Subscr_Ref
: Boolean;
1762 -- Set true if Expr is a subscript
1764 Is_Unconstrained_Subscr_Ref
: Boolean;
1765 -- Set true if Expr is a subscript of an unconstrained array. In this
1766 -- case we do not attempt to do an analysis of the value against the
1767 -- range of the subscript, since we don't know the actual subtype.
1770 -- Set to True if Expr should be regarded as a real value even though
1771 -- the type of Expr might be discrete.
1773 procedure Bad_Value
;
1774 -- Procedure called if value is determined to be out of range
1780 procedure Bad_Value
is
1782 Apply_Compile_Time_Constraint_Error
1783 (Expr
, "value not in range of}?", CE_Range_Check_Failed
,
1788 -- Start of processing for Apply_Scalar_Range_Check
1791 -- Return if check obviously not needed
1794 -- Not needed inside generic
1798 -- Not needed if previous error
1800 or else Target_Typ
= Any_Type
1801 or else Nkind
(Expr
) = N_Error
1803 -- Not needed for non-scalar type
1805 or else not Is_Scalar_Type
(Target_Typ
)
1807 -- Not needed if we know node raises CE already
1809 or else Raises_Constraint_Error
(Expr
)
1814 -- Now, see if checks are suppressed
1817 Is_List_Member
(Expr
) and then Nkind
(Parnt
) = N_Indexed_Component
;
1819 if Is_Subscr_Ref
then
1820 Arr
:= Prefix
(Parnt
);
1821 Arr_Typ
:= Get_Actual_Subtype_If_Available
(Arr
);
1824 if not Do_Range_Check
(Expr
) then
1826 -- Subscript reference. Check for Index_Checks suppressed
1828 if Is_Subscr_Ref
then
1830 -- Check array type and its base type
1832 if Index_Checks_Suppressed
(Arr_Typ
)
1833 or else Index_Checks_Suppressed
(Base_Type
(Arr_Typ
))
1837 -- Check array itself if it is an entity name
1839 elsif Is_Entity_Name
(Arr
)
1840 and then Index_Checks_Suppressed
(Entity
(Arr
))
1844 -- Check expression itself if it is an entity name
1846 elsif Is_Entity_Name
(Expr
)
1847 and then Index_Checks_Suppressed
(Entity
(Expr
))
1852 -- All other cases, check for Range_Checks suppressed
1855 -- Check target type and its base type
1857 if Range_Checks_Suppressed
(Target_Typ
)
1858 or else Range_Checks_Suppressed
(Base_Type
(Target_Typ
))
1862 -- Check expression itself if it is an entity name
1864 elsif Is_Entity_Name
(Expr
)
1865 and then Range_Checks_Suppressed
(Entity
(Expr
))
1869 -- If Expr is part of an assignment statement, then check left
1870 -- side of assignment if it is an entity name.
1872 elsif Nkind
(Parnt
) = N_Assignment_Statement
1873 and then Is_Entity_Name
(Name
(Parnt
))
1874 and then Range_Checks_Suppressed
(Entity
(Name
(Parnt
)))
1881 -- Do not set range checks if they are killed
1883 if Nkind
(Expr
) = N_Unchecked_Type_Conversion
1884 and then Kill_Range_Check
(Expr
)
1889 -- Do not set range checks for any values from System.Scalar_Values
1890 -- since the whole idea of such values is to avoid checking them!
1892 if Is_Entity_Name
(Expr
)
1893 and then Is_RTU
(Scope
(Entity
(Expr
)), System_Scalar_Values
)
1898 -- Now see if we need a check
1900 if No
(Source_Typ
) then
1901 S_Typ
:= Etype
(Expr
);
1903 S_Typ
:= Source_Typ
;
1906 if not Is_Scalar_Type
(S_Typ
) or else S_Typ
= Any_Type
then
1910 Is_Unconstrained_Subscr_Ref
:=
1911 Is_Subscr_Ref
and then not Is_Constrained
(Arr_Typ
);
1913 -- Always do a range check if the source type includes infinities and
1914 -- the target type does not include infinities. We do not do this if
1915 -- range checks are killed.
1917 if Is_Floating_Point_Type
(S_Typ
)
1918 and then Has_Infinities
(S_Typ
)
1919 and then not Has_Infinities
(Target_Typ
)
1921 Enable_Range_Check
(Expr
);
1924 -- Return if we know expression is definitely in the range of the target
1925 -- type as determined by Determine_Range. Right now we only do this for
1926 -- discrete types, and not fixed-point or floating-point types.
1928 -- The additional less-precise tests below catch these cases
1930 -- Note: skip this if we are given a source_typ, since the point of
1931 -- supplying a Source_Typ is to stop us looking at the expression.
1932 -- We could sharpen this test to be out parameters only ???
1934 if Is_Discrete_Type
(Target_Typ
)
1935 and then Is_Discrete_Type
(Etype
(Expr
))
1936 and then not Is_Unconstrained_Subscr_Ref
1937 and then No
(Source_Typ
)
1940 Tlo
: constant Node_Id
:= Type_Low_Bound
(Target_Typ
);
1941 Thi
: constant Node_Id
:= Type_High_Bound
(Target_Typ
);
1946 if Compile_Time_Known_Value
(Tlo
)
1947 and then Compile_Time_Known_Value
(Thi
)
1950 Lov
: constant Uint
:= Expr_Value
(Tlo
);
1951 Hiv
: constant Uint
:= Expr_Value
(Thi
);
1954 -- If range is null, we for sure have a constraint error
1955 -- (we don't even need to look at the value involved,
1956 -- since all possible values will raise CE).
1963 -- Otherwise determine range of value
1965 Determine_Range
(Expr
, OK
, Lo
, Hi
, Assume_Valid
=> True);
1969 -- If definitely in range, all OK
1971 if Lo
>= Lov
and then Hi
<= Hiv
then
1974 -- If definitely not in range, warn
1976 elsif Lov
> Hi
or else Hiv
< Lo
then
1980 -- Otherwise we don't know
1992 Is_Floating_Point_Type
(S_Typ
)
1993 or else (Is_Fixed_Point_Type
(S_Typ
) and then not Fixed_Int
);
1995 -- Check if we can determine at compile time whether Expr is in the
1996 -- range of the target type. Note that if S_Typ is within the bounds
1997 -- of Target_Typ then this must be the case. This check is meaningful
1998 -- only if this is not a conversion between integer and real types.
2000 if not Is_Unconstrained_Subscr_Ref
2002 Is_Discrete_Type
(S_Typ
) = Is_Discrete_Type
(Target_Typ
)
2004 (In_Subrange_Of
(S_Typ
, Target_Typ
, Fixed_Int
)
2006 Is_In_Range
(Expr
, Target_Typ
,
2007 Assume_Valid
=> True,
2008 Fixed_Int
=> Fixed_Int
,
2009 Int_Real
=> Int_Real
))
2013 elsif Is_Out_Of_Range
(Expr
, Target_Typ
,
2014 Assume_Valid
=> True,
2015 Fixed_Int
=> Fixed_Int
,
2016 Int_Real
=> Int_Real
)
2021 -- In the floating-point case, we only do range checks if the type is
2022 -- constrained. We definitely do NOT want range checks for unconstrained
2023 -- types, since we want to have infinities
2025 elsif Is_Floating_Point_Type
(S_Typ
) then
2026 if Is_Constrained
(S_Typ
) then
2027 Enable_Range_Check
(Expr
);
2030 -- For all other cases we enable a range check unconditionally
2033 Enable_Range_Check
(Expr
);
2036 end Apply_Scalar_Range_Check
;
2038 ----------------------------------
2039 -- Apply_Selected_Length_Checks --
2040 ----------------------------------
2042 procedure Apply_Selected_Length_Checks
2044 Target_Typ
: Entity_Id
;
2045 Source_Typ
: Entity_Id
;
2046 Do_Static
: Boolean)
2049 R_Result
: Check_Result
;
2052 Loc
: constant Source_Ptr
:= Sloc
(Ck_Node
);
2053 Checks_On
: constant Boolean :=
2054 (not Index_Checks_Suppressed
(Target_Typ
))
2056 (not Length_Checks_Suppressed
(Target_Typ
));
2059 if not Expander_Active
then
2064 Selected_Length_Checks
(Ck_Node
, Target_Typ
, Source_Typ
, Empty
);
2066 for J
in 1 .. 2 loop
2067 R_Cno
:= R_Result
(J
);
2068 exit when No
(R_Cno
);
2070 -- A length check may mention an Itype which is attached to a
2071 -- subsequent node. At the top level in a package this can cause
2072 -- an order-of-elaboration problem, so we make sure that the itype
2073 -- is referenced now.
2075 if Ekind
(Current_Scope
) = E_Package
2076 and then Is_Compilation_Unit
(Current_Scope
)
2078 Ensure_Defined
(Target_Typ
, Ck_Node
);
2080 if Present
(Source_Typ
) then
2081 Ensure_Defined
(Source_Typ
, Ck_Node
);
2083 elsif Is_Itype
(Etype
(Ck_Node
)) then
2084 Ensure_Defined
(Etype
(Ck_Node
), Ck_Node
);
2088 -- If the item is a conditional raise of constraint error, then have
2089 -- a look at what check is being performed and ???
2091 if Nkind
(R_Cno
) = N_Raise_Constraint_Error
2092 and then Present
(Condition
(R_Cno
))
2094 Cond
:= Condition
(R_Cno
);
2096 -- Case where node does not now have a dynamic check
2098 if not Has_Dynamic_Length_Check
(Ck_Node
) then
2100 -- If checks are on, just insert the check
2103 Insert_Action
(Ck_Node
, R_Cno
);
2105 if not Do_Static
then
2106 Set_Has_Dynamic_Length_Check
(Ck_Node
);
2109 -- If checks are off, then analyze the length check after
2110 -- temporarily attaching it to the tree in case the relevant
2111 -- condition can be evaluted at compile time. We still want a
2112 -- compile time warning in this case.
2115 Set_Parent
(R_Cno
, Ck_Node
);
2120 -- Output a warning if the condition is known to be True
2122 if Is_Entity_Name
(Cond
)
2123 and then Entity
(Cond
) = Standard_True
2125 Apply_Compile_Time_Constraint_Error
2126 (Ck_Node
, "wrong length for array of}?",
2127 CE_Length_Check_Failed
,
2131 -- If we were only doing a static check, or if checks are not
2132 -- on, then we want to delete the check, since it is not needed.
2133 -- We do this by replacing the if statement by a null statement
2135 elsif Do_Static
or else not Checks_On
then
2136 Remove_Warning_Messages
(R_Cno
);
2137 Rewrite
(R_Cno
, Make_Null_Statement
(Loc
));
2141 Install_Static_Check
(R_Cno
, Loc
);
2144 end Apply_Selected_Length_Checks
;
2146 ---------------------------------
2147 -- Apply_Selected_Range_Checks --
2148 ---------------------------------
2150 procedure Apply_Selected_Range_Checks
2152 Target_Typ
: Entity_Id
;
2153 Source_Typ
: Entity_Id
;
2154 Do_Static
: Boolean)
2157 R_Result
: Check_Result
;
2160 Loc
: constant Source_Ptr
:= Sloc
(Ck_Node
);
2161 Checks_On
: constant Boolean :=
2162 (not Index_Checks_Suppressed
(Target_Typ
))
2164 (not Range_Checks_Suppressed
(Target_Typ
));
2167 if not Expander_Active
or else not Checks_On
then
2172 Selected_Range_Checks
(Ck_Node
, Target_Typ
, Source_Typ
, Empty
);
2174 for J
in 1 .. 2 loop
2176 R_Cno
:= R_Result
(J
);
2177 exit when No
(R_Cno
);
2179 -- If the item is a conditional raise of constraint error, then have
2180 -- a look at what check is being performed and ???
2182 if Nkind
(R_Cno
) = N_Raise_Constraint_Error
2183 and then Present
(Condition
(R_Cno
))
2185 Cond
:= Condition
(R_Cno
);
2187 if not Has_Dynamic_Range_Check
(Ck_Node
) then
2188 Insert_Action
(Ck_Node
, R_Cno
);
2190 if not Do_Static
then
2191 Set_Has_Dynamic_Range_Check
(Ck_Node
);
2195 -- Output a warning if the condition is known to be True
2197 if Is_Entity_Name
(Cond
)
2198 and then Entity
(Cond
) = Standard_True
2200 -- Since an N_Range is technically not an expression, we have
2201 -- to set one of the bounds to C_E and then just flag the
2202 -- N_Range. The warning message will point to the lower bound
2203 -- and complain about a range, which seems OK.
2205 if Nkind
(Ck_Node
) = N_Range
then
2206 Apply_Compile_Time_Constraint_Error
2207 (Low_Bound
(Ck_Node
), "static range out of bounds of}?",
2208 CE_Range_Check_Failed
,
2212 Set_Raises_Constraint_Error
(Ck_Node
);
2215 Apply_Compile_Time_Constraint_Error
2216 (Ck_Node
, "static value out of range of}?",
2217 CE_Range_Check_Failed
,
2222 -- If we were only doing a static check, or if checks are not
2223 -- on, then we want to delete the check, since it is not needed.
2224 -- We do this by replacing the if statement by a null statement
2226 elsif Do_Static
or else not Checks_On
then
2227 Remove_Warning_Messages
(R_Cno
);
2228 Rewrite
(R_Cno
, Make_Null_Statement
(Loc
));
2232 Install_Static_Check
(R_Cno
, Loc
);
2235 end Apply_Selected_Range_Checks
;
2237 -------------------------------
2238 -- Apply_Static_Length_Check --
2239 -------------------------------
2241 procedure Apply_Static_Length_Check
2243 Target_Typ
: Entity_Id
;
2244 Source_Typ
: Entity_Id
:= Empty
)
2247 Apply_Selected_Length_Checks
2248 (Expr
, Target_Typ
, Source_Typ
, Do_Static
=> True);
2249 end Apply_Static_Length_Check
;
2251 -------------------------------------
2252 -- Apply_Subscript_Validity_Checks --
2253 -------------------------------------
2255 procedure Apply_Subscript_Validity_Checks
(Expr
: Node_Id
) is
2259 pragma Assert
(Nkind
(Expr
) = N_Indexed_Component
);
2261 -- Loop through subscripts
2263 Sub
:= First
(Expressions
(Expr
));
2264 while Present
(Sub
) loop
2266 -- Check one subscript. Note that we do not worry about enumeration
2267 -- type with holes, since we will convert the value to a Pos value
2268 -- for the subscript, and that convert will do the necessary validity
2271 Ensure_Valid
(Sub
, Holes_OK
=> True);
2273 -- Move to next subscript
2277 end Apply_Subscript_Validity_Checks
;
2279 ----------------------------------
2280 -- Apply_Type_Conversion_Checks --
2281 ----------------------------------
2283 procedure Apply_Type_Conversion_Checks
(N
: Node_Id
) is
2284 Target_Type
: constant Entity_Id
:= Etype
(N
);
2285 Target_Base
: constant Entity_Id
:= Base_Type
(Target_Type
);
2286 Expr
: constant Node_Id
:= Expression
(N
);
2287 Expr_Type
: constant Entity_Id
:= Etype
(Expr
);
2290 if Inside_A_Generic
then
2293 -- Skip these checks if serious errors detected, there are some nasty
2294 -- situations of incomplete trees that blow things up.
2296 elsif Serious_Errors_Detected
> 0 then
2299 -- Scalar type conversions of the form Target_Type (Expr) require a
2300 -- range check if we cannot be sure that Expr is in the base type of
2301 -- Target_Typ and also that Expr is in the range of Target_Typ. These
2302 -- are not quite the same condition from an implementation point of
2303 -- view, but clearly the second includes the first.
2305 elsif Is_Scalar_Type
(Target_Type
) then
2307 Conv_OK
: constant Boolean := Conversion_OK
(N
);
2308 -- If the Conversion_OK flag on the type conversion is set and no
2309 -- floating point type is involved in the type conversion then
2310 -- fixed point values must be read as integral values.
2312 Float_To_Int
: constant Boolean :=
2313 Is_Floating_Point_Type
(Expr_Type
)
2314 and then Is_Integer_Type
(Target_Type
);
2317 if not Overflow_Checks_Suppressed
(Target_Base
)
2319 In_Subrange_Of
(Expr_Type
, Target_Base
, Fixed_Int
=> Conv_OK
)
2320 and then not Float_To_Int
2322 Activate_Overflow_Check
(N
);
2325 if not Range_Checks_Suppressed
(Target_Type
)
2326 and then not Range_Checks_Suppressed
(Expr_Type
)
2328 if Float_To_Int
then
2329 Apply_Float_Conversion_Check
(Expr
, Target_Type
);
2331 Apply_Scalar_Range_Check
2332 (Expr
, Target_Type
, Fixed_Int
=> Conv_OK
);
2337 elsif Comes_From_Source
(N
)
2338 and then not Discriminant_Checks_Suppressed
(Target_Type
)
2339 and then Is_Record_Type
(Target_Type
)
2340 and then Is_Derived_Type
(Target_Type
)
2341 and then not Is_Tagged_Type
(Target_Type
)
2342 and then not Is_Constrained
(Target_Type
)
2343 and then Present
(Stored_Constraint
(Target_Type
))
2345 -- An unconstrained derived type may have inherited discriminant
2346 -- Build an actual discriminant constraint list using the stored
2347 -- constraint, to verify that the expression of the parent type
2348 -- satisfies the constraints imposed by the (unconstrained!)
2349 -- derived type. This applies to value conversions, not to view
2350 -- conversions of tagged types.
2353 Loc
: constant Source_Ptr
:= Sloc
(N
);
2355 Constraint
: Elmt_Id
;
2356 Discr_Value
: Node_Id
;
2359 New_Constraints
: constant Elist_Id
:= New_Elmt_List
;
2360 Old_Constraints
: constant Elist_Id
:=
2361 Discriminant_Constraint
(Expr_Type
);
2364 Constraint
:= First_Elmt
(Stored_Constraint
(Target_Type
));
2365 while Present
(Constraint
) loop
2366 Discr_Value
:= Node
(Constraint
);
2368 if Is_Entity_Name
(Discr_Value
)
2369 and then Ekind
(Entity
(Discr_Value
)) = E_Discriminant
2371 Discr
:= Corresponding_Discriminant
(Entity
(Discr_Value
));
2374 and then Scope
(Discr
) = Base_Type
(Expr_Type
)
2376 -- Parent is constrained by new discriminant. Obtain
2377 -- Value of original discriminant in expression. If the
2378 -- new discriminant has been used to constrain more than
2379 -- one of the stored discriminants, this will provide the
2380 -- required consistency check.
2383 Make_Selected_Component
(Loc
,
2385 Duplicate_Subexpr_No_Checks
2386 (Expr
, Name_Req
=> True),
2388 Make_Identifier
(Loc
, Chars
(Discr
))),
2392 -- Discriminant of more remote ancestor ???
2397 -- Derived type definition has an explicit value for this
2398 -- stored discriminant.
2402 (Duplicate_Subexpr_No_Checks
(Discr_Value
),
2406 Next_Elmt
(Constraint
);
2409 -- Use the unconstrained expression type to retrieve the
2410 -- discriminants of the parent, and apply momentarily the
2411 -- discriminant constraint synthesized above.
2413 Set_Discriminant_Constraint
(Expr_Type
, New_Constraints
);
2414 Cond
:= Build_Discriminant_Checks
(Expr
, Expr_Type
);
2415 Set_Discriminant_Constraint
(Expr_Type
, Old_Constraints
);
2418 Make_Raise_Constraint_Error
(Loc
,
2420 Reason
=> CE_Discriminant_Check_Failed
));
2423 -- For arrays, conversions are applied during expansion, to take into
2424 -- accounts changes of representation. The checks become range checks on
2425 -- the base type or length checks on the subtype, depending on whether
2426 -- the target type is unconstrained or constrained.
2431 end Apply_Type_Conversion_Checks
;
2433 ----------------------------------------------
2434 -- Apply_Universal_Integer_Attribute_Checks --
2435 ----------------------------------------------
2437 procedure Apply_Universal_Integer_Attribute_Checks
(N
: Node_Id
) is
2438 Loc
: constant Source_Ptr
:= Sloc
(N
);
2439 Typ
: constant Entity_Id
:= Etype
(N
);
2442 if Inside_A_Generic
then
2445 -- Nothing to do if checks are suppressed
2447 elsif Range_Checks_Suppressed
(Typ
)
2448 and then Overflow_Checks_Suppressed
(Typ
)
2452 -- Nothing to do if the attribute does not come from source. The
2453 -- internal attributes we generate of this type do not need checks,
2454 -- and furthermore the attempt to check them causes some circular
2455 -- elaboration orders when dealing with packed types.
2457 elsif not Comes_From_Source
(N
) then
2460 -- If the prefix is a selected component that depends on a discriminant
2461 -- the check may improperly expose a discriminant instead of using
2462 -- the bounds of the object itself. Set the type of the attribute to
2463 -- the base type of the context, so that a check will be imposed when
2464 -- needed (e.g. if the node appears as an index).
2466 elsif Nkind
(Prefix
(N
)) = N_Selected_Component
2467 and then Ekind
(Typ
) = E_Signed_Integer_Subtype
2468 and then Depends_On_Discriminant
(Scalar_Range
(Typ
))
2470 Set_Etype
(N
, Base_Type
(Typ
));
2472 -- Otherwise, replace the attribute node with a type conversion node
2473 -- whose expression is the attribute, retyped to universal integer, and
2474 -- whose subtype mark is the target type. The call to analyze this
2475 -- conversion will set range and overflow checks as required for proper
2476 -- detection of an out of range value.
2479 Set_Etype
(N
, Universal_Integer
);
2480 Set_Analyzed
(N
, True);
2483 Make_Type_Conversion
(Loc
,
2484 Subtype_Mark
=> New_Occurrence_Of
(Typ
, Loc
),
2485 Expression
=> Relocate_Node
(N
)));
2487 Analyze_And_Resolve
(N
, Typ
);
2490 end Apply_Universal_Integer_Attribute_Checks
;
2492 -------------------------------
2493 -- Build_Discriminant_Checks --
2494 -------------------------------
2496 function Build_Discriminant_Checks
2498 T_Typ
: Entity_Id
) return Node_Id
2500 Loc
: constant Source_Ptr
:= Sloc
(N
);
2503 Disc_Ent
: Entity_Id
;
2507 function Aggregate_Discriminant_Val
(Disc
: Entity_Id
) return Node_Id
;
2509 ----------------------------------
2510 -- Aggregate_Discriminant_Value --
2511 ----------------------------------
2513 function Aggregate_Discriminant_Val
(Disc
: Entity_Id
) return Node_Id
is
2517 -- The aggregate has been normalized with named associations. We use
2518 -- the Chars field to locate the discriminant to take into account
2519 -- discriminants in derived types, which carry the same name as those
2522 Assoc
:= First
(Component_Associations
(N
));
2523 while Present
(Assoc
) loop
2524 if Chars
(First
(Choices
(Assoc
))) = Chars
(Disc
) then
2525 return Expression
(Assoc
);
2531 -- Discriminant must have been found in the loop above
2533 raise Program_Error
;
2534 end Aggregate_Discriminant_Val
;
2536 -- Start of processing for Build_Discriminant_Checks
2539 -- Loop through discriminants evolving the condition
2542 Disc
:= First_Elmt
(Discriminant_Constraint
(T_Typ
));
2544 -- For a fully private type, use the discriminants of the parent type
2546 if Is_Private_Type
(T_Typ
)
2547 and then No
(Full_View
(T_Typ
))
2549 Disc_Ent
:= First_Discriminant
(Etype
(Base_Type
(T_Typ
)));
2551 Disc_Ent
:= First_Discriminant
(T_Typ
);
2554 while Present
(Disc
) loop
2555 Dval
:= Node
(Disc
);
2557 if Nkind
(Dval
) = N_Identifier
2558 and then Ekind
(Entity
(Dval
)) = E_Discriminant
2560 Dval
:= New_Occurrence_Of
(Discriminal
(Entity
(Dval
)), Loc
);
2562 Dval
:= Duplicate_Subexpr_No_Checks
(Dval
);
2565 -- If we have an Unchecked_Union node, we can infer the discriminants
2568 if Is_Unchecked_Union
(Base_Type
(T_Typ
)) then
2570 Get_Discriminant_Value
(
2571 First_Discriminant
(T_Typ
),
2573 Stored_Constraint
(T_Typ
)));
2575 elsif Nkind
(N
) = N_Aggregate
then
2577 Duplicate_Subexpr_No_Checks
2578 (Aggregate_Discriminant_Val
(Disc_Ent
));
2582 Make_Selected_Component
(Loc
,
2584 Duplicate_Subexpr_No_Checks
(N
, Name_Req
=> True),
2586 Make_Identifier
(Loc
, Chars
(Disc_Ent
)));
2588 Set_Is_In_Discriminant_Check
(Dref
);
2591 Evolve_Or_Else
(Cond
,
2594 Right_Opnd
=> Dval
));
2597 Next_Discriminant
(Disc_Ent
);
2601 end Build_Discriminant_Checks
;
2607 function Check_Needed
(Nod
: Node_Id
; Check
: Check_Type
) return Boolean is
2615 -- Always check if not simple entity
2617 if Nkind
(Nod
) not in N_Has_Entity
2618 or else not Comes_From_Source
(Nod
)
2623 -- Look up tree for short circuit
2630 -- Done if out of subexpression (note that we allow generated stuff
2631 -- such as itype declarations in this context, to keep the loop going
2632 -- since we may well have generated such stuff in complex situations.
2633 -- Also done if no parent (probably an error condition, but no point
2634 -- in behaving nasty if we find it!)
2637 or else (K
not in N_Subexpr
and then Comes_From_Source
(P
))
2641 -- Or/Or Else case, where test is part of the right operand, or is
2642 -- part of one of the actions associated with the right operand, and
2643 -- the left operand is an equality test.
2645 elsif K
= N_Op_Or
then
2646 exit when N
= Right_Opnd
(P
)
2647 and then Nkind
(Left_Opnd
(P
)) = N_Op_Eq
;
2649 elsif K
= N_Or_Else
then
2650 exit when (N
= Right_Opnd
(P
)
2653 and then List_Containing
(N
) = Actions
(P
)))
2654 and then Nkind
(Left_Opnd
(P
)) = N_Op_Eq
;
2656 -- Similar test for the And/And then case, where the left operand
2657 -- is an inequality test.
2659 elsif K
= N_Op_And
then
2660 exit when N
= Right_Opnd
(P
)
2661 and then Nkind
(Left_Opnd
(P
)) = N_Op_Ne
;
2663 elsif K
= N_And_Then
then
2664 exit when (N
= Right_Opnd
(P
)
2667 and then List_Containing
(N
) = Actions
(P
)))
2668 and then Nkind
(Left_Opnd
(P
)) = N_Op_Ne
;
2674 -- If we fall through the loop, then we have a conditional with an
2675 -- appropriate test as its left operand. So test further.
2678 R
:= Right_Opnd
(L
);
2681 -- Left operand of test must match original variable
2683 if Nkind
(L
) not in N_Has_Entity
2684 or else Entity
(L
) /= Entity
(Nod
)
2689 -- Right operand of test must be key value (zero or null)
2692 when Access_Check
=>
2693 if not Known_Null
(R
) then
2697 when Division_Check
=>
2698 if not Compile_Time_Known_Value
(R
)
2699 or else Expr_Value
(R
) /= Uint_0
2705 raise Program_Error
;
2708 -- Here we have the optimizable case, warn if not short-circuited
2710 if K
= N_Op_And
or else K
= N_Op_Or
then
2712 when Access_Check
=>
2714 ("Constraint_Error may be raised (access check)?",
2716 when Division_Check
=>
2718 ("Constraint_Error may be raised (zero divide)?",
2722 raise Program_Error
;
2725 if K
= N_Op_And
then
2726 Error_Msg_N
("use `AND THEN` instead of AND?", P
);
2728 Error_Msg_N
("use `OR ELSE` instead of OR?", P
);
2731 -- If not short-circuited, we need the ckeck
2735 -- If short-circuited, we can omit the check
2742 -----------------------------------
2743 -- Check_Valid_Lvalue_Subscripts --
2744 -----------------------------------
2746 procedure Check_Valid_Lvalue_Subscripts
(Expr
: Node_Id
) is
2748 -- Skip this if range checks are suppressed
2750 if Range_Checks_Suppressed
(Etype
(Expr
)) then
2753 -- Only do this check for expressions that come from source. We assume
2754 -- that expander generated assignments explicitly include any necessary
2755 -- checks. Note that this is not just an optimization, it avoids
2756 -- infinite recursions!
2758 elsif not Comes_From_Source
(Expr
) then
2761 -- For a selected component, check the prefix
2763 elsif Nkind
(Expr
) = N_Selected_Component
then
2764 Check_Valid_Lvalue_Subscripts
(Prefix
(Expr
));
2767 -- Case of indexed component
2769 elsif Nkind
(Expr
) = N_Indexed_Component
then
2770 Apply_Subscript_Validity_Checks
(Expr
);
2772 -- Prefix may itself be or contain an indexed component, and these
2773 -- subscripts need checking as well.
2775 Check_Valid_Lvalue_Subscripts
(Prefix
(Expr
));
2777 end Check_Valid_Lvalue_Subscripts
;
2779 ----------------------------------
2780 -- Null_Exclusion_Static_Checks --
2781 ----------------------------------
2783 procedure Null_Exclusion_Static_Checks
(N
: Node_Id
) is
2784 Error_Node
: Node_Id
;
2786 Has_Null
: constant Boolean := Has_Null_Exclusion
(N
);
2787 K
: constant Node_Kind
:= Nkind
(N
);
2792 (K
= N_Component_Declaration
2793 or else K
= N_Discriminant_Specification
2794 or else K
= N_Function_Specification
2795 or else K
= N_Object_Declaration
2796 or else K
= N_Parameter_Specification
);
2798 if K
= N_Function_Specification
then
2799 Typ
:= Etype
(Defining_Entity
(N
));
2801 Typ
:= Etype
(Defining_Identifier
(N
));
2805 when N_Component_Declaration
=>
2806 if Present
(Access_Definition
(Component_Definition
(N
))) then
2807 Error_Node
:= Component_Definition
(N
);
2809 Error_Node
:= Subtype_Indication
(Component_Definition
(N
));
2812 when N_Discriminant_Specification
=>
2813 Error_Node
:= Discriminant_Type
(N
);
2815 when N_Function_Specification
=>
2816 Error_Node
:= Result_Definition
(N
);
2818 when N_Object_Declaration
=>
2819 Error_Node
:= Object_Definition
(N
);
2821 when N_Parameter_Specification
=>
2822 Error_Node
:= Parameter_Type
(N
);
2825 raise Program_Error
;
2830 -- Enforce legality rule 3.10 (13): A null exclusion can only be
2831 -- applied to an access [sub]type.
2833 if not Is_Access_Type
(Typ
) then
2835 ("`NOT NULL` allowed only for an access type", Error_Node
);
2837 -- Enforce legality rule RM 3.10(14/1): A null exclusion can only
2838 -- be applied to a [sub]type that does not exclude null already.
2840 elsif Can_Never_Be_Null
(Typ
)
2841 and then Comes_From_Source
(Typ
)
2844 ("`NOT NULL` not allowed (& already excludes null)",
2849 -- Check that null-excluding objects are always initialized, except for
2850 -- deferred constants, for which the expression will appear in the full
2853 if K
= N_Object_Declaration
2854 and then No
(Expression
(N
))
2855 and then not Constant_Present
(N
)
2856 and then not No_Initialization
(N
)
2858 -- Add an expression that assigns null. This node is needed by
2859 -- Apply_Compile_Time_Constraint_Error, which will replace this with
2860 -- a Constraint_Error node.
2862 Set_Expression
(N
, Make_Null
(Sloc
(N
)));
2863 Set_Etype
(Expression
(N
), Etype
(Defining_Identifier
(N
)));
2865 Apply_Compile_Time_Constraint_Error
2866 (N
=> Expression
(N
),
2867 Msg
=> "(Ada 2005) null-excluding objects must be initialized?",
2868 Reason
=> CE_Null_Not_Allowed
);
2871 -- Check that a null-excluding component, formal or object is not being
2872 -- assigned a null value. Otherwise generate a warning message and
2873 -- replace Expression (N) by an N_Constraint_Error node.
2875 if K
/= N_Function_Specification
then
2876 Expr
:= Expression
(N
);
2878 if Present
(Expr
) and then Known_Null
(Expr
) then
2880 when N_Component_Declaration |
2881 N_Discriminant_Specification
=>
2882 Apply_Compile_Time_Constraint_Error
2884 Msg
=> "(Ada 2005) null not allowed " &
2885 "in null-excluding components?",
2886 Reason
=> CE_Null_Not_Allowed
);
2888 when N_Object_Declaration
=>
2889 Apply_Compile_Time_Constraint_Error
2891 Msg
=> "(Ada 2005) null not allowed " &
2892 "in null-excluding objects?",
2893 Reason
=> CE_Null_Not_Allowed
);
2895 when N_Parameter_Specification
=>
2896 Apply_Compile_Time_Constraint_Error
2898 Msg
=> "(Ada 2005) null not allowed " &
2899 "in null-excluding formals?",
2900 Reason
=> CE_Null_Not_Allowed
);
2907 end Null_Exclusion_Static_Checks
;
2909 ----------------------------------
2910 -- Conditional_Statements_Begin --
2911 ----------------------------------
2913 procedure Conditional_Statements_Begin
is
2915 Saved_Checks_TOS
:= Saved_Checks_TOS
+ 1;
2917 -- If stack overflows, kill all checks, that way we know to simply reset
2918 -- the number of saved checks to zero on return. This should never occur
2921 if Saved_Checks_TOS
> Saved_Checks_Stack
'Last then
2924 -- In the normal case, we just make a new stack entry saving the current
2925 -- number of saved checks for a later restore.
2928 Saved_Checks_Stack
(Saved_Checks_TOS
) := Num_Saved_Checks
;
2930 if Debug_Flag_CC
then
2931 w
("Conditional_Statements_Begin: Num_Saved_Checks = ",
2935 end Conditional_Statements_Begin
;
2937 --------------------------------
2938 -- Conditional_Statements_End --
2939 --------------------------------
2941 procedure Conditional_Statements_End
is
2943 pragma Assert
(Saved_Checks_TOS
> 0);
2945 -- If the saved checks stack overflowed, then we killed all checks, so
2946 -- setting the number of saved checks back to zero is correct. This
2947 -- should never occur in practice.
2949 if Saved_Checks_TOS
> Saved_Checks_Stack
'Last then
2950 Num_Saved_Checks
:= 0;
2952 -- In the normal case, restore the number of saved checks from the top
2956 Num_Saved_Checks
:= Saved_Checks_Stack
(Saved_Checks_TOS
);
2957 if Debug_Flag_CC
then
2958 w
("Conditional_Statements_End: Num_Saved_Checks = ",
2963 Saved_Checks_TOS
:= Saved_Checks_TOS
- 1;
2964 end Conditional_Statements_End
;
2966 ---------------------
2967 -- Determine_Range --
2968 ---------------------
2970 Cache_Size
: constant := 2 ** 10;
2971 type Cache_Index
is range 0 .. Cache_Size
- 1;
2972 -- Determine size of below cache (power of 2 is more efficient!)
2974 Determine_Range_Cache_N
: array (Cache_Index
) of Node_Id
;
2975 Determine_Range_Cache_V
: array (Cache_Index
) of Boolean;
2976 Determine_Range_Cache_Lo
: array (Cache_Index
) of Uint
;
2977 Determine_Range_Cache_Hi
: array (Cache_Index
) of Uint
;
2978 -- The above arrays are used to implement a small direct cache for
2979 -- Determine_Range calls. Because of the way Determine_Range recursively
2980 -- traces subexpressions, and because overflow checking calls the routine
2981 -- on the way up the tree, a quadratic behavior can otherwise be
2982 -- encountered in large expressions. The cache entry for node N is stored
2983 -- in the (N mod Cache_Size) entry, and can be validated by checking the
2984 -- actual node value stored there. The Range_Cache_V array records the
2985 -- setting of Assume_Valid for the cache entry.
2987 procedure Determine_Range
2992 Assume_Valid
: Boolean := False)
2994 Typ
: Entity_Id
:= Etype
(N
);
2995 -- Type to use, may get reset to base type for possibly invalid entity
2999 -- Lo and Hi bounds of left operand
3003 -- Lo and Hi bounds of right (or only) operand
3006 -- Temp variable used to hold a bound node
3009 -- High bound of base type of expression
3013 -- Refined values for low and high bounds, after tightening
3016 -- Used in lower level calls to indicate if call succeeded
3018 Cindex
: Cache_Index
;
3019 -- Used to search cache
3021 function OK_Operands
return Boolean;
3022 -- Used for binary operators. Determines the ranges of the left and
3023 -- right operands, and if they are both OK, returns True, and puts
3024 -- the results in Lo_Right, Hi_Right, Lo_Left, Hi_Left.
3030 function OK_Operands
return Boolean is
3033 (Left_Opnd
(N
), OK1
, Lo_Left
, Hi_Left
, Assume_Valid
);
3040 (Right_Opnd
(N
), OK1
, Lo_Right
, Hi_Right
, Assume_Valid
);
3044 -- Start of processing for Determine_Range
3047 -- Prevent junk warnings by initializing range variables
3054 -- If type is not defined, we can't determine its range
3058 -- We don't deal with anything except discrete types
3060 or else not Is_Discrete_Type
(Typ
)
3062 -- Ignore type for which an error has been posted, since range in
3063 -- this case may well be a bogosity deriving from the error. Also
3064 -- ignore if error posted on the reference node.
3066 or else Error_Posted
(N
) or else Error_Posted
(Typ
)
3072 -- For all other cases, we can determine the range
3076 -- If value is compile time known, then the possible range is the one
3077 -- value that we know this expression definitely has!
3079 if Compile_Time_Known_Value
(N
) then
3080 Lo
:= Expr_Value
(N
);
3085 -- Return if already in the cache
3087 Cindex
:= Cache_Index
(N
mod Cache_Size
);
3089 if Determine_Range_Cache_N
(Cindex
) = N
3091 Determine_Range_Cache_V
(Cindex
) = Assume_Valid
3093 Lo
:= Determine_Range_Cache_Lo
(Cindex
);
3094 Hi
:= Determine_Range_Cache_Hi
(Cindex
);
3098 -- Otherwise, start by finding the bounds of the type of the expression,
3099 -- the value cannot be outside this range (if it is, then we have an
3100 -- overflow situation, which is a separate check, we are talking here
3101 -- only about the expression value).
3103 -- First a check, never try to find the bounds of a generic type, since
3104 -- these bounds are always junk values, and it is only valid to look at
3105 -- the bounds in an instance.
3107 if Is_Generic_Type
(Typ
) then
3112 -- First step, change to use base type unless we know the value is valid
3114 if (Is_Entity_Name
(N
) and then Is_Known_Valid
(Entity
(N
)))
3115 or else Assume_No_Invalid_Values
3116 or else Assume_Valid
3120 Typ
:= Underlying_Type
(Base_Type
(Typ
));
3123 -- We use the actual bound unless it is dynamic, in which case use the
3124 -- corresponding base type bound if possible. If we can't get a bound
3125 -- then we figure we can't determine the range (a peculiar case, that
3126 -- perhaps cannot happen, but there is no point in bombing in this
3127 -- optimization circuit.
3129 -- First the low bound
3131 Bound
:= Type_Low_Bound
(Typ
);
3133 if Compile_Time_Known_Value
(Bound
) then
3134 Lo
:= Expr_Value
(Bound
);
3136 elsif Compile_Time_Known_Value
(Type_Low_Bound
(Base_Type
(Typ
))) then
3137 Lo
:= Expr_Value
(Type_Low_Bound
(Base_Type
(Typ
)));
3144 -- Now the high bound
3146 Bound
:= Type_High_Bound
(Typ
);
3148 -- We need the high bound of the base type later on, and this should
3149 -- always be compile time known. Again, it is not clear that this
3150 -- can ever be false, but no point in bombing.
3152 if Compile_Time_Known_Value
(Type_High_Bound
(Base_Type
(Typ
))) then
3153 Hbound
:= Expr_Value
(Type_High_Bound
(Base_Type
(Typ
)));
3161 -- If we have a static subtype, then that may have a tighter bound so
3162 -- use the upper bound of the subtype instead in this case.
3164 if Compile_Time_Known_Value
(Bound
) then
3165 Hi
:= Expr_Value
(Bound
);
3168 -- We may be able to refine this value in certain situations. If any
3169 -- refinement is possible, then Lor and Hir are set to possibly tighter
3170 -- bounds, and OK1 is set to True.
3174 -- For unary plus, result is limited by range of operand
3178 (Right_Opnd
(N
), OK1
, Lor
, Hir
, Assume_Valid
);
3180 -- For unary minus, determine range of operand, and negate it
3184 (Right_Opnd
(N
), OK1
, Lo_Right
, Hi_Right
, Assume_Valid
);
3191 -- For binary addition, get range of each operand and do the
3192 -- addition to get the result range.
3196 Lor
:= Lo_Left
+ Lo_Right
;
3197 Hir
:= Hi_Left
+ Hi_Right
;
3200 -- Division is tricky. The only case we consider is where the right
3201 -- operand is a positive constant, and in this case we simply divide
3202 -- the bounds of the left operand
3206 if Lo_Right
= Hi_Right
3207 and then Lo_Right
> 0
3209 Lor
:= Lo_Left
/ Lo_Right
;
3210 Hir
:= Hi_Left
/ Lo_Right
;
3217 -- For binary subtraction, get range of each operand and do the worst
3218 -- case subtraction to get the result range.
3220 when N_Op_Subtract
=>
3222 Lor
:= Lo_Left
- Hi_Right
;
3223 Hir
:= Hi_Left
- Lo_Right
;
3226 -- For MOD, if right operand is a positive constant, then result must
3227 -- be in the allowable range of mod results.
3231 if Lo_Right
= Hi_Right
3232 and then Lo_Right
/= 0
3234 if Lo_Right
> 0 then
3236 Hir
:= Lo_Right
- 1;
3238 else -- Lo_Right < 0
3239 Lor
:= Lo_Right
+ 1;
3248 -- For REM, if right operand is a positive constant, then result must
3249 -- be in the allowable range of mod results.
3253 if Lo_Right
= Hi_Right
3254 and then Lo_Right
/= 0
3257 Dval
: constant Uint
:= (abs Lo_Right
) - 1;
3260 -- The sign of the result depends on the sign of the
3261 -- dividend (but not on the sign of the divisor, hence
3262 -- the abs operation above).
3282 -- Attribute reference cases
3284 when N_Attribute_Reference
=>
3285 case Attribute_Name
(N
) is
3287 -- For Pos/Val attributes, we can refine the range using the
3288 -- possible range of values of the attribute expression.
3290 when Name_Pos | Name_Val
=>
3292 (First
(Expressions
(N
)), OK1
, Lor
, Hir
, Assume_Valid
);
3294 -- For Length attribute, use the bounds of the corresponding
3295 -- index type to refine the range.
3299 Atyp
: Entity_Id
:= Etype
(Prefix
(N
));
3307 if Is_Access_Type
(Atyp
) then
3308 Atyp
:= Designated_Type
(Atyp
);
3311 -- For string literal, we know exact value
3313 if Ekind
(Atyp
) = E_String_Literal_Subtype
then
3315 Lo
:= String_Literal_Length
(Atyp
);
3316 Hi
:= String_Literal_Length
(Atyp
);
3320 -- Otherwise check for expression given
3322 if No
(Expressions
(N
)) then
3326 UI_To_Int
(Expr_Value
(First
(Expressions
(N
))));
3329 Indx
:= First_Index
(Atyp
);
3330 for J
in 2 .. Inum
loop
3331 Indx
:= Next_Index
(Indx
);
3335 (Type_Low_Bound
(Etype
(Indx
)), OK1
, LL
, LU
,
3340 (Type_High_Bound
(Etype
(Indx
)), OK1
, UL
, UU
,
3345 -- The maximum value for Length is the biggest
3346 -- possible gap between the values of the bounds.
3347 -- But of course, this value cannot be negative.
3349 Hir
:= UI_Max
(Uint_0
, UU
- LL
+ 1);
3351 -- For constrained arrays, the minimum value for
3352 -- Length is taken from the actual value of the
3353 -- bounds, since the index will be exactly of
3356 if Is_Constrained
(Atyp
) then
3357 Lor
:= UI_Max
(Uint_0
, UL
- LU
+ 1);
3359 -- For an unconstrained array, the minimum value
3360 -- for length is always zero.
3369 -- No special handling for other attributes
3370 -- Probably more opportunities exist here ???
3377 -- For type conversion from one discrete type to another, we can
3378 -- refine the range using the converted value.
3380 when N_Type_Conversion
=>
3381 Determine_Range
(Expression
(N
), OK1
, Lor
, Hir
, Assume_Valid
);
3383 -- Nothing special to do for all other expression kinds
3391 -- At this stage, if OK1 is true, then we know that the actual
3392 -- result of the computed expression is in the range Lor .. Hir.
3393 -- We can use this to restrict the possible range of results.
3397 -- If the refined value of the low bound is greater than the
3398 -- type high bound, then reset it to the more restrictive
3399 -- value. However, we do NOT do this for the case of a modular
3400 -- type where the possible upper bound on the value is above the
3401 -- base type high bound, because that means the result could wrap.
3404 and then not (Is_Modular_Integer_Type
(Typ
)
3405 and then Hir
> Hbound
)
3410 -- Similarly, if the refined value of the high bound is less
3411 -- than the value so far, then reset it to the more restrictive
3412 -- value. Again, we do not do this if the refined low bound is
3413 -- negative for a modular type, since this would wrap.
3416 and then not (Is_Modular_Integer_Type
(Typ
)
3417 and then Lor
< Uint_0
)
3423 -- Set cache entry for future call and we are all done
3425 Determine_Range_Cache_N
(Cindex
) := N
;
3426 Determine_Range_Cache_V
(Cindex
) := Assume_Valid
;
3427 Determine_Range_Cache_Lo
(Cindex
) := Lo
;
3428 Determine_Range_Cache_Hi
(Cindex
) := Hi
;
3431 -- If any exception occurs, it means that we have some bug in the compiler
3432 -- possibly triggered by a previous error, or by some unforseen peculiar
3433 -- occurrence. However, this is only an optimization attempt, so there is
3434 -- really no point in crashing the compiler. Instead we just decide, too
3435 -- bad, we can't figure out a range in this case after all.
3440 -- Debug flag K disables this behavior (useful for debugging)
3442 if Debug_Flag_K
then
3450 end Determine_Range
;
3452 ------------------------------------
3453 -- Discriminant_Checks_Suppressed --
3454 ------------------------------------
3456 function Discriminant_Checks_Suppressed
(E
: Entity_Id
) return Boolean is
3459 if Is_Unchecked_Union
(E
) then
3461 elsif Checks_May_Be_Suppressed
(E
) then
3462 return Is_Check_Suppressed
(E
, Discriminant_Check
);
3466 return Scope_Suppress
(Discriminant_Check
);
3467 end Discriminant_Checks_Suppressed
;
3469 --------------------------------
3470 -- Division_Checks_Suppressed --
3471 --------------------------------
3473 function Division_Checks_Suppressed
(E
: Entity_Id
) return Boolean is
3475 if Present
(E
) and then Checks_May_Be_Suppressed
(E
) then
3476 return Is_Check_Suppressed
(E
, Division_Check
);
3478 return Scope_Suppress
(Division_Check
);
3480 end Division_Checks_Suppressed
;
3482 -----------------------------------
3483 -- Elaboration_Checks_Suppressed --
3484 -----------------------------------
3486 function Elaboration_Checks_Suppressed
(E
: Entity_Id
) return Boolean is
3488 -- The complication in this routine is that if we are in the dynamic
3489 -- model of elaboration, we also check All_Checks, since All_Checks
3490 -- does not set Elaboration_Check explicitly.
3493 if Kill_Elaboration_Checks
(E
) then
3496 elsif Checks_May_Be_Suppressed
(E
) then
3497 if Is_Check_Suppressed
(E
, Elaboration_Check
) then
3499 elsif Dynamic_Elaboration_Checks
then
3500 return Is_Check_Suppressed
(E
, All_Checks
);
3507 if Scope_Suppress
(Elaboration_Check
) then
3509 elsif Dynamic_Elaboration_Checks
then
3510 return Scope_Suppress
(All_Checks
);
3514 end Elaboration_Checks_Suppressed
;
3516 ---------------------------
3517 -- Enable_Overflow_Check --
3518 ---------------------------
3520 procedure Enable_Overflow_Check
(N
: Node_Id
) is
3521 Typ
: constant Entity_Id
:= Base_Type
(Etype
(N
));
3530 if Debug_Flag_CC
then
3531 w
("Enable_Overflow_Check for node ", Int
(N
));
3532 Write_Str
(" Source location = ");
3537 -- No check if overflow checks suppressed for type of node
3539 if Present
(Etype
(N
))
3540 and then Overflow_Checks_Suppressed
(Etype
(N
))
3544 -- Nothing to do for unsigned integer types, which do not overflow
3546 elsif Is_Modular_Integer_Type
(Typ
) then
3549 -- Nothing to do if the range of the result is known OK. We skip this
3550 -- for conversions, since the caller already did the check, and in any
3551 -- case the condition for deleting the check for a type conversion is
3554 elsif Nkind
(N
) /= N_Type_Conversion
then
3555 Determine_Range
(N
, OK
, Lo
, Hi
, Assume_Valid
=> True);
3557 -- Note in the test below that we assume that the range is not OK
3558 -- if a bound of the range is equal to that of the type. That's not
3559 -- quite accurate but we do this for the following reasons:
3561 -- a) The way that Determine_Range works, it will typically report
3562 -- the bounds of the value as being equal to the bounds of the
3563 -- type, because it either can't tell anything more precise, or
3564 -- does not think it is worth the effort to be more precise.
3566 -- b) It is very unusual to have a situation in which this would
3567 -- generate an unnecessary overflow check (an example would be
3568 -- a subtype with a range 0 .. Integer'Last - 1 to which the
3569 -- literal value one is added).
3571 -- c) The alternative is a lot of special casing in this routine
3572 -- which would partially duplicate Determine_Range processing.
3575 and then Lo
> Expr_Value
(Type_Low_Bound
(Typ
))
3576 and then Hi
< Expr_Value
(Type_High_Bound
(Typ
))
3578 if Debug_Flag_CC
then
3579 w
("No overflow check required");
3586 -- If not in optimizing mode, set flag and we are done. We are also done
3587 -- (and just set the flag) if the type is not a discrete type, since it
3588 -- is not worth the effort to eliminate checks for other than discrete
3589 -- types. In addition, we take this same path if we have stored the
3590 -- maximum number of checks possible already (a very unlikely situation,
3591 -- but we do not want to blow up!)
3593 if Optimization_Level
= 0
3594 or else not Is_Discrete_Type
(Etype
(N
))
3595 or else Num_Saved_Checks
= Saved_Checks
'Last
3597 Activate_Overflow_Check
(N
);
3599 if Debug_Flag_CC
then
3600 w
("Optimization off");
3606 -- Otherwise evaluate and check the expression
3611 Target_Type
=> Empty
,
3617 if Debug_Flag_CC
then
3618 w
("Called Find_Check");
3622 w
(" Check_Num = ", Chk
);
3623 w
(" Ent = ", Int
(Ent
));
3624 Write_Str
(" Ofs = ");
3629 -- If check is not of form to optimize, then set flag and we are done
3632 Activate_Overflow_Check
(N
);
3636 -- If check is already performed, then return without setting flag
3639 if Debug_Flag_CC
then
3640 w
("Check suppressed!");
3646 -- Here we will make a new entry for the new check
3648 Activate_Overflow_Check
(N
);
3649 Num_Saved_Checks
:= Num_Saved_Checks
+ 1;
3650 Saved_Checks
(Num_Saved_Checks
) :=
3655 Target_Type
=> Empty
);
3657 if Debug_Flag_CC
then
3658 w
("Make new entry, check number = ", Num_Saved_Checks
);
3659 w
(" Entity = ", Int
(Ent
));
3660 Write_Str
(" Offset = ");
3662 w
(" Check_Type = O");
3663 w
(" Target_Type = Empty");
3666 -- If we get an exception, then something went wrong, probably because of
3667 -- an error in the structure of the tree due to an incorrect program. Or it
3668 -- may be a bug in the optimization circuit. In either case the safest
3669 -- thing is simply to set the check flag unconditionally.
3673 Activate_Overflow_Check
(N
);
3675 if Debug_Flag_CC
then
3676 w
(" exception occurred, overflow flag set");
3680 end Enable_Overflow_Check
;
3682 ------------------------
3683 -- Enable_Range_Check --
3684 ------------------------
3686 procedure Enable_Range_Check
(N
: Node_Id
) is
3695 -- Return if unchecked type conversion with range check killed. In this
3696 -- case we never set the flag (that's what Kill_Range_Check is about!)
3698 if Nkind
(N
) = N_Unchecked_Type_Conversion
3699 and then Kill_Range_Check
(N
)
3704 -- Check for various cases where we should suppress the range check
3706 -- No check if range checks suppressed for type of node
3708 if Present
(Etype
(N
))
3709 and then Range_Checks_Suppressed
(Etype
(N
))
3713 -- No check if node is an entity name, and range checks are suppressed
3714 -- for this entity, or for the type of this entity.
3716 elsif Is_Entity_Name
(N
)
3717 and then (Range_Checks_Suppressed
(Entity
(N
))
3718 or else Range_Checks_Suppressed
(Etype
(Entity
(N
))))
3722 -- No checks if index of array, and index checks are suppressed for
3723 -- the array object or the type of the array.
3725 elsif Nkind
(Parent
(N
)) = N_Indexed_Component
then
3727 Pref
: constant Node_Id
:= Prefix
(Parent
(N
));
3729 if Is_Entity_Name
(Pref
)
3730 and then Index_Checks_Suppressed
(Entity
(Pref
))
3733 elsif Index_Checks_Suppressed
(Etype
(Pref
)) then
3739 -- Debug trace output
3741 if Debug_Flag_CC
then
3742 w
("Enable_Range_Check for node ", Int
(N
));
3743 Write_Str
(" Source location = ");
3748 -- If not in optimizing mode, set flag and we are done. We are also done
3749 -- (and just set the flag) if the type is not a discrete type, since it
3750 -- is not worth the effort to eliminate checks for other than discrete
3751 -- types. In addition, we take this same path if we have stored the
3752 -- maximum number of checks possible already (a very unlikely situation,
3753 -- but we do not want to blow up!)
3755 if Optimization_Level
= 0
3756 or else No
(Etype
(N
))
3757 or else not Is_Discrete_Type
(Etype
(N
))
3758 or else Num_Saved_Checks
= Saved_Checks
'Last
3760 Activate_Range_Check
(N
);
3762 if Debug_Flag_CC
then
3763 w
("Optimization off");
3769 -- Otherwise find out the target type
3773 -- For assignment, use left side subtype
3775 if Nkind
(P
) = N_Assignment_Statement
3776 and then Expression
(P
) = N
3778 Ttyp
:= Etype
(Name
(P
));
3780 -- For indexed component, use subscript subtype
3782 elsif Nkind
(P
) = N_Indexed_Component
then
3789 Atyp
:= Etype
(Prefix
(P
));
3791 if Is_Access_Type
(Atyp
) then
3792 Atyp
:= Designated_Type
(Atyp
);
3794 -- If the prefix is an access to an unconstrained array,
3795 -- perform check unconditionally: it depends on the bounds of
3796 -- an object and we cannot currently recognize whether the test
3797 -- may be redundant.
3799 if not Is_Constrained
(Atyp
) then
3800 Activate_Range_Check
(N
);
3804 -- Ditto if the prefix is an explicit dereference whose designated
3805 -- type is unconstrained.
3807 elsif Nkind
(Prefix
(P
)) = N_Explicit_Dereference
3808 and then not Is_Constrained
(Atyp
)
3810 Activate_Range_Check
(N
);
3814 Indx
:= First_Index
(Atyp
);
3815 Subs
:= First
(Expressions
(P
));
3818 Ttyp
:= Etype
(Indx
);
3827 -- For now, ignore all other cases, they are not so interesting
3830 if Debug_Flag_CC
then
3831 w
(" target type not found, flag set");
3834 Activate_Range_Check
(N
);
3838 -- Evaluate and check the expression
3843 Target_Type
=> Ttyp
,
3849 if Debug_Flag_CC
then
3850 w
("Called Find_Check");
3851 w
("Target_Typ = ", Int
(Ttyp
));
3855 w
(" Check_Num = ", Chk
);
3856 w
(" Ent = ", Int
(Ent
));
3857 Write_Str
(" Ofs = ");
3862 -- If check is not of form to optimize, then set flag and we are done
3865 if Debug_Flag_CC
then
3866 w
(" expression not of optimizable type, flag set");
3869 Activate_Range_Check
(N
);
3873 -- If check is already performed, then return without setting flag
3876 if Debug_Flag_CC
then
3877 w
("Check suppressed!");
3883 -- Here we will make a new entry for the new check
3885 Activate_Range_Check
(N
);
3886 Num_Saved_Checks
:= Num_Saved_Checks
+ 1;
3887 Saved_Checks
(Num_Saved_Checks
) :=
3892 Target_Type
=> Ttyp
);
3894 if Debug_Flag_CC
then
3895 w
("Make new entry, check number = ", Num_Saved_Checks
);
3896 w
(" Entity = ", Int
(Ent
));
3897 Write_Str
(" Offset = ");
3899 w
(" Check_Type = R");
3900 w
(" Target_Type = ", Int
(Ttyp
));
3901 pg
(Union_Id
(Ttyp
));
3904 -- If we get an exception, then something went wrong, probably because of
3905 -- an error in the structure of the tree due to an incorrect program. Or
3906 -- it may be a bug in the optimization circuit. In either case the safest
3907 -- thing is simply to set the check flag unconditionally.
3911 Activate_Range_Check
(N
);
3913 if Debug_Flag_CC
then
3914 w
(" exception occurred, range flag set");
3918 end Enable_Range_Check
;
3924 procedure Ensure_Valid
(Expr
: Node_Id
; Holes_OK
: Boolean := False) is
3925 Typ
: constant Entity_Id
:= Etype
(Expr
);
3928 -- Ignore call if we are not doing any validity checking
3930 if not Validity_Checks_On
then
3933 -- Ignore call if range or validity checks suppressed on entity or type
3935 elsif Range_Or_Validity_Checks_Suppressed
(Expr
) then
3938 -- No check required if expression is from the expander, we assume the
3939 -- expander will generate whatever checks are needed. Note that this is
3940 -- not just an optimization, it avoids infinite recursions!
3942 -- Unchecked conversions must be checked, unless they are initialized
3943 -- scalar values, as in a component assignment in an init proc.
3945 -- In addition, we force a check if Force_Validity_Checks is set
3947 elsif not Comes_From_Source
(Expr
)
3948 and then not Force_Validity_Checks
3949 and then (Nkind
(Expr
) /= N_Unchecked_Type_Conversion
3950 or else Kill_Range_Check
(Expr
))
3954 -- No check required if expression is known to have valid value
3956 elsif Expr_Known_Valid
(Expr
) then
3959 -- Ignore case of enumeration with holes where the flag is set not to
3960 -- worry about holes, since no special validity check is needed
3962 elsif Is_Enumeration_Type
(Typ
)
3963 and then Has_Non_Standard_Rep
(Typ
)
3968 -- No check required on the left-hand side of an assignment
3970 elsif Nkind
(Parent
(Expr
)) = N_Assignment_Statement
3971 and then Expr
= Name
(Parent
(Expr
))
3975 -- No check on a univeral real constant. The context will eventually
3976 -- convert it to a machine number for some target type, or report an
3979 elsif Nkind
(Expr
) = N_Real_Literal
3980 and then Etype
(Expr
) = Universal_Real
3984 -- If the expression denotes a component of a packed boolean arrray,
3985 -- no possible check applies. We ignore the old ACATS chestnuts that
3986 -- involve Boolean range True..True.
3988 -- Note: validity checks are generated for expressions that yield a
3989 -- scalar type, when it is possible to create a value that is outside of
3990 -- the type. If this is a one-bit boolean no such value exists. This is
3991 -- an optimization, and it also prevents compiler blowing up during the
3992 -- elaboration of improperly expanded packed array references.
3994 elsif Nkind
(Expr
) = N_Indexed_Component
3995 and then Is_Bit_Packed_Array
(Etype
(Prefix
(Expr
)))
3996 and then Root_Type
(Etype
(Expr
)) = Standard_Boolean
4000 -- An annoying special case. If this is an out parameter of a scalar
4001 -- type, then the value is not going to be accessed, therefore it is
4002 -- inappropriate to do any validity check at the call site.
4005 -- Only need to worry about scalar types
4007 if Is_Scalar_Type
(Typ
) then
4017 -- Find actual argument (which may be a parameter association)
4018 -- and the parent of the actual argument (the call statement)
4023 if Nkind
(P
) = N_Parameter_Association
then
4028 -- Only need to worry if we are argument of a procedure call
4029 -- since functions don't have out parameters. If this is an
4030 -- indirect or dispatching call, get signature from the
4033 if Nkind
(P
) = N_Procedure_Call_Statement
then
4034 L
:= Parameter_Associations
(P
);
4036 if Is_Entity_Name
(Name
(P
)) then
4037 E
:= Entity
(Name
(P
));
4039 pragma Assert
(Nkind
(Name
(P
)) = N_Explicit_Dereference
);
4040 E
:= Etype
(Name
(P
));
4043 -- Only need to worry if there are indeed actuals, and if
4044 -- this could be a procedure call, otherwise we cannot get a
4045 -- match (either we are not an argument, or the mode of the
4046 -- formal is not OUT). This test also filters out the
4049 if Is_Non_Empty_List
(L
)
4050 and then Is_Subprogram
(E
)
4052 -- This is the loop through parameters, looking for an
4053 -- OUT parameter for which we are the argument.
4055 F
:= First_Formal
(E
);
4057 while Present
(F
) loop
4058 if Ekind
(F
) = E_Out_Parameter
and then A
= N
then
4071 -- If we fall through, a validity check is required
4073 Insert_Valid_Check
(Expr
);
4075 if Is_Entity_Name
(Expr
)
4076 and then Safe_To_Capture_Value
(Expr
, Entity
(Expr
))
4078 Set_Is_Known_Valid
(Entity
(Expr
));
4082 ----------------------
4083 -- Expr_Known_Valid --
4084 ----------------------
4086 function Expr_Known_Valid
(Expr
: Node_Id
) return Boolean is
4087 Typ
: constant Entity_Id
:= Etype
(Expr
);
4090 -- Non-scalar types are always considered valid, since they never give
4091 -- rise to the issues of erroneous or bounded error behavior that are
4092 -- the concern. In formal reference manual terms the notion of validity
4093 -- only applies to scalar types. Note that even when packed arrays are
4094 -- represented using modular types, they are still arrays semantically,
4095 -- so they are also always valid (in particular, the unused bits can be
4096 -- random rubbish without affecting the validity of the array value).
4098 if not Is_Scalar_Type
(Typ
) or else Is_Packed_Array_Type
(Typ
) then
4101 -- If no validity checking, then everything is considered valid
4103 elsif not Validity_Checks_On
then
4106 -- Floating-point types are considered valid unless floating-point
4107 -- validity checks have been specifically turned on.
4109 elsif Is_Floating_Point_Type
(Typ
)
4110 and then not Validity_Check_Floating_Point
4114 -- If the expression is the value of an object that is known to be
4115 -- valid, then clearly the expression value itself is valid.
4117 elsif Is_Entity_Name
(Expr
)
4118 and then Is_Known_Valid
(Entity
(Expr
))
4122 -- References to discriminants are always considered valid. The value
4123 -- of a discriminant gets checked when the object is built. Within the
4124 -- record, we consider it valid, and it is important to do so, since
4125 -- otherwise we can try to generate bogus validity checks which
4126 -- reference discriminants out of scope. Discriminants of concurrent
4127 -- types are excluded for the same reason.
4129 elsif Is_Entity_Name
(Expr
)
4130 and then Denotes_Discriminant
(Expr
, Check_Concurrent
=> True)
4134 -- If the type is one for which all values are known valid, then we are
4135 -- sure that the value is valid except in the slightly odd case where
4136 -- the expression is a reference to a variable whose size has been
4137 -- explicitly set to a value greater than the object size.
4139 elsif Is_Known_Valid
(Typ
) then
4140 if Is_Entity_Name
(Expr
)
4141 and then Ekind
(Entity
(Expr
)) = E_Variable
4142 and then Esize
(Entity
(Expr
)) > Esize
(Typ
)
4149 -- Integer and character literals always have valid values, where
4150 -- appropriate these will be range checked in any case.
4152 elsif Nkind
(Expr
) = N_Integer_Literal
4154 Nkind
(Expr
) = N_Character_Literal
4158 -- If we have a type conversion or a qualification of a known valid
4159 -- value, then the result will always be valid.
4161 elsif Nkind
(Expr
) = N_Type_Conversion
4163 Nkind
(Expr
) = N_Qualified_Expression
4165 return Expr_Known_Valid
(Expression
(Expr
));
4167 -- The result of any operator is always considered valid, since we
4168 -- assume the necessary checks are done by the operator. For operators
4169 -- on floating-point operations, we must also check when the operation
4170 -- is the right-hand side of an assignment, or is an actual in a call.
4172 elsif Nkind
(Expr
) in N_Op
then
4173 if Is_Floating_Point_Type
(Typ
)
4174 and then Validity_Check_Floating_Point
4176 (Nkind
(Parent
(Expr
)) = N_Assignment_Statement
4177 or else Nkind
(Parent
(Expr
)) = N_Function_Call
4178 or else Nkind
(Parent
(Expr
)) = N_Parameter_Association
)
4185 -- The result of a membership test is always valid, since it is true or
4186 -- false, there are no other possibilities.
4188 elsif Nkind
(Expr
) in N_Membership_Test
then
4191 -- For all other cases, we do not know the expression is valid
4196 end Expr_Known_Valid
;
4202 procedure Find_Check
4204 Check_Type
: Character;
4205 Target_Type
: Entity_Id
;
4206 Entry_OK
: out Boolean;
4207 Check_Num
: out Nat
;
4208 Ent
: out Entity_Id
;
4211 function Within_Range_Of
4212 (Target_Type
: Entity_Id
;
4213 Check_Type
: Entity_Id
) return Boolean;
4214 -- Given a requirement for checking a range against Target_Type, and
4215 -- and a range Check_Type against which a check has already been made,
4216 -- determines if the check against check type is sufficient to ensure
4217 -- that no check against Target_Type is required.
4219 ---------------------
4220 -- Within_Range_Of --
4221 ---------------------
4223 function Within_Range_Of
4224 (Target_Type
: Entity_Id
;
4225 Check_Type
: Entity_Id
) return Boolean
4228 if Target_Type
= Check_Type
then
4233 Tlo
: constant Node_Id
:= Type_Low_Bound
(Target_Type
);
4234 Thi
: constant Node_Id
:= Type_High_Bound
(Target_Type
);
4235 Clo
: constant Node_Id
:= Type_Low_Bound
(Check_Type
);
4236 Chi
: constant Node_Id
:= Type_High_Bound
(Check_Type
);
4240 or else (Compile_Time_Known_Value
(Tlo
)
4242 Compile_Time_Known_Value
(Clo
)
4244 Expr_Value
(Clo
) >= Expr_Value
(Tlo
)))
4247 or else (Compile_Time_Known_Value
(Thi
)
4249 Compile_Time_Known_Value
(Chi
)
4251 Expr_Value
(Chi
) <= Expr_Value
(Clo
)))
4259 end Within_Range_Of
;
4261 -- Start of processing for Find_Check
4264 -- Establish default, in case no entry is found
4268 -- Case of expression is simple entity reference
4270 if Is_Entity_Name
(Expr
) then
4271 Ent
:= Entity
(Expr
);
4274 -- Case of expression is entity + known constant
4276 elsif Nkind
(Expr
) = N_Op_Add
4277 and then Compile_Time_Known_Value
(Right_Opnd
(Expr
))
4278 and then Is_Entity_Name
(Left_Opnd
(Expr
))
4280 Ent
:= Entity
(Left_Opnd
(Expr
));
4281 Ofs
:= Expr_Value
(Right_Opnd
(Expr
));
4283 -- Case of expression is entity - known constant
4285 elsif Nkind
(Expr
) = N_Op_Subtract
4286 and then Compile_Time_Known_Value
(Right_Opnd
(Expr
))
4287 and then Is_Entity_Name
(Left_Opnd
(Expr
))
4289 Ent
:= Entity
(Left_Opnd
(Expr
));
4290 Ofs
:= UI_Negate
(Expr_Value
(Right_Opnd
(Expr
)));
4292 -- Any other expression is not of the right form
4301 -- Come here with expression of appropriate form, check if entity is an
4302 -- appropriate one for our purposes.
4304 if (Ekind
(Ent
) = E_Variable
4305 or else Is_Constant_Object
(Ent
))
4306 and then not Is_Library_Level_Entity
(Ent
)
4314 -- See if there is matching check already
4316 for J
in reverse 1 .. Num_Saved_Checks
loop
4318 SC
: Saved_Check
renames Saved_Checks
(J
);
4321 if SC
.Killed
= False
4322 and then SC
.Entity
= Ent
4323 and then SC
.Offset
= Ofs
4324 and then SC
.Check_Type
= Check_Type
4325 and then Within_Range_Of
(Target_Type
, SC
.Target_Type
)
4333 -- If we fall through entry was not found
4338 ---------------------------------
4339 -- Generate_Discriminant_Check --
4340 ---------------------------------
4342 -- Note: the code for this procedure is derived from the
4343 -- Emit_Discriminant_Check Routine in trans.c.
4345 procedure Generate_Discriminant_Check
(N
: Node_Id
) is
4346 Loc
: constant Source_Ptr
:= Sloc
(N
);
4347 Pref
: constant Node_Id
:= Prefix
(N
);
4348 Sel
: constant Node_Id
:= Selector_Name
(N
);
4350 Orig_Comp
: constant Entity_Id
:=
4351 Original_Record_Component
(Entity
(Sel
));
4352 -- The original component to be checked
4354 Discr_Fct
: constant Entity_Id
:=
4355 Discriminant_Checking_Func
(Orig_Comp
);
4356 -- The discriminant checking function
4359 -- One discriminant to be checked in the type
4361 Real_Discr
: Entity_Id
;
4362 -- Actual discriminant in the call
4364 Pref_Type
: Entity_Id
;
4365 -- Type of relevant prefix (ignoring private/access stuff)
4368 -- List of arguments for function call
4371 -- Keep track of the formal corresponding to the actual we build for
4372 -- each discriminant, in order to be able to perform the necessary type
4376 -- Selected component reference for checking function argument
4379 Pref_Type
:= Etype
(Pref
);
4381 -- Force evaluation of the prefix, so that it does not get evaluated
4382 -- twice (once for the check, once for the actual reference). Such a
4383 -- double evaluation is always a potential source of inefficiency,
4384 -- and is functionally incorrect in the volatile case, or when the
4385 -- prefix may have side-effects. An entity or a component of an
4386 -- entity requires no evaluation.
4388 if Is_Entity_Name
(Pref
) then
4389 if Treat_As_Volatile
(Entity
(Pref
)) then
4390 Force_Evaluation
(Pref
, Name_Req
=> True);
4393 elsif Treat_As_Volatile
(Etype
(Pref
)) then
4394 Force_Evaluation
(Pref
, Name_Req
=> True);
4396 elsif Nkind
(Pref
) = N_Selected_Component
4397 and then Is_Entity_Name
(Prefix
(Pref
))
4402 Force_Evaluation
(Pref
, Name_Req
=> True);
4405 -- For a tagged type, use the scope of the original component to
4406 -- obtain the type, because ???
4408 if Is_Tagged_Type
(Scope
(Orig_Comp
)) then
4409 Pref_Type
:= Scope
(Orig_Comp
);
4411 -- For an untagged derived type, use the discriminants of the parent
4412 -- which have been renamed in the derivation, possibly by a one-to-many
4413 -- discriminant constraint. For non-tagged type, initially get the Etype
4417 if Is_Derived_Type
(Pref_Type
)
4418 and then Number_Discriminants
(Pref_Type
) /=
4419 Number_Discriminants
(Etype
(Base_Type
(Pref_Type
)))
4421 Pref_Type
:= Etype
(Base_Type
(Pref_Type
));
4425 -- We definitely should have a checking function, This routine should
4426 -- not be called if no discriminant checking function is present.
4428 pragma Assert
(Present
(Discr_Fct
));
4430 -- Create the list of the actual parameters for the call. This list
4431 -- is the list of the discriminant fields of the record expression to
4432 -- be discriminant checked.
4435 Formal
:= First_Formal
(Discr_Fct
);
4436 Discr
:= First_Discriminant
(Pref_Type
);
4437 while Present
(Discr
) loop
4439 -- If we have a corresponding discriminant field, and a parent
4440 -- subtype is present, then we want to use the corresponding
4441 -- discriminant since this is the one with the useful value.
4443 if Present
(Corresponding_Discriminant
(Discr
))
4444 and then Ekind
(Pref_Type
) = E_Record_Type
4445 and then Present
(Parent_Subtype
(Pref_Type
))
4447 Real_Discr
:= Corresponding_Discriminant
(Discr
);
4449 Real_Discr
:= Discr
;
4452 -- Construct the reference to the discriminant
4455 Make_Selected_Component
(Loc
,
4457 Unchecked_Convert_To
(Pref_Type
,
4458 Duplicate_Subexpr
(Pref
)),
4459 Selector_Name
=> New_Occurrence_Of
(Real_Discr
, Loc
));
4461 -- Manually analyze and resolve this selected component. We really
4462 -- want it just as it appears above, and do not want the expander
4463 -- playing discriminal games etc with this reference. Then we append
4464 -- the argument to the list we are gathering.
4466 Set_Etype
(Scomp
, Etype
(Real_Discr
));
4467 Set_Analyzed
(Scomp
, True);
4468 Append_To
(Args
, Convert_To
(Etype
(Formal
), Scomp
));
4470 Next_Formal_With_Extras
(Formal
);
4471 Next_Discriminant
(Discr
);
4474 -- Now build and insert the call
4477 Make_Raise_Constraint_Error
(Loc
,
4479 Make_Function_Call
(Loc
,
4480 Name
=> New_Occurrence_Of
(Discr_Fct
, Loc
),
4481 Parameter_Associations
=> Args
),
4482 Reason
=> CE_Discriminant_Check_Failed
));
4483 end Generate_Discriminant_Check
;
4485 ---------------------------
4486 -- Generate_Index_Checks --
4487 ---------------------------
4489 procedure Generate_Index_Checks
(N
: Node_Id
) is
4490 Loc
: constant Source_Ptr
:= Sloc
(N
);
4491 A
: constant Node_Id
:= Prefix
(N
);
4497 -- Ignore call if index checks suppressed for array object or type
4499 if (Is_Entity_Name
(A
) and then Index_Checks_Suppressed
(Entity
(A
)))
4500 or else Index_Checks_Suppressed
(Etype
(A
))
4505 -- Generate the checks
4507 Sub
:= First
(Expressions
(N
));
4509 while Present
(Sub
) loop
4510 if Do_Range_Check
(Sub
) then
4511 Set_Do_Range_Check
(Sub
, False);
4513 -- Force evaluation except for the case of a simple name of a
4514 -- non-volatile entity.
4516 if not Is_Entity_Name
(Sub
)
4517 or else Treat_As_Volatile
(Entity
(Sub
))
4519 Force_Evaluation
(Sub
);
4522 -- Generate a raise of constraint error with the appropriate
4523 -- reason and a condition of the form:
4525 -- Base_Type(Sub) not in array'range (subscript)
4527 -- Note that the reason we generate the conversion to the base
4528 -- type here is that we definitely want the range check to take
4529 -- place, even if it looks like the subtype is OK. Optimization
4530 -- considerations that allow us to omit the check have already
4531 -- been taken into account in the setting of the Do_Range_Check
4537 Num
:= New_List
(Make_Integer_Literal
(Loc
, Ind
));
4541 Make_Raise_Constraint_Error
(Loc
,
4545 Convert_To
(Base_Type
(Etype
(Sub
)),
4546 Duplicate_Subexpr_Move_Checks
(Sub
)),
4548 Make_Attribute_Reference
(Loc
,
4550 Duplicate_Subexpr_Move_Checks
(A
, Name_Req
=> True),
4551 Attribute_Name
=> Name_Range
,
4552 Expressions
=> Num
)),
4553 Reason
=> CE_Index_Check_Failed
));
4559 end Generate_Index_Checks
;
4561 --------------------------
4562 -- Generate_Range_Check --
4563 --------------------------
4565 procedure Generate_Range_Check
4567 Target_Type
: Entity_Id
;
4568 Reason
: RT_Exception_Code
)
4570 Loc
: constant Source_Ptr
:= Sloc
(N
);
4571 Source_Type
: constant Entity_Id
:= Etype
(N
);
4572 Source_Base_Type
: constant Entity_Id
:= Base_Type
(Source_Type
);
4573 Target_Base_Type
: constant Entity_Id
:= Base_Type
(Target_Type
);
4576 -- First special case, if the source type is already within the range
4577 -- of the target type, then no check is needed (probably we should have
4578 -- stopped Do_Range_Check from being set in the first place, but better
4579 -- late than later in preventing junk code!
4581 -- We do NOT apply this if the source node is a literal, since in this
4582 -- case the literal has already been labeled as having the subtype of
4585 if In_Subrange_Of
(Source_Type
, Target_Type
)
4587 (Nkind
(N
) = N_Integer_Literal
4589 Nkind
(N
) = N_Real_Literal
4591 Nkind
(N
) = N_Character_Literal
4594 and then Ekind
(Entity
(N
)) = E_Enumeration_Literal
))
4599 -- We need a check, so force evaluation of the node, so that it does
4600 -- not get evaluated twice (once for the check, once for the actual
4601 -- reference). Such a double evaluation is always a potential source
4602 -- of inefficiency, and is functionally incorrect in the volatile case.
4604 if not Is_Entity_Name
(N
)
4605 or else Treat_As_Volatile
(Entity
(N
))
4607 Force_Evaluation
(N
);
4610 -- The easiest case is when Source_Base_Type and Target_Base_Type are
4611 -- the same since in this case we can simply do a direct check of the
4612 -- value of N against the bounds of Target_Type.
4614 -- [constraint_error when N not in Target_Type]
4616 -- Note: this is by far the most common case, for example all cases of
4617 -- checks on the RHS of assignments are in this category, but not all
4618 -- cases are like this. Notably conversions can involve two types.
4620 if Source_Base_Type
= Target_Base_Type
then
4622 Make_Raise_Constraint_Error
(Loc
,
4625 Left_Opnd
=> Duplicate_Subexpr
(N
),
4626 Right_Opnd
=> New_Occurrence_Of
(Target_Type
, Loc
)),
4629 -- Next test for the case where the target type is within the bounds
4630 -- of the base type of the source type, since in this case we can
4631 -- simply convert these bounds to the base type of T to do the test.
4633 -- [constraint_error when N not in
4634 -- Source_Base_Type (Target_Type'First)
4636 -- Source_Base_Type(Target_Type'Last))]
4638 -- The conversions will always work and need no check
4640 -- Unchecked_Convert_To is used instead of Convert_To to handle the case
4641 -- of converting from an enumeration value to an integer type, such as
4642 -- occurs for the case of generating a range check on Enum'Val(Exp)
4643 -- (which used to be handled by gigi). This is OK, since the conversion
4644 -- itself does not require a check.
4646 elsif In_Subrange_Of
(Target_Type
, Source_Base_Type
) then
4648 Make_Raise_Constraint_Error
(Loc
,
4651 Left_Opnd
=> Duplicate_Subexpr
(N
),
4656 Unchecked_Convert_To
(Source_Base_Type
,
4657 Make_Attribute_Reference
(Loc
,
4659 New_Occurrence_Of
(Target_Type
, Loc
),
4660 Attribute_Name
=> Name_First
)),
4663 Unchecked_Convert_To
(Source_Base_Type
,
4664 Make_Attribute_Reference
(Loc
,
4666 New_Occurrence_Of
(Target_Type
, Loc
),
4667 Attribute_Name
=> Name_Last
)))),
4670 -- Note that at this stage we now that the Target_Base_Type is not in
4671 -- the range of the Source_Base_Type (since even the Target_Type itself
4672 -- is not in this range). It could still be the case that Source_Type is
4673 -- in range of the target base type since we have not checked that case.
4675 -- If that is the case, we can freely convert the source to the target,
4676 -- and then test the target result against the bounds.
4678 elsif In_Subrange_Of
(Source_Type
, Target_Base_Type
) then
4680 -- We make a temporary to hold the value of the converted value
4681 -- (converted to the base type), and then we will do the test against
4684 -- Tnn : constant Target_Base_Type := Target_Base_Type (N);
4685 -- [constraint_error when Tnn not in Target_Type]
4687 -- Then the conversion itself is replaced by an occurrence of Tnn
4690 Tnn
: constant Entity_Id
:=
4691 Make_Defining_Identifier
(Loc
,
4692 Chars
=> New_Internal_Name
('T'));
4695 Insert_Actions
(N
, New_List
(
4696 Make_Object_Declaration
(Loc
,
4697 Defining_Identifier
=> Tnn
,
4698 Object_Definition
=>
4699 New_Occurrence_Of
(Target_Base_Type
, Loc
),
4700 Constant_Present
=> True,
4702 Make_Type_Conversion
(Loc
,
4703 Subtype_Mark
=> New_Occurrence_Of
(Target_Base_Type
, Loc
),
4704 Expression
=> Duplicate_Subexpr
(N
))),
4706 Make_Raise_Constraint_Error
(Loc
,
4709 Left_Opnd
=> New_Occurrence_Of
(Tnn
, Loc
),
4710 Right_Opnd
=> New_Occurrence_Of
(Target_Type
, Loc
)),
4712 Reason
=> Reason
)));
4714 Rewrite
(N
, New_Occurrence_Of
(Tnn
, Loc
));
4716 -- Set the type of N, because the declaration for Tnn might not
4717 -- be analyzed yet, as is the case if N appears within a record
4718 -- declaration, as a discriminant constraint or expression.
4720 Set_Etype
(N
, Target_Base_Type
);
4723 -- At this stage, we know that we have two scalar types, which are
4724 -- directly convertible, and where neither scalar type has a base
4725 -- range that is in the range of the other scalar type.
4727 -- The only way this can happen is with a signed and unsigned type.
4728 -- So test for these two cases:
4731 -- Case of the source is unsigned and the target is signed
4733 if Is_Unsigned_Type
(Source_Base_Type
)
4734 and then not Is_Unsigned_Type
(Target_Base_Type
)
4736 -- If the source is unsigned and the target is signed, then we
4737 -- know that the source is not shorter than the target (otherwise
4738 -- the source base type would be in the target base type range).
4740 -- In other words, the unsigned type is either the same size as
4741 -- the target, or it is larger. It cannot be smaller.
4744 (Esize
(Source_Base_Type
) >= Esize
(Target_Base_Type
));
4746 -- We only need to check the low bound if the low bound of the
4747 -- target type is non-negative. If the low bound of the target
4748 -- type is negative, then we know that we will fit fine.
4750 -- If the high bound of the target type is negative, then we
4751 -- know we have a constraint error, since we can't possibly
4752 -- have a negative source.
4754 -- With these two checks out of the way, we can do the check
4755 -- using the source type safely
4757 -- This is definitely the most annoying case!
4759 -- [constraint_error
4760 -- when (Target_Type'First >= 0
4762 -- N < Source_Base_Type (Target_Type'First))
4763 -- or else Target_Type'Last < 0
4764 -- or else N > Source_Base_Type (Target_Type'Last)];
4766 -- We turn off all checks since we know that the conversions
4767 -- will work fine, given the guards for negative values.
4770 Make_Raise_Constraint_Error
(Loc
,
4776 Left_Opnd
=> Make_Op_Ge
(Loc
,
4778 Make_Attribute_Reference
(Loc
,
4780 New_Occurrence_Of
(Target_Type
, Loc
),
4781 Attribute_Name
=> Name_First
),
4782 Right_Opnd
=> Make_Integer_Literal
(Loc
, Uint_0
)),
4786 Left_Opnd
=> Duplicate_Subexpr
(N
),
4788 Convert_To
(Source_Base_Type
,
4789 Make_Attribute_Reference
(Loc
,
4791 New_Occurrence_Of
(Target_Type
, Loc
),
4792 Attribute_Name
=> Name_First
)))),
4797 Make_Attribute_Reference
(Loc
,
4798 Prefix
=> New_Occurrence_Of
(Target_Type
, Loc
),
4799 Attribute_Name
=> Name_Last
),
4800 Right_Opnd
=> Make_Integer_Literal
(Loc
, Uint_0
))),
4804 Left_Opnd
=> Duplicate_Subexpr
(N
),
4806 Convert_To
(Source_Base_Type
,
4807 Make_Attribute_Reference
(Loc
,
4808 Prefix
=> New_Occurrence_Of
(Target_Type
, Loc
),
4809 Attribute_Name
=> Name_Last
)))),
4812 Suppress
=> All_Checks
);
4814 -- Only remaining possibility is that the source is signed and
4815 -- the target is unsigned.
4818 pragma Assert
(not Is_Unsigned_Type
(Source_Base_Type
)
4819 and then Is_Unsigned_Type
(Target_Base_Type
));
4821 -- If the source is signed and the target is unsigned, then we
4822 -- know that the target is not shorter than the source (otherwise
4823 -- the target base type would be in the source base type range).
4825 -- In other words, the unsigned type is either the same size as
4826 -- the target, or it is larger. It cannot be smaller.
4828 -- Clearly we have an error if the source value is negative since
4829 -- no unsigned type can have negative values. If the source type
4830 -- is non-negative, then the check can be done using the target
4833 -- Tnn : constant Target_Base_Type (N) := Target_Type;
4835 -- [constraint_error
4836 -- when N < 0 or else Tnn not in Target_Type];
4838 -- We turn off all checks for the conversion of N to the target
4839 -- base type, since we generate the explicit check to ensure that
4840 -- the value is non-negative
4843 Tnn
: constant Entity_Id
:=
4844 Make_Defining_Identifier
(Loc
,
4845 Chars
=> New_Internal_Name
('T'));
4848 Insert_Actions
(N
, New_List
(
4849 Make_Object_Declaration
(Loc
,
4850 Defining_Identifier
=> Tnn
,
4851 Object_Definition
=>
4852 New_Occurrence_Of
(Target_Base_Type
, Loc
),
4853 Constant_Present
=> True,
4855 Make_Unchecked_Type_Conversion
(Loc
,
4857 New_Occurrence_Of
(Target_Base_Type
, Loc
),
4858 Expression
=> Duplicate_Subexpr
(N
))),
4860 Make_Raise_Constraint_Error
(Loc
,
4865 Left_Opnd
=> Duplicate_Subexpr
(N
),
4866 Right_Opnd
=> Make_Integer_Literal
(Loc
, Uint_0
)),
4870 Left_Opnd
=> New_Occurrence_Of
(Tnn
, Loc
),
4872 New_Occurrence_Of
(Target_Type
, Loc
))),
4875 Suppress
=> All_Checks
);
4877 -- Set the Etype explicitly, because Insert_Actions may have
4878 -- placed the declaration in the freeze list for an enclosing
4879 -- construct, and thus it is not analyzed yet.
4881 Set_Etype
(Tnn
, Target_Base_Type
);
4882 Rewrite
(N
, New_Occurrence_Of
(Tnn
, Loc
));
4886 end Generate_Range_Check
;
4892 function Get_Check_Id
(N
: Name_Id
) return Check_Id
is
4894 -- For standard check name, we can do a direct computation
4896 if N
in First_Check_Name
.. Last_Check_Name
then
4897 return Check_Id
(N
- (First_Check_Name
- 1));
4899 -- For non-standard names added by pragma Check_Name, search table
4902 for J
in All_Checks
+ 1 .. Check_Names
.Last
loop
4903 if Check_Names
.Table
(J
) = N
then
4909 -- No matching name found
4914 ---------------------
4915 -- Get_Discriminal --
4916 ---------------------
4918 function Get_Discriminal
(E
: Entity_Id
; Bound
: Node_Id
) return Node_Id
is
4919 Loc
: constant Source_Ptr
:= Sloc
(E
);
4924 -- The bound can be a bona fide parameter of a protected operation,
4925 -- rather than a prival encoded as an in-parameter.
4927 if No
(Discriminal_Link
(Entity
(Bound
))) then
4931 -- Climb the scope stack looking for an enclosing protected type. If
4932 -- we run out of scopes, return the bound itself.
4935 while Present
(Sc
) loop
4936 if Sc
= Standard_Standard
then
4939 elsif Ekind
(Sc
) = E_Protected_Type
then
4946 D
:= First_Discriminant
(Sc
);
4947 while Present
(D
) loop
4948 if Chars
(D
) = Chars
(Bound
) then
4949 return New_Occurrence_Of
(Discriminal
(D
), Loc
);
4952 Next_Discriminant
(D
);
4956 end Get_Discriminal
;
4958 ----------------------
4959 -- Get_Range_Checks --
4960 ----------------------
4962 function Get_Range_Checks
4964 Target_Typ
: Entity_Id
;
4965 Source_Typ
: Entity_Id
:= Empty
;
4966 Warn_Node
: Node_Id
:= Empty
) return Check_Result
4969 return Selected_Range_Checks
4970 (Ck_Node
, Target_Typ
, Source_Typ
, Warn_Node
);
4971 end Get_Range_Checks
;
4977 function Guard_Access
4980 Ck_Node
: Node_Id
) return Node_Id
4983 if Nkind
(Cond
) = N_Or_Else
then
4984 Set_Paren_Count
(Cond
, 1);
4987 if Nkind
(Ck_Node
) = N_Allocator
then
4994 Left_Opnd
=> Duplicate_Subexpr_No_Checks
(Ck_Node
),
4995 Right_Opnd
=> Make_Null
(Loc
)),
4996 Right_Opnd
=> Cond
);
5000 -----------------------------
5001 -- Index_Checks_Suppressed --
5002 -----------------------------
5004 function Index_Checks_Suppressed
(E
: Entity_Id
) return Boolean is
5006 if Present
(E
) and then Checks_May_Be_Suppressed
(E
) then
5007 return Is_Check_Suppressed
(E
, Index_Check
);
5009 return Scope_Suppress
(Index_Check
);
5011 end Index_Checks_Suppressed
;
5017 procedure Initialize
is
5019 for J
in Determine_Range_Cache_N
'Range loop
5020 Determine_Range_Cache_N
(J
) := Empty
;
5025 for J
in Int
range 1 .. All_Checks
loop
5026 Check_Names
.Append
(Name_Id
(Int
(First_Check_Name
) + J
- 1));
5030 -------------------------
5031 -- Insert_Range_Checks --
5032 -------------------------
5034 procedure Insert_Range_Checks
5035 (Checks
: Check_Result
;
5037 Suppress_Typ
: Entity_Id
;
5038 Static_Sloc
: Source_Ptr
:= No_Location
;
5039 Flag_Node
: Node_Id
:= Empty
;
5040 Do_Before
: Boolean := False)
5042 Internal_Flag_Node
: Node_Id
:= Flag_Node
;
5043 Internal_Static_Sloc
: Source_Ptr
:= Static_Sloc
;
5045 Check_Node
: Node_Id
;
5046 Checks_On
: constant Boolean :=
5047 (not Index_Checks_Suppressed
(Suppress_Typ
))
5049 (not Range_Checks_Suppressed
(Suppress_Typ
));
5052 -- For now we just return if Checks_On is false, however this should be
5053 -- enhanced to check for an always True value in the condition and to
5054 -- generate a compilation warning???
5056 if not Expander_Active
or else not Checks_On
then
5060 if Static_Sloc
= No_Location
then
5061 Internal_Static_Sloc
:= Sloc
(Node
);
5064 if No
(Flag_Node
) then
5065 Internal_Flag_Node
:= Node
;
5068 for J
in 1 .. 2 loop
5069 exit when No
(Checks
(J
));
5071 if Nkind
(Checks
(J
)) = N_Raise_Constraint_Error
5072 and then Present
(Condition
(Checks
(J
)))
5074 if not Has_Dynamic_Range_Check
(Internal_Flag_Node
) then
5075 Check_Node
:= Checks
(J
);
5076 Mark_Rewrite_Insertion
(Check_Node
);
5079 Insert_Before_And_Analyze
(Node
, Check_Node
);
5081 Insert_After_And_Analyze
(Node
, Check_Node
);
5084 Set_Has_Dynamic_Range_Check
(Internal_Flag_Node
);
5089 Make_Raise_Constraint_Error
(Internal_Static_Sloc
,
5090 Reason
=> CE_Range_Check_Failed
);
5091 Mark_Rewrite_Insertion
(Check_Node
);
5094 Insert_Before_And_Analyze
(Node
, Check_Node
);
5096 Insert_After_And_Analyze
(Node
, Check_Node
);
5100 end Insert_Range_Checks
;
5102 ------------------------
5103 -- Insert_Valid_Check --
5104 ------------------------
5106 procedure Insert_Valid_Check
(Expr
: Node_Id
) is
5107 Loc
: constant Source_Ptr
:= Sloc
(Expr
);
5111 -- Do not insert if checks off, or if not checking validity or
5112 -- if expression is known to be valid
5114 if not Validity_Checks_On
5115 or else Range_Or_Validity_Checks_Suppressed
(Expr
)
5116 or else Expr_Known_Valid
(Expr
)
5121 -- If we have a checked conversion, then validity check applies to
5122 -- the expression inside the conversion, not the result, since if
5123 -- the expression inside is valid, then so is the conversion result.
5126 while Nkind
(Exp
) = N_Type_Conversion
loop
5127 Exp
:= Expression
(Exp
);
5130 -- We are about to insert the validity check for Exp. We save and
5131 -- reset the Do_Range_Check flag over this validity check, and then
5132 -- put it back for the final original reference (Exp may be rewritten).
5135 DRC
: constant Boolean := Do_Range_Check
(Exp
);
5138 Set_Do_Range_Check
(Exp
, False);
5140 -- Force evaluation to avoid multiple reads for atomic/volatile
5142 if Is_Entity_Name
(Exp
)
5143 and then Is_Volatile
(Entity
(Exp
))
5145 Force_Evaluation
(Exp
, Name_Req
=> True);
5148 -- Insert the validity check. Note that we do this with validity
5149 -- checks turned off, to avoid recursion, we do not want validity
5150 -- checks on the validity checking code itself!
5154 Make_Raise_Constraint_Error
(Loc
,
5158 Make_Attribute_Reference
(Loc
,
5160 Duplicate_Subexpr_No_Checks
(Exp
, Name_Req
=> True),
5161 Attribute_Name
=> Name_Valid
)),
5162 Reason
=> CE_Invalid_Data
),
5163 Suppress
=> Validity_Check
);
5165 -- If the expression is a a reference to an element of a bit-packed
5166 -- array, then it is rewritten as a renaming declaration. If the
5167 -- expression is an actual in a call, it has not been expanded,
5168 -- waiting for the proper point at which to do it. The same happens
5169 -- with renamings, so that we have to force the expansion now. This
5170 -- non-local complication is due to code in exp_ch2,adb, exp_ch4.adb
5173 if Is_Entity_Name
(Exp
)
5174 and then Nkind
(Parent
(Entity
(Exp
))) =
5175 N_Object_Renaming_Declaration
5178 Old_Exp
: constant Node_Id
:= Name
(Parent
(Entity
(Exp
)));
5180 if Nkind
(Old_Exp
) = N_Indexed_Component
5181 and then Is_Bit_Packed_Array
(Etype
(Prefix
(Old_Exp
)))
5183 Expand_Packed_Element_Reference
(Old_Exp
);
5188 -- Put back the Do_Range_Check flag on the resulting (possibly
5189 -- rewritten) expression.
5191 -- Note: it might be thought that a validity check is not required
5192 -- when a range check is present, but that's not the case, because
5193 -- the back end is allowed to assume for the range check that the
5194 -- operand is within its declared range (an assumption that validity
5195 -- checking is all about NOT assuming!)
5197 -- Note: no need to worry about Possible_Local_Raise here, it will
5198 -- already have been called if original node has Do_Range_Check set.
5200 Set_Do_Range_Check
(Exp
, DRC
);
5202 end Insert_Valid_Check
;
5204 ----------------------------------
5205 -- Install_Null_Excluding_Check --
5206 ----------------------------------
5208 procedure Install_Null_Excluding_Check
(N
: Node_Id
) is
5209 Loc
: constant Source_Ptr
:= Sloc
(N
);
5210 Typ
: constant Entity_Id
:= Etype
(N
);
5212 function Safe_To_Capture_In_Parameter_Value
return Boolean;
5213 -- Determines if it is safe to capture Known_Non_Null status for an
5214 -- the entity referenced by node N. The caller ensures that N is indeed
5215 -- an entity name. It is safe to capture the non-null status for an IN
5216 -- parameter when the reference occurs within a declaration that is sure
5217 -- to be executed as part of the declarative region.
5219 procedure Mark_Non_Null
;
5220 -- After installation of check, if the node in question is an entity
5221 -- name, then mark this entity as non-null if possible.
5223 function Safe_To_Capture_In_Parameter_Value
return Boolean is
5224 E
: constant Entity_Id
:= Entity
(N
);
5225 S
: constant Entity_Id
:= Current_Scope
;
5229 if Ekind
(E
) /= E_In_Parameter
then
5233 -- Two initial context checks. We must be inside a subprogram body
5234 -- with declarations and reference must not appear in nested scopes.
5236 if (Ekind
(S
) /= E_Function
and then Ekind
(S
) /= E_Procedure
)
5237 or else Scope
(E
) /= S
5242 S_Par
:= Parent
(Parent
(S
));
5244 if Nkind
(S_Par
) /= N_Subprogram_Body
5245 or else No
(Declarations
(S_Par
))
5255 -- Retrieve the declaration node of N (if any). Note that N
5256 -- may be a part of a complex initialization expression.
5260 while Present
(P
) loop
5262 -- If we have a short circuit form, and we are within the right
5263 -- hand expression, we return false, since the right hand side
5264 -- is not guaranteed to be elaborated.
5266 if Nkind
(P
) in N_Short_Circuit
5267 and then N
= Right_Opnd
(P
)
5272 -- Similarly, if we are in a conditional expression and not
5273 -- part of the condition, then we return False, since neither
5274 -- the THEN or ELSE expressions will always be elaborated.
5276 if Nkind
(P
) = N_Conditional_Expression
5277 and then N
/= First
(Expressions
(P
))
5282 -- While traversing the parent chain, we find that N
5283 -- belongs to a statement, thus it may never appear in
5284 -- a declarative region.
5286 if Nkind
(P
) in N_Statement_Other_Than_Procedure_Call
5287 or else Nkind
(P
) = N_Procedure_Call_Statement
5292 -- If we are at a declaration, record it and exit
5294 if Nkind
(P
) in N_Declaration
5295 and then Nkind
(P
) not in N_Subprogram_Specification
5308 return List_Containing
(N_Decl
) = Declarations
(S_Par
);
5310 end Safe_To_Capture_In_Parameter_Value
;
5316 procedure Mark_Non_Null
is
5318 -- Only case of interest is if node N is an entity name
5320 if Is_Entity_Name
(N
) then
5322 -- For sure, we want to clear an indication that this is known to
5323 -- be null, since if we get past this check, it definitely is not!
5325 Set_Is_Known_Null
(Entity
(N
), False);
5327 -- We can mark the entity as known to be non-null if either it is
5328 -- safe to capture the value, or in the case of an IN parameter,
5329 -- which is a constant, if the check we just installed is in the
5330 -- declarative region of the subprogram body. In this latter case,
5331 -- a check is decisive for the rest of the body if the expression
5332 -- is sure to be elaborated, since we know we have to elaborate
5333 -- all declarations before executing the body.
5335 -- Couldn't this always be part of Safe_To_Capture_Value ???
5337 if Safe_To_Capture_Value
(N
, Entity
(N
))
5338 or else Safe_To_Capture_In_Parameter_Value
5340 Set_Is_Known_Non_Null
(Entity
(N
));
5345 -- Start of processing for Install_Null_Excluding_Check
5348 pragma Assert
(Is_Access_Type
(Typ
));
5350 -- No check inside a generic (why not???)
5352 if Inside_A_Generic
then
5356 -- No check needed if known to be non-null
5358 if Known_Non_Null
(N
) then
5362 -- If known to be null, here is where we generate a compile time check
5364 if Known_Null
(N
) then
5366 -- Avoid generating warning message inside init procs
5368 if not Inside_Init_Proc
then
5369 Apply_Compile_Time_Constraint_Error
5371 "null value not allowed here?",
5372 CE_Access_Check_Failed
);
5375 Make_Raise_Constraint_Error
(Loc
,
5376 Reason
=> CE_Access_Check_Failed
));
5383 -- If entity is never assigned, for sure a warning is appropriate
5385 if Is_Entity_Name
(N
) then
5386 Check_Unset_Reference
(N
);
5389 -- No check needed if checks are suppressed on the range. Note that we
5390 -- don't set Is_Known_Non_Null in this case (we could legitimately do
5391 -- so, since the program is erroneous, but we don't like to casually
5392 -- propagate such conclusions from erroneosity).
5394 if Access_Checks_Suppressed
(Typ
) then
5398 -- No check needed for access to concurrent record types generated by
5399 -- the expander. This is not just an optimization (though it does indeed
5400 -- remove junk checks). It also avoids generation of junk warnings.
5402 if Nkind
(N
) in N_Has_Chars
5403 and then Chars
(N
) = Name_uObject
5404 and then Is_Concurrent_Record_Type
5405 (Directly_Designated_Type
(Etype
(N
)))
5410 -- Otherwise install access check
5413 Make_Raise_Constraint_Error
(Loc
,
5416 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(N
),
5417 Right_Opnd
=> Make_Null
(Loc
)),
5418 Reason
=> CE_Access_Check_Failed
));
5421 end Install_Null_Excluding_Check
;
5423 --------------------------
5424 -- Install_Static_Check --
5425 --------------------------
5427 procedure Install_Static_Check
(R_Cno
: Node_Id
; Loc
: Source_Ptr
) is
5428 Stat
: constant Boolean := Is_Static_Expression
(R_Cno
);
5429 Typ
: constant Entity_Id
:= Etype
(R_Cno
);
5433 Make_Raise_Constraint_Error
(Loc
,
5434 Reason
=> CE_Range_Check_Failed
));
5435 Set_Analyzed
(R_Cno
);
5436 Set_Etype
(R_Cno
, Typ
);
5437 Set_Raises_Constraint_Error
(R_Cno
);
5438 Set_Is_Static_Expression
(R_Cno
, Stat
);
5440 -- Now deal with possible local raise handling
5442 Possible_Local_Raise
(R_Cno
, Standard_Constraint_Error
);
5443 end Install_Static_Check
;
5445 ---------------------
5446 -- Kill_All_Checks --
5447 ---------------------
5449 procedure Kill_All_Checks
is
5451 if Debug_Flag_CC
then
5452 w
("Kill_All_Checks");
5455 -- We reset the number of saved checks to zero, and also modify all
5456 -- stack entries for statement ranges to indicate that the number of
5457 -- checks at each level is now zero.
5459 Num_Saved_Checks
:= 0;
5461 -- Note: the Int'Min here avoids any possibility of J being out of
5462 -- range when called from e.g. Conditional_Statements_Begin.
5464 for J
in 1 .. Int
'Min (Saved_Checks_TOS
, Saved_Checks_Stack
'Last) loop
5465 Saved_Checks_Stack
(J
) := 0;
5467 end Kill_All_Checks
;
5473 procedure Kill_Checks
(V
: Entity_Id
) is
5475 if Debug_Flag_CC
then
5476 w
("Kill_Checks for entity", Int
(V
));
5479 for J
in 1 .. Num_Saved_Checks
loop
5480 if Saved_Checks
(J
).Entity
= V
then
5481 if Debug_Flag_CC
then
5482 w
(" Checks killed for saved check ", J
);
5485 Saved_Checks
(J
).Killed
:= True;
5490 ------------------------------
5491 -- Length_Checks_Suppressed --
5492 ------------------------------
5494 function Length_Checks_Suppressed
(E
: Entity_Id
) return Boolean is
5496 if Present
(E
) and then Checks_May_Be_Suppressed
(E
) then
5497 return Is_Check_Suppressed
(E
, Length_Check
);
5499 return Scope_Suppress
(Length_Check
);
5501 end Length_Checks_Suppressed
;
5503 --------------------------------
5504 -- Overflow_Checks_Suppressed --
5505 --------------------------------
5507 function Overflow_Checks_Suppressed
(E
: Entity_Id
) return Boolean is
5509 if Present
(E
) and then Checks_May_Be_Suppressed
(E
) then
5510 return Is_Check_Suppressed
(E
, Overflow_Check
);
5512 return Scope_Suppress
(Overflow_Check
);
5514 end Overflow_Checks_Suppressed
;
5516 -----------------------------
5517 -- Range_Checks_Suppressed --
5518 -----------------------------
5520 function Range_Checks_Suppressed
(E
: Entity_Id
) return Boolean is
5524 -- Note: for now we always suppress range checks on Vax float types,
5525 -- since Gigi does not know how to generate these checks.
5527 if Vax_Float
(E
) then
5529 elsif Kill_Range_Checks
(E
) then
5531 elsif Checks_May_Be_Suppressed
(E
) then
5532 return Is_Check_Suppressed
(E
, Range_Check
);
5536 return Scope_Suppress
(Range_Check
);
5537 end Range_Checks_Suppressed
;
5539 -----------------------------------------
5540 -- Range_Or_Validity_Checks_Suppressed --
5541 -----------------------------------------
5543 -- Note: the coding would be simpler here if we simply made appropriate
5544 -- calls to Range/Validity_Checks_Suppressed, but that would result in
5545 -- duplicated checks which we prefer to avoid.
5547 function Range_Or_Validity_Checks_Suppressed
5548 (Expr
: Node_Id
) return Boolean
5551 -- Immediate return if scope checks suppressed for either check
5553 if Scope_Suppress
(Range_Check
) or Scope_Suppress
(Validity_Check
) then
5557 -- If no expression, that's odd, decide that checks are suppressed,
5558 -- since we don't want anyone trying to do checks in this case, which
5559 -- is most likely the result of some other error.
5565 -- Expression is present, so perform suppress checks on type
5568 Typ
: constant Entity_Id
:= Etype
(Expr
);
5570 if Vax_Float
(Typ
) then
5572 elsif Checks_May_Be_Suppressed
(Typ
)
5573 and then (Is_Check_Suppressed
(Typ
, Range_Check
)
5575 Is_Check_Suppressed
(Typ
, Validity_Check
))
5581 -- If expression is an entity name, perform checks on this entity
5583 if Is_Entity_Name
(Expr
) then
5585 Ent
: constant Entity_Id
:= Entity
(Expr
);
5587 if Checks_May_Be_Suppressed
(Ent
) then
5588 return Is_Check_Suppressed
(Ent
, Range_Check
)
5589 or else Is_Check_Suppressed
(Ent
, Validity_Check
);
5594 -- If we fall through, no checks suppressed
5597 end Range_Or_Validity_Checks_Suppressed
;
5603 procedure Remove_Checks
(Expr
: Node_Id
) is
5604 function Process
(N
: Node_Id
) return Traverse_Result
;
5605 -- Process a single node during the traversal
5607 procedure Traverse
is new Traverse_Proc
(Process
);
5608 -- The traversal procedure itself
5614 function Process
(N
: Node_Id
) return Traverse_Result
is
5616 if Nkind
(N
) not in N_Subexpr
then
5620 Set_Do_Range_Check
(N
, False);
5624 Traverse
(Left_Opnd
(N
));
5627 when N_Attribute_Reference
=>
5628 Set_Do_Overflow_Check
(N
, False);
5630 when N_Function_Call
=>
5631 Set_Do_Tag_Check
(N
, False);
5634 Set_Do_Overflow_Check
(N
, False);
5638 Set_Do_Division_Check
(N
, False);
5641 Set_Do_Length_Check
(N
, False);
5644 Set_Do_Division_Check
(N
, False);
5647 Set_Do_Length_Check
(N
, False);
5650 Set_Do_Division_Check
(N
, False);
5653 Set_Do_Length_Check
(N
, False);
5660 Traverse
(Left_Opnd
(N
));
5663 when N_Selected_Component
=>
5664 Set_Do_Discriminant_Check
(N
, False);
5666 when N_Type_Conversion
=>
5667 Set_Do_Length_Check
(N
, False);
5668 Set_Do_Tag_Check
(N
, False);
5669 Set_Do_Overflow_Check
(N
, False);
5678 -- Start of processing for Remove_Checks
5684 ----------------------------
5685 -- Selected_Length_Checks --
5686 ----------------------------
5688 function Selected_Length_Checks
5690 Target_Typ
: Entity_Id
;
5691 Source_Typ
: Entity_Id
;
5692 Warn_Node
: Node_Id
) return Check_Result
5694 Loc
: constant Source_Ptr
:= Sloc
(Ck_Node
);
5697 Expr_Actual
: Node_Id
;
5699 Cond
: Node_Id
:= Empty
;
5700 Do_Access
: Boolean := False;
5701 Wnode
: Node_Id
:= Warn_Node
;
5702 Ret_Result
: Check_Result
:= (Empty
, Empty
);
5703 Num_Checks
: Natural := 0;
5705 procedure Add_Check
(N
: Node_Id
);
5706 -- Adds the action given to Ret_Result if N is non-Empty
5708 function Get_E_Length
(E
: Entity_Id
; Indx
: Nat
) return Node_Id
;
5709 function Get_N_Length
(N
: Node_Id
; Indx
: Nat
) return Node_Id
;
5710 -- Comments required ???
5712 function Same_Bounds
(L
: Node_Id
; R
: Node_Id
) return Boolean;
5713 -- True for equal literals and for nodes that denote the same constant
5714 -- entity, even if its value is not a static constant. This includes the
5715 -- case of a discriminal reference within an init proc. Removes some
5716 -- obviously superfluous checks.
5718 function Length_E_Cond
5719 (Exptyp
: Entity_Id
;
5721 Indx
: Nat
) return Node_Id
;
5722 -- Returns expression to compute:
5723 -- Typ'Length /= Exptyp'Length
5725 function Length_N_Cond
5728 Indx
: Nat
) return Node_Id
;
5729 -- Returns expression to compute:
5730 -- Typ'Length /= Expr'Length
5736 procedure Add_Check
(N
: Node_Id
) is
5740 -- For now, ignore attempt to place more than 2 checks ???
5742 if Num_Checks
= 2 then
5746 pragma Assert
(Num_Checks
<= 1);
5747 Num_Checks
:= Num_Checks
+ 1;
5748 Ret_Result
(Num_Checks
) := N
;
5756 function Get_E_Length
(E
: Entity_Id
; Indx
: Nat
) return Node_Id
is
5757 SE
: constant Entity_Id
:= Scope
(E
);
5759 E1
: Entity_Id
:= E
;
5762 if Ekind
(Scope
(E
)) = E_Record_Type
5763 and then Has_Discriminants
(Scope
(E
))
5765 N
:= Build_Discriminal_Subtype_Of_Component
(E
);
5768 Insert_Action
(Ck_Node
, N
);
5769 E1
:= Defining_Identifier
(N
);
5773 if Ekind
(E1
) = E_String_Literal_Subtype
then
5775 Make_Integer_Literal
(Loc
,
5776 Intval
=> String_Literal_Length
(E1
));
5778 elsif SE
/= Standard_Standard
5779 and then Ekind
(Scope
(SE
)) = E_Protected_Type
5780 and then Has_Discriminants
(Scope
(SE
))
5781 and then Has_Completion
(Scope
(SE
))
5782 and then not Inside_Init_Proc
5784 -- If the type whose length is needed is a private component
5785 -- constrained by a discriminant, we must expand the 'Length
5786 -- attribute into an explicit computation, using the discriminal
5787 -- of the current protected operation. This is because the actual
5788 -- type of the prival is constructed after the protected opera-
5789 -- tion has been fully expanded.
5792 Indx_Type
: Node_Id
;
5795 Do_Expand
: Boolean := False;
5798 Indx_Type
:= First_Index
(E
);
5800 for J
in 1 .. Indx
- 1 loop
5801 Next_Index
(Indx_Type
);
5804 Get_Index_Bounds
(Indx_Type
, Lo
, Hi
);
5806 if Nkind
(Lo
) = N_Identifier
5807 and then Ekind
(Entity
(Lo
)) = E_In_Parameter
5809 Lo
:= Get_Discriminal
(E
, Lo
);
5813 if Nkind
(Hi
) = N_Identifier
5814 and then Ekind
(Entity
(Hi
)) = E_In_Parameter
5816 Hi
:= Get_Discriminal
(E
, Hi
);
5821 if not Is_Entity_Name
(Lo
) then
5822 Lo
:= Duplicate_Subexpr_No_Checks
(Lo
);
5825 if not Is_Entity_Name
(Hi
) then
5826 Lo
:= Duplicate_Subexpr_No_Checks
(Hi
);
5832 Make_Op_Subtract
(Loc
,
5836 Right_Opnd
=> Make_Integer_Literal
(Loc
, 1));
5841 Make_Attribute_Reference
(Loc
,
5842 Attribute_Name
=> Name_Length
,
5844 New_Occurrence_Of
(E1
, Loc
));
5847 Set_Expressions
(N
, New_List
(
5848 Make_Integer_Literal
(Loc
, Indx
)));
5857 Make_Attribute_Reference
(Loc
,
5858 Attribute_Name
=> Name_Length
,
5860 New_Occurrence_Of
(E1
, Loc
));
5863 Set_Expressions
(N
, New_List
(
5864 Make_Integer_Literal
(Loc
, Indx
)));
5875 function Get_N_Length
(N
: Node_Id
; Indx
: Nat
) return Node_Id
is
5878 Make_Attribute_Reference
(Loc
,
5879 Attribute_Name
=> Name_Length
,
5881 Duplicate_Subexpr_No_Checks
(N
, Name_Req
=> True),
5882 Expressions
=> New_List
(
5883 Make_Integer_Literal
(Loc
, Indx
)));
5890 function Length_E_Cond
5891 (Exptyp
: Entity_Id
;
5893 Indx
: Nat
) return Node_Id
5898 Left_Opnd
=> Get_E_Length
(Typ
, Indx
),
5899 Right_Opnd
=> Get_E_Length
(Exptyp
, Indx
));
5906 function Length_N_Cond
5909 Indx
: Nat
) return Node_Id
5914 Left_Opnd
=> Get_E_Length
(Typ
, Indx
),
5915 Right_Opnd
=> Get_N_Length
(Expr
, Indx
));
5922 function Same_Bounds
(L
: Node_Id
; R
: Node_Id
) return Boolean is
5925 (Nkind
(L
) = N_Integer_Literal
5926 and then Nkind
(R
) = N_Integer_Literal
5927 and then Intval
(L
) = Intval
(R
))
5931 and then Ekind
(Entity
(L
)) = E_Constant
5932 and then ((Is_Entity_Name
(R
)
5933 and then Entity
(L
) = Entity
(R
))
5935 (Nkind
(R
) = N_Type_Conversion
5936 and then Is_Entity_Name
(Expression
(R
))
5937 and then Entity
(L
) = Entity
(Expression
(R
)))))
5941 and then Ekind
(Entity
(R
)) = E_Constant
5942 and then Nkind
(L
) = N_Type_Conversion
5943 and then Is_Entity_Name
(Expression
(L
))
5944 and then Entity
(R
) = Entity
(Expression
(L
)))
5948 and then Is_Entity_Name
(R
)
5949 and then Entity
(L
) = Entity
(R
)
5950 and then Ekind
(Entity
(L
)) = E_In_Parameter
5951 and then Inside_Init_Proc
);
5954 -- Start of processing for Selected_Length_Checks
5957 if not Expander_Active
then
5961 if Target_Typ
= Any_Type
5962 or else Target_Typ
= Any_Composite
5963 or else Raises_Constraint_Error
(Ck_Node
)
5972 T_Typ
:= Target_Typ
;
5974 if No
(Source_Typ
) then
5975 S_Typ
:= Etype
(Ck_Node
);
5977 S_Typ
:= Source_Typ
;
5980 if S_Typ
= Any_Type
or else S_Typ
= Any_Composite
then
5984 if Is_Access_Type
(T_Typ
) and then Is_Access_Type
(S_Typ
) then
5985 S_Typ
:= Designated_Type
(S_Typ
);
5986 T_Typ
:= Designated_Type
(T_Typ
);
5989 -- A simple optimization for the null case
5991 if Known_Null
(Ck_Node
) then
5996 if Is_Array_Type
(T_Typ
) and then Is_Array_Type
(S_Typ
) then
5997 if Is_Constrained
(T_Typ
) then
5999 -- The checking code to be generated will freeze the
6000 -- corresponding array type. However, we must freeze the
6001 -- type now, so that the freeze node does not appear within
6002 -- the generated condional expression, but ahead of it.
6004 Freeze_Before
(Ck_Node
, T_Typ
);
6006 Expr_Actual
:= Get_Referenced_Object
(Ck_Node
);
6007 Exptyp
:= Get_Actual_Subtype
(Ck_Node
);
6009 if Is_Access_Type
(Exptyp
) then
6010 Exptyp
:= Designated_Type
(Exptyp
);
6013 -- String_Literal case. This needs to be handled specially be-
6014 -- cause no index types are available for string literals. The
6015 -- condition is simply:
6017 -- T_Typ'Length = string-literal-length
6019 if Nkind
(Expr_Actual
) = N_String_Literal
6020 and then Ekind
(Etype
(Expr_Actual
)) = E_String_Literal_Subtype
6024 Left_Opnd
=> Get_E_Length
(T_Typ
, 1),
6026 Make_Integer_Literal
(Loc
,
6028 String_Literal_Length
(Etype
(Expr_Actual
))));
6030 -- General array case. Here we have a usable actual subtype for
6031 -- the expression, and the condition is built from the two types
6034 -- T_Typ'Length /= Exptyp'Length or else
6035 -- T_Typ'Length (2) /= Exptyp'Length (2) or else
6036 -- T_Typ'Length (3) /= Exptyp'Length (3) or else
6039 elsif Is_Constrained
(Exptyp
) then
6041 Ndims
: constant Nat
:= Number_Dimensions
(T_Typ
);
6054 -- At the library level, we need to ensure that the type of
6055 -- the object is elaborated before the check itself is
6056 -- emitted. This is only done if the object is in the
6057 -- current compilation unit, otherwise the type is frozen
6058 -- and elaborated in its unit.
6060 if Is_Itype
(Exptyp
)
6062 Ekind
(Cunit_Entity
(Current_Sem_Unit
)) = E_Package
6064 not In_Package_Body
(Cunit_Entity
(Current_Sem_Unit
))
6065 and then In_Open_Scopes
(Scope
(Exptyp
))
6067 Ref_Node
:= Make_Itype_Reference
(Sloc
(Ck_Node
));
6068 Set_Itype
(Ref_Node
, Exptyp
);
6069 Insert_Action
(Ck_Node
, Ref_Node
);
6072 L_Index
:= First_Index
(T_Typ
);
6073 R_Index
:= First_Index
(Exptyp
);
6075 for Indx
in 1 .. Ndims
loop
6076 if not (Nkind
(L_Index
) = N_Raise_Constraint_Error
6078 Nkind
(R_Index
) = N_Raise_Constraint_Error
)
6080 Get_Index_Bounds
(L_Index
, L_Low
, L_High
);
6081 Get_Index_Bounds
(R_Index
, R_Low
, R_High
);
6083 -- Deal with compile time length check. Note that we
6084 -- skip this in the access case, because the access
6085 -- value may be null, so we cannot know statically.
6088 and then Compile_Time_Known_Value
(L_Low
)
6089 and then Compile_Time_Known_Value
(L_High
)
6090 and then Compile_Time_Known_Value
(R_Low
)
6091 and then Compile_Time_Known_Value
(R_High
)
6093 if Expr_Value
(L_High
) >= Expr_Value
(L_Low
) then
6094 L_Length
:= Expr_Value
(L_High
) -
6095 Expr_Value
(L_Low
) + 1;
6097 L_Length
:= UI_From_Int
(0);
6100 if Expr_Value
(R_High
) >= Expr_Value
(R_Low
) then
6101 R_Length
:= Expr_Value
(R_High
) -
6102 Expr_Value
(R_Low
) + 1;
6104 R_Length
:= UI_From_Int
(0);
6107 if L_Length
> R_Length
then
6109 (Compile_Time_Constraint_Error
6110 (Wnode
, "too few elements for}?", T_Typ
));
6112 elsif L_Length
< R_Length
then
6114 (Compile_Time_Constraint_Error
6115 (Wnode
, "too many elements for}?", T_Typ
));
6118 -- The comparison for an individual index subtype
6119 -- is omitted if the corresponding index subtypes
6120 -- statically match, since the result is known to
6121 -- be true. Note that this test is worth while even
6122 -- though we do static evaluation, because non-static
6123 -- subtypes can statically match.
6126 Subtypes_Statically_Match
6127 (Etype
(L_Index
), Etype
(R_Index
))
6130 (Same_Bounds
(L_Low
, R_Low
)
6131 and then Same_Bounds
(L_High
, R_High
))
6134 (Cond
, Length_E_Cond
(Exptyp
, T_Typ
, Indx
));
6143 -- Handle cases where we do not get a usable actual subtype that
6144 -- is constrained. This happens for example in the function call
6145 -- and explicit dereference cases. In these cases, we have to get
6146 -- the length or range from the expression itself, making sure we
6147 -- do not evaluate it more than once.
6149 -- Here Ck_Node is the original expression, or more properly the
6150 -- result of applying Duplicate_Expr to the original tree, forcing
6151 -- the result to be a name.
6155 Ndims
: constant Nat
:= Number_Dimensions
(T_Typ
);
6158 -- Build the condition for the explicit dereference case
6160 for Indx
in 1 .. Ndims
loop
6162 (Cond
, Length_N_Cond
(Ck_Node
, T_Typ
, Indx
));
6169 -- Construct the test and insert into the tree
6171 if Present
(Cond
) then
6173 Cond
:= Guard_Access
(Cond
, Loc
, Ck_Node
);
6177 (Make_Raise_Constraint_Error
(Loc
,
6179 Reason
=> CE_Length_Check_Failed
));
6183 end Selected_Length_Checks
;
6185 ---------------------------
6186 -- Selected_Range_Checks --
6187 ---------------------------
6189 function Selected_Range_Checks
6191 Target_Typ
: Entity_Id
;
6192 Source_Typ
: Entity_Id
;
6193 Warn_Node
: Node_Id
) return Check_Result
6195 Loc
: constant Source_Ptr
:= Sloc
(Ck_Node
);
6198 Expr_Actual
: Node_Id
;
6200 Cond
: Node_Id
:= Empty
;
6201 Do_Access
: Boolean := False;
6202 Wnode
: Node_Id
:= Warn_Node
;
6203 Ret_Result
: Check_Result
:= (Empty
, Empty
);
6204 Num_Checks
: Integer := 0;
6206 procedure Add_Check
(N
: Node_Id
);
6207 -- Adds the action given to Ret_Result if N is non-Empty
6209 function Discrete_Range_Cond
6211 Typ
: Entity_Id
) return Node_Id
;
6212 -- Returns expression to compute:
6213 -- Low_Bound (Expr) < Typ'First
6215 -- High_Bound (Expr) > Typ'Last
6217 function Discrete_Expr_Cond
6219 Typ
: Entity_Id
) return Node_Id
;
6220 -- Returns expression to compute:
6225 function Get_E_First_Or_Last
6228 Nam
: Name_Id
) return Node_Id
;
6229 -- Returns expression to compute:
6230 -- E'First or E'Last
6232 function Get_N_First
(N
: Node_Id
; Indx
: Nat
) return Node_Id
;
6233 function Get_N_Last
(N
: Node_Id
; Indx
: Nat
) return Node_Id
;
6234 -- Returns expression to compute:
6235 -- N'First or N'Last using Duplicate_Subexpr_No_Checks
6237 function Range_E_Cond
6238 (Exptyp
: Entity_Id
;
6242 -- Returns expression to compute:
6243 -- Exptyp'First < Typ'First or else Exptyp'Last > Typ'Last
6245 function Range_Equal_E_Cond
6246 (Exptyp
: Entity_Id
;
6248 Indx
: Nat
) return Node_Id
;
6249 -- Returns expression to compute:
6250 -- Exptyp'First /= Typ'First or else Exptyp'Last /= Typ'Last
6252 function Range_N_Cond
6255 Indx
: Nat
) return Node_Id
;
6256 -- Return expression to compute:
6257 -- Expr'First < Typ'First or else Expr'Last > Typ'Last
6263 procedure Add_Check
(N
: Node_Id
) is
6267 -- For now, ignore attempt to place more than 2 checks ???
6269 if Num_Checks
= 2 then
6273 pragma Assert
(Num_Checks
<= 1);
6274 Num_Checks
:= Num_Checks
+ 1;
6275 Ret_Result
(Num_Checks
) := N
;
6279 -------------------------
6280 -- Discrete_Expr_Cond --
6281 -------------------------
6283 function Discrete_Expr_Cond
6285 Typ
: Entity_Id
) return Node_Id
6293 Convert_To
(Base_Type
(Typ
),
6294 Duplicate_Subexpr_No_Checks
(Expr
)),
6296 Convert_To
(Base_Type
(Typ
),
6297 Get_E_First_Or_Last
(Typ
, 0, Name_First
))),
6302 Convert_To
(Base_Type
(Typ
),
6303 Duplicate_Subexpr_No_Checks
(Expr
)),
6307 Get_E_First_Or_Last
(Typ
, 0, Name_Last
))));
6308 end Discrete_Expr_Cond
;
6310 -------------------------
6311 -- Discrete_Range_Cond --
6312 -------------------------
6314 function Discrete_Range_Cond
6316 Typ
: Entity_Id
) return Node_Id
6318 LB
: Node_Id
:= Low_Bound
(Expr
);
6319 HB
: Node_Id
:= High_Bound
(Expr
);
6321 Left_Opnd
: Node_Id
;
6322 Right_Opnd
: Node_Id
;
6325 if Nkind
(LB
) = N_Identifier
6326 and then Ekind
(Entity
(LB
)) = E_Discriminant
6328 LB
:= New_Occurrence_Of
(Discriminal
(Entity
(LB
)), Loc
);
6331 if Nkind
(HB
) = N_Identifier
6332 and then Ekind
(Entity
(HB
)) = E_Discriminant
6334 HB
:= New_Occurrence_Of
(Discriminal
(Entity
(HB
)), Loc
);
6341 (Base_Type
(Typ
), Duplicate_Subexpr_No_Checks
(LB
)),
6345 (Base_Type
(Typ
), Get_E_First_Or_Last
(Typ
, 0, Name_First
)));
6347 if Base_Type
(Typ
) = Typ
then
6350 elsif Compile_Time_Known_Value
(High_Bound
(Scalar_Range
(Typ
)))
6352 Compile_Time_Known_Value
(High_Bound
(Scalar_Range
6355 if Is_Floating_Point_Type
(Typ
) then
6356 if Expr_Value_R
(High_Bound
(Scalar_Range
(Typ
))) =
6357 Expr_Value_R
(High_Bound
(Scalar_Range
(Base_Type
(Typ
))))
6363 if Expr_Value
(High_Bound
(Scalar_Range
(Typ
))) =
6364 Expr_Value
(High_Bound
(Scalar_Range
(Base_Type
(Typ
))))
6375 (Base_Type
(Typ
), Duplicate_Subexpr_No_Checks
(HB
)),
6380 Get_E_First_Or_Last
(Typ
, 0, Name_Last
)));
6382 return Make_Or_Else
(Loc
, Left_Opnd
, Right_Opnd
);
6383 end Discrete_Range_Cond
;
6385 -------------------------
6386 -- Get_E_First_Or_Last --
6387 -------------------------
6389 function Get_E_First_Or_Last
6392 Nam
: Name_Id
) return Node_Id
6400 if Is_Array_Type
(E
) then
6401 N
:= First_Index
(E
);
6403 for J
in 2 .. Indx
loop
6408 N
:= Scalar_Range
(E
);
6411 if Nkind
(N
) = N_Subtype_Indication
then
6412 LB
:= Low_Bound
(Range_Expression
(Constraint
(N
)));
6413 HB
:= High_Bound
(Range_Expression
(Constraint
(N
)));
6415 elsif Is_Entity_Name
(N
) then
6416 LB
:= Type_Low_Bound
(Etype
(N
));
6417 HB
:= Type_High_Bound
(Etype
(N
));
6420 LB
:= Low_Bound
(N
);
6421 HB
:= High_Bound
(N
);
6424 if Nam
= Name_First
then
6430 if Nkind
(Bound
) = N_Identifier
6431 and then Ekind
(Entity
(Bound
)) = E_Discriminant
6433 -- If this is a task discriminant, and we are the body, we must
6434 -- retrieve the corresponding body discriminal. This is another
6435 -- consequence of the early creation of discriminals, and the
6436 -- need to generate constraint checks before their declarations
6437 -- are made visible.
6439 if Is_Concurrent_Record_Type
(Scope
(Entity
(Bound
))) then
6441 Tsk
: constant Entity_Id
:=
6442 Corresponding_Concurrent_Type
6443 (Scope
(Entity
(Bound
)));
6447 if In_Open_Scopes
(Tsk
)
6448 and then Has_Completion
(Tsk
)
6450 -- Find discriminant of original task, and use its
6451 -- current discriminal, which is the renaming within
6454 Disc
:= First_Discriminant
(Tsk
);
6455 while Present
(Disc
) loop
6456 if Chars
(Disc
) = Chars
(Entity
(Bound
)) then
6457 Set_Scope
(Discriminal
(Disc
), Tsk
);
6458 return New_Occurrence_Of
(Discriminal
(Disc
), Loc
);
6461 Next_Discriminant
(Disc
);
6464 -- That loop should always succeed in finding a matching
6465 -- entry and returning. Fatal error if not.
6467 raise Program_Error
;
6471 New_Occurrence_Of
(Discriminal
(Entity
(Bound
)), Loc
);
6475 return New_Occurrence_Of
(Discriminal
(Entity
(Bound
)), Loc
);
6478 elsif Nkind
(Bound
) = N_Identifier
6479 and then Ekind
(Entity
(Bound
)) = E_In_Parameter
6480 and then not Inside_Init_Proc
6482 return Get_Discriminal
(E
, Bound
);
6484 elsif Nkind
(Bound
) = N_Integer_Literal
then
6485 return Make_Integer_Literal
(Loc
, Intval
(Bound
));
6487 -- Case of a bound rewritten to an N_Raise_Constraint_Error node
6488 -- because it is an out-of-range value. Duplicate_Subexpr cannot be
6489 -- called on this node because an N_Raise_Constraint_Error is not
6490 -- side effect free, and we may not assume that we are in the proper
6491 -- context to remove side effects on it at the point of reference.
6493 elsif Nkind
(Bound
) = N_Raise_Constraint_Error
then
6494 return New_Copy_Tree
(Bound
);
6497 return Duplicate_Subexpr_No_Checks
(Bound
);
6499 end Get_E_First_Or_Last
;
6505 function Get_N_First
(N
: Node_Id
; Indx
: Nat
) return Node_Id
is
6508 Make_Attribute_Reference
(Loc
,
6509 Attribute_Name
=> Name_First
,
6511 Duplicate_Subexpr_No_Checks
(N
, Name_Req
=> True),
6512 Expressions
=> New_List
(
6513 Make_Integer_Literal
(Loc
, Indx
)));
6520 function Get_N_Last
(N
: Node_Id
; Indx
: Nat
) return Node_Id
is
6523 Make_Attribute_Reference
(Loc
,
6524 Attribute_Name
=> Name_Last
,
6526 Duplicate_Subexpr_No_Checks
(N
, Name_Req
=> True),
6527 Expressions
=> New_List
(
6528 Make_Integer_Literal
(Loc
, Indx
)));
6535 function Range_E_Cond
6536 (Exptyp
: Entity_Id
;
6538 Indx
: Nat
) return Node_Id
6545 Left_Opnd
=> Get_E_First_Or_Last
(Exptyp
, Indx
, Name_First
),
6546 Right_Opnd
=> Get_E_First_Or_Last
(Typ
, Indx
, Name_First
)),
6550 Left_Opnd
=> Get_E_First_Or_Last
(Exptyp
, Indx
, Name_Last
),
6551 Right_Opnd
=> Get_E_First_Or_Last
(Typ
, Indx
, Name_Last
)));
6554 ------------------------
6555 -- Range_Equal_E_Cond --
6556 ------------------------
6558 function Range_Equal_E_Cond
6559 (Exptyp
: Entity_Id
;
6561 Indx
: Nat
) return Node_Id
6568 Left_Opnd
=> Get_E_First_Or_Last
(Exptyp
, Indx
, Name_First
),
6569 Right_Opnd
=> Get_E_First_Or_Last
(Typ
, Indx
, Name_First
)),
6572 Left_Opnd
=> Get_E_First_Or_Last
(Exptyp
, Indx
, Name_Last
),
6573 Right_Opnd
=> Get_E_First_Or_Last
(Typ
, Indx
, Name_Last
)));
6574 end Range_Equal_E_Cond
;
6580 function Range_N_Cond
6583 Indx
: Nat
) return Node_Id
6590 Left_Opnd
=> Get_N_First
(Expr
, Indx
),
6591 Right_Opnd
=> Get_E_First_Or_Last
(Typ
, Indx
, Name_First
)),
6595 Left_Opnd
=> Get_N_Last
(Expr
, Indx
),
6596 Right_Opnd
=> Get_E_First_Or_Last
(Typ
, Indx
, Name_Last
)));
6599 -- Start of processing for Selected_Range_Checks
6602 if not Expander_Active
then
6606 if Target_Typ
= Any_Type
6607 or else Target_Typ
= Any_Composite
6608 or else Raises_Constraint_Error
(Ck_Node
)
6617 T_Typ
:= Target_Typ
;
6619 if No
(Source_Typ
) then
6620 S_Typ
:= Etype
(Ck_Node
);
6622 S_Typ
:= Source_Typ
;
6625 if S_Typ
= Any_Type
or else S_Typ
= Any_Composite
then
6629 -- The order of evaluating T_Typ before S_Typ seems to be critical
6630 -- because S_Typ can be derived from Etype (Ck_Node), if it's not passed
6631 -- in, and since Node can be an N_Range node, it might be invalid.
6632 -- Should there be an assert check somewhere for taking the Etype of
6633 -- an N_Range node ???
6635 if Is_Access_Type
(T_Typ
) and then Is_Access_Type
(S_Typ
) then
6636 S_Typ
:= Designated_Type
(S_Typ
);
6637 T_Typ
:= Designated_Type
(T_Typ
);
6640 -- A simple optimization for the null case
6642 if Known_Null
(Ck_Node
) then
6647 -- For an N_Range Node, check for a null range and then if not
6648 -- null generate a range check action.
6650 if Nkind
(Ck_Node
) = N_Range
then
6652 -- There's no point in checking a range against itself
6654 if Ck_Node
= Scalar_Range
(T_Typ
) then
6659 T_LB
: constant Node_Id
:= Type_Low_Bound
(T_Typ
);
6660 T_HB
: constant Node_Id
:= Type_High_Bound
(T_Typ
);
6661 Known_T_LB
: constant Boolean := Compile_Time_Known_Value
(T_LB
);
6662 Known_T_HB
: constant Boolean := Compile_Time_Known_Value
(T_HB
);
6664 LB
: Node_Id
:= Low_Bound
(Ck_Node
);
6665 HB
: Node_Id
:= High_Bound
(Ck_Node
);
6669 Null_Range
: Boolean;
6670 Out_Of_Range_L
: Boolean;
6671 Out_Of_Range_H
: Boolean;
6674 -- Compute what is known at compile time
6676 if Known_T_LB
and Known_T_HB
then
6677 if Compile_Time_Known_Value
(LB
) then
6680 -- There's no point in checking that a bound is within its
6681 -- own range so pretend that it is known in this case. First
6682 -- deal with low bound.
6684 elsif Ekind
(Etype
(LB
)) = E_Signed_Integer_Subtype
6685 and then Scalar_Range
(Etype
(LB
)) = Scalar_Range
(T_Typ
)
6694 -- Likewise for the high bound
6696 if Compile_Time_Known_Value
(HB
) then
6699 elsif Ekind
(Etype
(HB
)) = E_Signed_Integer_Subtype
6700 and then Scalar_Range
(Etype
(HB
)) = Scalar_Range
(T_Typ
)
6710 -- Check for case where everything is static and we can do the
6711 -- check at compile time. This is skipped if we have an access
6712 -- type, since the access value may be null.
6714 -- ??? This code can be improved since you only need to know that
6715 -- the two respective bounds (LB & T_LB or HB & T_HB) are known at
6716 -- compile time to emit pertinent messages.
6718 if Known_T_LB
and Known_T_HB
and Known_LB
and Known_HB
6721 -- Floating-point case
6723 if Is_Floating_Point_Type
(S_Typ
) then
6724 Null_Range
:= Expr_Value_R
(HB
) < Expr_Value_R
(LB
);
6726 (Expr_Value_R
(LB
) < Expr_Value_R
(T_LB
))
6728 (Expr_Value_R
(LB
) > Expr_Value_R
(T_HB
));
6731 (Expr_Value_R
(HB
) > Expr_Value_R
(T_HB
))
6733 (Expr_Value_R
(HB
) < Expr_Value_R
(T_LB
));
6735 -- Fixed or discrete type case
6738 Null_Range
:= Expr_Value
(HB
) < Expr_Value
(LB
);
6740 (Expr_Value
(LB
) < Expr_Value
(T_LB
))
6742 (Expr_Value
(LB
) > Expr_Value
(T_HB
));
6745 (Expr_Value
(HB
) > Expr_Value
(T_HB
))
6747 (Expr_Value
(HB
) < Expr_Value
(T_LB
));
6750 if not Null_Range
then
6751 if Out_Of_Range_L
then
6752 if No
(Warn_Node
) then
6754 (Compile_Time_Constraint_Error
6755 (Low_Bound
(Ck_Node
),
6756 "static value out of range of}?", T_Typ
));
6760 (Compile_Time_Constraint_Error
6762 "static range out of bounds of}?", T_Typ
));
6766 if Out_Of_Range_H
then
6767 if No
(Warn_Node
) then
6769 (Compile_Time_Constraint_Error
6770 (High_Bound
(Ck_Node
),
6771 "static value out of range of}?", T_Typ
));
6775 (Compile_Time_Constraint_Error
6777 "static range out of bounds of}?", T_Typ
));
6784 LB
: Node_Id
:= Low_Bound
(Ck_Node
);
6785 HB
: Node_Id
:= High_Bound
(Ck_Node
);
6788 -- If either bound is a discriminant and we are within the
6789 -- record declaration, it is a use of the discriminant in a
6790 -- constraint of a component, and nothing can be checked
6791 -- here. The check will be emitted within the init proc.
6792 -- Before then, the discriminal has no real meaning.
6793 -- Similarly, if the entity is a discriminal, there is no
6794 -- check to perform yet.
6796 -- The same holds within a discriminated synchronized type,
6797 -- where the discriminant may constrain a component or an
6800 if Nkind
(LB
) = N_Identifier
6801 and then Denotes_Discriminant
(LB
, True)
6803 if Current_Scope
= Scope
(Entity
(LB
))
6804 or else Is_Concurrent_Type
(Current_Scope
)
6805 or else Ekind
(Entity
(LB
)) /= E_Discriminant
6810 New_Occurrence_Of
(Discriminal
(Entity
(LB
)), Loc
);
6814 if Nkind
(HB
) = N_Identifier
6815 and then Denotes_Discriminant
(HB
, True)
6817 if Current_Scope
= Scope
(Entity
(HB
))
6818 or else Is_Concurrent_Type
(Current_Scope
)
6819 or else Ekind
(Entity
(HB
)) /= E_Discriminant
6824 New_Occurrence_Of
(Discriminal
(Entity
(HB
)), Loc
);
6828 Cond
:= Discrete_Range_Cond
(Ck_Node
, T_Typ
);
6829 Set_Paren_Count
(Cond
, 1);
6835 Left_Opnd
=> Duplicate_Subexpr_No_Checks
(HB
),
6836 Right_Opnd
=> Duplicate_Subexpr_No_Checks
(LB
)),
6837 Right_Opnd
=> Cond
);
6842 elsif Is_Scalar_Type
(S_Typ
) then
6844 -- This somewhat duplicates what Apply_Scalar_Range_Check does,
6845 -- except the above simply sets a flag in the node and lets
6846 -- gigi generate the check base on the Etype of the expression.
6847 -- Sometimes, however we want to do a dynamic check against an
6848 -- arbitrary target type, so we do that here.
6850 if Ekind
(Base_Type
(S_Typ
)) /= Ekind
(Base_Type
(T_Typ
)) then
6851 Cond
:= Discrete_Expr_Cond
(Ck_Node
, T_Typ
);
6853 -- For literals, we can tell if the constraint error will be
6854 -- raised at compile time, so we never need a dynamic check, but
6855 -- if the exception will be raised, then post the usual warning,
6856 -- and replace the literal with a raise constraint error
6857 -- expression. As usual, skip this for access types
6859 elsif Compile_Time_Known_Value
(Ck_Node
)
6860 and then not Do_Access
6863 LB
: constant Node_Id
:= Type_Low_Bound
(T_Typ
);
6864 UB
: constant Node_Id
:= Type_High_Bound
(T_Typ
);
6866 Out_Of_Range
: Boolean;
6867 Static_Bounds
: constant Boolean :=
6868 Compile_Time_Known_Value
(LB
)
6869 and Compile_Time_Known_Value
(UB
);
6872 -- Following range tests should use Sem_Eval routine ???
6874 if Static_Bounds
then
6875 if Is_Floating_Point_Type
(S_Typ
) then
6877 (Expr_Value_R
(Ck_Node
) < Expr_Value_R
(LB
))
6879 (Expr_Value_R
(Ck_Node
) > Expr_Value_R
(UB
));
6881 -- Fixed or discrete type
6885 Expr_Value
(Ck_Node
) < Expr_Value
(LB
)
6887 Expr_Value
(Ck_Node
) > Expr_Value
(UB
);
6890 -- Bounds of the type are static and the literal is out of
6891 -- range so output a warning message.
6893 if Out_Of_Range
then
6894 if No
(Warn_Node
) then
6896 (Compile_Time_Constraint_Error
6898 "static value out of range of}?", T_Typ
));
6902 (Compile_Time_Constraint_Error
6904 "static value out of range of}?", T_Typ
));
6909 Cond
:= Discrete_Expr_Cond
(Ck_Node
, T_Typ
);
6913 -- Here for the case of a non-static expression, we need a runtime
6914 -- check unless the source type range is guaranteed to be in the
6915 -- range of the target type.
6918 if not In_Subrange_Of
(S_Typ
, T_Typ
) then
6919 Cond
:= Discrete_Expr_Cond
(Ck_Node
, T_Typ
);
6924 if Is_Array_Type
(T_Typ
) and then Is_Array_Type
(S_Typ
) then
6925 if Is_Constrained
(T_Typ
) then
6927 Expr_Actual
:= Get_Referenced_Object
(Ck_Node
);
6928 Exptyp
:= Get_Actual_Subtype
(Expr_Actual
);
6930 if Is_Access_Type
(Exptyp
) then
6931 Exptyp
:= Designated_Type
(Exptyp
);
6934 -- String_Literal case. This needs to be handled specially be-
6935 -- cause no index types are available for string literals. The
6936 -- condition is simply:
6938 -- T_Typ'Length = string-literal-length
6940 if Nkind
(Expr_Actual
) = N_String_Literal
then
6943 -- General array case. Here we have a usable actual subtype for
6944 -- the expression, and the condition is built from the two types
6946 -- T_Typ'First < Exptyp'First or else
6947 -- T_Typ'Last > Exptyp'Last or else
6948 -- T_Typ'First(1) < Exptyp'First(1) or else
6949 -- T_Typ'Last(1) > Exptyp'Last(1) or else
6952 elsif Is_Constrained
(Exptyp
) then
6954 Ndims
: constant Nat
:= Number_Dimensions
(T_Typ
);
6960 L_Index
:= First_Index
(T_Typ
);
6961 R_Index
:= First_Index
(Exptyp
);
6963 for Indx
in 1 .. Ndims
loop
6964 if not (Nkind
(L_Index
) = N_Raise_Constraint_Error
6966 Nkind
(R_Index
) = N_Raise_Constraint_Error
)
6968 -- Deal with compile time length check. Note that we
6969 -- skip this in the access case, because the access
6970 -- value may be null, so we cannot know statically.
6973 Subtypes_Statically_Match
6974 (Etype
(L_Index
), Etype
(R_Index
))
6976 -- If the target type is constrained then we
6977 -- have to check for exact equality of bounds
6978 -- (required for qualified expressions).
6980 if Is_Constrained
(T_Typ
) then
6983 Range_Equal_E_Cond
(Exptyp
, T_Typ
, Indx
));
6986 (Cond
, Range_E_Cond
(Exptyp
, T_Typ
, Indx
));
6996 -- Handle cases where we do not get a usable actual subtype that
6997 -- is constrained. This happens for example in the function call
6998 -- and explicit dereference cases. In these cases, we have to get
6999 -- the length or range from the expression itself, making sure we
7000 -- do not evaluate it more than once.
7002 -- Here Ck_Node is the original expression, or more properly the
7003 -- result of applying Duplicate_Expr to the original tree,
7004 -- forcing the result to be a name.
7008 Ndims
: constant Nat
:= Number_Dimensions
(T_Typ
);
7011 -- Build the condition for the explicit dereference case
7013 for Indx
in 1 .. Ndims
loop
7015 (Cond
, Range_N_Cond
(Ck_Node
, T_Typ
, Indx
));
7021 -- For a conversion to an unconstrained array type, generate an
7022 -- Action to check that the bounds of the source value are within
7023 -- the constraints imposed by the target type (RM 4.6(38)). No
7024 -- check is needed for a conversion to an access to unconstrained
7025 -- array type, as 4.6(24.15/2) requires the designated subtypes
7026 -- of the two access types to statically match.
7028 if Nkind
(Parent
(Ck_Node
)) = N_Type_Conversion
7029 and then not Do_Access
7032 Opnd_Index
: Node_Id
;
7033 Targ_Index
: Node_Id
;
7034 Opnd_Range
: Node_Id
;
7037 Opnd_Index
:= First_Index
(Get_Actual_Subtype
(Ck_Node
));
7038 Targ_Index
:= First_Index
(T_Typ
);
7039 while Present
(Opnd_Index
) loop
7041 -- If the index is a range, use its bounds. If it is an
7042 -- entity (as will be the case if it is a named subtype
7043 -- or an itype created for a slice) retrieve its range.
7045 if Is_Entity_Name
(Opnd_Index
)
7046 and then Is_Type
(Entity
(Opnd_Index
))
7048 Opnd_Range
:= Scalar_Range
(Entity
(Opnd_Index
));
7050 Opnd_Range
:= Opnd_Index
;
7053 if Nkind
(Opnd_Range
) = N_Range
then
7055 (Low_Bound
(Opnd_Range
), Etype
(Targ_Index
),
7056 Assume_Valid
=> True)
7059 (High_Bound
(Opnd_Range
), Etype
(Targ_Index
),
7060 Assume_Valid
=> True)
7064 -- If null range, no check needed
7067 Compile_Time_Known_Value
(High_Bound
(Opnd_Range
))
7069 Compile_Time_Known_Value
(Low_Bound
(Opnd_Range
))
7071 Expr_Value
(High_Bound
(Opnd_Range
)) <
7072 Expr_Value
(Low_Bound
(Opnd_Range
))
7076 elsif Is_Out_Of_Range
7077 (Low_Bound
(Opnd_Range
), Etype
(Targ_Index
),
7078 Assume_Valid
=> True)
7081 (High_Bound
(Opnd_Range
), Etype
(Targ_Index
),
7082 Assume_Valid
=> True)
7085 (Compile_Time_Constraint_Error
7086 (Wnode
, "value out of range of}?", T_Typ
));
7092 (Opnd_Range
, Etype
(Targ_Index
)));
7096 Next_Index
(Opnd_Index
);
7097 Next_Index
(Targ_Index
);
7104 -- Construct the test and insert into the tree
7106 if Present
(Cond
) then
7108 Cond
:= Guard_Access
(Cond
, Loc
, Ck_Node
);
7112 (Make_Raise_Constraint_Error
(Loc
,
7114 Reason
=> CE_Range_Check_Failed
));
7118 end Selected_Range_Checks
;
7120 -------------------------------
7121 -- Storage_Checks_Suppressed --
7122 -------------------------------
7124 function Storage_Checks_Suppressed
(E
: Entity_Id
) return Boolean is
7126 if Present
(E
) and then Checks_May_Be_Suppressed
(E
) then
7127 return Is_Check_Suppressed
(E
, Storage_Check
);
7129 return Scope_Suppress
(Storage_Check
);
7131 end Storage_Checks_Suppressed
;
7133 ---------------------------
7134 -- Tag_Checks_Suppressed --
7135 ---------------------------
7137 function Tag_Checks_Suppressed
(E
: Entity_Id
) return Boolean is
7140 if Kill_Tag_Checks
(E
) then
7142 elsif Checks_May_Be_Suppressed
(E
) then
7143 return Is_Check_Suppressed
(E
, Tag_Check
);
7147 return Scope_Suppress
(Tag_Check
);
7148 end Tag_Checks_Suppressed
;
7150 --------------------------
7151 -- Validity_Check_Range --
7152 --------------------------
7154 procedure Validity_Check_Range
(N
: Node_Id
) is
7156 if Validity_Checks_On
and Validity_Check_Operands
then
7157 if Nkind
(N
) = N_Range
then
7158 Ensure_Valid
(Low_Bound
(N
));
7159 Ensure_Valid
(High_Bound
(N
));
7162 end Validity_Check_Range
;
7164 --------------------------------
7165 -- Validity_Checks_Suppressed --
7166 --------------------------------
7168 function Validity_Checks_Suppressed
(E
: Entity_Id
) return Boolean is
7170 if Present
(E
) and then Checks_May_Be_Suppressed
(E
) then
7171 return Is_Check_Suppressed
(E
, Validity_Check
);
7173 return Scope_Suppress
(Validity_Check
);
7175 end Validity_Checks_Suppressed
;