1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 1992-2017, 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 Casing
; use Casing
;
28 with Debug
; use Debug
;
29 with Einfo
; use Einfo
;
30 with Elists
; use Elists
;
31 with Eval_Fat
; use Eval_Fat
;
32 with Exp_Ch11
; use Exp_Ch11
;
33 with Exp_Ch2
; use Exp_Ch2
;
34 with Exp_Ch4
; use Exp_Ch4
;
35 with Exp_Pakd
; use Exp_Pakd
;
36 with Exp_Util
; use Exp_Util
;
37 with Expander
; use Expander
;
38 with Freeze
; use Freeze
;
40 with Nlists
; use Nlists
;
41 with Nmake
; use Nmake
;
43 with Output
; use Output
;
44 with Restrict
; use Restrict
;
45 with Rident
; use Rident
;
46 with Rtsfind
; use Rtsfind
;
48 with Sem_Aux
; use Sem_Aux
;
49 with Sem_Ch3
; use Sem_Ch3
;
50 with Sem_Ch8
; use Sem_Ch8
;
51 with Sem_Disp
; use Sem_Disp
;
52 with Sem_Eval
; use Sem_Eval
;
53 with Sem_Res
; use Sem_Res
;
54 with Sem_Util
; use Sem_Util
;
55 with Sem_Warn
; use Sem_Warn
;
56 with Sinfo
; use Sinfo
;
57 with Sinput
; use Sinput
;
58 with Snames
; use Snames
;
59 with Sprint
; use Sprint
;
60 with Stand
; use Stand
;
61 with Stringt
; use Stringt
;
62 with Targparm
; use Targparm
;
63 with Tbuild
; use Tbuild
;
64 with Ttypes
; use Ttypes
;
65 with Validsw
; use Validsw
;
67 package body Checks
is
69 -- General note: many of these routines are concerned with generating
70 -- checking code to make sure that constraint error is raised at runtime.
71 -- Clearly this code is only needed if the expander is active, since
72 -- otherwise we will not be generating code or going into the runtime
75 -- We therefore disconnect most of these checks if the expander is
76 -- inactive. This has the additional benefit that we do not need to
77 -- worry about the tree being messed up by previous errors (since errors
78 -- turn off expansion anyway).
80 -- There are a few exceptions to the above rule. For instance routines
81 -- such as Apply_Scalar_Range_Check that do not insert any code can be
82 -- safely called even when the Expander is inactive (but Errors_Detected
83 -- is 0). The benefit of executing this code when expansion is off, is
84 -- the ability to emit constraint error warning for static expressions
85 -- even when we are not generating code.
87 -- The above is modified in gnatprove mode to ensure that proper check
88 -- flags are always placed, even if expansion is off.
90 -------------------------------------
91 -- Suppression of Redundant Checks --
92 -------------------------------------
94 -- This unit implements a limited circuit for removal of redundant
95 -- checks. The processing is based on a tracing of simple sequential
96 -- flow. For any sequence of statements, we save expressions that are
97 -- marked to be checked, and then if the same expression appears later
98 -- with the same check, then under certain circumstances, the second
99 -- check can be suppressed.
101 -- Basically, we can suppress the check if we know for certain that
102 -- the previous expression has been elaborated (together with its
103 -- check), and we know that the exception frame is the same, and that
104 -- nothing has happened to change the result of the exception.
106 -- Let us examine each of these three conditions in turn to describe
107 -- how we ensure that this condition is met.
109 -- First, we need to know for certain that the previous expression has
110 -- been executed. This is done principally by the mechanism of calling
111 -- Conditional_Statements_Begin at the start of any statement sequence
112 -- and Conditional_Statements_End at the end. The End call causes all
113 -- checks remembered since the Begin call to be discarded. This does
114 -- miss a few cases, notably the case of a nested BEGIN-END block with
115 -- no exception handlers. But the important thing is to be conservative.
116 -- The other protection is that all checks are discarded if a label
117 -- is encountered, since then the assumption of sequential execution
118 -- is violated, and we don't know enough about the flow.
120 -- Second, we need to know that the exception frame is the same. We
121 -- do this by killing all remembered checks when we enter a new frame.
122 -- Again, that's over-conservative, but generally the cases we can help
123 -- with are pretty local anyway (like the body of a loop for example).
125 -- Third, we must be sure to forget any checks which are no longer valid.
126 -- This is done by two mechanisms, first the Kill_Checks_Variable call is
127 -- used to note any changes to local variables. We only attempt to deal
128 -- with checks involving local variables, so we do not need to worry
129 -- about global variables. Second, a call to any non-global procedure
130 -- causes us to abandon all stored checks, since such a all may affect
131 -- the values of any local variables.
133 -- The following define the data structures used to deal with remembering
134 -- checks so that redundant checks can be eliminated as described above.
136 -- Right now, the only expressions that we deal with are of the form of
137 -- simple local objects (either declared locally, or IN parameters) or
138 -- such objects plus/minus a compile time known constant. We can do
139 -- more later on if it seems worthwhile, but this catches many simple
140 -- cases in practice.
142 -- The following record type reflects a single saved check. An entry
143 -- is made in the stack of saved checks if and only if the expression
144 -- has been elaborated with the indicated checks.
146 type Saved_Check
is record
148 -- Set True if entry is killed by Kill_Checks
151 -- The entity involved in the expression that is checked
154 -- A compile time value indicating the result of adding or
155 -- subtracting a compile time value. This value is to be
156 -- added to the value of the Entity. A value of zero is
157 -- used for the case of a simple entity reference.
159 Check_Type
: Character;
160 -- This is set to 'R' for a range check (in which case Target_Type
161 -- is set to the target type for the range check) or to 'O' for an
162 -- overflow check (in which case Target_Type is set to Empty).
164 Target_Type
: Entity_Id
;
165 -- Used only if Do_Range_Check is set. Records the target type for
166 -- the check. We need this, because a check is a duplicate only if
167 -- it has the same target type (or more accurately one with a
168 -- range that is smaller or equal to the stored target type of a
172 -- The following table keeps track of saved checks. Rather than use an
173 -- extensible table, we just use a table of fixed size, and we discard
174 -- any saved checks that do not fit. That's very unlikely to happen and
175 -- this is only an optimization in any case.
177 Saved_Checks
: array (Int
range 1 .. 200) of Saved_Check
;
178 -- Array of saved checks
180 Num_Saved_Checks
: Nat
:= 0;
181 -- Number of saved checks
183 -- The following stack keeps track of statement ranges. It is treated
184 -- as a stack. When Conditional_Statements_Begin is called, an entry
185 -- is pushed onto this stack containing the value of Num_Saved_Checks
186 -- at the time of the call. Then when Conditional_Statements_End is
187 -- called, this value is popped off and used to reset Num_Saved_Checks.
189 -- Note: again, this is a fixed length stack with a size that should
190 -- always be fine. If the value of the stack pointer goes above the
191 -- limit, then we just forget all saved checks.
193 Saved_Checks_Stack
: array (Int
range 1 .. 100) of Nat
;
194 Saved_Checks_TOS
: Nat
:= 0;
196 -----------------------
197 -- Local Subprograms --
198 -----------------------
200 procedure Apply_Arithmetic_Overflow_Strict
(N
: Node_Id
);
201 -- Used to apply arithmetic overflow checks for all cases except operators
202 -- on signed arithmetic types in MINIMIZED/ELIMINATED case (for which we
203 -- call Apply_Arithmetic_Overflow_Minimized_Eliminated below). N can be a
204 -- signed integer arithmetic operator (but not an if or case expression).
205 -- It is also called for types other than signed integers.
207 procedure Apply_Arithmetic_Overflow_Minimized_Eliminated
(Op
: Node_Id
);
208 -- Used to apply arithmetic overflow checks for the case where the overflow
209 -- checking mode is MINIMIZED or ELIMINATED and we have a signed integer
210 -- arithmetic op (which includes the case of if and case expressions). Note
211 -- that Do_Overflow_Check may or may not be set for node Op. In these modes
212 -- we have work to do even if overflow checking is suppressed.
214 procedure Apply_Division_Check
219 -- N is an N_Op_Div, N_Op_Rem, or N_Op_Mod node. This routine applies
220 -- division checks as required if the Do_Division_Check flag is set.
221 -- Rlo and Rhi give the possible range of the right operand, these values
222 -- can be referenced and trusted only if ROK is set True.
224 procedure Apply_Float_Conversion_Check
226 Target_Typ
: Entity_Id
);
227 -- The checks on a conversion from a floating-point type to an integer
228 -- type are delicate. They have to be performed before conversion, they
229 -- have to raise an exception when the operand is a NaN, and rounding must
230 -- be taken into account to determine the safe bounds of the operand.
232 procedure Apply_Selected_Length_Checks
234 Target_Typ
: Entity_Id
;
235 Source_Typ
: Entity_Id
;
236 Do_Static
: Boolean);
237 -- This is the subprogram that does all the work for Apply_Length_Check
238 -- and Apply_Static_Length_Check. Expr, Target_Typ and Source_Typ are as
239 -- described for the above routines. The Do_Static flag indicates that
240 -- only a static check is to be done.
242 procedure Apply_Selected_Range_Checks
244 Target_Typ
: Entity_Id
;
245 Source_Typ
: Entity_Id
;
246 Do_Static
: Boolean);
247 -- This is the subprogram that does all the work for Apply_Range_Check.
248 -- Expr, Target_Typ and Source_Typ are as described for the above
249 -- routine. The Do_Static flag indicates that only a static check is
252 type Check_Type
is new Check_Id
range Access_Check
.. Division_Check
;
253 function Check_Needed
(Nod
: Node_Id
; Check
: Check_Type
) return Boolean;
254 -- This function is used to see if an access or division by zero check is
255 -- needed. The check is to be applied to a single variable appearing in the
256 -- source, and N is the node for the reference. If N is not of this form,
257 -- True is returned with no further processing. If N is of the right form,
258 -- then further processing determines if the given Check is needed.
260 -- The particular circuit is to see if we have the case of a check that is
261 -- not needed because it appears in the right operand of a short circuited
262 -- conditional where the left operand guards the check. For example:
264 -- if Var = 0 or else Q / Var > 12 then
268 -- In this example, the division check is not required. At the same time
269 -- we can issue warnings for suspicious use of non-short-circuited forms,
272 -- if Var = 0 or Q / Var > 12 then
278 Check_Type
: Character;
279 Target_Type
: Entity_Id
;
280 Entry_OK
: out Boolean;
284 -- This routine is used by Enable_Range_Check and Enable_Overflow_Check
285 -- to see if a check is of the form for optimization, and if so, to see
286 -- if it has already been performed. Expr is the expression to check,
287 -- and Check_Type is 'R' for a range check, 'O' for an overflow check.
288 -- Target_Type is the target type for a range check, and Empty for an
289 -- overflow check. If the entry is not of the form for optimization,
290 -- then Entry_OK is set to False, and the remaining out parameters
291 -- are undefined. If the entry is OK, then Ent/Ofs are set to the
292 -- entity and offset from the expression. Check_Num is the number of
293 -- a matching saved entry in Saved_Checks, or zero if no such entry
296 function Get_Discriminal
(E
: Entity_Id
; Bound
: Node_Id
) return Node_Id
;
297 -- If a discriminal is used in constraining a prival, Return reference
298 -- to the discriminal of the protected body (which renames the parameter
299 -- of the enclosing protected operation). This clumsy transformation is
300 -- needed because privals are created too late and their actual subtypes
301 -- are not available when analysing the bodies of the protected operations.
302 -- This function is called whenever the bound is an entity and the scope
303 -- indicates a protected operation. If the bound is an in-parameter of
304 -- a protected operation that is not a prival, the function returns the
306 -- To be cleaned up???
308 function Guard_Access
311 Ck_Node
: Node_Id
) return Node_Id
;
312 -- In the access type case, guard the test with a test to ensure
313 -- that the access value is non-null, since the checks do not
314 -- not apply to null access values.
316 procedure Install_Static_Check
(R_Cno
: Node_Id
; Loc
: Source_Ptr
);
317 -- Called by Apply_{Length,Range}_Checks to rewrite the tree with the
318 -- Constraint_Error node.
320 function Is_Signed_Integer_Arithmetic_Op
(N
: Node_Id
) return Boolean;
321 -- Returns True if node N is for an arithmetic operation with signed
322 -- integer operands. This includes unary and binary operators, and also
323 -- if and case expression nodes where the dependent expressions are of
324 -- a signed integer type. These are the kinds of nodes for which special
325 -- handling applies in MINIMIZED or ELIMINATED overflow checking mode.
327 function Range_Or_Validity_Checks_Suppressed
328 (Expr
: Node_Id
) return Boolean;
329 -- Returns True if either range or validity checks or both are suppressed
330 -- for the type of the given expression, or, if the expression is the name
331 -- of an entity, if these checks are suppressed for the entity.
333 function Selected_Length_Checks
335 Target_Typ
: Entity_Id
;
336 Source_Typ
: Entity_Id
;
337 Warn_Node
: Node_Id
) return Check_Result
;
338 -- Like Apply_Selected_Length_Checks, except it doesn't modify
339 -- anything, just returns a list of nodes as described in the spec of
340 -- this package for the Range_Check function.
341 -- ??? In fact it does construct the test and insert it into the tree,
342 -- and insert actions in various ways (calling Insert_Action directly
343 -- in particular) so we do not call it in GNATprove mode, contrary to
344 -- Selected_Range_Checks.
346 function Selected_Range_Checks
348 Target_Typ
: Entity_Id
;
349 Source_Typ
: Entity_Id
;
350 Warn_Node
: Node_Id
) return Check_Result
;
351 -- Like Apply_Selected_Range_Checks, except it doesn't modify anything,
352 -- just returns a list of nodes as described in the spec of this package
353 -- for the Range_Check function.
355 ------------------------------
356 -- Access_Checks_Suppressed --
357 ------------------------------
359 function Access_Checks_Suppressed
(E
: Entity_Id
) return Boolean is
361 if Present
(E
) and then Checks_May_Be_Suppressed
(E
) then
362 return Is_Check_Suppressed
(E
, Access_Check
);
364 return Scope_Suppress
.Suppress
(Access_Check
);
366 end Access_Checks_Suppressed
;
368 -------------------------------------
369 -- Accessibility_Checks_Suppressed --
370 -------------------------------------
372 function Accessibility_Checks_Suppressed
(E
: Entity_Id
) return Boolean is
374 if Present
(E
) and then Checks_May_Be_Suppressed
(E
) then
375 return Is_Check_Suppressed
(E
, Accessibility_Check
);
377 return Scope_Suppress
.Suppress
(Accessibility_Check
);
379 end Accessibility_Checks_Suppressed
;
381 -----------------------------
382 -- Activate_Division_Check --
383 -----------------------------
385 procedure Activate_Division_Check
(N
: Node_Id
) is
387 Set_Do_Division_Check
(N
, True);
388 Possible_Local_Raise
(N
, Standard_Constraint_Error
);
389 end Activate_Division_Check
;
391 -----------------------------
392 -- Activate_Overflow_Check --
393 -----------------------------
395 procedure Activate_Overflow_Check
(N
: Node_Id
) is
396 Typ
: constant Entity_Id
:= Etype
(N
);
399 -- Floating-point case. If Etype is not set (this can happen when we
400 -- activate a check on a node that has not yet been analyzed), then
401 -- we assume we do not have a floating-point type (as per our spec).
403 if Present
(Typ
) and then Is_Floating_Point_Type
(Typ
) then
405 -- Ignore call if we have no automatic overflow checks on the target
406 -- and Check_Float_Overflow mode is not set. These are the cases in
407 -- which we expect to generate infinities and NaN's with no check.
409 if not (Machine_Overflows_On_Target
or Check_Float_Overflow
) then
412 -- Ignore for unary operations ("+", "-", abs) since these can never
413 -- result in overflow for floating-point cases.
415 elsif Nkind
(N
) in N_Unary_Op
then
418 -- Otherwise we will set the flag
427 -- Nothing to do for Rem/Mod/Plus (overflow not possible, the check
428 -- for zero-divide is a divide check, not an overflow check).
430 if Nkind_In
(N
, N_Op_Rem
, N_Op_Mod
, N_Op_Plus
) then
435 -- Fall through for cases where we do set the flag
437 Set_Do_Overflow_Check
(N
, True);
438 Possible_Local_Raise
(N
, Standard_Constraint_Error
);
439 end Activate_Overflow_Check
;
441 --------------------------
442 -- Activate_Range_Check --
443 --------------------------
445 procedure Activate_Range_Check
(N
: Node_Id
) is
447 Set_Do_Range_Check
(N
, True);
448 Possible_Local_Raise
(N
, Standard_Constraint_Error
);
449 end Activate_Range_Check
;
451 ---------------------------------
452 -- Alignment_Checks_Suppressed --
453 ---------------------------------
455 function Alignment_Checks_Suppressed
(E
: Entity_Id
) return Boolean is
457 if Present
(E
) and then Checks_May_Be_Suppressed
(E
) then
458 return Is_Check_Suppressed
(E
, Alignment_Check
);
460 return Scope_Suppress
.Suppress
(Alignment_Check
);
462 end Alignment_Checks_Suppressed
;
464 ----------------------------------
465 -- Allocation_Checks_Suppressed --
466 ----------------------------------
468 -- Note: at the current time there are no calls to this function, because
469 -- the relevant check is in the run-time, so it is not a check that the
470 -- compiler can suppress anyway, but we still have to recognize the check
471 -- name Allocation_Check since it is part of the standard.
473 function Allocation_Checks_Suppressed
(E
: Entity_Id
) return Boolean is
475 if Present
(E
) and then Checks_May_Be_Suppressed
(E
) then
476 return Is_Check_Suppressed
(E
, Allocation_Check
);
478 return Scope_Suppress
.Suppress
(Allocation_Check
);
480 end Allocation_Checks_Suppressed
;
482 -------------------------
483 -- Append_Range_Checks --
484 -------------------------
486 procedure Append_Range_Checks
487 (Checks
: Check_Result
;
489 Suppress_Typ
: Entity_Id
;
490 Static_Sloc
: Source_Ptr
;
493 Checks_On
: constant Boolean :=
494 not Index_Checks_Suppressed
(Suppress_Typ
)
496 not Range_Checks_Suppressed
(Suppress_Typ
);
498 Internal_Flag_Node
: constant Node_Id
:= Flag_Node
;
499 Internal_Static_Sloc
: constant Source_Ptr
:= Static_Sloc
;
502 -- For now we just return if Checks_On is false, however this should be
503 -- enhanced to check for an always True value in the condition and to
504 -- generate a compilation warning???
506 if not Checks_On
then
511 exit when No
(Checks
(J
));
513 if Nkind
(Checks
(J
)) = N_Raise_Constraint_Error
514 and then Present
(Condition
(Checks
(J
)))
516 if not Has_Dynamic_Range_Check
(Internal_Flag_Node
) then
517 Append_To
(Stmts
, Checks
(J
));
518 Set_Has_Dynamic_Range_Check
(Internal_Flag_Node
);
524 Make_Raise_Constraint_Error
(Internal_Static_Sloc
,
525 Reason
=> CE_Range_Check_Failed
));
528 end Append_Range_Checks
;
530 ------------------------
531 -- Apply_Access_Check --
532 ------------------------
534 procedure Apply_Access_Check
(N
: Node_Id
) is
535 P
: constant Node_Id
:= Prefix
(N
);
538 -- We do not need checks if we are not generating code (i.e. the
539 -- expander is not active). This is not just an optimization, there
540 -- are cases (e.g. with pragma Debug) where generating the checks
541 -- can cause real trouble).
543 if not Expander_Active
then
547 -- No check if short circuiting makes check unnecessary
549 if not Check_Needed
(P
, Access_Check
) then
553 -- No check if accessing the Offset_To_Top component of a dispatch
554 -- table. They are safe by construction.
556 if Tagged_Type_Expansion
557 and then Present
(Etype
(P
))
558 and then RTU_Loaded
(Ada_Tags
)
559 and then RTE_Available
(RE_Offset_To_Top_Ptr
)
560 and then Etype
(P
) = RTE
(RE_Offset_To_Top_Ptr
)
565 -- Otherwise go ahead and install the check
567 Install_Null_Excluding_Check
(P
);
568 end Apply_Access_Check
;
570 -------------------------------
571 -- Apply_Accessibility_Check --
572 -------------------------------
574 procedure Apply_Accessibility_Check
577 Insert_Node
: Node_Id
)
579 Loc
: constant Source_Ptr
:= Sloc
(N
);
580 Param_Ent
: Entity_Id
:= Param_Entity
(N
);
581 Param_Level
: Node_Id
;
582 Type_Level
: Node_Id
;
585 if Ada_Version
>= Ada_2012
586 and then not Present
(Param_Ent
)
587 and then Is_Entity_Name
(N
)
588 and then Ekind_In
(Entity
(N
), E_Constant
, E_Variable
)
589 and then Present
(Effective_Extra_Accessibility
(Entity
(N
)))
591 Param_Ent
:= Entity
(N
);
592 while Present
(Renamed_Object
(Param_Ent
)) loop
594 -- Renamed_Object must return an Entity_Name here
595 -- because of preceding "Present (E_E_A (...))" test.
597 Param_Ent
:= Entity
(Renamed_Object
(Param_Ent
));
601 if Inside_A_Generic
then
604 -- Only apply the run-time check if the access parameter has an
605 -- associated extra access level parameter and when the level of the
606 -- type is less deep than the level of the access parameter, and
607 -- accessibility checks are not suppressed.
609 elsif Present
(Param_Ent
)
610 and then Present
(Extra_Accessibility
(Param_Ent
))
611 and then UI_Gt
(Object_Access_Level
(N
),
612 Deepest_Type_Access_Level
(Typ
))
613 and then not Accessibility_Checks_Suppressed
(Param_Ent
)
614 and then not Accessibility_Checks_Suppressed
(Typ
)
617 New_Occurrence_Of
(Extra_Accessibility
(Param_Ent
), Loc
);
620 Make_Integer_Literal
(Loc
, Deepest_Type_Access_Level
(Typ
));
622 -- Raise Program_Error if the accessibility level of the access
623 -- parameter is deeper than the level of the target access type.
625 Insert_Action
(Insert_Node
,
626 Make_Raise_Program_Error
(Loc
,
629 Left_Opnd
=> Param_Level
,
630 Right_Opnd
=> Type_Level
),
631 Reason
=> PE_Accessibility_Check_Failed
));
633 Analyze_And_Resolve
(N
);
635 end Apply_Accessibility_Check
;
637 --------------------------------
638 -- Apply_Address_Clause_Check --
639 --------------------------------
641 procedure Apply_Address_Clause_Check
(E
: Entity_Id
; N
: Node_Id
) is
642 pragma Assert
(Nkind
(N
) = N_Freeze_Entity
);
644 AC
: constant Node_Id
:= Address_Clause
(E
);
645 Loc
: constant Source_Ptr
:= Sloc
(AC
);
646 Typ
: constant Entity_Id
:= Etype
(E
);
649 -- Address expression (not necessarily the same as Aexp, for example
650 -- when Aexp is a reference to a constant, in which case Expr gets
651 -- reset to reference the value expression of the constant).
654 -- See if alignment check needed. Note that we never need a check if the
655 -- maximum alignment is one, since the check will always succeed.
657 -- Note: we do not check for checks suppressed here, since that check
658 -- was done in Sem_Ch13 when the address clause was processed. We are
659 -- only called if checks were not suppressed. The reason for this is
660 -- that we have to delay the call to Apply_Alignment_Check till freeze
661 -- time (so that all types etc are elaborated), but we have to check
662 -- the status of check suppressing at the point of the address clause.
665 or else not Check_Address_Alignment
(AC
)
666 or else Maximum_Alignment
= 1
671 -- Obtain expression from address clause
673 Expr
:= Address_Value
(Expression
(AC
));
675 -- See if we know that Expr has an acceptable value at compile time. If
676 -- it hasn't or we don't know, we defer issuing the warning until the
677 -- end of the compilation to take into account back end annotations.
679 if Compile_Time_Known_Value
(Expr
)
680 and then (Known_Alignment
(E
) or else Known_Alignment
(Typ
))
683 AL
: Uint
:= Alignment
(Typ
);
686 -- The object alignment might be more restrictive than the type
689 if Known_Alignment
(E
) then
693 if Expr_Value
(Expr
) mod AL
= 0 then
698 -- If the expression has the form X'Address, then we can find out if the
699 -- object X has an alignment that is compatible with the object E. If it
700 -- hasn't or we don't know, we defer issuing the warning until the end
701 -- of the compilation to take into account back end annotations.
703 elsif Nkind
(Expr
) = N_Attribute_Reference
704 and then Attribute_Name
(Expr
) = Name_Address
706 Has_Compatible_Alignment
(E
, Prefix
(Expr
), False) = Known_Compatible
711 -- Here we do not know if the value is acceptable. Strictly we don't
712 -- have to do anything, since if the alignment is bad, we have an
713 -- erroneous program. However we are allowed to check for erroneous
714 -- conditions and we decide to do this by default if the check is not
717 -- However, don't do the check if elaboration code is unwanted
719 if Restriction_Active
(No_Elaboration_Code
) then
722 -- Generate a check to raise PE if alignment may be inappropriate
725 -- If the original expression is a non-static constant, use the name
726 -- of the constant itself rather than duplicating its initialization
727 -- expression, which was extracted above.
729 -- Note: Expr is empty if the address-clause is applied to in-mode
730 -- actuals (allowed by 13.1(22)).
732 if not Present
(Expr
)
734 (Is_Entity_Name
(Expression
(AC
))
735 and then Ekind
(Entity
(Expression
(AC
))) = E_Constant
736 and then Nkind
(Parent
(Entity
(Expression
(AC
)))) =
737 N_Object_Declaration
)
739 Expr
:= New_Copy_Tree
(Expression
(AC
));
741 Remove_Side_Effects
(Expr
);
744 if No
(Actions
(N
)) then
745 Set_Actions
(N
, New_List
);
748 Prepend_To
(Actions
(N
),
749 Make_Raise_Program_Error
(Loc
,
756 (RTE
(RE_Integer_Address
), Expr
),
758 Make_Attribute_Reference
(Loc
,
759 Prefix
=> New_Occurrence_Of
(E
, Loc
),
760 Attribute_Name
=> Name_Alignment
)),
761 Right_Opnd
=> Make_Integer_Literal
(Loc
, Uint_0
)),
762 Reason
=> PE_Misaligned_Address_Value
));
764 Warning_Msg
:= No_Error_Msg
;
765 Analyze
(First
(Actions
(N
)), Suppress
=> All_Checks
);
767 -- If the above raise action generated a warning message (for example
768 -- from Warn_On_Non_Local_Exception mode with the active restriction
769 -- No_Exception_Propagation).
771 if Warning_Msg
/= No_Error_Msg
then
773 -- If the expression has a known at compile time value, then
774 -- once we know the alignment of the type, we can check if the
775 -- exception will be raised or not, and if not, we don't need
776 -- the warning so we will kill the warning later on.
778 if Compile_Time_Known_Value
(Expr
) then
779 Alignment_Warnings
.Append
780 ((E
=> E
, A
=> Expr_Value
(Expr
), W
=> Warning_Msg
));
782 -- Add explanation of the warning generated by the check
786 ("\address value may be incompatible with alignment of "
796 -- If we have some missing run time component in configurable run time
797 -- mode then just skip the check (it is not required in any case).
799 when RE_Not_Available
=>
801 end Apply_Address_Clause_Check
;
803 -------------------------------------
804 -- Apply_Arithmetic_Overflow_Check --
805 -------------------------------------
807 procedure Apply_Arithmetic_Overflow_Check
(N
: Node_Id
) is
809 -- Use old routine in almost all cases (the only case we are treating
810 -- specially is the case of a signed integer arithmetic op with the
811 -- overflow checking mode set to MINIMIZED or ELIMINATED).
813 if Overflow_Check_Mode
= Strict
814 or else not Is_Signed_Integer_Arithmetic_Op
(N
)
816 Apply_Arithmetic_Overflow_Strict
(N
);
818 -- Otherwise use the new routine for the case of a signed integer
819 -- arithmetic op, with Do_Overflow_Check set to True, and the checking
820 -- mode is MINIMIZED or ELIMINATED.
823 Apply_Arithmetic_Overflow_Minimized_Eliminated
(N
);
825 end Apply_Arithmetic_Overflow_Check
;
827 --------------------------------------
828 -- Apply_Arithmetic_Overflow_Strict --
829 --------------------------------------
831 -- This routine is called only if the type is an integer type and an
832 -- arithmetic overflow check may be needed for op (add, subtract, or
833 -- multiply). This check is performed if Backend_Overflow_Checks_On_Target
834 -- is not enabled and Do_Overflow_Check is set. In this case we expand the
835 -- operation into a more complex sequence of tests that ensures that
836 -- overflow is properly caught.
838 -- This is used in CHECKED modes. It is identical to the code for this
839 -- cases before the big overflow earthquake, thus ensuring that in this
840 -- modes we have compatible behavior (and reliability) to what was there
841 -- before. It is also called for types other than signed integers, and if
842 -- the Do_Overflow_Check flag is off.
844 -- Note: we also call this routine if we decide in the MINIMIZED case
845 -- to give up and just generate an overflow check without any fuss.
847 procedure Apply_Arithmetic_Overflow_Strict
(N
: Node_Id
) is
848 Loc
: constant Source_Ptr
:= Sloc
(N
);
849 Typ
: constant Entity_Id
:= Etype
(N
);
850 Rtyp
: constant Entity_Id
:= Root_Type
(Typ
);
853 -- Nothing to do if Do_Overflow_Check not set or overflow checks
856 if not Do_Overflow_Check
(N
) then
860 -- An interesting special case. If the arithmetic operation appears as
861 -- the operand of a type conversion:
865 -- and all the following conditions apply:
867 -- arithmetic operation is for a signed integer type
868 -- target type type1 is a static integer subtype
869 -- range of x and y are both included in the range of type1
870 -- range of x op y is included in the range of type1
871 -- size of type1 is at least twice the result size of op
873 -- then we don't do an overflow check in any case. Instead, we transform
874 -- the operation so that we end up with:
876 -- type1 (type1 (x) op type1 (y))
878 -- This avoids intermediate overflow before the conversion. It is
879 -- explicitly permitted by RM 3.5.4(24):
881 -- For the execution of a predefined operation of a signed integer
882 -- type, the implementation need not raise Constraint_Error if the
883 -- result is outside the base range of the type, so long as the
884 -- correct result is produced.
886 -- It's hard to imagine that any programmer counts on the exception
887 -- being raised in this case, and in any case it's wrong coding to
888 -- have this expectation, given the RM permission. Furthermore, other
889 -- Ada compilers do allow such out of range results.
891 -- Note that we do this transformation even if overflow checking is
892 -- off, since this is precisely about giving the "right" result and
893 -- avoiding the need for an overflow check.
895 -- Note: this circuit is partially redundant with respect to the similar
896 -- processing in Exp_Ch4.Expand_N_Type_Conversion, but the latter deals
897 -- with cases that do not come through here. We still need the following
898 -- processing even with the Exp_Ch4 code in place, since we want to be
899 -- sure not to generate the arithmetic overflow check in these cases
900 -- (Exp_Ch4 would have a hard time removing them once generated).
902 if Is_Signed_Integer_Type
(Typ
)
903 and then Nkind
(Parent
(N
)) = N_Type_Conversion
905 Conversion_Optimization
: declare
906 Target_Type
: constant Entity_Id
:=
907 Base_Type
(Entity
(Subtype_Mark
(Parent
(N
))));
921 if Is_Integer_Type
(Target_Type
)
922 and then RM_Size
(Root_Type
(Target_Type
)) >= 2 * RM_Size
(Rtyp
)
924 Tlo
:= Expr_Value
(Type_Low_Bound
(Target_Type
));
925 Thi
:= Expr_Value
(Type_High_Bound
(Target_Type
));
928 (Left_Opnd
(N
), LOK
, Llo
, Lhi
, Assume_Valid
=> True);
930 (Right_Opnd
(N
), ROK
, Rlo
, Rhi
, Assume_Valid
=> True);
933 and then Tlo
<= Llo
and then Lhi
<= Thi
934 and then Tlo
<= Rlo
and then Rhi
<= Thi
936 Determine_Range
(N
, VOK
, Vlo
, Vhi
, Assume_Valid
=> True);
938 if VOK
and then Tlo
<= Vlo
and then Vhi
<= Thi
then
939 Rewrite
(Left_Opnd
(N
),
940 Make_Type_Conversion
(Loc
,
941 Subtype_Mark
=> New_Occurrence_Of
(Target_Type
, Loc
),
942 Expression
=> Relocate_Node
(Left_Opnd
(N
))));
944 Rewrite
(Right_Opnd
(N
),
945 Make_Type_Conversion
(Loc
,
946 Subtype_Mark
=> New_Occurrence_Of
(Target_Type
, Loc
),
947 Expression
=> Relocate_Node
(Right_Opnd
(N
))));
949 -- Rewrite the conversion operand so that the original
950 -- node is retained, in order to avoid the warning for
951 -- redundant conversions in Resolve_Type_Conversion.
953 Rewrite
(N
, Relocate_Node
(N
));
955 Set_Etype
(N
, Target_Type
);
957 Analyze_And_Resolve
(Left_Opnd
(N
), Target_Type
);
958 Analyze_And_Resolve
(Right_Opnd
(N
), Target_Type
);
960 -- Given that the target type is twice the size of the
961 -- source type, overflow is now impossible, so we can
962 -- safely kill the overflow check and return.
964 Set_Do_Overflow_Check
(N
, False);
969 end Conversion_Optimization
;
972 -- Now see if an overflow check is required
975 Siz
: constant Int
:= UI_To_Int
(Esize
(Rtyp
));
976 Dsiz
: constant Int
:= Siz
* 2;
983 -- Skip check if back end does overflow checks, or the overflow flag
984 -- is not set anyway, or we are not doing code expansion, or the
985 -- parent node is a type conversion whose operand is an arithmetic
986 -- operation on signed integers on which the expander can promote
987 -- later the operands to type Integer (see Expand_N_Type_Conversion).
989 if Backend_Overflow_Checks_On_Target
990 or else not Do_Overflow_Check
(N
)
991 or else not Expander_Active
992 or else (Present
(Parent
(N
))
993 and then Nkind
(Parent
(N
)) = N_Type_Conversion
994 and then Integer_Promotion_Possible
(Parent
(N
)))
999 -- Otherwise, generate the full general code for front end overflow
1000 -- detection, which works by doing arithmetic in a larger type:
1006 -- Typ (Checktyp (x) op Checktyp (y));
1008 -- where Typ is the type of the original expression, and Checktyp is
1009 -- an integer type of sufficient length to hold the largest possible
1012 -- If the size of check type exceeds the size of Long_Long_Integer,
1013 -- we use a different approach, expanding to:
1015 -- typ (xxx_With_Ovflo_Check (Integer_64 (x), Integer (y)))
1017 -- where xxx is Add, Multiply or Subtract as appropriate
1019 -- Find check type if one exists
1021 if Dsiz
<= Standard_Integer_Size
then
1022 Ctyp
:= Standard_Integer
;
1024 elsif Dsiz
<= Standard_Long_Long_Integer_Size
then
1025 Ctyp
:= Standard_Long_Long_Integer
;
1027 -- No check type exists, use runtime call
1030 if Nkind
(N
) = N_Op_Add
then
1031 Cent
:= RE_Add_With_Ovflo_Check
;
1033 elsif Nkind
(N
) = N_Op_Multiply
then
1034 Cent
:= RE_Multiply_With_Ovflo_Check
;
1037 pragma Assert
(Nkind
(N
) = N_Op_Subtract
);
1038 Cent
:= RE_Subtract_With_Ovflo_Check
;
1043 Make_Function_Call
(Loc
,
1044 Name
=> New_Occurrence_Of
(RTE
(Cent
), Loc
),
1045 Parameter_Associations
=> New_List
(
1046 OK_Convert_To
(RTE
(RE_Integer_64
), Left_Opnd
(N
)),
1047 OK_Convert_To
(RTE
(RE_Integer_64
), Right_Opnd
(N
))))));
1049 Analyze_And_Resolve
(N
, Typ
);
1053 -- If we fall through, we have the case where we do the arithmetic
1054 -- in the next higher type and get the check by conversion. In these
1055 -- cases Ctyp is set to the type to be used as the check type.
1057 Opnod
:= Relocate_Node
(N
);
1059 Opnd
:= OK_Convert_To
(Ctyp
, Left_Opnd
(Opnod
));
1062 Set_Etype
(Opnd
, Ctyp
);
1063 Set_Analyzed
(Opnd
, True);
1064 Set_Left_Opnd
(Opnod
, Opnd
);
1066 Opnd
:= OK_Convert_To
(Ctyp
, Right_Opnd
(Opnod
));
1069 Set_Etype
(Opnd
, Ctyp
);
1070 Set_Analyzed
(Opnd
, True);
1071 Set_Right_Opnd
(Opnod
, Opnd
);
1073 -- The type of the operation changes to the base type of the check
1074 -- type, and we reset the overflow check indication, since clearly no
1075 -- overflow is possible now that we are using a double length type.
1076 -- We also set the Analyzed flag to avoid a recursive attempt to
1079 Set_Etype
(Opnod
, Base_Type
(Ctyp
));
1080 Set_Do_Overflow_Check
(Opnod
, False);
1081 Set_Analyzed
(Opnod
, True);
1083 -- Now build the outer conversion
1085 Opnd
:= OK_Convert_To
(Typ
, Opnod
);
1087 Set_Etype
(Opnd
, Typ
);
1089 -- In the discrete type case, we directly generate the range check
1090 -- for the outer operand. This range check will implement the
1091 -- required overflow check.
1093 if Is_Discrete_Type
(Typ
) then
1095 Generate_Range_Check
1096 (Expression
(N
), Typ
, CE_Overflow_Check_Failed
);
1098 -- For other types, we enable overflow checking on the conversion,
1099 -- after setting the node as analyzed to prevent recursive attempts
1100 -- to expand the conversion node.
1103 Set_Analyzed
(Opnd
, True);
1104 Enable_Overflow_Check
(Opnd
);
1109 when RE_Not_Available
=>
1112 end Apply_Arithmetic_Overflow_Strict
;
1114 ----------------------------------------------------
1115 -- Apply_Arithmetic_Overflow_Minimized_Eliminated --
1116 ----------------------------------------------------
1118 procedure Apply_Arithmetic_Overflow_Minimized_Eliminated
(Op
: Node_Id
) is
1119 pragma Assert
(Is_Signed_Integer_Arithmetic_Op
(Op
));
1121 Loc
: constant Source_Ptr
:= Sloc
(Op
);
1122 P
: constant Node_Id
:= Parent
(Op
);
1124 LLIB
: constant Entity_Id
:= Base_Type
(Standard_Long_Long_Integer
);
1125 -- Operands and results are of this type when we convert
1127 Result_Type
: constant Entity_Id
:= Etype
(Op
);
1128 -- Original result type
1130 Check_Mode
: constant Overflow_Mode_Type
:= Overflow_Check_Mode
;
1131 pragma Assert
(Check_Mode
in Minimized_Or_Eliminated
);
1134 -- Ranges of values for result
1137 -- Nothing to do if our parent is one of the following:
1139 -- Another signed integer arithmetic op
1140 -- A membership operation
1141 -- A comparison operation
1143 -- In all these cases, we will process at the higher level (and then
1144 -- this node will be processed during the downwards recursion that
1145 -- is part of the processing in Minimize_Eliminate_Overflows).
1147 if Is_Signed_Integer_Arithmetic_Op
(P
)
1148 or else Nkind
(P
) in N_Membership_Test
1149 or else Nkind
(P
) in N_Op_Compare
1151 -- This is also true for an alternative in a case expression
1153 or else Nkind
(P
) = N_Case_Expression_Alternative
1155 -- This is also true for a range operand in a membership test
1157 or else (Nkind
(P
) = N_Range
1158 and then Nkind
(Parent
(P
)) in N_Membership_Test
)
1160 -- If_Expressions and Case_Expressions are treated as arithmetic
1161 -- ops, but if they appear in an assignment or similar contexts
1162 -- there is no overflow check that starts from that parent node,
1163 -- so apply check now.
1165 if Nkind_In
(P
, N_If_Expression
, N_Case_Expression
)
1166 and then not Is_Signed_Integer_Arithmetic_Op
(Parent
(P
))
1174 -- Otherwise, we have a top level arithmetic operation node, and this
1175 -- is where we commence the special processing for MINIMIZED/ELIMINATED
1176 -- modes. This is the case where we tell the machinery not to move into
1177 -- Bignum mode at this top level (of course the top level operation
1178 -- will still be in Bignum mode if either of its operands are of type
1181 Minimize_Eliminate_Overflows
(Op
, Lo
, Hi
, Top_Level
=> True);
1183 -- That call may but does not necessarily change the result type of Op.
1184 -- It is the job of this routine to undo such changes, so that at the
1185 -- top level, we have the proper type. This "undoing" is a point at
1186 -- which a final overflow check may be applied.
1188 -- If the result type was not fiddled we are all set. We go to base
1189 -- types here because things may have been rewritten to generate the
1190 -- base type of the operand types.
1192 if Base_Type
(Etype
(Op
)) = Base_Type
(Result_Type
) then
1197 elsif Is_RTE
(Etype
(Op
), RE_Bignum
) then
1199 -- We need a sequence that looks like:
1201 -- Rnn : Result_Type;
1204 -- M : Mark_Id := SS_Mark;
1206 -- Rnn := Long_Long_Integer'Base (From_Bignum (Op));
1210 -- This block is inserted (using Insert_Actions), and then the node
1211 -- is replaced with a reference to Rnn.
1213 -- If our parent is a conversion node then there is no point in
1214 -- generating a conversion to Result_Type. Instead, we let the parent
1215 -- handle this. Note that this special case is not just about
1216 -- optimization. Consider
1220 -- X := Long_Long_Integer'Base (A * (B ** C));
1222 -- Now the product may fit in Long_Long_Integer but not in Integer.
1223 -- In MINIMIZED/ELIMINATED mode, we don't want to introduce an
1224 -- overflow exception for this intermediate value.
1227 Blk
: constant Node_Id
:= Make_Bignum_Block
(Loc
);
1228 Rnn
: constant Entity_Id
:= Make_Temporary
(Loc
, 'R', Op
);
1234 RHS
:= Convert_From_Bignum
(Op
);
1236 if Nkind
(P
) /= N_Type_Conversion
then
1237 Convert_To_And_Rewrite
(Result_Type
, RHS
);
1238 Rtype
:= Result_Type
;
1240 -- Interesting question, do we need a check on that conversion
1241 -- operation. Answer, not if we know the result is in range.
1242 -- At the moment we are not taking advantage of this. To be
1243 -- looked at later ???
1250 (First
(Statements
(Handled_Statement_Sequence
(Blk
))),
1251 Make_Assignment_Statement
(Loc
,
1252 Name
=> New_Occurrence_Of
(Rnn
, Loc
),
1253 Expression
=> RHS
));
1255 Insert_Actions
(Op
, New_List
(
1256 Make_Object_Declaration
(Loc
,
1257 Defining_Identifier
=> Rnn
,
1258 Object_Definition
=> New_Occurrence_Of
(Rtype
, Loc
)),
1261 Rewrite
(Op
, New_Occurrence_Of
(Rnn
, Loc
));
1262 Analyze_And_Resolve
(Op
);
1265 -- Here we know the result is Long_Long_Integer'Base, or that it has
1266 -- been rewritten because the parent operation is a conversion. See
1267 -- Apply_Arithmetic_Overflow_Strict.Conversion_Optimization.
1271 (Etype
(Op
) = LLIB
or else Nkind
(Parent
(Op
)) = N_Type_Conversion
);
1273 -- All we need to do here is to convert the result to the proper
1274 -- result type. As explained above for the Bignum case, we can
1275 -- omit this if our parent is a type conversion.
1277 if Nkind
(P
) /= N_Type_Conversion
then
1278 Convert_To_And_Rewrite
(Result_Type
, Op
);
1281 Analyze_And_Resolve
(Op
);
1283 end Apply_Arithmetic_Overflow_Minimized_Eliminated
;
1285 ----------------------------
1286 -- Apply_Constraint_Check --
1287 ----------------------------
1289 procedure Apply_Constraint_Check
1292 No_Sliding
: Boolean := False)
1294 Desig_Typ
: Entity_Id
;
1297 -- No checks inside a generic (check the instantiations)
1299 if Inside_A_Generic
then
1303 -- Apply required constraint checks
1305 if Is_Scalar_Type
(Typ
) then
1306 Apply_Scalar_Range_Check
(N
, Typ
);
1308 elsif Is_Array_Type
(Typ
) then
1310 -- A useful optimization: an aggregate with only an others clause
1311 -- always has the right bounds.
1313 if Nkind
(N
) = N_Aggregate
1314 and then No
(Expressions
(N
))
1316 (First
(Choices
(First
(Component_Associations
(N
)))))
1322 if Is_Constrained
(Typ
) then
1323 Apply_Length_Check
(N
, Typ
);
1326 Apply_Range_Check
(N
, Typ
);
1329 Apply_Range_Check
(N
, Typ
);
1332 elsif (Is_Record_Type
(Typ
) or else Is_Private_Type
(Typ
))
1333 and then Has_Discriminants
(Base_Type
(Typ
))
1334 and then Is_Constrained
(Typ
)
1336 Apply_Discriminant_Check
(N
, Typ
);
1338 elsif Is_Access_Type
(Typ
) then
1340 Desig_Typ
:= Designated_Type
(Typ
);
1342 -- No checks necessary if expression statically null
1344 if Known_Null
(N
) then
1345 if Can_Never_Be_Null
(Typ
) then
1346 Install_Null_Excluding_Check
(N
);
1349 -- No sliding possible on access to arrays
1351 elsif Is_Array_Type
(Desig_Typ
) then
1352 if Is_Constrained
(Desig_Typ
) then
1353 Apply_Length_Check
(N
, Typ
);
1356 Apply_Range_Check
(N
, Typ
);
1358 -- Do not install a discriminant check for a constrained subtype
1359 -- created for an unconstrained nominal type because the subtype
1360 -- has the correct constraints by construction.
1362 elsif Has_Discriminants
(Base_Type
(Desig_Typ
))
1363 and then Is_Constrained
(Desig_Typ
)
1364 and then not Is_Constr_Subt_For_U_Nominal
(Desig_Typ
)
1366 Apply_Discriminant_Check
(N
, Typ
);
1369 -- Apply the 2005 Null_Excluding check. Note that we do not apply
1370 -- this check if the constraint node is illegal, as shown by having
1371 -- an error posted. This additional guard prevents cascaded errors
1372 -- and compiler aborts on illegal programs involving Ada 2005 checks.
1374 if Can_Never_Be_Null
(Typ
)
1375 and then not Can_Never_Be_Null
(Etype
(N
))
1376 and then not Error_Posted
(N
)
1378 Install_Null_Excluding_Check
(N
);
1381 end Apply_Constraint_Check
;
1383 ------------------------------
1384 -- Apply_Discriminant_Check --
1385 ------------------------------
1387 procedure Apply_Discriminant_Check
1390 Lhs
: Node_Id
:= Empty
)
1392 Loc
: constant Source_Ptr
:= Sloc
(N
);
1393 Do_Access
: constant Boolean := Is_Access_Type
(Typ
);
1394 S_Typ
: Entity_Id
:= Etype
(N
);
1398 function Denotes_Explicit_Dereference
(Obj
: Node_Id
) return Boolean;
1399 -- A heap object with an indefinite subtype is constrained by its
1400 -- initial value, and assigning to it requires a constraint_check.
1401 -- The target may be an explicit dereference, or a renaming of one.
1403 function Is_Aliased_Unconstrained_Component
return Boolean;
1404 -- It is possible for an aliased component to have a nominal
1405 -- unconstrained subtype (through instantiation). If this is a
1406 -- discriminated component assigned in the expansion of an aggregate
1407 -- in an initialization, the check must be suppressed. This unusual
1408 -- situation requires a predicate of its own.
1410 ----------------------------------
1411 -- Denotes_Explicit_Dereference --
1412 ----------------------------------
1414 function Denotes_Explicit_Dereference
(Obj
: Node_Id
) return Boolean is
1417 Nkind
(Obj
) = N_Explicit_Dereference
1419 (Is_Entity_Name
(Obj
)
1420 and then Present
(Renamed_Object
(Entity
(Obj
)))
1421 and then Nkind
(Renamed_Object
(Entity
(Obj
))) =
1422 N_Explicit_Dereference
);
1423 end Denotes_Explicit_Dereference
;
1425 ----------------------------------------
1426 -- Is_Aliased_Unconstrained_Component --
1427 ----------------------------------------
1429 function Is_Aliased_Unconstrained_Component
return Boolean is
1434 if Nkind
(Lhs
) /= N_Selected_Component
then
1437 Comp
:= Entity
(Selector_Name
(Lhs
));
1438 Pref
:= Prefix
(Lhs
);
1441 if Ekind
(Comp
) /= E_Component
1442 or else not Is_Aliased
(Comp
)
1447 return not Comes_From_Source
(Pref
)
1448 and then In_Instance
1449 and then not Is_Constrained
(Etype
(Comp
));
1450 end Is_Aliased_Unconstrained_Component
;
1452 -- Start of processing for Apply_Discriminant_Check
1456 T_Typ
:= Designated_Type
(Typ
);
1461 -- Only apply checks when generating code and discriminant checks are
1462 -- not suppressed. In GNATprove mode, we do not apply the checks, but we
1463 -- still analyze the expression to possibly issue errors on SPARK code
1464 -- when a run-time error can be detected at compile time.
1466 if not GNATprove_Mode
then
1467 if not Expander_Active
1468 or else Discriminant_Checks_Suppressed
(T_Typ
)
1474 -- No discriminant checks necessary for an access when expression is
1475 -- statically Null. This is not only an optimization, it is fundamental
1476 -- because otherwise discriminant checks may be generated in init procs
1477 -- for types containing an access to a not-yet-frozen record, causing a
1478 -- deadly forward reference.
1480 -- Also, if the expression is of an access type whose designated type is
1481 -- incomplete, then the access value must be null and we suppress the
1484 if Known_Null
(N
) then
1487 elsif Is_Access_Type
(S_Typ
) then
1488 S_Typ
:= Designated_Type
(S_Typ
);
1490 if Ekind
(S_Typ
) = E_Incomplete_Type
then
1495 -- If an assignment target is present, then we need to generate the
1496 -- actual subtype if the target is a parameter or aliased object with
1497 -- an unconstrained nominal subtype.
1499 -- Ada 2005 (AI-363): For Ada 2005, we limit the building of the actual
1500 -- subtype to the parameter and dereference cases, since other aliased
1501 -- objects are unconstrained (unless the nominal subtype is explicitly
1505 and then (Present
(Param_Entity
(Lhs
))
1506 or else (Ada_Version
< Ada_2005
1507 and then not Is_Constrained
(T_Typ
)
1508 and then Is_Aliased_View
(Lhs
)
1509 and then not Is_Aliased_Unconstrained_Component
)
1510 or else (Ada_Version
>= Ada_2005
1511 and then not Is_Constrained
(T_Typ
)
1512 and then Denotes_Explicit_Dereference
(Lhs
)
1513 and then Nkind
(Original_Node
(Lhs
)) /=
1516 T_Typ
:= Get_Actual_Subtype
(Lhs
);
1519 -- Nothing to do if the type is unconstrained (this is the case where
1520 -- the actual subtype in the RM sense of N is unconstrained and no check
1523 if not Is_Constrained
(T_Typ
) then
1526 -- Ada 2005: nothing to do if the type is one for which there is a
1527 -- partial view that is constrained.
1529 elsif Ada_Version
>= Ada_2005
1530 and then Object_Type_Has_Constrained_Partial_View
1531 (Typ
=> Base_Type
(T_Typ
),
1532 Scop
=> Current_Scope
)
1537 -- Nothing to do if the type is an Unchecked_Union
1539 if Is_Unchecked_Union
(Base_Type
(T_Typ
)) then
1543 -- Suppress checks if the subtypes are the same. The check must be
1544 -- preserved in an assignment to a formal, because the constraint is
1545 -- given by the actual.
1547 if Nkind
(Original_Node
(N
)) /= N_Allocator
1549 or else not Is_Entity_Name
(Lhs
)
1550 or else No
(Param_Entity
(Lhs
)))
1553 or else (Do_Access
and then Designated_Type
(Typ
) = S_Typ
))
1554 and then not Is_Aliased_View
(Lhs
)
1559 -- We can also eliminate checks on allocators with a subtype mark that
1560 -- coincides with the context type. The context type may be a subtype
1561 -- without a constraint (common case, a generic actual).
1563 elsif Nkind
(Original_Node
(N
)) = N_Allocator
1564 and then Is_Entity_Name
(Expression
(Original_Node
(N
)))
1567 Alloc_Typ
: constant Entity_Id
:=
1568 Entity
(Expression
(Original_Node
(N
)));
1571 if Alloc_Typ
= T_Typ
1572 or else (Nkind
(Parent
(T_Typ
)) = N_Subtype_Declaration
1573 and then Is_Entity_Name
(
1574 Subtype_Indication
(Parent
(T_Typ
)))
1575 and then Alloc_Typ
= Base_Type
(T_Typ
))
1583 -- See if we have a case where the types are both constrained, and all
1584 -- the constraints are constants. In this case, we can do the check
1585 -- successfully at compile time.
1587 -- We skip this check for the case where the node is rewritten as
1588 -- an allocator, because it already carries the context subtype,
1589 -- and extracting the discriminants from the aggregate is messy.
1591 if Is_Constrained
(S_Typ
)
1592 and then Nkind
(Original_Node
(N
)) /= N_Allocator
1602 -- S_Typ may not have discriminants in the case where it is a
1603 -- private type completed by a default discriminated type. In that
1604 -- case, we need to get the constraints from the underlying type.
1605 -- If the underlying type is unconstrained (i.e. has no default
1606 -- discriminants) no check is needed.
1608 if Has_Discriminants
(S_Typ
) then
1609 Discr
:= First_Discriminant
(S_Typ
);
1610 DconS
:= First_Elmt
(Discriminant_Constraint
(S_Typ
));
1613 Discr
:= First_Discriminant
(Underlying_Type
(S_Typ
));
1616 (Discriminant_Constraint
(Underlying_Type
(S_Typ
)));
1622 -- A further optimization: if T_Typ is derived from S_Typ
1623 -- without imposing a constraint, no check is needed.
1625 if Nkind
(Original_Node
(Parent
(T_Typ
))) =
1626 N_Full_Type_Declaration
1629 Type_Def
: constant Node_Id
:=
1630 Type_Definition
(Original_Node
(Parent
(T_Typ
)));
1632 if Nkind
(Type_Def
) = N_Derived_Type_Definition
1633 and then Is_Entity_Name
(Subtype_Indication
(Type_Def
))
1634 and then Entity
(Subtype_Indication
(Type_Def
)) = S_Typ
1642 -- Constraint may appear in full view of type
1644 if Ekind
(T_Typ
) = E_Private_Subtype
1645 and then Present
(Full_View
(T_Typ
))
1648 First_Elmt
(Discriminant_Constraint
(Full_View
(T_Typ
)));
1651 First_Elmt
(Discriminant_Constraint
(T_Typ
));
1654 while Present
(Discr
) loop
1655 ItemS
:= Node
(DconS
);
1656 ItemT
:= Node
(DconT
);
1658 -- For a discriminated component type constrained by the
1659 -- current instance of an enclosing type, there is no
1660 -- applicable discriminant check.
1662 if Nkind
(ItemT
) = N_Attribute_Reference
1663 and then Is_Access_Type
(Etype
(ItemT
))
1664 and then Is_Entity_Name
(Prefix
(ItemT
))
1665 and then Is_Type
(Entity
(Prefix
(ItemT
)))
1670 -- If the expressions for the discriminants are identical
1671 -- and it is side-effect free (for now just an entity),
1672 -- this may be a shared constraint, e.g. from a subtype
1673 -- without a constraint introduced as a generic actual.
1674 -- Examine other discriminants if any.
1677 and then Is_Entity_Name
(ItemS
)
1681 elsif not Is_OK_Static_Expression
(ItemS
)
1682 or else not Is_OK_Static_Expression
(ItemT
)
1686 elsif Expr_Value
(ItemS
) /= Expr_Value
(ItemT
) then
1687 if Do_Access
then -- needs run-time check.
1690 Apply_Compile_Time_Constraint_Error
1691 (N
, "incorrect value for discriminant&??",
1692 CE_Discriminant_Check_Failed
, Ent
=> Discr
);
1699 Next_Discriminant
(Discr
);
1708 -- In GNATprove mode, we do not apply the checks
1710 if GNATprove_Mode
then
1714 -- Here we need a discriminant check. First build the expression
1715 -- for the comparisons of the discriminants:
1717 -- (n.disc1 /= typ.disc1) or else
1718 -- (n.disc2 /= typ.disc2) or else
1720 -- (n.discn /= typ.discn)
1722 Cond
:= Build_Discriminant_Checks
(N
, T_Typ
);
1724 -- If Lhs is set and is a parameter, then the condition is guarded by:
1725 -- lhs'constrained and then (condition built above)
1727 if Present
(Param_Entity
(Lhs
)) then
1731 Make_Attribute_Reference
(Loc
,
1732 Prefix
=> New_Occurrence_Of
(Param_Entity
(Lhs
), Loc
),
1733 Attribute_Name
=> Name_Constrained
),
1734 Right_Opnd
=> Cond
);
1738 Cond
:= Guard_Access
(Cond
, Loc
, N
);
1742 Make_Raise_Constraint_Error
(Loc
,
1744 Reason
=> CE_Discriminant_Check_Failed
));
1745 end Apply_Discriminant_Check
;
1747 -------------------------
1748 -- Apply_Divide_Checks --
1749 -------------------------
1751 procedure Apply_Divide_Checks
(N
: Node_Id
) is
1752 Loc
: constant Source_Ptr
:= Sloc
(N
);
1753 Typ
: constant Entity_Id
:= Etype
(N
);
1754 Left
: constant Node_Id
:= Left_Opnd
(N
);
1755 Right
: constant Node_Id
:= Right_Opnd
(N
);
1757 Mode
: constant Overflow_Mode_Type
:= Overflow_Check_Mode
;
1758 -- Current overflow checking mode
1768 pragma Warnings
(Off
, Lhi
);
1769 -- Don't actually use this value
1772 -- If we are operating in MINIMIZED or ELIMINATED mode, and we are
1773 -- operating on signed integer types, then the only thing this routine
1774 -- does is to call Apply_Arithmetic_Overflow_Minimized_Eliminated. That
1775 -- procedure will (possibly later on during recursive downward calls),
1776 -- ensure that any needed overflow/division checks are properly applied.
1778 if Mode
in Minimized_Or_Eliminated
1779 and then Is_Signed_Integer_Type
(Typ
)
1781 Apply_Arithmetic_Overflow_Minimized_Eliminated
(N
);
1785 -- Proceed here in SUPPRESSED or CHECKED modes
1788 and then not Backend_Divide_Checks_On_Target
1789 and then Check_Needed
(Right
, Division_Check
)
1791 Determine_Range
(Right
, ROK
, Rlo
, Rhi
, Assume_Valid
=> True);
1793 -- Deal with division check
1795 if Do_Division_Check
(N
)
1796 and then not Division_Checks_Suppressed
(Typ
)
1798 Apply_Division_Check
(N
, Rlo
, Rhi
, ROK
);
1801 -- Deal with overflow check
1803 if Do_Overflow_Check
(N
)
1804 and then not Overflow_Checks_Suppressed
(Etype
(N
))
1806 Set_Do_Overflow_Check
(N
, False);
1808 -- Test for extremely annoying case of xxx'First divided by -1
1809 -- for division of signed integer types (only overflow case).
1811 if Nkind
(N
) = N_Op_Divide
1812 and then Is_Signed_Integer_Type
(Typ
)
1814 Determine_Range
(Left
, LOK
, Llo
, Lhi
, Assume_Valid
=> True);
1815 LLB
:= Expr_Value
(Type_Low_Bound
(Base_Type
(Typ
)));
1817 if ((not ROK
) or else (Rlo
<= (-1) and then (-1) <= Rhi
))
1819 ((not LOK
) or else (Llo
= LLB
))
1821 -- Ensure that expressions are not evaluated twice (once
1822 -- for their runtime checks and once for their regular
1825 Force_Evaluation
(Left
, Mode
=> Strict
);
1826 Force_Evaluation
(Right
, Mode
=> Strict
);
1829 Make_Raise_Constraint_Error
(Loc
,
1835 Duplicate_Subexpr_Move_Checks
(Left
),
1836 Right_Opnd
=> Make_Integer_Literal
(Loc
, LLB
)),
1840 Left_Opnd
=> Duplicate_Subexpr
(Right
),
1841 Right_Opnd
=> Make_Integer_Literal
(Loc
, -1))),
1843 Reason
=> CE_Overflow_Check_Failed
));
1848 end Apply_Divide_Checks
;
1850 --------------------------
1851 -- Apply_Division_Check --
1852 --------------------------
1854 procedure Apply_Division_Check
1860 pragma Assert
(Do_Division_Check
(N
));
1862 Loc
: constant Source_Ptr
:= Sloc
(N
);
1863 Right
: constant Node_Id
:= Right_Opnd
(N
);
1867 and then not Backend_Divide_Checks_On_Target
1868 and then Check_Needed
(Right
, Division_Check
)
1870 -- See if division by zero possible, and if so generate test. This
1871 -- part of the test is not controlled by the -gnato switch, since
1872 -- it is a Division_Check and not an Overflow_Check.
1874 if Do_Division_Check
(N
) then
1875 Set_Do_Division_Check
(N
, False);
1877 if (not ROK
) or else (Rlo
<= 0 and then 0 <= Rhi
) then
1879 Make_Raise_Constraint_Error
(Loc
,
1882 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Right
),
1883 Right_Opnd
=> Make_Integer_Literal
(Loc
, 0)),
1884 Reason
=> CE_Divide_By_Zero
));
1888 end Apply_Division_Check
;
1890 ----------------------------------
1891 -- Apply_Float_Conversion_Check --
1892 ----------------------------------
1894 -- Let F and I be the source and target types of the conversion. The RM
1895 -- specifies that a floating-point value X is rounded to the nearest
1896 -- integer, with halfway cases being rounded away from zero. The rounded
1897 -- value of X is checked against I'Range.
1899 -- The catch in the above paragraph is that there is no good way to know
1900 -- whether the round-to-integer operation resulted in overflow. A remedy is
1901 -- to perform a range check in the floating-point domain instead, however:
1903 -- (1) The bounds may not be known at compile time
1904 -- (2) The check must take into account rounding or truncation.
1905 -- (3) The range of type I may not be exactly representable in F.
1906 -- (4) For the rounding case, The end-points I'First - 0.5 and
1907 -- I'Last + 0.5 may or may not be in range, depending on the
1908 -- sign of I'First and I'Last.
1909 -- (5) X may be a NaN, which will fail any comparison
1911 -- The following steps correctly convert X with rounding:
1913 -- (1) If either I'First or I'Last is not known at compile time, use
1914 -- I'Base instead of I in the next three steps and perform a
1915 -- regular range check against I'Range after conversion.
1916 -- (2) If I'First - 0.5 is representable in F then let Lo be that
1917 -- value and define Lo_OK as (I'First > 0). Otherwise, let Lo be
1918 -- F'Machine (I'First) and let Lo_OK be (Lo >= I'First).
1919 -- In other words, take one of the closest floating-point numbers
1920 -- (which is an integer value) to I'First, and see if it is in
1922 -- (3) If I'Last + 0.5 is representable in F then let Hi be that value
1923 -- and define Hi_OK as (I'Last < 0). Otherwise, let Hi be
1924 -- F'Machine (I'Last) and let Hi_OK be (Hi <= I'Last).
1925 -- (4) Raise CE when (Lo_OK and X < Lo) or (not Lo_OK and X <= Lo)
1926 -- or (Hi_OK and X > Hi) or (not Hi_OK and X >= Hi)
1928 -- For the truncating case, replace steps (2) and (3) as follows:
1929 -- (2) If I'First > 0, then let Lo be F'Pred (I'First) and let Lo_OK
1930 -- be False. Otherwise, let Lo be F'Succ (I'First - 1) and let
1932 -- (3) If I'Last < 0, then let Hi be F'Succ (I'Last) and let Hi_OK
1933 -- be False. Otherwise let Hi be F'Pred (I'Last + 1) and let
1936 procedure Apply_Float_Conversion_Check
1938 Target_Typ
: Entity_Id
)
1940 LB
: constant Node_Id
:= Type_Low_Bound
(Target_Typ
);
1941 HB
: constant Node_Id
:= Type_High_Bound
(Target_Typ
);
1942 Loc
: constant Source_Ptr
:= Sloc
(Ck_Node
);
1943 Expr_Type
: constant Entity_Id
:= Base_Type
(Etype
(Ck_Node
));
1944 Target_Base
: constant Entity_Id
:=
1945 Implementation_Base_Type
(Target_Typ
);
1947 Par
: constant Node_Id
:= Parent
(Ck_Node
);
1948 pragma Assert
(Nkind
(Par
) = N_Type_Conversion
);
1949 -- Parent of check node, must be a type conversion
1951 Truncate
: constant Boolean := Float_Truncate
(Par
);
1952 Max_Bound
: constant Uint
:=
1954 (Machine_Radix_Value
(Expr_Type
),
1955 Machine_Mantissa_Value
(Expr_Type
) - 1) - 1;
1957 -- Largest bound, so bound plus or minus half is a machine number of F
1959 Ifirst
, Ilast
: Uint
;
1960 -- Bounds of integer type
1963 -- Bounds to check in floating-point domain
1965 Lo_OK
, Hi_OK
: Boolean;
1966 -- True iff Lo resp. Hi belongs to I'Range
1968 Lo_Chk
, Hi_Chk
: Node_Id
;
1969 -- Expressions that are False iff check fails
1971 Reason
: RT_Exception_Code
;
1974 -- We do not need checks if we are not generating code (i.e. the full
1975 -- expander is not active). In SPARK mode, we specifically don't want
1976 -- the frontend to expand these checks, which are dealt with directly
1977 -- in the formal verification backend.
1979 if not Expander_Active
then
1983 if not Compile_Time_Known_Value
(LB
)
1984 or not Compile_Time_Known_Value
(HB
)
1987 -- First check that the value falls in the range of the base type,
1988 -- to prevent overflow during conversion and then perform a
1989 -- regular range check against the (dynamic) bounds.
1991 pragma Assert
(Target_Base
/= Target_Typ
);
1993 Temp
: constant Entity_Id
:= Make_Temporary
(Loc
, 'T', Par
);
1996 Apply_Float_Conversion_Check
(Ck_Node
, Target_Base
);
1997 Set_Etype
(Temp
, Target_Base
);
1999 Insert_Action
(Parent
(Par
),
2000 Make_Object_Declaration
(Loc
,
2001 Defining_Identifier
=> Temp
,
2002 Object_Definition
=> New_Occurrence_Of
(Target_Typ
, Loc
),
2003 Expression
=> New_Copy_Tree
(Par
)),
2004 Suppress
=> All_Checks
);
2007 Make_Raise_Constraint_Error
(Loc
,
2010 Left_Opnd
=> New_Occurrence_Of
(Temp
, Loc
),
2011 Right_Opnd
=> New_Occurrence_Of
(Target_Typ
, Loc
)),
2012 Reason
=> CE_Range_Check_Failed
));
2013 Rewrite
(Par
, New_Occurrence_Of
(Temp
, Loc
));
2019 -- Get the (static) bounds of the target type
2021 Ifirst
:= Expr_Value
(LB
);
2022 Ilast
:= Expr_Value
(HB
);
2024 -- A simple optimization: if the expression is a universal literal,
2025 -- we can do the comparison with the bounds and the conversion to
2026 -- an integer type statically. The range checks are unchanged.
2028 if Nkind
(Ck_Node
) = N_Real_Literal
2029 and then Etype
(Ck_Node
) = Universal_Real
2030 and then Is_Integer_Type
(Target_Typ
)
2031 and then Nkind
(Parent
(Ck_Node
)) = N_Type_Conversion
2034 Int_Val
: constant Uint
:= UR_To_Uint
(Realval
(Ck_Node
));
2037 if Int_Val
<= Ilast
and then Int_Val
>= Ifirst
then
2039 -- Conversion is safe
2041 Rewrite
(Parent
(Ck_Node
),
2042 Make_Integer_Literal
(Loc
, UI_To_Int
(Int_Val
)));
2043 Analyze_And_Resolve
(Parent
(Ck_Node
), Target_Typ
);
2049 -- Check against lower bound
2051 if Truncate
and then Ifirst
> 0 then
2052 Lo
:= Pred
(Expr_Type
, UR_From_Uint
(Ifirst
));
2056 Lo
:= Succ
(Expr_Type
, UR_From_Uint
(Ifirst
- 1));
2059 elsif abs (Ifirst
) < Max_Bound
then
2060 Lo
:= UR_From_Uint
(Ifirst
) - Ureal_Half
;
2061 Lo_OK
:= (Ifirst
> 0);
2064 Lo
:= Machine
(Expr_Type
, UR_From_Uint
(Ifirst
), Round_Even
, Ck_Node
);
2065 Lo_OK
:= (Lo
>= UR_From_Uint
(Ifirst
));
2070 -- Lo_Chk := (X >= Lo)
2072 Lo_Chk
:= Make_Op_Ge
(Loc
,
2073 Left_Opnd
=> Duplicate_Subexpr_No_Checks
(Ck_Node
),
2074 Right_Opnd
=> Make_Real_Literal
(Loc
, Lo
));
2077 -- Lo_Chk := (X > Lo)
2079 Lo_Chk
:= Make_Op_Gt
(Loc
,
2080 Left_Opnd
=> Duplicate_Subexpr_No_Checks
(Ck_Node
),
2081 Right_Opnd
=> Make_Real_Literal
(Loc
, Lo
));
2084 -- Check against higher bound
2086 if Truncate
and then Ilast
< 0 then
2087 Hi
:= Succ
(Expr_Type
, UR_From_Uint
(Ilast
));
2091 Hi
:= Pred
(Expr_Type
, UR_From_Uint
(Ilast
+ 1));
2094 elsif abs (Ilast
) < Max_Bound
then
2095 Hi
:= UR_From_Uint
(Ilast
) + Ureal_Half
;
2096 Hi_OK
:= (Ilast
< 0);
2098 Hi
:= Machine
(Expr_Type
, UR_From_Uint
(Ilast
), Round_Even
, Ck_Node
);
2099 Hi_OK
:= (Hi
<= UR_From_Uint
(Ilast
));
2104 -- Hi_Chk := (X <= Hi)
2106 Hi_Chk
:= Make_Op_Le
(Loc
,
2107 Left_Opnd
=> Duplicate_Subexpr_No_Checks
(Ck_Node
),
2108 Right_Opnd
=> Make_Real_Literal
(Loc
, Hi
));
2111 -- Hi_Chk := (X < Hi)
2113 Hi_Chk
:= Make_Op_Lt
(Loc
,
2114 Left_Opnd
=> Duplicate_Subexpr_No_Checks
(Ck_Node
),
2115 Right_Opnd
=> Make_Real_Literal
(Loc
, Hi
));
2118 -- If the bounds of the target type are the same as those of the base
2119 -- type, the check is an overflow check as a range check is not
2120 -- performed in these cases.
2122 if Expr_Value
(Type_Low_Bound
(Target_Base
)) = Ifirst
2123 and then Expr_Value
(Type_High_Bound
(Target_Base
)) = Ilast
2125 Reason
:= CE_Overflow_Check_Failed
;
2127 Reason
:= CE_Range_Check_Failed
;
2130 -- Raise CE if either conditions does not hold
2132 Insert_Action
(Ck_Node
,
2133 Make_Raise_Constraint_Error
(Loc
,
2134 Condition
=> Make_Op_Not
(Loc
, Make_And_Then
(Loc
, Lo_Chk
, Hi_Chk
)),
2136 end Apply_Float_Conversion_Check
;
2138 ------------------------
2139 -- Apply_Length_Check --
2140 ------------------------
2142 procedure Apply_Length_Check
2144 Target_Typ
: Entity_Id
;
2145 Source_Typ
: Entity_Id
:= Empty
)
2148 Apply_Selected_Length_Checks
2149 (Ck_Node
, Target_Typ
, Source_Typ
, Do_Static
=> False);
2150 end Apply_Length_Check
;
2152 -------------------------------------
2153 -- Apply_Parameter_Aliasing_Checks --
2154 -------------------------------------
2156 procedure Apply_Parameter_Aliasing_Checks
2160 Loc
: constant Source_Ptr
:= Sloc
(Call
);
2162 function May_Cause_Aliasing
2163 (Formal_1
: Entity_Id
;
2164 Formal_2
: Entity_Id
) return Boolean;
2165 -- Determine whether two formal parameters can alias each other
2166 -- depending on their modes.
2168 function Original_Actual
(N
: Node_Id
) return Node_Id
;
2169 -- The expander may replace an actual with a temporary for the sake of
2170 -- side effect removal. The temporary may hide a potential aliasing as
2171 -- it does not share the address of the actual. This routine attempts
2172 -- to retrieve the original actual.
2174 procedure Overlap_Check
2175 (Actual_1
: Node_Id
;
2177 Formal_1
: Entity_Id
;
2178 Formal_2
: Entity_Id
;
2179 Check
: in out Node_Id
);
2180 -- Create a check to determine whether Actual_1 overlaps with Actual_2.
2181 -- If detailed exception messages are enabled, the check is augmented to
2182 -- provide information about the names of the corresponding formals. See
2183 -- the body for details. Actual_1 and Actual_2 denote the two actuals to
2184 -- be tested. Formal_1 and Formal_2 denote the corresponding formals.
2185 -- Check contains all and-ed simple tests generated so far or remains
2186 -- unchanged in the case of detailed exception messaged.
2188 ------------------------
2189 -- May_Cause_Aliasing --
2190 ------------------------
2192 function May_Cause_Aliasing
2193 (Formal_1
: Entity_Id
;
2194 Formal_2
: Entity_Id
) return Boolean
2197 -- The following combination cannot lead to aliasing
2199 -- Formal 1 Formal 2
2202 if Ekind
(Formal_1
) = E_In_Parameter
2204 Ekind
(Formal_2
) = E_In_Parameter
2208 -- The following combinations may lead to aliasing
2210 -- Formal 1 Formal 2
2220 end May_Cause_Aliasing
;
2222 ---------------------
2223 -- Original_Actual --
2224 ---------------------
2226 function Original_Actual
(N
: Node_Id
) return Node_Id
is
2228 if Nkind
(N
) = N_Type_Conversion
then
2229 return Expression
(N
);
2231 -- The expander created a temporary to capture the result of a type
2232 -- conversion where the expression is the real actual.
2234 elsif Nkind
(N
) = N_Identifier
2235 and then Present
(Original_Node
(N
))
2236 and then Nkind
(Original_Node
(N
)) = N_Type_Conversion
2238 return Expression
(Original_Node
(N
));
2242 end Original_Actual
;
2248 procedure Overlap_Check
2249 (Actual_1
: Node_Id
;
2251 Formal_1
: Entity_Id
;
2252 Formal_2
: Entity_Id
;
2253 Check
: in out Node_Id
)
2256 ID_Casing
: constant Casing_Type
:=
2257 Identifier_Casing
(Source_Index
(Current_Sem_Unit
));
2261 -- Actual_1'Overlaps_Storage (Actual_2)
2264 Make_Attribute_Reference
(Loc
,
2265 Prefix
=> New_Copy_Tree
(Original_Actual
(Actual_1
)),
2266 Attribute_Name
=> Name_Overlaps_Storage
,
2268 New_List
(New_Copy_Tree
(Original_Actual
(Actual_2
))));
2270 -- Generate the following check when detailed exception messages are
2273 -- if Actual_1'Overlaps_Storage (Actual_2) then
2274 -- raise Program_Error with <detailed message>;
2277 if Exception_Extra_Info
then
2280 -- Do not generate location information for internal calls
2282 if Comes_From_Source
(Call
) then
2283 Store_String_Chars
(Build_Location_String
(Loc
));
2284 Store_String_Char
(' ');
2287 Store_String_Chars
("aliased parameters, actuals for """);
2289 Get_Name_String
(Chars
(Formal_1
));
2290 Set_Casing
(ID_Casing
);
2291 Store_String_Chars
(Name_Buffer
(1 .. Name_Len
));
2293 Store_String_Chars
(""" and """);
2295 Get_Name_String
(Chars
(Formal_2
));
2296 Set_Casing
(ID_Casing
);
2297 Store_String_Chars
(Name_Buffer
(1 .. Name_Len
));
2299 Store_String_Chars
(""" overlap");
2301 Insert_Action
(Call
,
2302 Make_If_Statement
(Loc
,
2304 Then_Statements
=> New_List
(
2305 Make_Raise_Statement
(Loc
,
2307 New_Occurrence_Of
(Standard_Program_Error
, Loc
),
2308 Expression
=> Make_String_Literal
(Loc
, End_String
)))));
2310 -- Create a sequence of overlapping checks by and-ing them all
2320 Right_Opnd
=> Cond
);
2330 Formal_1
: Entity_Id
;
2331 Formal_2
: Entity_Id
;
2332 Orig_Act_1
: Node_Id
;
2333 Orig_Act_2
: Node_Id
;
2335 -- Start of processing for Apply_Parameter_Aliasing_Checks
2340 Actual_1
:= First_Actual
(Call
);
2341 Formal_1
:= First_Formal
(Subp
);
2342 while Present
(Actual_1
) and then Present
(Formal_1
) loop
2343 Orig_Act_1
:= Original_Actual
(Actual_1
);
2345 -- Ensure that the actual is an object that is not passed by value.
2346 -- Elementary types are always passed by value, therefore actuals of
2347 -- such types cannot lead to aliasing. An aggregate is an object in
2348 -- Ada 2012, but an actual that is an aggregate cannot overlap with
2349 -- another actual. A type that is By_Reference (such as an array of
2350 -- controlled types) is not subject to the check because any update
2351 -- will be done in place and a subsequent read will always see the
2352 -- correct value, see RM 6.2 (12/3).
2354 if Nkind
(Orig_Act_1
) = N_Aggregate
2355 or else (Nkind
(Orig_Act_1
) = N_Qualified_Expression
2356 and then Nkind
(Expression
(Orig_Act_1
)) = N_Aggregate
)
2360 elsif Is_Object_Reference
(Orig_Act_1
)
2361 and then not Is_Elementary_Type
(Etype
(Orig_Act_1
))
2362 and then not Is_By_Reference_Type
(Etype
(Orig_Act_1
))
2364 Actual_2
:= Next_Actual
(Actual_1
);
2365 Formal_2
:= Next_Formal
(Formal_1
);
2366 while Present
(Actual_2
) and then Present
(Formal_2
) loop
2367 Orig_Act_2
:= Original_Actual
(Actual_2
);
2369 -- The other actual we are testing against must also denote
2370 -- a non pass-by-value object. Generate the check only when
2371 -- the mode of the two formals may lead to aliasing.
2373 if Is_Object_Reference
(Orig_Act_2
)
2374 and then not Is_Elementary_Type
(Etype
(Orig_Act_2
))
2375 and then May_Cause_Aliasing
(Formal_1
, Formal_2
)
2377 Remove_Side_Effects
(Actual_1
);
2378 Remove_Side_Effects
(Actual_2
);
2381 (Actual_1
=> Actual_1
,
2382 Actual_2
=> Actual_2
,
2383 Formal_1
=> Formal_1
,
2384 Formal_2
=> Formal_2
,
2388 Next_Actual
(Actual_2
);
2389 Next_Formal
(Formal_2
);
2393 Next_Actual
(Actual_1
);
2394 Next_Formal
(Formal_1
);
2397 -- Place a simple check right before the call
2399 if Present
(Check
) and then not Exception_Extra_Info
then
2400 Insert_Action
(Call
,
2401 Make_Raise_Program_Error
(Loc
,
2403 Reason
=> PE_Aliased_Parameters
));
2405 end Apply_Parameter_Aliasing_Checks
;
2407 -------------------------------------
2408 -- Apply_Parameter_Validity_Checks --
2409 -------------------------------------
2411 procedure Apply_Parameter_Validity_Checks
(Subp
: Entity_Id
) is
2412 Subp_Decl
: Node_Id
;
2414 procedure Add_Validity_Check
2415 (Formal
: Entity_Id
;
2417 For_Result
: Boolean := False);
2418 -- Add a single 'Valid[_Scalar] check which verifies the initialization
2419 -- of Formal. Prag_Nam denotes the pre or post condition pragma name.
2420 -- Set flag For_Result when to verify the result of a function.
2422 ------------------------
2423 -- Add_Validity_Check --
2424 ------------------------
2426 procedure Add_Validity_Check
2427 (Formal
: Entity_Id
;
2429 For_Result
: Boolean := False)
2431 procedure Build_Pre_Post_Condition
(Expr
: Node_Id
);
2432 -- Create a pre/postcondition pragma that tests expression Expr
2434 ------------------------------
2435 -- Build_Pre_Post_Condition --
2436 ------------------------------
2438 procedure Build_Pre_Post_Condition
(Expr
: Node_Id
) is
2439 Loc
: constant Source_Ptr
:= Sloc
(Subp
);
2447 Pragma_Argument_Associations
=> New_List
(
2448 Make_Pragma_Argument_Association
(Loc
,
2449 Chars
=> Name_Check
,
2450 Expression
=> Expr
)));
2452 -- Add a message unless exception messages are suppressed
2454 if not Exception_Locations_Suppressed
then
2455 Append_To
(Pragma_Argument_Associations
(Prag
),
2456 Make_Pragma_Argument_Association
(Loc
,
2457 Chars
=> Name_Message
,
2459 Make_String_Literal
(Loc
,
2461 & Get_Name_String
(Prag_Nam
)
2463 & Build_Location_String
(Loc
))));
2466 -- Insert the pragma in the tree
2468 if Nkind
(Parent
(Subp_Decl
)) = N_Compilation_Unit
then
2469 Add_Global_Declaration
(Prag
);
2472 -- PPC pragmas associated with subprogram bodies must be inserted
2473 -- in the declarative part of the body.
2475 elsif Nkind
(Subp_Decl
) = N_Subprogram_Body
then
2476 Decls
:= Declarations
(Subp_Decl
);
2480 Set_Declarations
(Subp_Decl
, Decls
);
2483 Prepend_To
(Decls
, Prag
);
2486 -- For subprogram declarations insert the PPC pragma right after
2487 -- the declarative node.
2490 Insert_After_And_Analyze
(Subp_Decl
, Prag
);
2492 end Build_Pre_Post_Condition
;
2496 Loc
: constant Source_Ptr
:= Sloc
(Subp
);
2497 Typ
: constant Entity_Id
:= Etype
(Formal
);
2501 -- Start of processing for Add_Validity_Check
2504 -- For scalars, generate 'Valid test
2506 if Is_Scalar_Type
(Typ
) then
2509 -- For any non-scalar with scalar parts, generate 'Valid_Scalars test
2511 elsif Scalar_Part_Present
(Typ
) then
2512 Nam
:= Name_Valid_Scalars
;
2514 -- No test needed for other cases (no scalars to test)
2520 -- Step 1: Create the expression to verify the validity of the
2523 Check
:= New_Occurrence_Of
(Formal
, Loc
);
2525 -- When processing a function result, use 'Result. Generate
2530 Make_Attribute_Reference
(Loc
,
2532 Attribute_Name
=> Name_Result
);
2536 -- Context['Result]'Valid[_Scalars]
2539 Make_Attribute_Reference
(Loc
,
2541 Attribute_Name
=> Nam
);
2543 -- Step 2: Create a pre or post condition pragma
2545 Build_Pre_Post_Condition
(Check
);
2546 end Add_Validity_Check
;
2551 Subp_Spec
: Node_Id
;
2553 -- Start of processing for Apply_Parameter_Validity_Checks
2556 -- Extract the subprogram specification and declaration nodes
2558 Subp_Spec
:= Parent
(Subp
);
2560 if Nkind
(Subp_Spec
) = N_Defining_Program_Unit_Name
then
2561 Subp_Spec
:= Parent
(Subp_Spec
);
2564 Subp_Decl
:= Parent
(Subp_Spec
);
2566 if not Comes_From_Source
(Subp
)
2568 -- Do not process formal subprograms because the corresponding actual
2569 -- will receive the proper checks when the instance is analyzed.
2571 or else Is_Formal_Subprogram
(Subp
)
2573 -- Do not process imported subprograms since pre and postconditions
2574 -- are never verified on routines coming from a different language.
2576 or else Is_Imported
(Subp
)
2577 or else Is_Intrinsic_Subprogram
(Subp
)
2579 -- The PPC pragmas generated by this routine do not correspond to
2580 -- source aspects, therefore they cannot be applied to abstract
2583 or else Nkind
(Subp_Decl
) = N_Abstract_Subprogram_Declaration
2585 -- Do not consider subprogram renaminds because the renamed entity
2586 -- already has the proper PPC pragmas.
2588 or else Nkind
(Subp_Decl
) = N_Subprogram_Renaming_Declaration
2590 -- Do not process null procedures because there is no benefit of
2591 -- adding the checks to a no action routine.
2593 or else (Nkind
(Subp_Spec
) = N_Procedure_Specification
2594 and then Null_Present
(Subp_Spec
))
2599 -- Inspect all the formals applying aliasing and scalar initialization
2600 -- checks where applicable.
2602 Formal
:= First_Formal
(Subp
);
2603 while Present
(Formal
) loop
2605 -- Generate the following scalar initialization checks for each
2606 -- formal parameter:
2608 -- mode IN - Pre => Formal'Valid[_Scalars]
2609 -- mode IN OUT - Pre, Post => Formal'Valid[_Scalars]
2610 -- mode OUT - Post => Formal'Valid[_Scalars]
2612 if Check_Validity_Of_Parameters
then
2613 if Ekind_In
(Formal
, E_In_Parameter
, E_In_Out_Parameter
) then
2614 Add_Validity_Check
(Formal
, Name_Precondition
, False);
2617 if Ekind_In
(Formal
, E_In_Out_Parameter
, E_Out_Parameter
) then
2618 Add_Validity_Check
(Formal
, Name_Postcondition
, False);
2622 Next_Formal
(Formal
);
2625 -- Generate following scalar initialization check for function result:
2627 -- Post => Subp'Result'Valid[_Scalars]
2629 if Check_Validity_Of_Parameters
and then Ekind
(Subp
) = E_Function
then
2630 Add_Validity_Check
(Subp
, Name_Postcondition
, True);
2632 end Apply_Parameter_Validity_Checks
;
2634 ---------------------------
2635 -- Apply_Predicate_Check --
2636 ---------------------------
2638 procedure Apply_Predicate_Check
2641 Fun
: Entity_Id
:= Empty
)
2646 if Predicate_Checks_Suppressed
(Empty
) then
2649 elsif Predicates_Ignored
(Typ
) then
2652 elsif Present
(Predicate_Function
(Typ
)) then
2654 while Present
(S
) and then not Is_Subprogram
(S
) loop
2658 -- A predicate check does not apply within internally generated
2659 -- subprograms, such as TSS functions.
2661 if Within_Internal_Subprogram
then
2664 -- If the check appears within the predicate function itself, it
2665 -- means that the user specified a check whose formal is the
2666 -- predicated subtype itself, rather than some covering type. This
2667 -- is likely to be a common error, and thus deserves a warning.
2669 elsif Present
(S
) and then S
= Predicate_Function
(Typ
) then
2671 ("predicate check includes a call to& that requires a "
2672 & "predicate check??", Parent
(N
), Fun
);
2674 ("\this will result in infinite recursion??", Parent
(N
));
2676 if Is_First_Subtype
(Typ
) then
2678 ("\use an explicit subtype of& to carry the predicate",
2683 Make_Raise_Storage_Error
(Sloc
(N
),
2684 Reason
=> SE_Infinite_Recursion
));
2686 -- Here for normal case of predicate active
2689 -- If the type has a static predicate and the expression is known
2690 -- at compile time, see if the expression satisfies the predicate.
2692 Check_Expression_Against_Static_Predicate
(N
, Typ
);
2694 if not Expander_Active
then
2698 -- For an entity of the type, generate a call to the predicate
2699 -- function, unless its type is an actual subtype, which is not
2700 -- visible outside of the enclosing subprogram.
2702 if Is_Entity_Name
(N
)
2703 and then not Is_Actual_Subtype
(Typ
)
2706 Make_Predicate_Check
2707 (Typ
, New_Occurrence_Of
(Entity
(N
), Sloc
(N
))));
2709 -- If the expression is not an entity it may have side effects,
2710 -- and the following call will create an object declaration for
2711 -- it. We disable checks during its analysis, to prevent an
2712 -- infinite recursion.
2716 Make_Predicate_Check
2717 (Typ
, Duplicate_Subexpr
(N
)), Suppress
=> All_Checks
);
2721 end Apply_Predicate_Check
;
2723 -----------------------
2724 -- Apply_Range_Check --
2725 -----------------------
2727 procedure Apply_Range_Check
2729 Target_Typ
: Entity_Id
;
2730 Source_Typ
: Entity_Id
:= Empty
)
2733 Apply_Selected_Range_Checks
2734 (Ck_Node
, Target_Typ
, Source_Typ
, Do_Static
=> False);
2735 end Apply_Range_Check
;
2737 ------------------------------
2738 -- Apply_Scalar_Range_Check --
2739 ------------------------------
2741 -- Note that Apply_Scalar_Range_Check never turns the Do_Range_Check flag
2742 -- off if it is already set on.
2744 procedure Apply_Scalar_Range_Check
2746 Target_Typ
: Entity_Id
;
2747 Source_Typ
: Entity_Id
:= Empty
;
2748 Fixed_Int
: Boolean := False)
2750 Parnt
: constant Node_Id
:= Parent
(Expr
);
2752 Arr
: Node_Id
:= Empty
; -- initialize to prevent warning
2753 Arr_Typ
: Entity_Id
:= Empty
; -- initialize to prevent warning
2754 OK
: Boolean := False; -- initialize to prevent warning
2756 Is_Subscr_Ref
: Boolean;
2757 -- Set true if Expr is a subscript
2759 Is_Unconstrained_Subscr_Ref
: Boolean;
2760 -- Set true if Expr is a subscript of an unconstrained array. In this
2761 -- case we do not attempt to do an analysis of the value against the
2762 -- range of the subscript, since we don't know the actual subtype.
2765 -- Set to True if Expr should be regarded as a real value even though
2766 -- the type of Expr might be discrete.
2768 procedure Bad_Value
(Warn
: Boolean := False);
2769 -- Procedure called if value is determined to be out of range. Warn is
2770 -- True to force a warning instead of an error, even when SPARK_Mode is
2777 procedure Bad_Value
(Warn
: Boolean := False) is
2779 Apply_Compile_Time_Constraint_Error
2780 (Expr
, "value not in range of}??", CE_Range_Check_Failed
,
2786 -- Start of processing for Apply_Scalar_Range_Check
2789 -- Return if check obviously not needed
2792 -- Not needed inside generic
2796 -- Not needed if previous error
2798 or else Target_Typ
= Any_Type
2799 or else Nkind
(Expr
) = N_Error
2801 -- Not needed for non-scalar type
2803 or else not Is_Scalar_Type
(Target_Typ
)
2805 -- Not needed if we know node raises CE already
2807 or else Raises_Constraint_Error
(Expr
)
2812 -- Now, see if checks are suppressed
2815 Is_List_Member
(Expr
) and then Nkind
(Parnt
) = N_Indexed_Component
;
2817 if Is_Subscr_Ref
then
2818 Arr
:= Prefix
(Parnt
);
2819 Arr_Typ
:= Get_Actual_Subtype_If_Available
(Arr
);
2821 if Is_Access_Type
(Arr_Typ
) then
2822 Arr_Typ
:= Designated_Type
(Arr_Typ
);
2826 if not Do_Range_Check
(Expr
) then
2828 -- Subscript reference. Check for Index_Checks suppressed
2830 if Is_Subscr_Ref
then
2832 -- Check array type and its base type
2834 if Index_Checks_Suppressed
(Arr_Typ
)
2835 or else Index_Checks_Suppressed
(Base_Type
(Arr_Typ
))
2839 -- Check array itself if it is an entity name
2841 elsif Is_Entity_Name
(Arr
)
2842 and then Index_Checks_Suppressed
(Entity
(Arr
))
2846 -- Check expression itself if it is an entity name
2848 elsif Is_Entity_Name
(Expr
)
2849 and then Index_Checks_Suppressed
(Entity
(Expr
))
2854 -- All other cases, check for Range_Checks suppressed
2857 -- Check target type and its base type
2859 if Range_Checks_Suppressed
(Target_Typ
)
2860 or else Range_Checks_Suppressed
(Base_Type
(Target_Typ
))
2864 -- Check expression itself if it is an entity name
2866 elsif Is_Entity_Name
(Expr
)
2867 and then Range_Checks_Suppressed
(Entity
(Expr
))
2871 -- If Expr is part of an assignment statement, then check left
2872 -- side of assignment if it is an entity name.
2874 elsif Nkind
(Parnt
) = N_Assignment_Statement
2875 and then Is_Entity_Name
(Name
(Parnt
))
2876 and then Range_Checks_Suppressed
(Entity
(Name
(Parnt
)))
2883 -- Do not set range checks if they are killed
2885 if Nkind
(Expr
) = N_Unchecked_Type_Conversion
2886 and then Kill_Range_Check
(Expr
)
2891 -- Do not set range checks for any values from System.Scalar_Values
2892 -- since the whole idea of such values is to avoid checking them.
2894 if Is_Entity_Name
(Expr
)
2895 and then Is_RTU
(Scope
(Entity
(Expr
)), System_Scalar_Values
)
2900 -- Now see if we need a check
2902 if No
(Source_Typ
) then
2903 S_Typ
:= Etype
(Expr
);
2905 S_Typ
:= Source_Typ
;
2908 if not Is_Scalar_Type
(S_Typ
) or else S_Typ
= Any_Type
then
2912 Is_Unconstrained_Subscr_Ref
:=
2913 Is_Subscr_Ref
and then not Is_Constrained
(Arr_Typ
);
2915 -- Special checks for floating-point type
2917 if Is_Floating_Point_Type
(S_Typ
) then
2919 -- Always do a range check if the source type includes infinities and
2920 -- the target type does not include infinities. We do not do this if
2921 -- range checks are killed.
2922 -- If the expression is a literal and the bounds of the type are
2923 -- static constants it may be possible to optimize the check.
2925 if Has_Infinities
(S_Typ
)
2926 and then not Has_Infinities
(Target_Typ
)
2928 -- If the expression is a literal and the bounds of the type are
2929 -- static constants it may be possible to optimize the check.
2931 if Nkind
(Expr
) = N_Real_Literal
then
2933 Tlo
: constant Node_Id
:= Type_Low_Bound
(Target_Typ
);
2934 Thi
: constant Node_Id
:= Type_High_Bound
(Target_Typ
);
2937 if Compile_Time_Known_Value
(Tlo
)
2938 and then Compile_Time_Known_Value
(Thi
)
2939 and then Expr_Value_R
(Expr
) >= Expr_Value_R
(Tlo
)
2940 and then Expr_Value_R
(Expr
) <= Expr_Value_R
(Thi
)
2944 Enable_Range_Check
(Expr
);
2949 Enable_Range_Check
(Expr
);
2954 -- Return if we know expression is definitely in the range of the target
2955 -- type as determined by Determine_Range. Right now we only do this for
2956 -- discrete types, and not fixed-point or floating-point types.
2958 -- The additional less-precise tests below catch these cases
2960 -- In GNATprove_Mode, also deal with the case of a conversion from
2961 -- floating-point to integer. It is only possible because analysis
2962 -- in GNATprove rules out the possibility of a NaN or infinite value.
2964 -- Note: skip this if we are given a source_typ, since the point of
2965 -- supplying a Source_Typ is to stop us looking at the expression.
2966 -- We could sharpen this test to be out parameters only ???
2968 if Is_Discrete_Type
(Target_Typ
)
2969 and then (Is_Discrete_Type
(Etype
(Expr
))
2970 or else (GNATprove_Mode
2971 and then Is_Floating_Point_Type
(Etype
(Expr
))))
2972 and then not Is_Unconstrained_Subscr_Ref
2973 and then No
(Source_Typ
)
2976 Thi
: constant Node_Id
:= Type_High_Bound
(Target_Typ
);
2977 Tlo
: constant Node_Id
:= Type_Low_Bound
(Target_Typ
);
2980 if Compile_Time_Known_Value
(Tlo
)
2981 and then Compile_Time_Known_Value
(Thi
)
2984 Hiv
: constant Uint
:= Expr_Value
(Thi
);
2985 Lov
: constant Uint
:= Expr_Value
(Tlo
);
2990 -- If range is null, we for sure have a constraint error (we
2991 -- don't even need to look at the value involved, since all
2992 -- possible values will raise CE).
2996 -- When SPARK_Mode is On, force a warning instead of
2997 -- an error in that case, as this likely corresponds
2998 -- to deactivated code.
3000 Bad_Value
(Warn
=> SPARK_Mode
= On
);
3002 -- In GNATprove mode, we enable the range check so that
3003 -- GNATprove will issue a message if it cannot be proved.
3005 if GNATprove_Mode
then
3006 Enable_Range_Check
(Expr
);
3012 -- Otherwise determine range of value
3014 if Is_Discrete_Type
(Etype
(Expr
)) then
3016 (Expr
, OK
, Lo
, Hi
, Assume_Valid
=> True);
3018 -- When converting a float to an integer type, determine the
3019 -- range in real first, and then convert the bounds using
3020 -- UR_To_Uint which correctly rounds away from zero when
3021 -- half way between two integers, as required by normal
3022 -- Ada 95 rounding semantics. It is only possible because
3023 -- analysis in GNATprove rules out the possibility of a NaN
3024 -- or infinite value.
3026 elsif GNATprove_Mode
3027 and then Is_Floating_Point_Type
(Etype
(Expr
))
3035 (Expr
, OK
, Lor
, Hir
, Assume_Valid
=> True);
3038 Lo
:= UR_To_Uint
(Lor
);
3039 Hi
:= UR_To_Uint
(Hir
);
3046 -- If definitely in range, all OK
3048 if Lo
>= Lov
and then Hi
<= Hiv
then
3051 -- If definitely not in range, warn
3053 elsif Lov
> Hi
or else Hiv
< Lo
then
3057 -- Otherwise we don't know
3069 Is_Floating_Point_Type
(S_Typ
)
3070 or else (Is_Fixed_Point_Type
(S_Typ
) and then not Fixed_Int
);
3072 -- Check if we can determine at compile time whether Expr is in the
3073 -- range of the target type. Note that if S_Typ is within the bounds
3074 -- of Target_Typ then this must be the case. This check is meaningful
3075 -- only if this is not a conversion between integer and real types.
3077 if not Is_Unconstrained_Subscr_Ref
3078 and then Is_Discrete_Type
(S_Typ
) = Is_Discrete_Type
(Target_Typ
)
3080 (In_Subrange_Of
(S_Typ
, Target_Typ
, Fixed_Int
)
3082 -- Also check if the expression itself is in the range of the
3083 -- target type if it is a known at compile time value. We skip
3084 -- this test if S_Typ is set since for OUT and IN OUT parameters
3085 -- the Expr itself is not relevant to the checking.
3089 and then Is_In_Range
(Expr
, Target_Typ
,
3090 Assume_Valid
=> True,
3091 Fixed_Int
=> Fixed_Int
,
3092 Int_Real
=> Int_Real
)))
3096 elsif Is_Out_Of_Range
(Expr
, Target_Typ
,
3097 Assume_Valid
=> True,
3098 Fixed_Int
=> Fixed_Int
,
3099 Int_Real
=> Int_Real
)
3104 -- Floating-point case
3105 -- In the floating-point case, we only do range checks if the type is
3106 -- constrained. We definitely do NOT want range checks for unconstrained
3107 -- types, since we want to have infinities, except when
3108 -- Check_Float_Overflow is set.
3110 elsif Is_Floating_Point_Type
(S_Typ
) then
3111 if Is_Constrained
(S_Typ
) or else Check_Float_Overflow
then
3112 Enable_Range_Check
(Expr
);
3115 -- For all other cases we enable a range check unconditionally
3118 Enable_Range_Check
(Expr
);
3121 end Apply_Scalar_Range_Check
;
3123 ----------------------------------
3124 -- Apply_Selected_Length_Checks --
3125 ----------------------------------
3127 procedure Apply_Selected_Length_Checks
3129 Target_Typ
: Entity_Id
;
3130 Source_Typ
: Entity_Id
;
3131 Do_Static
: Boolean)
3133 Checks_On
: constant Boolean :=
3134 not Index_Checks_Suppressed
(Target_Typ
)
3136 not Length_Checks_Suppressed
(Target_Typ
);
3138 Loc
: constant Source_Ptr
:= Sloc
(Ck_Node
);
3142 R_Result
: Check_Result
;
3145 -- Only apply checks when generating code
3147 -- Note: this means that we lose some useful warnings if the expander
3150 if not Expander_Active
then
3155 Selected_Length_Checks
(Ck_Node
, Target_Typ
, Source_Typ
, Empty
);
3157 for J
in 1 .. 2 loop
3158 R_Cno
:= R_Result
(J
);
3159 exit when No
(R_Cno
);
3161 -- A length check may mention an Itype which is attached to a
3162 -- subsequent node. At the top level in a package this can cause
3163 -- an order-of-elaboration problem, so we make sure that the itype
3164 -- is referenced now.
3166 if Ekind
(Current_Scope
) = E_Package
3167 and then Is_Compilation_Unit
(Current_Scope
)
3169 Ensure_Defined
(Target_Typ
, Ck_Node
);
3171 if Present
(Source_Typ
) then
3172 Ensure_Defined
(Source_Typ
, Ck_Node
);
3174 elsif Is_Itype
(Etype
(Ck_Node
)) then
3175 Ensure_Defined
(Etype
(Ck_Node
), Ck_Node
);
3179 -- If the item is a conditional raise of constraint error, then have
3180 -- a look at what check is being performed and ???
3182 if Nkind
(R_Cno
) = N_Raise_Constraint_Error
3183 and then Present
(Condition
(R_Cno
))
3185 Cond
:= Condition
(R_Cno
);
3187 -- Case where node does not now have a dynamic check
3189 if not Has_Dynamic_Length_Check
(Ck_Node
) then
3191 -- If checks are on, just insert the check
3194 Insert_Action
(Ck_Node
, R_Cno
);
3196 if not Do_Static
then
3197 Set_Has_Dynamic_Length_Check
(Ck_Node
);
3200 -- If checks are off, then analyze the length check after
3201 -- temporarily attaching it to the tree in case the relevant
3202 -- condition can be evaluated at compile time. We still want a
3203 -- compile time warning in this case.
3206 Set_Parent
(R_Cno
, Ck_Node
);
3211 -- Output a warning if the condition is known to be True
3213 if Is_Entity_Name
(Cond
)
3214 and then Entity
(Cond
) = Standard_True
3216 Apply_Compile_Time_Constraint_Error
3217 (Ck_Node
, "wrong length for array of}??",
3218 CE_Length_Check_Failed
,
3222 -- If we were only doing a static check, or if checks are not
3223 -- on, then we want to delete the check, since it is not needed.
3224 -- We do this by replacing the if statement by a null statement
3226 elsif Do_Static
or else not Checks_On
then
3227 Remove_Warning_Messages
(R_Cno
);
3228 Rewrite
(R_Cno
, Make_Null_Statement
(Loc
));
3232 Install_Static_Check
(R_Cno
, Loc
);
3235 end Apply_Selected_Length_Checks
;
3237 ---------------------------------
3238 -- Apply_Selected_Range_Checks --
3239 ---------------------------------
3241 procedure Apply_Selected_Range_Checks
3243 Target_Typ
: Entity_Id
;
3244 Source_Typ
: Entity_Id
;
3245 Do_Static
: Boolean)
3247 Checks_On
: constant Boolean :=
3248 not Index_Checks_Suppressed
(Target_Typ
)
3250 not Range_Checks_Suppressed
(Target_Typ
);
3252 Loc
: constant Source_Ptr
:= Sloc
(Ck_Node
);
3256 R_Result
: Check_Result
;
3259 -- Only apply checks when generating code. In GNATprove mode, we do not
3260 -- apply the checks, but we still call Selected_Range_Checks to possibly
3261 -- issue errors on SPARK code when a run-time error can be detected at
3264 if not GNATprove_Mode
then
3265 if not Expander_Active
or not Checks_On
then
3271 Selected_Range_Checks
(Ck_Node
, Target_Typ
, Source_Typ
, Empty
);
3273 if GNATprove_Mode
then
3277 for J
in 1 .. 2 loop
3278 R_Cno
:= R_Result
(J
);
3279 exit when No
(R_Cno
);
3281 -- The range check requires runtime evaluation. Depending on what its
3282 -- triggering condition is, the check may be converted into a compile
3283 -- time constraint check.
3285 if Nkind
(R_Cno
) = N_Raise_Constraint_Error
3286 and then Present
(Condition
(R_Cno
))
3288 Cond
:= Condition
(R_Cno
);
3290 -- Insert the range check before the related context. Note that
3291 -- this action analyses the triggering condition.
3293 Insert_Action
(Ck_Node
, R_Cno
);
3295 -- This old code doesn't make sense, why is the context flagged as
3296 -- requiring dynamic range checks now in the middle of generating
3299 if not Do_Static
then
3300 Set_Has_Dynamic_Range_Check
(Ck_Node
);
3303 -- The triggering condition evaluates to True, the range check
3304 -- can be converted into a compile time constraint check.
3306 if Is_Entity_Name
(Cond
)
3307 and then Entity
(Cond
) = Standard_True
3309 -- Since an N_Range is technically not an expression, we have
3310 -- to set one of the bounds to C_E and then just flag the
3311 -- N_Range. The warning message will point to the lower bound
3312 -- and complain about a range, which seems OK.
3314 if Nkind
(Ck_Node
) = N_Range
then
3315 Apply_Compile_Time_Constraint_Error
3316 (Low_Bound
(Ck_Node
),
3317 "static range out of bounds of}??",
3318 CE_Range_Check_Failed
,
3322 Set_Raises_Constraint_Error
(Ck_Node
);
3325 Apply_Compile_Time_Constraint_Error
3327 "static value out of range of}??",
3328 CE_Range_Check_Failed
,
3333 -- If we were only doing a static check, or if checks are not
3334 -- on, then we want to delete the check, since it is not needed.
3335 -- We do this by replacing the if statement by a null statement
3337 elsif Do_Static
then
3338 Remove_Warning_Messages
(R_Cno
);
3339 Rewrite
(R_Cno
, Make_Null_Statement
(Loc
));
3342 -- The range check raises Constraint_Error explicitly
3345 Install_Static_Check
(R_Cno
, Loc
);
3348 end Apply_Selected_Range_Checks
;
3350 -------------------------------
3351 -- Apply_Static_Length_Check --
3352 -------------------------------
3354 procedure Apply_Static_Length_Check
3356 Target_Typ
: Entity_Id
;
3357 Source_Typ
: Entity_Id
:= Empty
)
3360 Apply_Selected_Length_Checks
3361 (Expr
, Target_Typ
, Source_Typ
, Do_Static
=> True);
3362 end Apply_Static_Length_Check
;
3364 -------------------------------------
3365 -- Apply_Subscript_Validity_Checks --
3366 -------------------------------------
3368 procedure Apply_Subscript_Validity_Checks
(Expr
: Node_Id
) is
3372 pragma Assert
(Nkind
(Expr
) = N_Indexed_Component
);
3374 -- Loop through subscripts
3376 Sub
:= First
(Expressions
(Expr
));
3377 while Present
(Sub
) loop
3379 -- Check one subscript. Note that we do not worry about enumeration
3380 -- type with holes, since we will convert the value to a Pos value
3381 -- for the subscript, and that convert will do the necessary validity
3384 Ensure_Valid
(Sub
, Holes_OK
=> True);
3386 -- Move to next subscript
3390 end Apply_Subscript_Validity_Checks
;
3392 ----------------------------------
3393 -- Apply_Type_Conversion_Checks --
3394 ----------------------------------
3396 procedure Apply_Type_Conversion_Checks
(N
: Node_Id
) is
3397 Target_Type
: constant Entity_Id
:= Etype
(N
);
3398 Target_Base
: constant Entity_Id
:= Base_Type
(Target_Type
);
3399 Expr
: constant Node_Id
:= Expression
(N
);
3401 Expr_Type
: constant Entity_Id
:= Underlying_Type
(Etype
(Expr
));
3402 -- Note: if Etype (Expr) is a private type without discriminants, its
3403 -- full view might have discriminants with defaults, so we need the
3404 -- full view here to retrieve the constraints.
3407 if Inside_A_Generic
then
3410 -- Skip these checks if serious errors detected, there are some nasty
3411 -- situations of incomplete trees that blow things up.
3413 elsif Serious_Errors_Detected
> 0 then
3416 -- Never generate discriminant checks for Unchecked_Union types
3418 elsif Present
(Expr_Type
)
3419 and then Is_Unchecked_Union
(Expr_Type
)
3423 -- Scalar type conversions of the form Target_Type (Expr) require a
3424 -- range check if we cannot be sure that Expr is in the base type of
3425 -- Target_Typ and also that Expr is in the range of Target_Typ. These
3426 -- are not quite the same condition from an implementation point of
3427 -- view, but clearly the second includes the first.
3429 elsif Is_Scalar_Type
(Target_Type
) then
3431 Conv_OK
: constant Boolean := Conversion_OK
(N
);
3432 -- If the Conversion_OK flag on the type conversion is set and no
3433 -- floating-point type is involved in the type conversion then
3434 -- fixed-point values must be read as integral values.
3436 Float_To_Int
: constant Boolean :=
3437 Is_Floating_Point_Type
(Expr_Type
)
3438 and then Is_Integer_Type
(Target_Type
);
3441 if not Overflow_Checks_Suppressed
(Target_Base
)
3442 and then not Overflow_Checks_Suppressed
(Target_Type
)
3444 In_Subrange_Of
(Expr_Type
, Target_Base
, Fixed_Int
=> Conv_OK
)
3445 and then not Float_To_Int
3447 -- A small optimization: the attribute 'Pos applied to an
3448 -- enumeration type has a known range, even though its type is
3449 -- Universal_Integer. So in numeric conversions it is usually
3450 -- within range of the target integer type. Use the static
3451 -- bounds of the base types to check. Disable this optimization
3452 -- in case of a generic formal discrete type, because we don't
3453 -- necessarily know the upper bound yet.
3455 if Nkind
(Expr
) = N_Attribute_Reference
3456 and then Attribute_Name
(Expr
) = Name_Pos
3457 and then Is_Enumeration_Type
(Etype
(Prefix
(Expr
)))
3458 and then not Is_Generic_Type
(Etype
(Prefix
(Expr
)))
3459 and then Is_Integer_Type
(Target_Type
)
3462 Enum_T
: constant Entity_Id
:=
3463 Root_Type
(Etype
(Prefix
(Expr
)));
3464 Int_T
: constant Entity_Id
:= Base_Type
(Target_Type
);
3465 Last_I
: constant Uint
:=
3466 Intval
(High_Bound
(Scalar_Range
(Int_T
)));
3470 -- Character types have no explicit literals, so we use
3471 -- the known number of characters in the type.
3473 if Root_Type
(Enum_T
) = Standard_Character
then
3474 Last_E
:= UI_From_Int
(255);
3476 elsif Enum_T
= Standard_Wide_Character
3477 or else Enum_T
= Standard_Wide_Wide_Character
3479 Last_E
:= UI_From_Int
(65535);
3484 (Entity
(High_Bound
(Scalar_Range
(Enum_T
))));
3487 if Last_E
<= Last_I
then
3491 Activate_Overflow_Check
(N
);
3496 Activate_Overflow_Check
(N
);
3500 if not Range_Checks_Suppressed
(Target_Type
)
3501 and then not Range_Checks_Suppressed
(Expr_Type
)
3504 and then not GNATprove_Mode
3506 Apply_Float_Conversion_Check
(Expr
, Target_Type
);
3508 Apply_Scalar_Range_Check
3509 (Expr
, Target_Type
, Fixed_Int
=> Conv_OK
);
3511 -- If the target type has predicates, we need to indicate
3512 -- the need for a check, even if Determine_Range finds that
3513 -- the value is within bounds. This may be the case e.g for
3514 -- a division with a constant denominator.
3516 if Has_Predicates
(Target_Type
) then
3517 Enable_Range_Check
(Expr
);
3523 elsif Comes_From_Source
(N
)
3524 and then not Discriminant_Checks_Suppressed
(Target_Type
)
3525 and then Is_Record_Type
(Target_Type
)
3526 and then Is_Derived_Type
(Target_Type
)
3527 and then not Is_Tagged_Type
(Target_Type
)
3528 and then not Is_Constrained
(Target_Type
)
3529 and then Present
(Stored_Constraint
(Target_Type
))
3531 -- An unconstrained derived type may have inherited discriminant.
3532 -- Build an actual discriminant constraint list using the stored
3533 -- constraint, to verify that the expression of the parent type
3534 -- satisfies the constraints imposed by the (unconstrained) derived
3535 -- type. This applies to value conversions, not to view conversions
3539 Loc
: constant Source_Ptr
:= Sloc
(N
);
3541 Constraint
: Elmt_Id
;
3542 Discr_Value
: Node_Id
;
3545 New_Constraints
: constant Elist_Id
:= New_Elmt_List
;
3546 Old_Constraints
: constant Elist_Id
:=
3547 Discriminant_Constraint
(Expr_Type
);
3550 Constraint
:= First_Elmt
(Stored_Constraint
(Target_Type
));
3551 while Present
(Constraint
) loop
3552 Discr_Value
:= Node
(Constraint
);
3554 if Is_Entity_Name
(Discr_Value
)
3555 and then Ekind
(Entity
(Discr_Value
)) = E_Discriminant
3557 Discr
:= Corresponding_Discriminant
(Entity
(Discr_Value
));
3560 and then Scope
(Discr
) = Base_Type
(Expr_Type
)
3562 -- Parent is constrained by new discriminant. Obtain
3563 -- Value of original discriminant in expression. If the
3564 -- new discriminant has been used to constrain more than
3565 -- one of the stored discriminants, this will provide the
3566 -- required consistency check.
3569 (Make_Selected_Component
(Loc
,
3571 Duplicate_Subexpr_No_Checks
3572 (Expr
, Name_Req
=> True),
3574 Make_Identifier
(Loc
, Chars
(Discr
))),
3578 -- Discriminant of more remote ancestor ???
3583 -- Derived type definition has an explicit value for this
3584 -- stored discriminant.
3588 (Duplicate_Subexpr_No_Checks
(Discr_Value
),
3592 Next_Elmt
(Constraint
);
3595 -- Use the unconstrained expression type to retrieve the
3596 -- discriminants of the parent, and apply momentarily the
3597 -- discriminant constraint synthesized above.
3599 Set_Discriminant_Constraint
(Expr_Type
, New_Constraints
);
3600 Cond
:= Build_Discriminant_Checks
(Expr
, Expr_Type
);
3601 Set_Discriminant_Constraint
(Expr_Type
, Old_Constraints
);
3604 Make_Raise_Constraint_Error
(Loc
,
3606 Reason
=> CE_Discriminant_Check_Failed
));
3609 -- For arrays, checks are set now, but conversions are applied during
3610 -- expansion, to take into accounts changes of representation. The
3611 -- checks become range checks on the base type or length checks on the
3612 -- subtype, depending on whether the target type is unconstrained or
3613 -- constrained. Note that the range check is put on the expression of a
3614 -- type conversion, while the length check is put on the type conversion
3617 elsif Is_Array_Type
(Target_Type
) then
3618 if Is_Constrained
(Target_Type
) then
3619 Set_Do_Length_Check
(N
);
3621 Set_Do_Range_Check
(Expr
);
3624 end Apply_Type_Conversion_Checks
;
3626 ----------------------------------------------
3627 -- Apply_Universal_Integer_Attribute_Checks --
3628 ----------------------------------------------
3630 procedure Apply_Universal_Integer_Attribute_Checks
(N
: Node_Id
) is
3631 Loc
: constant Source_Ptr
:= Sloc
(N
);
3632 Typ
: constant Entity_Id
:= Etype
(N
);
3635 if Inside_A_Generic
then
3638 -- Nothing to do if checks are suppressed
3640 elsif Range_Checks_Suppressed
(Typ
)
3641 and then Overflow_Checks_Suppressed
(Typ
)
3645 -- Nothing to do if the attribute does not come from source. The
3646 -- internal attributes we generate of this type do not need checks,
3647 -- and furthermore the attempt to check them causes some circular
3648 -- elaboration orders when dealing with packed types.
3650 elsif not Comes_From_Source
(N
) then
3653 -- If the prefix is a selected component that depends on a discriminant
3654 -- the check may improperly expose a discriminant instead of using
3655 -- the bounds of the object itself. Set the type of the attribute to
3656 -- the base type of the context, so that a check will be imposed when
3657 -- needed (e.g. if the node appears as an index).
3659 elsif Nkind
(Prefix
(N
)) = N_Selected_Component
3660 and then Ekind
(Typ
) = E_Signed_Integer_Subtype
3661 and then Depends_On_Discriminant
(Scalar_Range
(Typ
))
3663 Set_Etype
(N
, Base_Type
(Typ
));
3665 -- Otherwise, replace the attribute node with a type conversion node
3666 -- whose expression is the attribute, retyped to universal integer, and
3667 -- whose subtype mark is the target type. The call to analyze this
3668 -- conversion will set range and overflow checks as required for proper
3669 -- detection of an out of range value.
3672 Set_Etype
(N
, Universal_Integer
);
3673 Set_Analyzed
(N
, True);
3676 Make_Type_Conversion
(Loc
,
3677 Subtype_Mark
=> New_Occurrence_Of
(Typ
, Loc
),
3678 Expression
=> Relocate_Node
(N
)));
3680 Analyze_And_Resolve
(N
, Typ
);
3683 end Apply_Universal_Integer_Attribute_Checks
;
3685 -------------------------------------
3686 -- Atomic_Synchronization_Disabled --
3687 -------------------------------------
3689 -- Note: internally Disable/Enable_Atomic_Synchronization is implemented
3690 -- using a bogus check called Atomic_Synchronization. This is to make it
3691 -- more convenient to get exactly the same semantics as [Un]Suppress.
3693 function Atomic_Synchronization_Disabled
(E
: Entity_Id
) return Boolean is
3695 -- If debug flag d.e is set, always return False, i.e. all atomic sync
3696 -- looks enabled, since it is never disabled.
3698 if Debug_Flag_Dot_E
then
3701 -- If debug flag d.d is set then always return True, i.e. all atomic
3702 -- sync looks disabled, since it always tests True.
3704 elsif Debug_Flag_Dot_D
then
3707 -- If entity present, then check result for that entity
3709 elsif Present
(E
) and then Checks_May_Be_Suppressed
(E
) then
3710 return Is_Check_Suppressed
(E
, Atomic_Synchronization
);
3712 -- Otherwise result depends on current scope setting
3715 return Scope_Suppress
.Suppress
(Atomic_Synchronization
);
3717 end Atomic_Synchronization_Disabled
;
3719 -------------------------------
3720 -- Build_Discriminant_Checks --
3721 -------------------------------
3723 function Build_Discriminant_Checks
3725 T_Typ
: Entity_Id
) return Node_Id
3727 Loc
: constant Source_Ptr
:= Sloc
(N
);
3730 Disc_Ent
: Entity_Id
;
3734 function Aggregate_Discriminant_Val
(Disc
: Entity_Id
) return Node_Id
;
3736 ----------------------------------
3737 -- Aggregate_Discriminant_Value --
3738 ----------------------------------
3740 function Aggregate_Discriminant_Val
(Disc
: Entity_Id
) return Node_Id
is
3744 -- The aggregate has been normalized with named associations. We use
3745 -- the Chars field to locate the discriminant to take into account
3746 -- discriminants in derived types, which carry the same name as those
3749 Assoc
:= First
(Component_Associations
(N
));
3750 while Present
(Assoc
) loop
3751 if Chars
(First
(Choices
(Assoc
))) = Chars
(Disc
) then
3752 return Expression
(Assoc
);
3758 -- Discriminant must have been found in the loop above
3760 raise Program_Error
;
3761 end Aggregate_Discriminant_Val
;
3763 -- Start of processing for Build_Discriminant_Checks
3766 -- Loop through discriminants evolving the condition
3769 Disc
:= First_Elmt
(Discriminant_Constraint
(T_Typ
));
3771 -- For a fully private type, use the discriminants of the parent type
3773 if Is_Private_Type
(T_Typ
)
3774 and then No
(Full_View
(T_Typ
))
3776 Disc_Ent
:= First_Discriminant
(Etype
(Base_Type
(T_Typ
)));
3778 Disc_Ent
:= First_Discriminant
(T_Typ
);
3781 while Present
(Disc
) loop
3782 Dval
:= Node
(Disc
);
3784 if Nkind
(Dval
) = N_Identifier
3785 and then Ekind
(Entity
(Dval
)) = E_Discriminant
3787 Dval
:= New_Occurrence_Of
(Discriminal
(Entity
(Dval
)), Loc
);
3789 Dval
:= Duplicate_Subexpr_No_Checks
(Dval
);
3792 -- If we have an Unchecked_Union node, we can infer the discriminants
3795 if Is_Unchecked_Union
(Base_Type
(T_Typ
)) then
3797 Get_Discriminant_Value
(
3798 First_Discriminant
(T_Typ
),
3800 Stored_Constraint
(T_Typ
)));
3802 elsif Nkind
(N
) = N_Aggregate
then
3804 Duplicate_Subexpr_No_Checks
3805 (Aggregate_Discriminant_Val
(Disc_Ent
));
3809 Make_Selected_Component
(Loc
,
3811 Duplicate_Subexpr_No_Checks
(N
, Name_Req
=> True),
3812 Selector_Name
=> Make_Identifier
(Loc
, Chars
(Disc_Ent
)));
3814 Set_Is_In_Discriminant_Check
(Dref
);
3817 Evolve_Or_Else
(Cond
,
3820 Right_Opnd
=> Dval
));
3823 Next_Discriminant
(Disc_Ent
);
3827 end Build_Discriminant_Checks
;
3833 function Check_Needed
(Nod
: Node_Id
; Check
: Check_Type
) return Boolean is
3840 function Left_Expression
(Op
: Node_Id
) return Node_Id
;
3841 -- Return the relevant expression from the left operand of the given
3842 -- short circuit form: this is LO itself, except if LO is a qualified
3843 -- expression, a type conversion, or an expression with actions, in
3844 -- which case this is Left_Expression (Expression (LO)).
3846 ---------------------
3847 -- Left_Expression --
3848 ---------------------
3850 function Left_Expression
(Op
: Node_Id
) return Node_Id
is
3851 LE
: Node_Id
:= Left_Opnd
(Op
);
3853 while Nkind_In
(LE
, N_Qualified_Expression
,
3855 N_Expression_With_Actions
)
3857 LE
:= Expression
(LE
);
3861 end Left_Expression
;
3863 -- Start of processing for Check_Needed
3866 -- Always check if not simple entity
3868 if Nkind
(Nod
) not in N_Has_Entity
3869 or else not Comes_From_Source
(Nod
)
3874 -- Look up tree for short circuit
3881 -- Done if out of subexpression (note that we allow generated stuff
3882 -- such as itype declarations in this context, to keep the loop going
3883 -- since we may well have generated such stuff in complex situations.
3884 -- Also done if no parent (probably an error condition, but no point
3885 -- in behaving nasty if we find it).
3888 or else (K
not in N_Subexpr
and then Comes_From_Source
(P
))
3892 -- Or/Or Else case, where test is part of the right operand, or is
3893 -- part of one of the actions associated with the right operand, and
3894 -- the left operand is an equality test.
3896 elsif K
= N_Op_Or
then
3897 exit when N
= Right_Opnd
(P
)
3898 and then Nkind
(Left_Expression
(P
)) = N_Op_Eq
;
3900 elsif K
= N_Or_Else
then
3901 exit when (N
= Right_Opnd
(P
)
3904 and then List_Containing
(N
) = Actions
(P
)))
3905 and then Nkind
(Left_Expression
(P
)) = N_Op_Eq
;
3907 -- Similar test for the And/And then case, where the left operand
3908 -- is an inequality test.
3910 elsif K
= N_Op_And
then
3911 exit when N
= Right_Opnd
(P
)
3912 and then Nkind
(Left_Expression
(P
)) = N_Op_Ne
;
3914 elsif K
= N_And_Then
then
3915 exit when (N
= Right_Opnd
(P
)
3918 and then List_Containing
(N
) = Actions
(P
)))
3919 and then Nkind
(Left_Expression
(P
)) = N_Op_Ne
;
3925 -- If we fall through the loop, then we have a conditional with an
3926 -- appropriate test as its left operand, so look further.
3928 L
:= Left_Expression
(P
);
3930 -- L is an "=" or "/=" operator: extract its operands
3932 R
:= Right_Opnd
(L
);
3935 -- Left operand of test must match original variable
3937 if Nkind
(L
) not in N_Has_Entity
or else Entity
(L
) /= Entity
(Nod
) then
3941 -- Right operand of test must be key value (zero or null)
3944 when Access_Check
=>
3945 if not Known_Null
(R
) then
3949 when Division_Check
=>
3950 if not Compile_Time_Known_Value
(R
)
3951 or else Expr_Value
(R
) /= Uint_0
3957 raise Program_Error
;
3960 -- Here we have the optimizable case, warn if not short-circuited
3962 if K
= N_Op_And
or else K
= N_Op_Or
then
3963 Error_Msg_Warn
:= SPARK_Mode
/= On
;
3966 when Access_Check
=>
3967 if GNATprove_Mode
then
3969 ("Constraint_Error might have been raised (access check)",
3973 ("Constraint_Error may be raised (access check)??",
3977 when Division_Check
=>
3978 if GNATprove_Mode
then
3980 ("Constraint_Error might have been raised (zero divide)",
3984 ("Constraint_Error may be raised (zero divide)??",
3989 raise Program_Error
;
3992 if K
= N_Op_And
then
3993 Error_Msg_N
-- CODEFIX
3994 ("use `AND THEN` instead of AND??", P
);
3996 Error_Msg_N
-- CODEFIX
3997 ("use `OR ELSE` instead of OR??", P
);
4000 -- If not short-circuited, we need the check
4004 -- If short-circuited, we can omit the check
4011 -----------------------------------
4012 -- Check_Valid_Lvalue_Subscripts --
4013 -----------------------------------
4015 procedure Check_Valid_Lvalue_Subscripts
(Expr
: Node_Id
) is
4017 -- Skip this if range checks are suppressed
4019 if Range_Checks_Suppressed
(Etype
(Expr
)) then
4022 -- Only do this check for expressions that come from source. We assume
4023 -- that expander generated assignments explicitly include any necessary
4024 -- checks. Note that this is not just an optimization, it avoids
4025 -- infinite recursions.
4027 elsif not Comes_From_Source
(Expr
) then
4030 -- For a selected component, check the prefix
4032 elsif Nkind
(Expr
) = N_Selected_Component
then
4033 Check_Valid_Lvalue_Subscripts
(Prefix
(Expr
));
4036 -- Case of indexed component
4038 elsif Nkind
(Expr
) = N_Indexed_Component
then
4039 Apply_Subscript_Validity_Checks
(Expr
);
4041 -- Prefix may itself be or contain an indexed component, and these
4042 -- subscripts need checking as well.
4044 Check_Valid_Lvalue_Subscripts
(Prefix
(Expr
));
4046 end Check_Valid_Lvalue_Subscripts
;
4048 ----------------------------------
4049 -- Null_Exclusion_Static_Checks --
4050 ----------------------------------
4052 procedure Null_Exclusion_Static_Checks
4054 Comp
: Node_Id
:= Empty
;
4055 Array_Comp
: Boolean := False)
4057 Has_Null
: constant Boolean := Has_Null_Exclusion
(N
);
4058 Kind
: constant Node_Kind
:= Nkind
(N
);
4059 Error_Nod
: Node_Id
;
4065 (Nkind_In
(Kind
, N_Component_Declaration
,
4066 N_Discriminant_Specification
,
4067 N_Function_Specification
,
4068 N_Object_Declaration
,
4069 N_Parameter_Specification
));
4071 if Kind
= N_Function_Specification
then
4072 Typ
:= Etype
(Defining_Entity
(N
));
4074 Typ
:= Etype
(Defining_Identifier
(N
));
4078 when N_Component_Declaration
=>
4079 if Present
(Access_Definition
(Component_Definition
(N
))) then
4080 Error_Nod
:= Component_Definition
(N
);
4082 Error_Nod
:= Subtype_Indication
(Component_Definition
(N
));
4085 when N_Discriminant_Specification
=>
4086 Error_Nod
:= Discriminant_Type
(N
);
4088 when N_Function_Specification
=>
4089 Error_Nod
:= Result_Definition
(N
);
4091 when N_Object_Declaration
=>
4092 Error_Nod
:= Object_Definition
(N
);
4094 when N_Parameter_Specification
=>
4095 Error_Nod
:= Parameter_Type
(N
);
4098 raise Program_Error
;
4103 -- Enforce legality rule 3.10 (13): A null exclusion can only be
4104 -- applied to an access [sub]type.
4106 if not Is_Access_Type
(Typ
) then
4108 ("`NOT NULL` allowed only for an access type", Error_Nod
);
4110 -- Enforce legality rule RM 3.10(14/1): A null exclusion can only
4111 -- be applied to a [sub]type that does not exclude null already.
4113 elsif Can_Never_Be_Null
(Typ
) and then Comes_From_Source
(Typ
) then
4115 ("`NOT NULL` not allowed (& already excludes null)",
4120 -- Check that null-excluding objects are always initialized, except for
4121 -- deferred constants, for which the expression will appear in the full
4124 if Kind
= N_Object_Declaration
4125 and then No
(Expression
(N
))
4126 and then not Constant_Present
(N
)
4127 and then not No_Initialization
(N
)
4129 if Present
(Comp
) then
4131 -- Specialize the warning message to indicate that we are dealing
4132 -- with an uninitialized composite object that has a defaulted
4133 -- null-excluding component.
4135 Error_Msg_Name_1
:= Chars
(Defining_Identifier
(Comp
));
4136 Error_Msg_Name_2
:= Chars
(Defining_Identifier
(N
));
4139 (Compile_Time_Constraint_Error
4142 "(Ada 2005) null-excluding component % of object % must "
4143 & "be initialized??",
4144 Ent
=> Defining_Identifier
(Comp
)));
4146 -- This is a case of an array with null-excluding components, so
4147 -- indicate that in the warning.
4149 elsif Array_Comp
then
4151 (Compile_Time_Constraint_Error
4154 "(Ada 2005) null-excluding array components must "
4155 & "be initialized??",
4156 Ent
=> Defining_Identifier
(N
)));
4158 -- Normal case of object of a null-excluding access type
4161 -- Add an expression that assigns null. This node is needed by
4162 -- Apply_Compile_Time_Constraint_Error, which will replace this
4163 -- with a Constraint_Error node.
4165 Set_Expression
(N
, Make_Null
(Sloc
(N
)));
4166 Set_Etype
(Expression
(N
), Etype
(Defining_Identifier
(N
)));
4168 Apply_Compile_Time_Constraint_Error
4169 (N
=> Expression
(N
),
4171 "(Ada 2005) null-excluding objects must be initialized??",
4172 Reason
=> CE_Null_Not_Allowed
);
4176 -- Check that a null-excluding component, formal or object is not being
4177 -- assigned a null value. Otherwise generate a warning message and
4178 -- replace Expression (N) by an N_Constraint_Error node.
4180 if Kind
/= N_Function_Specification
then
4181 Expr
:= Expression
(N
);
4183 if Present
(Expr
) and then Known_Null
(Expr
) then
4185 when N_Component_Declaration
4186 | N_Discriminant_Specification
4188 Apply_Compile_Time_Constraint_Error
4191 "(Ada 2005) null not allowed in null-excluding "
4193 Reason
=> CE_Null_Not_Allowed
);
4195 when N_Object_Declaration
=>
4196 Apply_Compile_Time_Constraint_Error
4199 "(Ada 2005) null not allowed in null-excluding "
4201 Reason
=> CE_Null_Not_Allowed
);
4203 when N_Parameter_Specification
=>
4204 Apply_Compile_Time_Constraint_Error
4207 "(Ada 2005) null not allowed in null-excluding "
4209 Reason
=> CE_Null_Not_Allowed
);
4216 end Null_Exclusion_Static_Checks
;
4218 ----------------------------------
4219 -- Conditional_Statements_Begin --
4220 ----------------------------------
4222 procedure Conditional_Statements_Begin
is
4224 Saved_Checks_TOS
:= Saved_Checks_TOS
+ 1;
4226 -- If stack overflows, kill all checks, that way we know to simply reset
4227 -- the number of saved checks to zero on return. This should never occur
4230 if Saved_Checks_TOS
> Saved_Checks_Stack
'Last then
4233 -- In the normal case, we just make a new stack entry saving the current
4234 -- number of saved checks for a later restore.
4237 Saved_Checks_Stack
(Saved_Checks_TOS
) := Num_Saved_Checks
;
4239 if Debug_Flag_CC
then
4240 w
("Conditional_Statements_Begin: Num_Saved_Checks = ",
4244 end Conditional_Statements_Begin
;
4246 --------------------------------
4247 -- Conditional_Statements_End --
4248 --------------------------------
4250 procedure Conditional_Statements_End
is
4252 pragma Assert
(Saved_Checks_TOS
> 0);
4254 -- If the saved checks stack overflowed, then we killed all checks, so
4255 -- setting the number of saved checks back to zero is correct. This
4256 -- should never occur in practice.
4258 if Saved_Checks_TOS
> Saved_Checks_Stack
'Last then
4259 Num_Saved_Checks
:= 0;
4261 -- In the normal case, restore the number of saved checks from the top
4265 Num_Saved_Checks
:= Saved_Checks_Stack
(Saved_Checks_TOS
);
4267 if Debug_Flag_CC
then
4268 w
("Conditional_Statements_End: Num_Saved_Checks = ",
4273 Saved_Checks_TOS
:= Saved_Checks_TOS
- 1;
4274 end Conditional_Statements_End
;
4276 -------------------------
4277 -- Convert_From_Bignum --
4278 -------------------------
4280 function Convert_From_Bignum
(N
: Node_Id
) return Node_Id
is
4281 Loc
: constant Source_Ptr
:= Sloc
(N
);
4284 pragma Assert
(Is_RTE
(Etype
(N
), RE_Bignum
));
4286 -- Construct call From Bignum
4289 Make_Function_Call
(Loc
,
4291 New_Occurrence_Of
(RTE
(RE_From_Bignum
), Loc
),
4292 Parameter_Associations
=> New_List
(Relocate_Node
(N
)));
4293 end Convert_From_Bignum
;
4295 -----------------------
4296 -- Convert_To_Bignum --
4297 -----------------------
4299 function Convert_To_Bignum
(N
: Node_Id
) return Node_Id
is
4300 Loc
: constant Source_Ptr
:= Sloc
(N
);
4303 -- Nothing to do if Bignum already except call Relocate_Node
4305 if Is_RTE
(Etype
(N
), RE_Bignum
) then
4306 return Relocate_Node
(N
);
4308 -- Otherwise construct call to To_Bignum, converting the operand to the
4309 -- required Long_Long_Integer form.
4312 pragma Assert
(Is_Signed_Integer_Type
(Etype
(N
)));
4314 Make_Function_Call
(Loc
,
4316 New_Occurrence_Of
(RTE
(RE_To_Bignum
), Loc
),
4317 Parameter_Associations
=> New_List
(
4318 Convert_To
(Standard_Long_Long_Integer
, Relocate_Node
(N
))));
4320 end Convert_To_Bignum
;
4322 ---------------------
4323 -- Determine_Range --
4324 ---------------------
4326 Cache_Size
: constant := 2 ** 10;
4327 type Cache_Index
is range 0 .. Cache_Size
- 1;
4328 -- Determine size of below cache (power of 2 is more efficient)
4330 Determine_Range_Cache_N
: array (Cache_Index
) of Node_Id
;
4331 Determine_Range_Cache_V
: array (Cache_Index
) of Boolean;
4332 Determine_Range_Cache_Lo
: array (Cache_Index
) of Uint
;
4333 Determine_Range_Cache_Hi
: array (Cache_Index
) of Uint
;
4334 Determine_Range_Cache_Lo_R
: array (Cache_Index
) of Ureal
;
4335 Determine_Range_Cache_Hi_R
: array (Cache_Index
) of Ureal
;
4336 -- The above arrays are used to implement a small direct cache for
4337 -- Determine_Range and Determine_Range_R calls. Because of the way these
4338 -- subprograms recursively traces subexpressions, and because overflow
4339 -- checking calls the routine on the way up the tree, a quadratic behavior
4340 -- can otherwise be encountered in large expressions. The cache entry for
4341 -- node N is stored in the (N mod Cache_Size) entry, and can be validated
4342 -- by checking the actual node value stored there. The Range_Cache_V array
4343 -- records the setting of Assume_Valid for the cache entry.
4345 procedure Determine_Range
4350 Assume_Valid
: Boolean := False)
4352 Typ
: Entity_Id
:= Etype
(N
);
4353 -- Type to use, may get reset to base type for possibly invalid entity
4357 -- Lo and Hi bounds of left operand
4361 -- Lo and Hi bounds of right (or only) operand
4364 -- Temp variable used to hold a bound node
4367 -- High bound of base type of expression
4371 -- Refined values for low and high bounds, after tightening
4374 -- Used in lower level calls to indicate if call succeeded
4376 Cindex
: Cache_Index
;
4377 -- Used to search cache
4382 function OK_Operands
return Boolean;
4383 -- Used for binary operators. Determines the ranges of the left and
4384 -- right operands, and if they are both OK, returns True, and puts
4385 -- the results in Lo_Right, Hi_Right, Lo_Left, Hi_Left.
4391 function OK_Operands
return Boolean is
4394 (Left_Opnd
(N
), OK1
, Lo_Left
, Hi_Left
, Assume_Valid
);
4401 (Right_Opnd
(N
), OK1
, Lo_Right
, Hi_Right
, Assume_Valid
);
4405 -- Start of processing for Determine_Range
4408 -- Prevent junk warnings by initializing range variables
4415 -- For temporary constants internally generated to remove side effects
4416 -- we must use the corresponding expression to determine the range of
4417 -- the expression. But note that the expander can also generate
4418 -- constants in other cases, including deferred constants.
4420 if Is_Entity_Name
(N
)
4421 and then Nkind
(Parent
(Entity
(N
))) = N_Object_Declaration
4422 and then Ekind
(Entity
(N
)) = E_Constant
4423 and then Is_Internal_Name
(Chars
(Entity
(N
)))
4425 if Present
(Expression
(Parent
(Entity
(N
)))) then
4427 (Expression
(Parent
(Entity
(N
))), OK
, Lo
, Hi
, Assume_Valid
);
4429 elsif Present
(Full_View
(Entity
(N
))) then
4431 (Expression
(Parent
(Full_View
(Entity
(N
)))),
4432 OK
, Lo
, Hi
, Assume_Valid
);
4440 -- If type is not defined, we can't determine its range
4444 -- We don't deal with anything except discrete types
4446 or else not Is_Discrete_Type
(Typ
)
4448 -- Ignore type for which an error has been posted, since range in
4449 -- this case may well be a bogosity deriving from the error. Also
4450 -- ignore if error posted on the reference node.
4452 or else Error_Posted
(N
) or else Error_Posted
(Typ
)
4458 -- For all other cases, we can determine the range
4462 -- If value is compile time known, then the possible range is the one
4463 -- value that we know this expression definitely has.
4465 if Compile_Time_Known_Value
(N
) then
4466 Lo
:= Expr_Value
(N
);
4471 -- Return if already in the cache
4473 Cindex
:= Cache_Index
(N
mod Cache_Size
);
4475 if Determine_Range_Cache_N
(Cindex
) = N
4477 Determine_Range_Cache_V
(Cindex
) = Assume_Valid
4479 Lo
:= Determine_Range_Cache_Lo
(Cindex
);
4480 Hi
:= Determine_Range_Cache_Hi
(Cindex
);
4484 -- Otherwise, start by finding the bounds of the type of the expression,
4485 -- the value cannot be outside this range (if it is, then we have an
4486 -- overflow situation, which is a separate check, we are talking here
4487 -- only about the expression value).
4489 -- First a check, never try to find the bounds of a generic type, since
4490 -- these bounds are always junk values, and it is only valid to look at
4491 -- the bounds in an instance.
4493 if Is_Generic_Type
(Typ
) then
4498 -- First step, change to use base type unless we know the value is valid
4500 if (Is_Entity_Name
(N
) and then Is_Known_Valid
(Entity
(N
)))
4501 or else Assume_No_Invalid_Values
4502 or else Assume_Valid
4506 Typ
:= Underlying_Type
(Base_Type
(Typ
));
4509 -- Retrieve the base type. Handle the case where the base type is a
4510 -- private enumeration type.
4512 Btyp
:= Base_Type
(Typ
);
4514 if Is_Private_Type
(Btyp
) and then Present
(Full_View
(Btyp
)) then
4515 Btyp
:= Full_View
(Btyp
);
4518 -- We use the actual bound unless it is dynamic, in which case use the
4519 -- corresponding base type bound if possible. If we can't get a bound
4520 -- then we figure we can't determine the range (a peculiar case, that
4521 -- perhaps cannot happen, but there is no point in bombing in this
4522 -- optimization circuit.
4524 -- First the low bound
4526 Bound
:= Type_Low_Bound
(Typ
);
4528 if Compile_Time_Known_Value
(Bound
) then
4529 Lo
:= Expr_Value
(Bound
);
4531 elsif Compile_Time_Known_Value
(Type_Low_Bound
(Btyp
)) then
4532 Lo
:= Expr_Value
(Type_Low_Bound
(Btyp
));
4539 -- Now the high bound
4541 Bound
:= Type_High_Bound
(Typ
);
4543 -- We need the high bound of the base type later on, and this should
4544 -- always be compile time known. Again, it is not clear that this
4545 -- can ever be false, but no point in bombing.
4547 if Compile_Time_Known_Value
(Type_High_Bound
(Btyp
)) then
4548 Hbound
:= Expr_Value
(Type_High_Bound
(Btyp
));
4556 -- If we have a static subtype, then that may have a tighter bound so
4557 -- use the upper bound of the subtype instead in this case.
4559 if Compile_Time_Known_Value
(Bound
) then
4560 Hi
:= Expr_Value
(Bound
);
4563 -- We may be able to refine this value in certain situations. If any
4564 -- refinement is possible, then Lor and Hir are set to possibly tighter
4565 -- bounds, and OK1 is set to True.
4569 -- For unary plus, result is limited by range of operand
4573 (Right_Opnd
(N
), OK1
, Lor
, Hir
, Assume_Valid
);
4575 -- For unary minus, determine range of operand, and negate it
4579 (Right_Opnd
(N
), OK1
, Lo_Right
, Hi_Right
, Assume_Valid
);
4586 -- For binary addition, get range of each operand and do the
4587 -- addition to get the result range.
4591 Lor
:= Lo_Left
+ Lo_Right
;
4592 Hir
:= Hi_Left
+ Hi_Right
;
4595 -- Division is tricky. The only case we consider is where the right
4596 -- operand is a positive constant, and in this case we simply divide
4597 -- the bounds of the left operand
4601 if Lo_Right
= Hi_Right
4602 and then Lo_Right
> 0
4604 Lor
:= Lo_Left
/ Lo_Right
;
4605 Hir
:= Hi_Left
/ Lo_Right
;
4611 -- For binary subtraction, get range of each operand and do the worst
4612 -- case subtraction to get the result range.
4614 when N_Op_Subtract
=>
4616 Lor
:= Lo_Left
- Hi_Right
;
4617 Hir
:= Hi_Left
- Lo_Right
;
4620 -- For MOD, if right operand is a positive constant, then result must
4621 -- be in the allowable range of mod results.
4625 if Lo_Right
= Hi_Right
4626 and then Lo_Right
/= 0
4628 if Lo_Right
> 0 then
4630 Hir
:= Lo_Right
- 1;
4632 else -- Lo_Right < 0
4633 Lor
:= Lo_Right
+ 1;
4642 -- For REM, if right operand is a positive constant, then result must
4643 -- be in the allowable range of mod results.
4647 if Lo_Right
= Hi_Right
and then Lo_Right
/= 0 then
4649 Dval
: constant Uint
:= (abs Lo_Right
) - 1;
4652 -- The sign of the result depends on the sign of the
4653 -- dividend (but not on the sign of the divisor, hence
4654 -- the abs operation above).
4674 -- Attribute reference cases
4676 when N_Attribute_Reference
=>
4677 case Attribute_Name
(N
) is
4679 -- For Pos/Val attributes, we can refine the range using the
4680 -- possible range of values of the attribute expression.
4686 (First
(Expressions
(N
)), OK1
, Lor
, Hir
, Assume_Valid
);
4688 -- For Length attribute, use the bounds of the corresponding
4689 -- index type to refine the range.
4693 Atyp
: Entity_Id
:= Etype
(Prefix
(N
));
4701 if Is_Access_Type
(Atyp
) then
4702 Atyp
:= Designated_Type
(Atyp
);
4705 -- For string literal, we know exact value
4707 if Ekind
(Atyp
) = E_String_Literal_Subtype
then
4709 Lo
:= String_Literal_Length
(Atyp
);
4710 Hi
:= String_Literal_Length
(Atyp
);
4714 -- Otherwise check for expression given
4716 if No
(Expressions
(N
)) then
4720 UI_To_Int
(Expr_Value
(First
(Expressions
(N
))));
4723 Indx
:= First_Index
(Atyp
);
4724 for J
in 2 .. Inum
loop
4725 Indx
:= Next_Index
(Indx
);
4728 -- If the index type is a formal type or derived from
4729 -- one, the bounds are not static.
4731 if Is_Generic_Type
(Root_Type
(Etype
(Indx
))) then
4737 (Type_Low_Bound
(Etype
(Indx
)), OK1
, LL
, LU
,
4742 (Type_High_Bound
(Etype
(Indx
)), OK1
, UL
, UU
,
4747 -- The maximum value for Length is the biggest
4748 -- possible gap between the values of the bounds.
4749 -- But of course, this value cannot be negative.
4751 Hir
:= UI_Max
(Uint_0
, UU
- LL
+ 1);
4753 -- For constrained arrays, the minimum value for
4754 -- Length is taken from the actual value of the
4755 -- bounds, since the index will be exactly of this
4758 if Is_Constrained
(Atyp
) then
4759 Lor
:= UI_Max
(Uint_0
, UL
- LU
+ 1);
4761 -- For an unconstrained array, the minimum value
4762 -- for length is always zero.
4771 -- No special handling for other attributes
4772 -- Probably more opportunities exist here???
4779 when N_Type_Conversion
=>
4781 -- For type conversion from one discrete type to another, we can
4782 -- refine the range using the converted value.
4784 if Is_Discrete_Type
(Etype
(Expression
(N
))) then
4785 Determine_Range
(Expression
(N
), OK1
, Lor
, Hir
, Assume_Valid
);
4787 -- When converting a float to an integer type, determine the range
4788 -- in real first, and then convert the bounds using UR_To_Uint
4789 -- which correctly rounds away from zero when half way between two
4790 -- integers, as required by normal Ada 95 rounding semantics. It
4791 -- is only possible because analysis in GNATprove rules out the
4792 -- possibility of a NaN or infinite value.
4794 elsif GNATprove_Mode
4795 and then Is_Floating_Point_Type
(Etype
(Expression
(N
)))
4798 Lor_Real
, Hir_Real
: Ureal
;
4800 Determine_Range_R
(Expression
(N
), OK1
, Lor_Real
, Hir_Real
,
4804 Lor
:= UR_To_Uint
(Lor_Real
);
4805 Hir
:= UR_To_Uint
(Hir_Real
);
4813 -- Nothing special to do for all other expression kinds
4821 -- At this stage, if OK1 is true, then we know that the actual result of
4822 -- the computed expression is in the range Lor .. Hir. We can use this
4823 -- to restrict the possible range of results.
4827 -- If the refined value of the low bound is greater than the type
4828 -- low bound, then reset it to the more restrictive value. However,
4829 -- we do NOT do this for the case of a modular type where the
4830 -- possible upper bound on the value is above the base type high
4831 -- bound, because that means the result could wrap.
4834 and then not (Is_Modular_Integer_Type
(Typ
) and then Hir
> Hbound
)
4839 -- Similarly, if the refined value of the high bound is less than the
4840 -- value so far, then reset it to the more restrictive value. Again,
4841 -- we do not do this if the refined low bound is negative for a
4842 -- modular type, since this would wrap.
4845 and then not (Is_Modular_Integer_Type
(Typ
) and then Lor
< Uint_0
)
4851 -- Set cache entry for future call and we are all done
4853 Determine_Range_Cache_N
(Cindex
) := N
;
4854 Determine_Range_Cache_V
(Cindex
) := Assume_Valid
;
4855 Determine_Range_Cache_Lo
(Cindex
) := Lo
;
4856 Determine_Range_Cache_Hi
(Cindex
) := Hi
;
4859 -- If any exception occurs, it means that we have some bug in the compiler,
4860 -- possibly triggered by a previous error, or by some unforeseen peculiar
4861 -- occurrence. However, this is only an optimization attempt, so there is
4862 -- really no point in crashing the compiler. Instead we just decide, too
4863 -- bad, we can't figure out a range in this case after all.
4868 -- Debug flag K disables this behavior (useful for debugging)
4870 if Debug_Flag_K
then
4878 end Determine_Range
;
4880 -----------------------
4881 -- Determine_Range_R --
4882 -----------------------
4884 procedure Determine_Range_R
4889 Assume_Valid
: Boolean := False)
4891 Typ
: Entity_Id
:= Etype
(N
);
4892 -- Type to use, may get reset to base type for possibly invalid entity
4896 -- Lo and Hi bounds of left operand
4900 -- Lo and Hi bounds of right (or only) operand
4903 -- Temp variable used to hold a bound node
4906 -- High bound of base type of expression
4910 -- Refined values for low and high bounds, after tightening
4913 -- Used in lower level calls to indicate if call succeeded
4915 Cindex
: Cache_Index
;
4916 -- Used to search cache
4921 function OK_Operands
return Boolean;
4922 -- Used for binary operators. Determines the ranges of the left and
4923 -- right operands, and if they are both OK, returns True, and puts
4924 -- the results in Lo_Right, Hi_Right, Lo_Left, Hi_Left.
4926 function Round_Machine
(B
: Ureal
) return Ureal
;
4927 -- B is a real bound. Round it using mode Round_Even.
4933 function OK_Operands
return Boolean is
4936 (Left_Opnd
(N
), OK1
, Lo_Left
, Hi_Left
, Assume_Valid
);
4943 (Right_Opnd
(N
), OK1
, Lo_Right
, Hi_Right
, Assume_Valid
);
4951 function Round_Machine
(B
: Ureal
) return Ureal
is
4953 return Machine
(Typ
, B
, Round_Even
, N
);
4956 -- Start of processing for Determine_Range_R
4959 -- Prevent junk warnings by initializing range variables
4966 -- For temporary constants internally generated to remove side effects
4967 -- we must use the corresponding expression to determine the range of
4968 -- the expression. But note that the expander can also generate
4969 -- constants in other cases, including deferred constants.
4971 if Is_Entity_Name
(N
)
4972 and then Nkind
(Parent
(Entity
(N
))) = N_Object_Declaration
4973 and then Ekind
(Entity
(N
)) = E_Constant
4974 and then Is_Internal_Name
(Chars
(Entity
(N
)))
4976 if Present
(Expression
(Parent
(Entity
(N
)))) then
4978 (Expression
(Parent
(Entity
(N
))), OK
, Lo
, Hi
, Assume_Valid
);
4980 elsif Present
(Full_View
(Entity
(N
))) then
4982 (Expression
(Parent
(Full_View
(Entity
(N
)))),
4983 OK
, Lo
, Hi
, Assume_Valid
);
4992 -- If type is not defined, we can't determine its range
4996 -- We don't deal with anything except IEEE floating-point types
4998 or else not Is_Floating_Point_Type
(Typ
)
4999 or else Float_Rep
(Typ
) /= IEEE_Binary
5001 -- Ignore type for which an error has been posted, since range in
5002 -- this case may well be a bogosity deriving from the error. Also
5003 -- ignore if error posted on the reference node.
5005 or else Error_Posted
(N
) or else Error_Posted
(Typ
)
5011 -- For all other cases, we can determine the range
5015 -- If value is compile time known, then the possible range is the one
5016 -- value that we know this expression definitely has.
5018 if Compile_Time_Known_Value
(N
) then
5019 Lo
:= Expr_Value_R
(N
);
5024 -- Return if already in the cache
5026 Cindex
:= Cache_Index
(N
mod Cache_Size
);
5028 if Determine_Range_Cache_N
(Cindex
) = N
5030 Determine_Range_Cache_V
(Cindex
) = Assume_Valid
5032 Lo
:= Determine_Range_Cache_Lo_R
(Cindex
);
5033 Hi
:= Determine_Range_Cache_Hi_R
(Cindex
);
5037 -- Otherwise, start by finding the bounds of the type of the expression,
5038 -- the value cannot be outside this range (if it is, then we have an
5039 -- overflow situation, which is a separate check, we are talking here
5040 -- only about the expression value).
5042 -- First a check, never try to find the bounds of a generic type, since
5043 -- these bounds are always junk values, and it is only valid to look at
5044 -- the bounds in an instance.
5046 if Is_Generic_Type
(Typ
) then
5051 -- First step, change to use base type unless we know the value is valid
5053 if (Is_Entity_Name
(N
) and then Is_Known_Valid
(Entity
(N
)))
5054 or else Assume_No_Invalid_Values
5055 or else Assume_Valid
5059 Typ
:= Underlying_Type
(Base_Type
(Typ
));
5062 -- Retrieve the base type. Handle the case where the base type is a
5065 Btyp
:= Base_Type
(Typ
);
5067 if Is_Private_Type
(Btyp
) and then Present
(Full_View
(Btyp
)) then
5068 Btyp
:= Full_View
(Btyp
);
5071 -- We use the actual bound unless it is dynamic, in which case use the
5072 -- corresponding base type bound if possible. If we can't get a bound
5073 -- then we figure we can't determine the range (a peculiar case, that
5074 -- perhaps cannot happen, but there is no point in bombing in this
5075 -- optimization circuit).
5077 -- First the low bound
5079 Bound
:= Type_Low_Bound
(Typ
);
5081 if Compile_Time_Known_Value
(Bound
) then
5082 Lo
:= Expr_Value_R
(Bound
);
5084 elsif Compile_Time_Known_Value
(Type_Low_Bound
(Btyp
)) then
5085 Lo
:= Expr_Value_R
(Type_Low_Bound
(Btyp
));
5092 -- Now the high bound
5094 Bound
:= Type_High_Bound
(Typ
);
5096 -- We need the high bound of the base type later on, and this should
5097 -- always be compile time known. Again, it is not clear that this
5098 -- can ever be false, but no point in bombing.
5100 if Compile_Time_Known_Value
(Type_High_Bound
(Btyp
)) then
5101 Hbound
:= Expr_Value_R
(Type_High_Bound
(Btyp
));
5109 -- If we have a static subtype, then that may have a tighter bound so
5110 -- use the upper bound of the subtype instead in this case.
5112 if Compile_Time_Known_Value
(Bound
) then
5113 Hi
:= Expr_Value_R
(Bound
);
5116 -- We may be able to refine this value in certain situations. If any
5117 -- refinement is possible, then Lor and Hir are set to possibly tighter
5118 -- bounds, and OK1 is set to True.
5122 -- For unary plus, result is limited by range of operand
5126 (Right_Opnd
(N
), OK1
, Lor
, Hir
, Assume_Valid
);
5128 -- For unary minus, determine range of operand, and negate it
5132 (Right_Opnd
(N
), OK1
, Lo_Right
, Hi_Right
, Assume_Valid
);
5139 -- For binary addition, get range of each operand and do the
5140 -- addition to get the result range.
5144 Lor
:= Round_Machine
(Lo_Left
+ Lo_Right
);
5145 Hir
:= Round_Machine
(Hi_Left
+ Hi_Right
);
5148 -- For binary subtraction, get range of each operand and do the worst
5149 -- case subtraction to get the result range.
5151 when N_Op_Subtract
=>
5153 Lor
:= Round_Machine
(Lo_Left
- Hi_Right
);
5154 Hir
:= Round_Machine
(Hi_Left
- Lo_Right
);
5157 -- For multiplication, get range of each operand and do the
5158 -- four multiplications to get the result range.
5160 when N_Op_Multiply
=>
5163 M1
: constant Ureal
:= Round_Machine
(Lo_Left
* Lo_Right
);
5164 M2
: constant Ureal
:= Round_Machine
(Lo_Left
* Hi_Right
);
5165 M3
: constant Ureal
:= Round_Machine
(Hi_Left
* Lo_Right
);
5166 M4
: constant Ureal
:= Round_Machine
(Hi_Left
* Hi_Right
);
5169 Lor
:= UR_Min
(UR_Min
(M1
, M2
), UR_Min
(M3
, M4
));
5170 Hir
:= UR_Max
(UR_Max
(M1
, M2
), UR_Max
(M3
, M4
));
5174 -- For division, consider separately the cases where the right
5175 -- operand is positive or negative. Otherwise, the right operand
5176 -- can be arbitrarily close to zero, so the result is likely to
5177 -- be unbounded in one direction, do not attempt to compute it.
5182 -- Right operand is positive
5184 if Lo_Right
> Ureal_0
then
5186 -- If the low bound of the left operand is negative, obtain
5187 -- the overall low bound by dividing it by the smallest
5188 -- value of the right operand, and otherwise by the largest
5189 -- value of the right operand.
5191 if Lo_Left
< Ureal_0
then
5192 Lor
:= Round_Machine
(Lo_Left
/ Lo_Right
);
5194 Lor
:= Round_Machine
(Lo_Left
/ Hi_Right
);
5197 -- If the high bound of the left operand is negative, obtain
5198 -- the overall high bound by dividing it by the largest
5199 -- value of the right operand, and otherwise by the
5200 -- smallest value of the right operand.
5202 if Hi_Left
< Ureal_0
then
5203 Hir
:= Round_Machine
(Hi_Left
/ Hi_Right
);
5205 Hir
:= Round_Machine
(Hi_Left
/ Lo_Right
);
5208 -- Right operand is negative
5210 elsif Hi_Right
< Ureal_0
then
5212 -- If the low bound of the left operand is negative, obtain
5213 -- the overall low bound by dividing it by the largest
5214 -- value of the right operand, and otherwise by the smallest
5215 -- value of the right operand.
5217 if Lo_Left
< Ureal_0
then
5218 Lor
:= Round_Machine
(Lo_Left
/ Hi_Right
);
5220 Lor
:= Round_Machine
(Lo_Left
/ Lo_Right
);
5223 -- If the high bound of the left operand is negative, obtain
5224 -- the overall high bound by dividing it by the smallest
5225 -- value of the right operand, and otherwise by the
5226 -- largest value of the right operand.
5228 if Hi_Left
< Ureal_0
then
5229 Hir
:= Round_Machine
(Hi_Left
/ Lo_Right
);
5231 Hir
:= Round_Machine
(Hi_Left
/ Hi_Right
);
5239 when N_Type_Conversion
=>
5241 -- For type conversion from one floating-point type to another, we
5242 -- can refine the range using the converted value.
5244 if Is_Floating_Point_Type
(Etype
(Expression
(N
))) then
5245 Determine_Range_R
(Expression
(N
), OK1
, Lor
, Hir
, Assume_Valid
);
5247 -- When converting an integer to a floating-point type, determine
5248 -- the range in integer first, and then convert the bounds.
5250 elsif Is_Discrete_Type
(Etype
(Expression
(N
))) then
5257 (Expression
(N
), OK1
, Lor_Int
, Hir_Int
, Assume_Valid
);
5260 Lor
:= Round_Machine
(UR_From_Uint
(Lor_Int
));
5261 Hir
:= Round_Machine
(UR_From_Uint
(Hir_Int
));
5269 -- Nothing special to do for all other expression kinds
5277 -- At this stage, if OK1 is true, then we know that the actual result of
5278 -- the computed expression is in the range Lor .. Hir. We can use this
5279 -- to restrict the possible range of results.
5283 -- If the refined value of the low bound is greater than the type
5284 -- low bound, then reset it to the more restrictive value.
5290 -- Similarly, if the refined value of the high bound is less than the
5291 -- value so far, then reset it to the more restrictive value.
5298 -- Set cache entry for future call and we are all done
5300 Determine_Range_Cache_N
(Cindex
) := N
;
5301 Determine_Range_Cache_V
(Cindex
) := Assume_Valid
;
5302 Determine_Range_Cache_Lo_R
(Cindex
) := Lo
;
5303 Determine_Range_Cache_Hi_R
(Cindex
) := Hi
;
5306 -- If any exception occurs, it means that we have some bug in the compiler,
5307 -- possibly triggered by a previous error, or by some unforeseen peculiar
5308 -- occurrence. However, this is only an optimization attempt, so there is
5309 -- really no point in crashing the compiler. Instead we just decide, too
5310 -- bad, we can't figure out a range in this case after all.
5315 -- Debug flag K disables this behavior (useful for debugging)
5317 if Debug_Flag_K
then
5325 end Determine_Range_R
;
5327 ------------------------------------
5328 -- Discriminant_Checks_Suppressed --
5329 ------------------------------------
5331 function Discriminant_Checks_Suppressed
(E
: Entity_Id
) return Boolean is
5334 if Is_Unchecked_Union
(E
) then
5336 elsif Checks_May_Be_Suppressed
(E
) then
5337 return Is_Check_Suppressed
(E
, Discriminant_Check
);
5341 return Scope_Suppress
.Suppress
(Discriminant_Check
);
5342 end Discriminant_Checks_Suppressed
;
5344 --------------------------------
5345 -- Division_Checks_Suppressed --
5346 --------------------------------
5348 function Division_Checks_Suppressed
(E
: Entity_Id
) return Boolean is
5350 if Present
(E
) and then Checks_May_Be_Suppressed
(E
) then
5351 return Is_Check_Suppressed
(E
, Division_Check
);
5353 return Scope_Suppress
.Suppress
(Division_Check
);
5355 end Division_Checks_Suppressed
;
5357 --------------------------------------
5358 -- Duplicated_Tag_Checks_Suppressed --
5359 --------------------------------------
5361 function Duplicated_Tag_Checks_Suppressed
(E
: Entity_Id
) return Boolean is
5363 if Present
(E
) and then Checks_May_Be_Suppressed
(E
) then
5364 return Is_Check_Suppressed
(E
, Duplicated_Tag_Check
);
5366 return Scope_Suppress
.Suppress
(Duplicated_Tag_Check
);
5368 end Duplicated_Tag_Checks_Suppressed
;
5370 -----------------------------------
5371 -- Elaboration_Checks_Suppressed --
5372 -----------------------------------
5374 function Elaboration_Checks_Suppressed
(E
: Entity_Id
) return Boolean is
5376 -- The complication in this routine is that if we are in the dynamic
5377 -- model of elaboration, we also check All_Checks, since All_Checks
5378 -- does not set Elaboration_Check explicitly.
5381 if Kill_Elaboration_Checks
(E
) then
5384 elsif Checks_May_Be_Suppressed
(E
) then
5385 if Is_Check_Suppressed
(E
, Elaboration_Check
) then
5387 elsif Dynamic_Elaboration_Checks
then
5388 return Is_Check_Suppressed
(E
, All_Checks
);
5395 if Scope_Suppress
.Suppress
(Elaboration_Check
) then
5397 elsif Dynamic_Elaboration_Checks
then
5398 return Scope_Suppress
.Suppress
(All_Checks
);
5402 end Elaboration_Checks_Suppressed
;
5404 ---------------------------
5405 -- Enable_Overflow_Check --
5406 ---------------------------
5408 procedure Enable_Overflow_Check
(N
: Node_Id
) is
5409 Typ
: constant Entity_Id
:= Base_Type
(Etype
(N
));
5410 Mode
: constant Overflow_Mode_Type
:= Overflow_Check_Mode
;
5418 Do_Ovflow_Check
: Boolean;
5421 if Debug_Flag_CC
then
5422 w
("Enable_Overflow_Check for node ", Int
(N
));
5423 Write_Str
(" Source location = ");
5428 -- No check if overflow checks suppressed for type of node
5430 if Overflow_Checks_Suppressed
(Etype
(N
)) then
5433 -- Nothing to do for unsigned integer types, which do not overflow
5435 elsif Is_Modular_Integer_Type
(Typ
) then
5439 -- This is the point at which processing for STRICT mode diverges
5440 -- from processing for MINIMIZED/ELIMINATED modes. This divergence is
5441 -- probably more extreme that it needs to be, but what is going on here
5442 -- is that when we introduced MINIMIZED/ELIMINATED modes, we wanted
5443 -- to leave the processing for STRICT mode untouched. There were
5444 -- two reasons for this. First it avoided any incompatible change of
5445 -- behavior. Second, it guaranteed that STRICT mode continued to be
5448 -- The big difference is that in STRICT mode there is a fair amount of
5449 -- circuitry to try to avoid setting the Do_Overflow_Check flag if we
5450 -- know that no check is needed. We skip all that in the two new modes,
5451 -- since really overflow checking happens over a whole subtree, and we
5452 -- do the corresponding optimizations later on when applying the checks.
5454 if Mode
in Minimized_Or_Eliminated
then
5455 if not (Overflow_Checks_Suppressed
(Etype
(N
)))
5456 and then not (Is_Entity_Name
(N
)
5457 and then Overflow_Checks_Suppressed
(Entity
(N
)))
5459 Activate_Overflow_Check
(N
);
5462 if Debug_Flag_CC
then
5463 w
("Minimized/Eliminated mode");
5469 -- Remainder of processing is for STRICT case, and is unchanged from
5470 -- earlier versions preceding the addition of MINIMIZED/ELIMINATED.
5472 -- Nothing to do if the range of the result is known OK. We skip this
5473 -- for conversions, since the caller already did the check, and in any
5474 -- case the condition for deleting the check for a type conversion is
5477 if Nkind
(N
) /= N_Type_Conversion
then
5478 Determine_Range
(N
, OK
, Lo
, Hi
, Assume_Valid
=> True);
5480 -- Note in the test below that we assume that the range is not OK
5481 -- if a bound of the range is equal to that of the type. That's not
5482 -- quite accurate but we do this for the following reasons:
5484 -- a) The way that Determine_Range works, it will typically report
5485 -- the bounds of the value as being equal to the bounds of the
5486 -- type, because it either can't tell anything more precise, or
5487 -- does not think it is worth the effort to be more precise.
5489 -- b) It is very unusual to have a situation in which this would
5490 -- generate an unnecessary overflow check (an example would be
5491 -- a subtype with a range 0 .. Integer'Last - 1 to which the
5492 -- literal value one is added).
5494 -- c) The alternative is a lot of special casing in this routine
5495 -- which would partially duplicate Determine_Range processing.
5498 Do_Ovflow_Check
:= True;
5500 -- Note that the following checks are quite deliberately > and <
5501 -- rather than >= and <= as explained above.
5503 if Lo
> Expr_Value
(Type_Low_Bound
(Typ
))
5505 Hi
< Expr_Value
(Type_High_Bound
(Typ
))
5507 Do_Ovflow_Check
:= False;
5509 -- Despite the comments above, it is worth dealing specially with
5510 -- division specially. The only case where integer division can
5511 -- overflow is (largest negative number) / (-1). So we will do
5512 -- an extra range analysis to see if this is possible.
5514 elsif Nkind
(N
) = N_Op_Divide
then
5516 (Left_Opnd
(N
), OK
, Lo
, Hi
, Assume_Valid
=> True);
5518 if OK
and then Lo
> Expr_Value
(Type_Low_Bound
(Typ
)) then
5519 Do_Ovflow_Check
:= False;
5523 (Right_Opnd
(N
), OK
, Lo
, Hi
, Assume_Valid
=> True);
5525 if OK
and then (Lo
> Uint_Minus_1
5529 Do_Ovflow_Check
:= False;
5534 -- If no overflow check required, we are done
5536 if not Do_Ovflow_Check
then
5537 if Debug_Flag_CC
then
5538 w
("No overflow check required");
5546 -- If not in optimizing mode, set flag and we are done. We are also done
5547 -- (and just set the flag) if the type is not a discrete type, since it
5548 -- is not worth the effort to eliminate checks for other than discrete
5549 -- types. In addition, we take this same path if we have stored the
5550 -- maximum number of checks possible already (a very unlikely situation,
5551 -- but we do not want to blow up).
5553 if Optimization_Level
= 0
5554 or else not Is_Discrete_Type
(Etype
(N
))
5555 or else Num_Saved_Checks
= Saved_Checks
'Last
5557 Activate_Overflow_Check
(N
);
5559 if Debug_Flag_CC
then
5560 w
("Optimization off");
5566 -- Otherwise evaluate and check the expression
5571 Target_Type
=> Empty
,
5577 if Debug_Flag_CC
then
5578 w
("Called Find_Check");
5582 w
(" Check_Num = ", Chk
);
5583 w
(" Ent = ", Int
(Ent
));
5584 Write_Str
(" Ofs = ");
5589 -- If check is not of form to optimize, then set flag and we are done
5592 Activate_Overflow_Check
(N
);
5596 -- If check is already performed, then return without setting flag
5599 if Debug_Flag_CC
then
5600 w
("Check suppressed!");
5606 -- Here we will make a new entry for the new check
5608 Activate_Overflow_Check
(N
);
5609 Num_Saved_Checks
:= Num_Saved_Checks
+ 1;
5610 Saved_Checks
(Num_Saved_Checks
) :=
5615 Target_Type
=> Empty
);
5617 if Debug_Flag_CC
then
5618 w
("Make new entry, check number = ", Num_Saved_Checks
);
5619 w
(" Entity = ", Int
(Ent
));
5620 Write_Str
(" Offset = ");
5622 w
(" Check_Type = O");
5623 w
(" Target_Type = Empty");
5626 -- If we get an exception, then something went wrong, probably because of
5627 -- an error in the structure of the tree due to an incorrect program. Or
5628 -- it may be a bug in the optimization circuit. In either case the safest
5629 -- thing is simply to set the check flag unconditionally.
5633 Activate_Overflow_Check
(N
);
5635 if Debug_Flag_CC
then
5636 w
(" exception occurred, overflow flag set");
5640 end Enable_Overflow_Check
;
5642 ------------------------
5643 -- Enable_Range_Check --
5644 ------------------------
5646 procedure Enable_Range_Check
(N
: Node_Id
) is
5655 -- Return if unchecked type conversion with range check killed. In this
5656 -- case we never set the flag (that's what Kill_Range_Check is about).
5658 if Nkind
(N
) = N_Unchecked_Type_Conversion
5659 and then Kill_Range_Check
(N
)
5664 -- Do not set range check flag if parent is assignment statement or
5665 -- object declaration with Suppress_Assignment_Checks flag set
5667 if Nkind_In
(Parent
(N
), N_Assignment_Statement
, N_Object_Declaration
)
5668 and then Suppress_Assignment_Checks
(Parent
(N
))
5673 -- Check for various cases where we should suppress the range check
5675 -- No check if range checks suppressed for type of node
5677 if Present
(Etype
(N
)) and then Range_Checks_Suppressed
(Etype
(N
)) then
5680 -- No check if node is an entity name, and range checks are suppressed
5681 -- for this entity, or for the type of this entity.
5683 elsif Is_Entity_Name
(N
)
5684 and then (Range_Checks_Suppressed
(Entity
(N
))
5685 or else Range_Checks_Suppressed
(Etype
(Entity
(N
))))
5689 -- No checks if index of array, and index checks are suppressed for
5690 -- the array object or the type of the array.
5692 elsif Nkind
(Parent
(N
)) = N_Indexed_Component
then
5694 Pref
: constant Node_Id
:= Prefix
(Parent
(N
));
5696 if Is_Entity_Name
(Pref
)
5697 and then Index_Checks_Suppressed
(Entity
(Pref
))
5700 elsif Index_Checks_Suppressed
(Etype
(Pref
)) then
5706 -- Debug trace output
5708 if Debug_Flag_CC
then
5709 w
("Enable_Range_Check for node ", Int
(N
));
5710 Write_Str
(" Source location = ");
5715 -- If not in optimizing mode, set flag and we are done. We are also done
5716 -- (and just set the flag) if the type is not a discrete type, since it
5717 -- is not worth the effort to eliminate checks for other than discrete
5718 -- types. In addition, we take this same path if we have stored the
5719 -- maximum number of checks possible already (a very unlikely situation,
5720 -- but we do not want to blow up).
5722 if Optimization_Level
= 0
5723 or else No
(Etype
(N
))
5724 or else not Is_Discrete_Type
(Etype
(N
))
5725 or else Num_Saved_Checks
= Saved_Checks
'Last
5727 Activate_Range_Check
(N
);
5729 if Debug_Flag_CC
then
5730 w
("Optimization off");
5736 -- Otherwise find out the target type
5740 -- For assignment, use left side subtype
5742 if Nkind
(P
) = N_Assignment_Statement
5743 and then Expression
(P
) = N
5745 Ttyp
:= Etype
(Name
(P
));
5747 -- For indexed component, use subscript subtype
5749 elsif Nkind
(P
) = N_Indexed_Component
then
5756 Atyp
:= Etype
(Prefix
(P
));
5758 if Is_Access_Type
(Atyp
) then
5759 Atyp
:= Designated_Type
(Atyp
);
5761 -- If the prefix is an access to an unconstrained array,
5762 -- perform check unconditionally: it depends on the bounds of
5763 -- an object and we cannot currently recognize whether the test
5764 -- may be redundant.
5766 if not Is_Constrained
(Atyp
) then
5767 Activate_Range_Check
(N
);
5771 -- Ditto if prefix is simply an unconstrained array. We used
5772 -- to think this case was OK, if the prefix was not an explicit
5773 -- dereference, but we have now seen a case where this is not
5774 -- true, so it is safer to just suppress the optimization in this
5775 -- case. The back end is getting better at eliminating redundant
5776 -- checks in any case, so the loss won't be important.
5778 elsif Is_Array_Type
(Atyp
)
5779 and then not Is_Constrained
(Atyp
)
5781 Activate_Range_Check
(N
);
5785 Indx
:= First_Index
(Atyp
);
5786 Subs
:= First
(Expressions
(P
));
5789 Ttyp
:= Etype
(Indx
);
5798 -- For now, ignore all other cases, they are not so interesting
5801 if Debug_Flag_CC
then
5802 w
(" target type not found, flag set");
5805 Activate_Range_Check
(N
);
5809 -- Evaluate and check the expression
5814 Target_Type
=> Ttyp
,
5820 if Debug_Flag_CC
then
5821 w
("Called Find_Check");
5822 w
("Target_Typ = ", Int
(Ttyp
));
5826 w
(" Check_Num = ", Chk
);
5827 w
(" Ent = ", Int
(Ent
));
5828 Write_Str
(" Ofs = ");
5833 -- If check is not of form to optimize, then set flag and we are done
5836 if Debug_Flag_CC
then
5837 w
(" expression not of optimizable type, flag set");
5840 Activate_Range_Check
(N
);
5844 -- If check is already performed, then return without setting flag
5847 if Debug_Flag_CC
then
5848 w
("Check suppressed!");
5854 -- Here we will make a new entry for the new check
5856 Activate_Range_Check
(N
);
5857 Num_Saved_Checks
:= Num_Saved_Checks
+ 1;
5858 Saved_Checks
(Num_Saved_Checks
) :=
5863 Target_Type
=> Ttyp
);
5865 if Debug_Flag_CC
then
5866 w
("Make new entry, check number = ", Num_Saved_Checks
);
5867 w
(" Entity = ", Int
(Ent
));
5868 Write_Str
(" Offset = ");
5870 w
(" Check_Type = R");
5871 w
(" Target_Type = ", Int
(Ttyp
));
5872 pg
(Union_Id
(Ttyp
));
5875 -- If we get an exception, then something went wrong, probably because of
5876 -- an error in the structure of the tree due to an incorrect program. Or
5877 -- it may be a bug in the optimization circuit. In either case the safest
5878 -- thing is simply to set the check flag unconditionally.
5882 Activate_Range_Check
(N
);
5884 if Debug_Flag_CC
then
5885 w
(" exception occurred, range flag set");
5889 end Enable_Range_Check
;
5895 procedure Ensure_Valid
5897 Holes_OK
: Boolean := False;
5898 Related_Id
: Entity_Id
:= Empty
;
5899 Is_Low_Bound
: Boolean := False;
5900 Is_High_Bound
: Boolean := False)
5902 Typ
: constant Entity_Id
:= Etype
(Expr
);
5905 -- Ignore call if we are not doing any validity checking
5907 if not Validity_Checks_On
then
5910 -- Ignore call if range or validity checks suppressed on entity or type
5912 elsif Range_Or_Validity_Checks_Suppressed
(Expr
) then
5915 -- No check required if expression is from the expander, we assume the
5916 -- expander will generate whatever checks are needed. Note that this is
5917 -- not just an optimization, it avoids infinite recursions.
5919 -- Unchecked conversions must be checked, unless they are initialized
5920 -- scalar values, as in a component assignment in an init proc.
5922 -- In addition, we force a check if Force_Validity_Checks is set
5924 elsif not Comes_From_Source
(Expr
)
5925 and then not Force_Validity_Checks
5926 and then (Nkind
(Expr
) /= N_Unchecked_Type_Conversion
5927 or else Kill_Range_Check
(Expr
))
5931 -- No check required if expression is known to have valid value
5933 elsif Expr_Known_Valid
(Expr
) then
5936 -- No check needed within a generated predicate function. Validity
5937 -- of input value will have been checked earlier.
5939 elsif Ekind
(Current_Scope
) = E_Function
5940 and then Is_Predicate_Function
(Current_Scope
)
5944 -- Ignore case of enumeration with holes where the flag is set not to
5945 -- worry about holes, since no special validity check is needed
5947 elsif Is_Enumeration_Type
(Typ
)
5948 and then Has_Non_Standard_Rep
(Typ
)
5953 -- No check required on the left-hand side of an assignment
5955 elsif Nkind
(Parent
(Expr
)) = N_Assignment_Statement
5956 and then Expr
= Name
(Parent
(Expr
))
5960 -- No check on a universal real constant. The context will eventually
5961 -- convert it to a machine number for some target type, or report an
5964 elsif Nkind
(Expr
) = N_Real_Literal
5965 and then Etype
(Expr
) = Universal_Real
5969 -- If the expression denotes a component of a packed boolean array,
5970 -- no possible check applies. We ignore the old ACATS chestnuts that
5971 -- involve Boolean range True..True.
5973 -- Note: validity checks are generated for expressions that yield a
5974 -- scalar type, when it is possible to create a value that is outside of
5975 -- the type. If this is a one-bit boolean no such value exists. This is
5976 -- an optimization, and it also prevents compiler blowing up during the
5977 -- elaboration of improperly expanded packed array references.
5979 elsif Nkind
(Expr
) = N_Indexed_Component
5980 and then Is_Bit_Packed_Array
(Etype
(Prefix
(Expr
)))
5981 and then Root_Type
(Etype
(Expr
)) = Standard_Boolean
5985 -- For an expression with actions, we want to insert the validity check
5986 -- on the final Expression.
5988 elsif Nkind
(Expr
) = N_Expression_With_Actions
then
5989 Ensure_Valid
(Expression
(Expr
));
5992 -- An annoying special case. If this is an out parameter of a scalar
5993 -- type, then the value is not going to be accessed, therefore it is
5994 -- inappropriate to do any validity check at the call site.
5997 -- Only need to worry about scalar types
5999 if Is_Scalar_Type
(Typ
) then
6009 -- Find actual argument (which may be a parameter association)
6010 -- and the parent of the actual argument (the call statement)
6015 if Nkind
(P
) = N_Parameter_Association
then
6020 -- Only need to worry if we are argument of a procedure call
6021 -- since functions don't have out parameters. If this is an
6022 -- indirect or dispatching call, get signature from the
6025 if Nkind
(P
) = N_Procedure_Call_Statement
then
6026 L
:= Parameter_Associations
(P
);
6028 if Is_Entity_Name
(Name
(P
)) then
6029 E
:= Entity
(Name
(P
));
6031 pragma Assert
(Nkind
(Name
(P
)) = N_Explicit_Dereference
);
6032 E
:= Etype
(Name
(P
));
6035 -- Only need to worry if there are indeed actuals, and if
6036 -- this could be a procedure call, otherwise we cannot get a
6037 -- match (either we are not an argument, or the mode of the
6038 -- formal is not OUT). This test also filters out the
6041 if Is_Non_Empty_List
(L
) and then Is_Subprogram
(E
) then
6043 -- This is the loop through parameters, looking for an
6044 -- OUT parameter for which we are the argument.
6046 F
:= First_Formal
(E
);
6048 while Present
(F
) loop
6049 if Ekind
(F
) = E_Out_Parameter
and then A
= N
then
6062 -- If this is a boolean expression, only its elementary operands need
6063 -- checking: if they are valid, a boolean or short-circuit operation
6064 -- with them will be valid as well.
6066 if Base_Type
(Typ
) = Standard_Boolean
6068 (Nkind
(Expr
) in N_Op
or else Nkind
(Expr
) in N_Short_Circuit
)
6073 -- If we fall through, a validity check is required
6075 Insert_Valid_Check
(Expr
, Related_Id
, Is_Low_Bound
, Is_High_Bound
);
6077 if Is_Entity_Name
(Expr
)
6078 and then Safe_To_Capture_Value
(Expr
, Entity
(Expr
))
6080 Set_Is_Known_Valid
(Entity
(Expr
));
6084 ----------------------
6085 -- Expr_Known_Valid --
6086 ----------------------
6088 function Expr_Known_Valid
(Expr
: Node_Id
) return Boolean is
6089 Typ
: constant Entity_Id
:= Etype
(Expr
);
6092 -- Non-scalar types are always considered valid, since they never give
6093 -- rise to the issues of erroneous or bounded error behavior that are
6094 -- the concern. In formal reference manual terms the notion of validity
6095 -- only applies to scalar types. Note that even when packed arrays are
6096 -- represented using modular types, they are still arrays semantically,
6097 -- so they are also always valid (in particular, the unused bits can be
6098 -- random rubbish without affecting the validity of the array value).
6100 if not Is_Scalar_Type
(Typ
) or else Is_Packed_Array_Impl_Type
(Typ
) then
6103 -- If no validity checking, then everything is considered valid
6105 elsif not Validity_Checks_On
then
6108 -- Floating-point types are considered valid unless floating-point
6109 -- validity checks have been specifically turned on.
6111 elsif Is_Floating_Point_Type
(Typ
)
6112 and then not Validity_Check_Floating_Point
6116 -- If the expression is the value of an object that is known to be
6117 -- valid, then clearly the expression value itself is valid.
6119 elsif Is_Entity_Name
(Expr
)
6120 and then Is_Known_Valid
(Entity
(Expr
))
6122 -- Exclude volatile variables
6124 and then not Treat_As_Volatile
(Entity
(Expr
))
6128 -- References to discriminants are always considered valid. The value
6129 -- of a discriminant gets checked when the object is built. Within the
6130 -- record, we consider it valid, and it is important to do so, since
6131 -- otherwise we can try to generate bogus validity checks which
6132 -- reference discriminants out of scope. Discriminants of concurrent
6133 -- types are excluded for the same reason.
6135 elsif Is_Entity_Name
(Expr
)
6136 and then Denotes_Discriminant
(Expr
, Check_Concurrent
=> True)
6140 -- If the type is one for which all values are known valid, then we are
6141 -- sure that the value is valid except in the slightly odd case where
6142 -- the expression is a reference to a variable whose size has been
6143 -- explicitly set to a value greater than the object size.
6145 elsif Is_Known_Valid
(Typ
) then
6146 if Is_Entity_Name
(Expr
)
6147 and then Ekind
(Entity
(Expr
)) = E_Variable
6148 and then Esize
(Entity
(Expr
)) > Esize
(Typ
)
6155 -- Integer and character literals always have valid values, where
6156 -- appropriate these will be range checked in any case.
6158 elsif Nkind_In
(Expr
, N_Integer_Literal
, N_Character_Literal
) then
6161 -- If we have a type conversion or a qualification of a known valid
6162 -- value, then the result will always be valid.
6164 elsif Nkind_In
(Expr
, N_Type_Conversion
, N_Qualified_Expression
) then
6165 return Expr_Known_Valid
(Expression
(Expr
));
6167 -- Case of expression is a non-floating-point operator. In this case we
6168 -- can assume the result is valid the generated code for the operator
6169 -- will include whatever checks are needed (e.g. range checks) to ensure
6170 -- validity. This assumption does not hold for the floating-point case,
6171 -- since floating-point operators can generate Infinite or NaN results
6172 -- which are considered invalid.
6174 -- Historical note: in older versions, the exemption of floating-point
6175 -- types from this assumption was done only in cases where the parent
6176 -- was an assignment, function call or parameter association. Presumably
6177 -- the idea was that in other contexts, the result would be checked
6178 -- elsewhere, but this list of cases was missing tests (at least the
6179 -- N_Object_Declaration case, as shown by a reported missing validity
6180 -- check), and it is not clear why function calls but not procedure
6181 -- calls were tested for. It really seems more accurate and much
6182 -- safer to recognize that expressions which are the result of a
6183 -- floating-point operator can never be assumed to be valid.
6185 elsif Nkind
(Expr
) in N_Op
and then not Is_Floating_Point_Type
(Typ
) then
6188 -- The result of a membership test is always valid, since it is true or
6189 -- false, there are no other possibilities.
6191 elsif Nkind
(Expr
) in N_Membership_Test
then
6194 -- For all other cases, we do not know the expression is valid
6199 end Expr_Known_Valid
;
6205 procedure Find_Check
6207 Check_Type
: Character;
6208 Target_Type
: Entity_Id
;
6209 Entry_OK
: out Boolean;
6210 Check_Num
: out Nat
;
6211 Ent
: out Entity_Id
;
6214 function Within_Range_Of
6215 (Target_Type
: Entity_Id
;
6216 Check_Type
: Entity_Id
) return Boolean;
6217 -- Given a requirement for checking a range against Target_Type, and
6218 -- and a range Check_Type against which a check has already been made,
6219 -- determines if the check against check type is sufficient to ensure
6220 -- that no check against Target_Type is required.
6222 ---------------------
6223 -- Within_Range_Of --
6224 ---------------------
6226 function Within_Range_Of
6227 (Target_Type
: Entity_Id
;
6228 Check_Type
: Entity_Id
) return Boolean
6231 if Target_Type
= Check_Type
then
6236 Tlo
: constant Node_Id
:= Type_Low_Bound
(Target_Type
);
6237 Thi
: constant Node_Id
:= Type_High_Bound
(Target_Type
);
6238 Clo
: constant Node_Id
:= Type_Low_Bound
(Check_Type
);
6239 Chi
: constant Node_Id
:= Type_High_Bound
(Check_Type
);
6243 or else (Compile_Time_Known_Value
(Tlo
)
6245 Compile_Time_Known_Value
(Clo
)
6247 Expr_Value
(Clo
) >= Expr_Value
(Tlo
)))
6250 or else (Compile_Time_Known_Value
(Thi
)
6252 Compile_Time_Known_Value
(Chi
)
6254 Expr_Value
(Chi
) <= Expr_Value
(Clo
)))
6262 end Within_Range_Of
;
6264 -- Start of processing for Find_Check
6267 -- Establish default, in case no entry is found
6271 -- Case of expression is simple entity reference
6273 if Is_Entity_Name
(Expr
) then
6274 Ent
:= Entity
(Expr
);
6277 -- Case of expression is entity + known constant
6279 elsif Nkind
(Expr
) = N_Op_Add
6280 and then Compile_Time_Known_Value
(Right_Opnd
(Expr
))
6281 and then Is_Entity_Name
(Left_Opnd
(Expr
))
6283 Ent
:= Entity
(Left_Opnd
(Expr
));
6284 Ofs
:= Expr_Value
(Right_Opnd
(Expr
));
6286 -- Case of expression is entity - known constant
6288 elsif Nkind
(Expr
) = N_Op_Subtract
6289 and then Compile_Time_Known_Value
(Right_Opnd
(Expr
))
6290 and then Is_Entity_Name
(Left_Opnd
(Expr
))
6292 Ent
:= Entity
(Left_Opnd
(Expr
));
6293 Ofs
:= UI_Negate
(Expr_Value
(Right_Opnd
(Expr
)));
6295 -- Any other expression is not of the right form
6304 -- Come here with expression of appropriate form, check if entity is an
6305 -- appropriate one for our purposes.
6307 if (Ekind
(Ent
) = E_Variable
6308 or else Is_Constant_Object
(Ent
))
6309 and then not Is_Library_Level_Entity
(Ent
)
6317 -- See if there is matching check already
6319 for J
in reverse 1 .. Num_Saved_Checks
loop
6321 SC
: Saved_Check
renames Saved_Checks
(J
);
6323 if SC
.Killed
= False
6324 and then SC
.Entity
= Ent
6325 and then SC
.Offset
= Ofs
6326 and then SC
.Check_Type
= Check_Type
6327 and then Within_Range_Of
(Target_Type
, SC
.Target_Type
)
6335 -- If we fall through entry was not found
6340 ---------------------------------
6341 -- Generate_Discriminant_Check --
6342 ---------------------------------
6344 -- Note: the code for this procedure is derived from the
6345 -- Emit_Discriminant_Check Routine in trans.c.
6347 procedure Generate_Discriminant_Check
(N
: Node_Id
) is
6348 Loc
: constant Source_Ptr
:= Sloc
(N
);
6349 Pref
: constant Node_Id
:= Prefix
(N
);
6350 Sel
: constant Node_Id
:= Selector_Name
(N
);
6352 Orig_Comp
: constant Entity_Id
:=
6353 Original_Record_Component
(Entity
(Sel
));
6354 -- The original component to be checked
6356 Discr_Fct
: constant Entity_Id
:=
6357 Discriminant_Checking_Func
(Orig_Comp
);
6358 -- The discriminant checking function
6361 -- One discriminant to be checked in the type
6363 Real_Discr
: Entity_Id
;
6364 -- Actual discriminant in the call
6366 Pref_Type
: Entity_Id
;
6367 -- Type of relevant prefix (ignoring private/access stuff)
6370 -- List of arguments for function call
6373 -- Keep track of the formal corresponding to the actual we build for
6374 -- each discriminant, in order to be able to perform the necessary type
6378 -- Selected component reference for checking function argument
6381 Pref_Type
:= Etype
(Pref
);
6383 -- Force evaluation of the prefix, so that it does not get evaluated
6384 -- twice (once for the check, once for the actual reference). Such a
6385 -- double evaluation is always a potential source of inefficiency, and
6386 -- is functionally incorrect in the volatile case, or when the prefix
6387 -- may have side effects. A nonvolatile entity or a component of a
6388 -- nonvolatile entity requires no evaluation.
6390 if Is_Entity_Name
(Pref
) then
6391 if Treat_As_Volatile
(Entity
(Pref
)) then
6392 Force_Evaluation
(Pref
, Name_Req
=> True);
6395 elsif Treat_As_Volatile
(Etype
(Pref
)) then
6396 Force_Evaluation
(Pref
, Name_Req
=> True);
6398 elsif Nkind
(Pref
) = N_Selected_Component
6399 and then Is_Entity_Name
(Prefix
(Pref
))
6404 Force_Evaluation
(Pref
, Name_Req
=> True);
6407 -- For a tagged type, use the scope of the original component to
6408 -- obtain the type, because ???
6410 if Is_Tagged_Type
(Scope
(Orig_Comp
)) then
6411 Pref_Type
:= Scope
(Orig_Comp
);
6413 -- For an untagged derived type, use the discriminants of the parent
6414 -- which have been renamed in the derivation, possibly by a one-to-many
6415 -- discriminant constraint. For untagged type, initially get the Etype
6419 if Is_Derived_Type
(Pref_Type
)
6420 and then Number_Discriminants
(Pref_Type
) /=
6421 Number_Discriminants
(Etype
(Base_Type
(Pref_Type
)))
6423 Pref_Type
:= Etype
(Base_Type
(Pref_Type
));
6427 -- We definitely should have a checking function, This routine should
6428 -- not be called if no discriminant checking function is present.
6430 pragma Assert
(Present
(Discr_Fct
));
6432 -- Create the list of the actual parameters for the call. This list
6433 -- is the list of the discriminant fields of the record expression to
6434 -- be discriminant checked.
6437 Formal
:= First_Formal
(Discr_Fct
);
6438 Discr
:= First_Discriminant
(Pref_Type
);
6439 while Present
(Discr
) loop
6441 -- If we have a corresponding discriminant field, and a parent
6442 -- subtype is present, then we want to use the corresponding
6443 -- discriminant since this is the one with the useful value.
6445 if Present
(Corresponding_Discriminant
(Discr
))
6446 and then Ekind
(Pref_Type
) = E_Record_Type
6447 and then Present
(Parent_Subtype
(Pref_Type
))
6449 Real_Discr
:= Corresponding_Discriminant
(Discr
);
6451 Real_Discr
:= Discr
;
6454 -- Construct the reference to the discriminant
6457 Make_Selected_Component
(Loc
,
6459 Unchecked_Convert_To
(Pref_Type
,
6460 Duplicate_Subexpr
(Pref
)),
6461 Selector_Name
=> New_Occurrence_Of
(Real_Discr
, Loc
));
6463 -- Manually analyze and resolve this selected component. We really
6464 -- want it just as it appears above, and do not want the expander
6465 -- playing discriminal games etc with this reference. Then we append
6466 -- the argument to the list we are gathering.
6468 Set_Etype
(Scomp
, Etype
(Real_Discr
));
6469 Set_Analyzed
(Scomp
, True);
6470 Append_To
(Args
, Convert_To
(Etype
(Formal
), Scomp
));
6472 Next_Formal_With_Extras
(Formal
);
6473 Next_Discriminant
(Discr
);
6476 -- Now build and insert the call
6479 Make_Raise_Constraint_Error
(Loc
,
6481 Make_Function_Call
(Loc
,
6482 Name
=> New_Occurrence_Of
(Discr_Fct
, Loc
),
6483 Parameter_Associations
=> Args
),
6484 Reason
=> CE_Discriminant_Check_Failed
));
6485 end Generate_Discriminant_Check
;
6487 ---------------------------
6488 -- Generate_Index_Checks --
6489 ---------------------------
6491 procedure Generate_Index_Checks
(N
: Node_Id
) is
6493 function Entity_Of_Prefix
return Entity_Id
;
6494 -- Returns the entity of the prefix of N (or Empty if not found)
6496 ----------------------
6497 -- Entity_Of_Prefix --
6498 ----------------------
6500 function Entity_Of_Prefix
return Entity_Id
is
6505 while not Is_Entity_Name
(P
) loop
6506 if not Nkind_In
(P
, N_Selected_Component
,
6507 N_Indexed_Component
)
6516 end Entity_Of_Prefix
;
6520 Loc
: constant Source_Ptr
:= Sloc
(N
);
6521 A
: constant Node_Id
:= Prefix
(N
);
6522 A_Ent
: constant Entity_Id
:= Entity_Of_Prefix
;
6525 -- Start of processing for Generate_Index_Checks
6528 -- Ignore call if the prefix is not an array since we have a serious
6529 -- error in the sources. Ignore it also if index checks are suppressed
6530 -- for array object or type.
6532 if not Is_Array_Type
(Etype
(A
))
6533 or else (Present
(A_Ent
) and then Index_Checks_Suppressed
(A_Ent
))
6534 or else Index_Checks_Suppressed
(Etype
(A
))
6538 -- The indexed component we are dealing with contains 'Loop_Entry in its
6539 -- prefix. This case arises when analysis has determined that constructs
6542 -- Prefix'Loop_Entry (Expr)
6543 -- Prefix'Loop_Entry (Expr1, Expr2, ... ExprN)
6545 -- require rewriting for error detection purposes. A side effect of this
6546 -- action is the generation of index checks that mention 'Loop_Entry.
6547 -- Delay the generation of the check until 'Loop_Entry has been properly
6548 -- expanded. This is done in Expand_Loop_Entry_Attributes.
6550 elsif Nkind
(Prefix
(N
)) = N_Attribute_Reference
6551 and then Attribute_Name
(Prefix
(N
)) = Name_Loop_Entry
6556 -- Generate a raise of constraint error with the appropriate reason and
6557 -- a condition of the form:
6559 -- Base_Type (Sub) not in Array'Range (Subscript)
6561 -- Note that the reason we generate the conversion to the base type here
6562 -- is that we definitely want the range check to take place, even if it
6563 -- looks like the subtype is OK. Optimization considerations that allow
6564 -- us to omit the check have already been taken into account in the
6565 -- setting of the Do_Range_Check flag earlier on.
6567 Sub
:= First
(Expressions
(N
));
6569 -- Handle string literals
6571 if Ekind
(Etype
(A
)) = E_String_Literal_Subtype
then
6572 if Do_Range_Check
(Sub
) then
6573 Set_Do_Range_Check
(Sub
, False);
6575 -- For string literals we obtain the bounds of the string from the
6576 -- associated subtype.
6579 Make_Raise_Constraint_Error
(Loc
,
6583 Convert_To
(Base_Type
(Etype
(Sub
)),
6584 Duplicate_Subexpr_Move_Checks
(Sub
)),
6586 Make_Attribute_Reference
(Loc
,
6587 Prefix
=> New_Occurrence_Of
(Etype
(A
), Loc
),
6588 Attribute_Name
=> Name_Range
)),
6589 Reason
=> CE_Index_Check_Failed
));
6596 A_Idx
: Node_Id
:= Empty
;
6603 A_Idx
:= First_Index
(Etype
(A
));
6605 while Present
(Sub
) loop
6606 if Do_Range_Check
(Sub
) then
6607 Set_Do_Range_Check
(Sub
, False);
6609 -- Force evaluation except for the case of a simple name of
6610 -- a nonvolatile entity.
6612 if not Is_Entity_Name
(Sub
)
6613 or else Treat_As_Volatile
(Entity
(Sub
))
6615 Force_Evaluation
(Sub
);
6618 if Nkind
(A_Idx
) = N_Range
then
6621 elsif Nkind
(A_Idx
) = N_Identifier
6622 or else Nkind
(A_Idx
) = N_Expanded_Name
6624 A_Range
:= Scalar_Range
(Entity
(A_Idx
));
6626 else pragma Assert
(Nkind
(A_Idx
) = N_Subtype_Indication
);
6627 A_Range
:= Range_Expression
(Constraint
(A_Idx
));
6630 -- For array objects with constant bounds we can generate
6631 -- the index check using the bounds of the type of the index
6634 and then Ekind
(A_Ent
) = E_Variable
6635 and then Is_Constant_Bound
(Low_Bound
(A_Range
))
6636 and then Is_Constant_Bound
(High_Bound
(A_Range
))
6639 Make_Attribute_Reference
(Loc
,
6641 New_Occurrence_Of
(Etype
(A_Idx
), Loc
),
6642 Attribute_Name
=> Name_Range
);
6644 -- For arrays with non-constant bounds we cannot generate
6645 -- the index check using the bounds of the type of the index
6646 -- since it may reference discriminants of some enclosing
6647 -- type. We obtain the bounds directly from the prefix
6654 Num
:= New_List
(Make_Integer_Literal
(Loc
, Ind
));
6658 Make_Attribute_Reference
(Loc
,
6660 Duplicate_Subexpr_Move_Checks
(A
, Name_Req
=> True),
6661 Attribute_Name
=> Name_Range
,
6662 Expressions
=> Num
);
6666 Make_Raise_Constraint_Error
(Loc
,
6670 Convert_To
(Base_Type
(Etype
(Sub
)),
6671 Duplicate_Subexpr_Move_Checks
(Sub
)),
6672 Right_Opnd
=> Range_N
),
6673 Reason
=> CE_Index_Check_Failed
));
6676 A_Idx
:= Next_Index
(A_Idx
);
6682 end Generate_Index_Checks
;
6684 --------------------------
6685 -- Generate_Range_Check --
6686 --------------------------
6688 procedure Generate_Range_Check
6690 Target_Type
: Entity_Id
;
6691 Reason
: RT_Exception_Code
)
6693 Loc
: constant Source_Ptr
:= Sloc
(N
);
6694 Source_Type
: constant Entity_Id
:= Etype
(N
);
6695 Source_Base_Type
: constant Entity_Id
:= Base_Type
(Source_Type
);
6696 Target_Base_Type
: constant Entity_Id
:= Base_Type
(Target_Type
);
6698 procedure Convert_And_Check_Range
;
6699 -- Convert the conversion operand to the target base type and save in
6700 -- a temporary. Then check the converted value against the range of the
6703 -----------------------------
6704 -- Convert_And_Check_Range --
6705 -----------------------------
6707 procedure Convert_And_Check_Range
is
6708 Tnn
: constant Entity_Id
:= Make_Temporary
(Loc
, 'T', N
);
6711 -- We make a temporary to hold the value of the converted value
6712 -- (converted to the base type), and then do the test against this
6713 -- temporary. The conversion itself is replaced by an occurrence of
6714 -- Tnn and followed by the explicit range check. Note that checks
6715 -- are suppressed for this code, since we don't want a recursive
6716 -- range check popping up.
6718 -- Tnn : constant Target_Base_Type := Target_Base_Type (N);
6719 -- [constraint_error when Tnn not in Target_Type]
6721 Insert_Actions
(N
, New_List
(
6722 Make_Object_Declaration
(Loc
,
6723 Defining_Identifier
=> Tnn
,
6724 Object_Definition
=> New_Occurrence_Of
(Target_Base_Type
, Loc
),
6725 Constant_Present
=> True,
6727 Make_Type_Conversion
(Loc
,
6728 Subtype_Mark
=> New_Occurrence_Of
(Target_Base_Type
, Loc
),
6729 Expression
=> Duplicate_Subexpr
(N
))),
6731 Make_Raise_Constraint_Error
(Loc
,
6734 Left_Opnd
=> New_Occurrence_Of
(Tnn
, Loc
),
6735 Right_Opnd
=> New_Occurrence_Of
(Target_Type
, Loc
)),
6737 Suppress
=> All_Checks
);
6739 Rewrite
(N
, New_Occurrence_Of
(Tnn
, Loc
));
6741 -- Set the type of N, because the declaration for Tnn might not
6742 -- be analyzed yet, as is the case if N appears within a record
6743 -- declaration, as a discriminant constraint or expression.
6745 Set_Etype
(N
, Target_Base_Type
);
6746 end Convert_And_Check_Range
;
6748 -- Start of processing for Generate_Range_Check
6751 -- First special case, if the source type is already within the range
6752 -- of the target type, then no check is needed (probably we should have
6753 -- stopped Do_Range_Check from being set in the first place, but better
6754 -- late than never in preventing junk code and junk flag settings.
6756 if In_Subrange_Of
(Source_Type
, Target_Type
)
6758 -- We do NOT apply this if the source node is a literal, since in this
6759 -- case the literal has already been labeled as having the subtype of
6763 (Nkind_In
(N
, N_Integer_Literal
, N_Real_Literal
, N_Character_Literal
)
6766 and then Ekind
(Entity
(N
)) = E_Enumeration_Literal
))
6768 Set_Do_Range_Check
(N
, False);
6772 -- Here a check is needed. If the expander is not active, or if we are
6773 -- in GNATProve mode, then simply set the Do_Range_Check flag and we
6774 -- are done. In both these cases, we just want to see the range check
6775 -- flag set, we do not want to generate the explicit range check code.
6777 if GNATprove_Mode
or else not Expander_Active
then
6778 Set_Do_Range_Check
(N
, True);
6782 -- Here we will generate an explicit range check, so we don't want to
6783 -- set the Do_Range check flag, since the range check is taken care of
6784 -- by the code we will generate.
6786 Set_Do_Range_Check
(N
, False);
6788 -- Force evaluation of the node, so that it does not get evaluated twice
6789 -- (once for the check, once for the actual reference). Such a double
6790 -- evaluation is always a potential source of inefficiency, and is
6791 -- functionally incorrect in the volatile case.
6793 if not Is_Entity_Name
(N
) or else Treat_As_Volatile
(Entity
(N
)) then
6794 Force_Evaluation
(N
);
6797 -- The easiest case is when Source_Base_Type and Target_Base_Type are
6798 -- the same since in this case we can simply do a direct check of the
6799 -- value of N against the bounds of Target_Type.
6801 -- [constraint_error when N not in Target_Type]
6803 -- Note: this is by far the most common case, for example all cases of
6804 -- checks on the RHS of assignments are in this category, but not all
6805 -- cases are like this. Notably conversions can involve two types.
6807 if Source_Base_Type
= Target_Base_Type
then
6809 -- Insert the explicit range check. Note that we suppress checks for
6810 -- this code, since we don't want a recursive range check popping up.
6813 Make_Raise_Constraint_Error
(Loc
,
6816 Left_Opnd
=> Duplicate_Subexpr
(N
),
6817 Right_Opnd
=> New_Occurrence_Of
(Target_Type
, Loc
)),
6819 Suppress
=> All_Checks
);
6821 -- Next test for the case where the target type is within the bounds
6822 -- of the base type of the source type, since in this case we can
6823 -- simply convert these bounds to the base type of T to do the test.
6825 -- [constraint_error when N not in
6826 -- Source_Base_Type (Target_Type'First)
6828 -- Source_Base_Type(Target_Type'Last))]
6830 -- The conversions will always work and need no check
6832 -- Unchecked_Convert_To is used instead of Convert_To to handle the case
6833 -- of converting from an enumeration value to an integer type, such as
6834 -- occurs for the case of generating a range check on Enum'Val(Exp)
6835 -- (which used to be handled by gigi). This is OK, since the conversion
6836 -- itself does not require a check.
6838 elsif In_Subrange_Of
(Target_Type
, Source_Base_Type
) then
6840 -- Insert the explicit range check. Note that we suppress checks for
6841 -- this code, since we don't want a recursive range check popping up.
6843 if Is_Discrete_Type
(Source_Base_Type
)
6845 Is_Discrete_Type
(Target_Base_Type
)
6848 Make_Raise_Constraint_Error
(Loc
,
6851 Left_Opnd
=> Duplicate_Subexpr
(N
),
6856 Unchecked_Convert_To
(Source_Base_Type
,
6857 Make_Attribute_Reference
(Loc
,
6859 New_Occurrence_Of
(Target_Type
, Loc
),
6860 Attribute_Name
=> Name_First
)),
6863 Unchecked_Convert_To
(Source_Base_Type
,
6864 Make_Attribute_Reference
(Loc
,
6866 New_Occurrence_Of
(Target_Type
, Loc
),
6867 Attribute_Name
=> Name_Last
)))),
6869 Suppress
=> All_Checks
);
6871 -- For conversions involving at least one type that is not discrete,
6872 -- first convert to target type and then generate the range check.
6873 -- This avoids problems with values that are close to a bound of the
6874 -- target type that would fail a range check when done in a larger
6875 -- source type before converting but would pass if converted with
6876 -- rounding and then checked (such as in float-to-float conversions).
6879 Convert_And_Check_Range
;
6882 -- Note that at this stage we now that the Target_Base_Type is not in
6883 -- the range of the Source_Base_Type (since even the Target_Type itself
6884 -- is not in this range). It could still be the case that Source_Type is
6885 -- in range of the target base type since we have not checked that case.
6887 -- If that is the case, we can freely convert the source to the target,
6888 -- and then test the target result against the bounds.
6890 elsif In_Subrange_Of
(Source_Type
, Target_Base_Type
) then
6891 Convert_And_Check_Range
;
6893 -- At this stage, we know that we have two scalar types, which are
6894 -- directly convertible, and where neither scalar type has a base
6895 -- range that is in the range of the other scalar type.
6897 -- The only way this can happen is with a signed and unsigned type.
6898 -- So test for these two cases:
6901 -- Case of the source is unsigned and the target is signed
6903 if Is_Unsigned_Type
(Source_Base_Type
)
6904 and then not Is_Unsigned_Type
(Target_Base_Type
)
6906 -- If the source is unsigned and the target is signed, then we
6907 -- know that the source is not shorter than the target (otherwise
6908 -- the source base type would be in the target base type range).
6910 -- In other words, the unsigned type is either the same size as
6911 -- the target, or it is larger. It cannot be smaller.
6914 (Esize
(Source_Base_Type
) >= Esize
(Target_Base_Type
));
6916 -- We only need to check the low bound if the low bound of the
6917 -- target type is non-negative. If the low bound of the target
6918 -- type is negative, then we know that we will fit fine.
6920 -- If the high bound of the target type is negative, then we
6921 -- know we have a constraint error, since we can't possibly
6922 -- have a negative source.
6924 -- With these two checks out of the way, we can do the check
6925 -- using the source type safely
6927 -- This is definitely the most annoying case.
6929 -- [constraint_error
6930 -- when (Target_Type'First >= 0
6932 -- N < Source_Base_Type (Target_Type'First))
6933 -- or else Target_Type'Last < 0
6934 -- or else N > Source_Base_Type (Target_Type'Last)];
6936 -- We turn off all checks since we know that the conversions
6937 -- will work fine, given the guards for negative values.
6940 Make_Raise_Constraint_Error
(Loc
,
6946 Left_Opnd
=> Make_Op_Ge
(Loc
,
6948 Make_Attribute_Reference
(Loc
,
6950 New_Occurrence_Of
(Target_Type
, Loc
),
6951 Attribute_Name
=> Name_First
),
6952 Right_Opnd
=> Make_Integer_Literal
(Loc
, Uint_0
)),
6956 Left_Opnd
=> Duplicate_Subexpr
(N
),
6958 Convert_To
(Source_Base_Type
,
6959 Make_Attribute_Reference
(Loc
,
6961 New_Occurrence_Of
(Target_Type
, Loc
),
6962 Attribute_Name
=> Name_First
)))),
6967 Make_Attribute_Reference
(Loc
,
6968 Prefix
=> New_Occurrence_Of
(Target_Type
, Loc
),
6969 Attribute_Name
=> Name_Last
),
6970 Right_Opnd
=> Make_Integer_Literal
(Loc
, Uint_0
))),
6974 Left_Opnd
=> Duplicate_Subexpr
(N
),
6976 Convert_To
(Source_Base_Type
,
6977 Make_Attribute_Reference
(Loc
,
6978 Prefix
=> New_Occurrence_Of
(Target_Type
, Loc
),
6979 Attribute_Name
=> Name_Last
)))),
6982 Suppress
=> All_Checks
);
6984 -- Only remaining possibility is that the source is signed and
6985 -- the target is unsigned.
6988 pragma Assert
(not Is_Unsigned_Type
(Source_Base_Type
)
6989 and then Is_Unsigned_Type
(Target_Base_Type
));
6991 -- If the source is signed and the target is unsigned, then we
6992 -- know that the target is not shorter than the source (otherwise
6993 -- the target base type would be in the source base type range).
6995 -- In other words, the unsigned type is either the same size as
6996 -- the target, or it is larger. It cannot be smaller.
6998 -- Clearly we have an error if the source value is negative since
6999 -- no unsigned type can have negative values. If the source type
7000 -- is non-negative, then the check can be done using the target
7003 -- Tnn : constant Target_Base_Type (N) := Target_Type;
7005 -- [constraint_error
7006 -- when N < 0 or else Tnn not in Target_Type];
7008 -- We turn off all checks for the conversion of N to the target
7009 -- base type, since we generate the explicit check to ensure that
7010 -- the value is non-negative
7013 Tnn
: constant Entity_Id
:= Make_Temporary
(Loc
, 'T', N
);
7016 Insert_Actions
(N
, New_List
(
7017 Make_Object_Declaration
(Loc
,
7018 Defining_Identifier
=> Tnn
,
7019 Object_Definition
=>
7020 New_Occurrence_Of
(Target_Base_Type
, Loc
),
7021 Constant_Present
=> True,
7023 Make_Unchecked_Type_Conversion
(Loc
,
7025 New_Occurrence_Of
(Target_Base_Type
, Loc
),
7026 Expression
=> Duplicate_Subexpr
(N
))),
7028 Make_Raise_Constraint_Error
(Loc
,
7033 Left_Opnd
=> Duplicate_Subexpr
(N
),
7034 Right_Opnd
=> Make_Integer_Literal
(Loc
, Uint_0
)),
7038 Left_Opnd
=> New_Occurrence_Of
(Tnn
, Loc
),
7040 New_Occurrence_Of
(Target_Type
, Loc
))),
7043 Suppress
=> All_Checks
);
7045 -- Set the Etype explicitly, because Insert_Actions may have
7046 -- placed the declaration in the freeze list for an enclosing
7047 -- construct, and thus it is not analyzed yet.
7049 Set_Etype
(Tnn
, Target_Base_Type
);
7050 Rewrite
(N
, New_Occurrence_Of
(Tnn
, Loc
));
7054 end Generate_Range_Check
;
7060 function Get_Check_Id
(N
: Name_Id
) return Check_Id
is
7062 -- For standard check name, we can do a direct computation
7064 if N
in First_Check_Name
.. Last_Check_Name
then
7065 return Check_Id
(N
- (First_Check_Name
- 1));
7067 -- For non-standard names added by pragma Check_Name, search table
7070 for J
in All_Checks
+ 1 .. Check_Names
.Last
loop
7071 if Check_Names
.Table
(J
) = N
then
7077 -- No matching name found
7082 ---------------------
7083 -- Get_Discriminal --
7084 ---------------------
7086 function Get_Discriminal
(E
: Entity_Id
; Bound
: Node_Id
) return Node_Id
is
7087 Loc
: constant Source_Ptr
:= Sloc
(E
);
7092 -- The bound can be a bona fide parameter of a protected operation,
7093 -- rather than a prival encoded as an in-parameter.
7095 if No
(Discriminal_Link
(Entity
(Bound
))) then
7099 -- Climb the scope stack looking for an enclosing protected type. If
7100 -- we run out of scopes, return the bound itself.
7103 while Present
(Sc
) loop
7104 if Sc
= Standard_Standard
then
7106 elsif Ekind
(Sc
) = E_Protected_Type
then
7113 D
:= First_Discriminant
(Sc
);
7114 while Present
(D
) loop
7115 if Chars
(D
) = Chars
(Bound
) then
7116 return New_Occurrence_Of
(Discriminal
(D
), Loc
);
7119 Next_Discriminant
(D
);
7123 end Get_Discriminal
;
7125 ----------------------
7126 -- Get_Range_Checks --
7127 ----------------------
7129 function Get_Range_Checks
7131 Target_Typ
: Entity_Id
;
7132 Source_Typ
: Entity_Id
:= Empty
;
7133 Warn_Node
: Node_Id
:= Empty
) return Check_Result
7137 Selected_Range_Checks
(Ck_Node
, Target_Typ
, Source_Typ
, Warn_Node
);
7138 end Get_Range_Checks
;
7144 function Guard_Access
7147 Ck_Node
: Node_Id
) return Node_Id
7150 if Nkind
(Cond
) = N_Or_Else
then
7151 Set_Paren_Count
(Cond
, 1);
7154 if Nkind
(Ck_Node
) = N_Allocator
then
7162 Left_Opnd
=> Duplicate_Subexpr_No_Checks
(Ck_Node
),
7163 Right_Opnd
=> Make_Null
(Loc
)),
7164 Right_Opnd
=> Cond
);
7168 -----------------------------
7169 -- Index_Checks_Suppressed --
7170 -----------------------------
7172 function Index_Checks_Suppressed
(E
: Entity_Id
) return Boolean is
7174 if Present
(E
) and then Checks_May_Be_Suppressed
(E
) then
7175 return Is_Check_Suppressed
(E
, Index_Check
);
7177 return Scope_Suppress
.Suppress
(Index_Check
);
7179 end Index_Checks_Suppressed
;
7185 procedure Initialize
is
7187 for J
in Determine_Range_Cache_N
'Range loop
7188 Determine_Range_Cache_N
(J
) := Empty
;
7193 for J
in Int
range 1 .. All_Checks
loop
7194 Check_Names
.Append
(Name_Id
(Int
(First_Check_Name
) + J
- 1));
7198 -------------------------
7199 -- Insert_Range_Checks --
7200 -------------------------
7202 procedure Insert_Range_Checks
7203 (Checks
: Check_Result
;
7205 Suppress_Typ
: Entity_Id
;
7206 Static_Sloc
: Source_Ptr
:= No_Location
;
7207 Flag_Node
: Node_Id
:= Empty
;
7208 Do_Before
: Boolean := False)
7210 Checks_On
: constant Boolean :=
7211 not Index_Checks_Suppressed
(Suppress_Typ
)
7213 not Range_Checks_Suppressed
(Suppress_Typ
);
7215 Check_Node
: Node_Id
;
7216 Internal_Flag_Node
: Node_Id
:= Flag_Node
;
7217 Internal_Static_Sloc
: Source_Ptr
:= Static_Sloc
;
7220 -- For now we just return if Checks_On is false, however this should be
7221 -- enhanced to check for an always True value in the condition and to
7222 -- generate a compilation warning???
7224 if not Expander_Active
or not Checks_On
then
7228 if Static_Sloc
= No_Location
then
7229 Internal_Static_Sloc
:= Sloc
(Node
);
7232 if No
(Flag_Node
) then
7233 Internal_Flag_Node
:= Node
;
7236 for J
in 1 .. 2 loop
7237 exit when No
(Checks
(J
));
7239 if Nkind
(Checks
(J
)) = N_Raise_Constraint_Error
7240 and then Present
(Condition
(Checks
(J
)))
7242 if not Has_Dynamic_Range_Check
(Internal_Flag_Node
) then
7243 Check_Node
:= Checks
(J
);
7244 Mark_Rewrite_Insertion
(Check_Node
);
7247 Insert_Before_And_Analyze
(Node
, Check_Node
);
7249 Insert_After_And_Analyze
(Node
, Check_Node
);
7252 Set_Has_Dynamic_Range_Check
(Internal_Flag_Node
);
7257 Make_Raise_Constraint_Error
(Internal_Static_Sloc
,
7258 Reason
=> CE_Range_Check_Failed
);
7259 Mark_Rewrite_Insertion
(Check_Node
);
7262 Insert_Before_And_Analyze
(Node
, Check_Node
);
7264 Insert_After_And_Analyze
(Node
, Check_Node
);
7268 end Insert_Range_Checks
;
7270 ------------------------
7271 -- Insert_Valid_Check --
7272 ------------------------
7274 procedure Insert_Valid_Check
7276 Related_Id
: Entity_Id
:= Empty
;
7277 Is_Low_Bound
: Boolean := False;
7278 Is_High_Bound
: Boolean := False)
7280 Loc
: constant Source_Ptr
:= Sloc
(Expr
);
7281 Typ
: constant Entity_Id
:= Etype
(Expr
);
7285 -- Do not insert if checks off, or if not checking validity or if
7286 -- expression is known to be valid.
7288 if not Validity_Checks_On
7289 or else Range_Or_Validity_Checks_Suppressed
(Expr
)
7290 or else Expr_Known_Valid
(Expr
)
7294 -- Do not insert checks within a predicate function. This will arise
7295 -- if the current unit and the predicate function are being compiled
7296 -- with validity checks enabled.
7298 elsif Present
(Predicate_Function
(Typ
))
7299 and then Current_Scope
= Predicate_Function
(Typ
)
7303 -- If the expression is a packed component of a modular type of the
7304 -- right size, the data is always valid.
7306 elsif Nkind
(Expr
) = N_Selected_Component
7307 and then Present
(Component_Clause
(Entity
(Selector_Name
(Expr
))))
7308 and then Is_Modular_Integer_Type
(Typ
)
7309 and then Modulus
(Typ
) = 2 ** Esize
(Entity
(Selector_Name
(Expr
)))
7313 -- Do not generate a validity check when inside a generic unit as this
7314 -- is an expansion activity.
7316 elsif Inside_A_Generic
then
7320 -- If we have a checked conversion, then validity check applies to
7321 -- the expression inside the conversion, not the result, since if
7322 -- the expression inside is valid, then so is the conversion result.
7325 while Nkind
(Exp
) = N_Type_Conversion
loop
7326 Exp
:= Expression
(Exp
);
7329 -- Do not generate a check for a variable which already validates the
7330 -- value of an assignable object.
7332 if Is_Validation_Variable_Reference
(Exp
) then
7336 -- We are about to insert the validity check for Exp. We save and
7337 -- reset the Do_Range_Check flag over this validity check, and then
7338 -- put it back for the final original reference (Exp may be rewritten).
7341 DRC
: constant Boolean := Do_Range_Check
(Exp
);
7349 Set_Do_Range_Check
(Exp
, False);
7351 -- If the expression denotes an assignable object, capture its value
7352 -- in a variable and replace the original expression by the variable.
7353 -- This approach has several effects:
7355 -- 1) The evaluation of the object results in only one read in the
7356 -- case where the object is atomic or volatile.
7358 -- Var ... := Object; -- read
7360 -- 2) The captured value is the one verified by attribute 'Valid.
7361 -- As a result the object is not evaluated again, which would
7362 -- result in an unwanted read in the case where the object is
7363 -- atomic or volatile.
7365 -- if not Var'Valid then -- OK, no read of Object
7367 -- if not Object'Valid then -- Wrong, extra read of Object
7369 -- 3) The captured value replaces the original object reference.
7370 -- As a result the object is not evaluated again, in the same
7373 -- ... Var ... -- OK, no read of Object
7375 -- ... Object ... -- Wrong, extra read of Object
7377 -- 4) The use of a variable to capture the value of the object
7378 -- allows the propagation of any changes back to the original
7381 -- procedure Call (Val : in out ...);
7383 -- Var : ... := Object; -- read Object
7384 -- if not Var'Valid then -- validity check
7385 -- Call (Var); -- modify Var
7386 -- Object := Var; -- update Object
7388 if Is_Variable
(Exp
) then
7389 Obj
:= New_Copy_Tree
(Exp
);
7390 Var_Id
:= Make_Temporary
(Loc
, 'T', Exp
);
7393 Make_Object_Declaration
(Loc
,
7394 Defining_Identifier
=> Var_Id
,
7395 Object_Definition
=> New_Occurrence_Of
(Typ
, Loc
),
7396 Expression
=> Relocate_Node
(Exp
)));
7397 Set_Validated_Object
(Var_Id
, Obj
);
7399 Rewrite
(Exp
, New_Occurrence_Of
(Var_Id
, Loc
));
7400 PV
:= New_Occurrence_Of
(Var_Id
, Loc
);
7402 -- Otherwise the expression does not denote a variable. Force its
7403 -- evaluation by capturing its value in a constant. Generate:
7405 -- Temp : constant ... := Exp;
7410 Related_Id
=> Related_Id
,
7411 Is_Low_Bound
=> Is_Low_Bound
,
7412 Is_High_Bound
=> Is_High_Bound
);
7414 PV
:= New_Copy_Tree
(Exp
);
7417 -- A rather specialized test. If PV is an analyzed expression which
7418 -- is an indexed component of a packed array that has not been
7419 -- properly expanded, turn off its Analyzed flag to make sure it
7420 -- gets properly reexpanded. If the prefix is an access value,
7421 -- the dereference will be added later.
7423 -- The reason this arises is that Duplicate_Subexpr_No_Checks did
7424 -- an analyze with the old parent pointer. This may point e.g. to
7425 -- a subprogram call, which deactivates this expansion.
7428 and then Nkind
(PV
) = N_Indexed_Component
7429 and then Is_Array_Type
(Etype
(Prefix
(PV
)))
7430 and then Present
(Packed_Array_Impl_Type
(Etype
(Prefix
(PV
))))
7432 Set_Analyzed
(PV
, False);
7435 -- Build the raise CE node to check for validity. We build a type
7436 -- qualification for the prefix, since it may not be of the form of
7437 -- a name, and we don't care in this context!
7440 Make_Raise_Constraint_Error
(Loc
,
7444 Make_Attribute_Reference
(Loc
,
7446 Attribute_Name
=> Name_Valid
)),
7447 Reason
=> CE_Invalid_Data
);
7449 -- Insert the validity check. Note that we do this with validity
7450 -- checks turned off, to avoid recursion, we do not want validity
7451 -- checks on the validity checking code itself.
7453 Insert_Action
(Expr
, CE
, Suppress
=> Validity_Check
);
7455 -- If the expression is a reference to an element of a bit-packed
7456 -- array, then it is rewritten as a renaming declaration. If the
7457 -- expression is an actual in a call, it has not been expanded,
7458 -- waiting for the proper point at which to do it. The same happens
7459 -- with renamings, so that we have to force the expansion now. This
7460 -- non-local complication is due to code in exp_ch2,adb, exp_ch4.adb
7463 if Is_Entity_Name
(Exp
)
7464 and then Nkind
(Parent
(Entity
(Exp
))) =
7465 N_Object_Renaming_Declaration
7468 Old_Exp
: constant Node_Id
:= Name
(Parent
(Entity
(Exp
)));
7470 if Nkind
(Old_Exp
) = N_Indexed_Component
7471 and then Is_Bit_Packed_Array
(Etype
(Prefix
(Old_Exp
)))
7473 Expand_Packed_Element_Reference
(Old_Exp
);
7478 -- Put back the Do_Range_Check flag on the resulting (possibly
7479 -- rewritten) expression.
7481 -- Note: it might be thought that a validity check is not required
7482 -- when a range check is present, but that's not the case, because
7483 -- the back end is allowed to assume for the range check that the
7484 -- operand is within its declared range (an assumption that validity
7485 -- checking is all about NOT assuming).
7487 -- Note: no need to worry about Possible_Local_Raise here, it will
7488 -- already have been called if original node has Do_Range_Check set.
7490 Set_Do_Range_Check
(Exp
, DRC
);
7492 end Insert_Valid_Check
;
7494 -------------------------------------
7495 -- Is_Signed_Integer_Arithmetic_Op --
7496 -------------------------------------
7498 function Is_Signed_Integer_Arithmetic_Op
(N
: Node_Id
) return Boolean is
7512 return Is_Signed_Integer_Type
(Etype
(N
));
7514 when N_Case_Expression
7517 return Is_Signed_Integer_Type
(Etype
(N
));
7522 end Is_Signed_Integer_Arithmetic_Op
;
7524 ----------------------------------
7525 -- Install_Null_Excluding_Check --
7526 ----------------------------------
7528 procedure Install_Null_Excluding_Check
(N
: Node_Id
) is
7529 Loc
: constant Source_Ptr
:= Sloc
(Parent
(N
));
7530 Typ
: constant Entity_Id
:= Etype
(N
);
7532 function Safe_To_Capture_In_Parameter_Value
return Boolean;
7533 -- Determines if it is safe to capture Known_Non_Null status for an
7534 -- the entity referenced by node N. The caller ensures that N is indeed
7535 -- an entity name. It is safe to capture the non-null status for an IN
7536 -- parameter when the reference occurs within a declaration that is sure
7537 -- to be executed as part of the declarative region.
7539 procedure Mark_Non_Null
;
7540 -- After installation of check, if the node in question is an entity
7541 -- name, then mark this entity as non-null if possible.
7543 function Safe_To_Capture_In_Parameter_Value
return Boolean is
7544 E
: constant Entity_Id
:= Entity
(N
);
7545 S
: constant Entity_Id
:= Current_Scope
;
7549 if Ekind
(E
) /= E_In_Parameter
then
7553 -- Two initial context checks. We must be inside a subprogram body
7554 -- with declarations and reference must not appear in nested scopes.
7556 if (Ekind
(S
) /= E_Function
and then Ekind
(S
) /= E_Procedure
)
7557 or else Scope
(E
) /= S
7562 S_Par
:= Parent
(Parent
(S
));
7564 if Nkind
(S_Par
) /= N_Subprogram_Body
7565 or else No
(Declarations
(S_Par
))
7575 -- Retrieve the declaration node of N (if any). Note that N
7576 -- may be a part of a complex initialization expression.
7580 while Present
(P
) loop
7582 -- If we have a short circuit form, and we are within the right
7583 -- hand expression, we return false, since the right hand side
7584 -- is not guaranteed to be elaborated.
7586 if Nkind
(P
) in N_Short_Circuit
7587 and then N
= Right_Opnd
(P
)
7592 -- Similarly, if we are in an if expression and not part of the
7593 -- condition, then we return False, since neither the THEN or
7594 -- ELSE dependent expressions will always be elaborated.
7596 if Nkind
(P
) = N_If_Expression
7597 and then N
/= First
(Expressions
(P
))
7602 -- If within a case expression, and not part of the expression,
7603 -- then return False, since a particular dependent expression
7604 -- may not always be elaborated
7606 if Nkind
(P
) = N_Case_Expression
7607 and then N
/= Expression
(P
)
7612 -- While traversing the parent chain, if node N belongs to a
7613 -- statement, then it may never appear in a declarative region.
7615 if Nkind
(P
) in N_Statement_Other_Than_Procedure_Call
7616 or else Nkind
(P
) = N_Procedure_Call_Statement
7621 -- If we are at a declaration, record it and exit
7623 if Nkind
(P
) in N_Declaration
7624 and then Nkind
(P
) not in N_Subprogram_Specification
7637 return List_Containing
(N_Decl
) = Declarations
(S_Par
);
7639 end Safe_To_Capture_In_Parameter_Value
;
7645 procedure Mark_Non_Null
is
7647 -- Only case of interest is if node N is an entity name
7649 if Is_Entity_Name
(N
) then
7651 -- For sure, we want to clear an indication that this is known to
7652 -- be null, since if we get past this check, it definitely is not.
7654 Set_Is_Known_Null
(Entity
(N
), False);
7656 -- We can mark the entity as known to be non-null if either it is
7657 -- safe to capture the value, or in the case of an IN parameter,
7658 -- which is a constant, if the check we just installed is in the
7659 -- declarative region of the subprogram body. In this latter case,
7660 -- a check is decisive for the rest of the body if the expression
7661 -- is sure to be elaborated, since we know we have to elaborate
7662 -- all declarations before executing the body.
7664 -- Couldn't this always be part of Safe_To_Capture_Value ???
7666 if Safe_To_Capture_Value
(N
, Entity
(N
))
7667 or else Safe_To_Capture_In_Parameter_Value
7669 Set_Is_Known_Non_Null
(Entity
(N
));
7674 -- Start of processing for Install_Null_Excluding_Check
7677 pragma Assert
(Is_Access_Type
(Typ
));
7679 -- No check inside a generic, check will be emitted in instance
7681 if Inside_A_Generic
then
7685 -- No check needed if known to be non-null
7687 if Known_Non_Null
(N
) then
7691 -- If known to be null, here is where we generate a compile time check
7693 if Known_Null
(N
) then
7695 -- Avoid generating warning message inside init procs. In SPARK mode
7696 -- we can go ahead and call Apply_Compile_Time_Constraint_Error
7697 -- since it will be turned into an error in any case.
7699 if (not Inside_Init_Proc
or else SPARK_Mode
= On
)
7701 -- Do not emit the warning within a conditional expression,
7702 -- where the expression might not be evaluated, and the warning
7703 -- appear as extraneous noise.
7705 and then not Within_Case_Or_If_Expression
(N
)
7707 Apply_Compile_Time_Constraint_Error
7708 (N
, "null value not allowed here??", CE_Access_Check_Failed
);
7710 -- Remaining cases, where we silently insert the raise
7714 Make_Raise_Constraint_Error
(Loc
,
7715 Reason
=> CE_Access_Check_Failed
));
7722 -- If entity is never assigned, for sure a warning is appropriate
7724 if Is_Entity_Name
(N
) then
7725 Check_Unset_Reference
(N
);
7728 -- No check needed if checks are suppressed on the range. Note that we
7729 -- don't set Is_Known_Non_Null in this case (we could legitimately do
7730 -- so, since the program is erroneous, but we don't like to casually
7731 -- propagate such conclusions from erroneosity).
7733 if Access_Checks_Suppressed
(Typ
) then
7737 -- No check needed for access to concurrent record types generated by
7738 -- the expander. This is not just an optimization (though it does indeed
7739 -- remove junk checks). It also avoids generation of junk warnings.
7741 if Nkind
(N
) in N_Has_Chars
7742 and then Chars
(N
) = Name_uObject
7743 and then Is_Concurrent_Record_Type
7744 (Directly_Designated_Type
(Etype
(N
)))
7749 -- No check needed in interface thunks since the runtime check is
7750 -- already performed at the caller side.
7752 if Is_Thunk
(Current_Scope
) then
7756 -- No check needed for the Get_Current_Excep.all.all idiom generated by
7757 -- the expander within exception handlers, since we know that the value
7758 -- can never be null.
7760 -- Is this really the right way to do this? Normally we generate such
7761 -- code in the expander with checks off, and that's how we suppress this
7762 -- kind of junk check ???
7764 if Nkind
(N
) = N_Function_Call
7765 and then Nkind
(Name
(N
)) = N_Explicit_Dereference
7766 and then Nkind
(Prefix
(Name
(N
))) = N_Identifier
7767 and then Is_RTE
(Entity
(Prefix
(Name
(N
))), RE_Get_Current_Excep
)
7772 -- Otherwise install access check
7775 Make_Raise_Constraint_Error
(Loc
,
7778 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(N
),
7779 Right_Opnd
=> Make_Null
(Loc
)),
7780 Reason
=> CE_Access_Check_Failed
));
7783 end Install_Null_Excluding_Check
;
7785 -----------------------------------------
7786 -- Install_Primitive_Elaboration_Check --
7787 -----------------------------------------
7789 procedure Install_Primitive_Elaboration_Check
(Subp_Body
: Node_Id
) is
7790 function Within_Compilation_Unit_Instance
7791 (Subp_Id
: Entity_Id
) return Boolean;
7792 -- Determine whether subprogram Subp_Id appears within an instance which
7793 -- acts as a compilation unit.
7795 --------------------------------------
7796 -- Within_Compilation_Unit_Instance --
7797 --------------------------------------
7799 function Within_Compilation_Unit_Instance
7800 (Subp_Id
: Entity_Id
) return Boolean
7805 -- Examine the scope chain looking for a compilation-unit-level
7808 Pack
:= Scope
(Subp_Id
);
7809 while Present
(Pack
) and then Pack
/= Standard_Standard
loop
7810 if Ekind
(Pack
) = E_Package
7811 and then Is_Generic_Instance
(Pack
)
7812 and then Nkind
(Parent
(Unit_Declaration_Node
(Pack
))) =
7818 Pack
:= Scope
(Pack
);
7822 end Within_Compilation_Unit_Instance
;
7824 -- Local declarations
7826 Context
: constant Node_Id
:= Parent
(Subp_Body
);
7827 Loc
: constant Source_Ptr
:= Sloc
(Subp_Body
);
7828 Subp_Id
: constant Entity_Id
:= Unique_Defining_Entity
(Subp_Body
);
7829 Subp_Decl
: constant Node_Id
:= Unit_Declaration_Node
(Subp_Id
);
7832 Flag_Id
: Entity_Id
;
7834 Tag_Typ
: Entity_Id
;
7836 -- Start of processing for Install_Primitive_Elaboration_Check
7839 -- Do not generate an elaboration check in compilation modes where
7840 -- expansion is not desirable.
7842 if ASIS_Mode
or GNATprove_Mode
then
7845 -- Do not generate an elaboration check if all checks have been
7848 elsif Suppress_Checks
then
7851 -- Do not generate an elaboration check if the related subprogram is
7852 -- not subjected to accessibility checks.
7854 elsif Elaboration_Checks_Suppressed
(Subp_Id
) then
7857 -- Do not generate an elaboration check if such code is not desirable
7859 elsif Restriction_Active
(No_Elaboration_Code
) then
7862 -- Do not consider subprograms which act as compilation units, because
7863 -- they cannot be the target of a dispatching call.
7865 elsif Nkind
(Context
) = N_Compilation_Unit
then
7868 -- Only nonabstract library-level source primitives are considered for
7872 (Comes_From_Source
(Subp_Id
)
7873 and then Is_Library_Level_Entity
(Subp_Id
)
7874 and then Is_Primitive
(Subp_Id
)
7875 and then not Is_Abstract_Subprogram
(Subp_Id
))
7879 -- Do not consider inlined primitives, because once the body is inlined
7880 -- the reference to the elaboration flag will be out of place and will
7881 -- result in an undefined symbol.
7883 elsif Is_Inlined
(Subp_Id
) or else Has_Pragma_Inline
(Subp_Id
) then
7886 -- Do not generate a duplicate elaboration check. This happens only in
7887 -- the case of primitives completed by an expression function, as the
7888 -- corresponding body is apparently analyzed and expanded twice.
7890 elsif Analyzed
(Subp_Body
) then
7893 -- Do not consider primitives which occur within an instance that acts
7894 -- as a compilation unit. Such an instance defines its spec and body out
7895 -- of order (body is first) within the tree, which causes the reference
7896 -- to the elaboration flag to appear as an undefined symbol.
7898 elsif Within_Compilation_Unit_Instance
(Subp_Id
) then
7902 Tag_Typ
:= Find_Dispatching_Type
(Subp_Id
);
7904 -- Only tagged primitives may be the target of a dispatching call
7906 if No
(Tag_Typ
) then
7909 -- Do not consider finalization-related primitives, because they may
7910 -- need to be called while elaboration is taking place.
7912 elsif Is_Controlled
(Tag_Typ
)
7913 and then Nam_In
(Chars
(Subp_Id
), Name_Adjust
,
7920 -- Create the declaration of the elaboration flag. The name carries a
7921 -- unique counter in case of name overloading.
7924 Make_Defining_Identifier
(Loc
,
7925 Chars
=> New_External_Name
(Chars
(Subp_Id
), 'F', -1));
7926 Set_Is_Frozen
(Flag_Id
);
7928 -- Insert the declaration of the elaboration flag in front of the
7929 -- primitive spec and analyze it in the proper context.
7931 Push_Scope
(Scope
(Subp_Id
));
7934 -- F : Boolean := False;
7936 Insert_Action
(Subp_Decl
,
7937 Make_Object_Declaration
(Loc
,
7938 Defining_Identifier
=> Flag_Id
,
7939 Object_Definition
=> New_Occurrence_Of
(Standard_Boolean
, Loc
),
7940 Expression
=> New_Occurrence_Of
(Standard_False
, Loc
)));
7943 -- Prevent the compiler from optimizing the elaboration check by killing
7944 -- the current value of the flag and the associated assignment.
7946 Set_Current_Value
(Flag_Id
, Empty
);
7947 Set_Last_Assignment
(Flag_Id
, Empty
);
7949 -- Add a check at the top of the body declarations to ensure that the
7950 -- elaboration flag has been set.
7952 Decls
:= Declarations
(Subp_Body
);
7956 Set_Declarations
(Subp_Body
, Decls
);
7961 -- raise Program_Error with "access before elaboration";
7965 Make_Raise_Program_Error
(Loc
,
7968 Right_Opnd
=> New_Occurrence_Of
(Flag_Id
, Loc
)),
7969 Reason
=> PE_Access_Before_Elaboration
));
7971 Analyze
(First
(Decls
));
7973 -- Set the elaboration flag once the body has been elaborated. Insert
7974 -- the statement after the subprogram stub when the primitive body is
7977 if Nkind
(Context
) = N_Subunit
then
7978 Set_Ins
:= Corresponding_Stub
(Context
);
7980 Set_Ins
:= Subp_Body
;
7986 Insert_After_And_Analyze
(Set_Ins
,
7987 Make_Assignment_Statement
(Loc
,
7988 Name
=> New_Occurrence_Of
(Flag_Id
, Loc
),
7989 Expression
=> New_Occurrence_Of
(Standard_True
, Loc
)));
7990 end Install_Primitive_Elaboration_Check
;
7992 --------------------------
7993 -- Install_Static_Check --
7994 --------------------------
7996 procedure Install_Static_Check
(R_Cno
: Node_Id
; Loc
: Source_Ptr
) is
7997 Stat
: constant Boolean := Is_OK_Static_Expression
(R_Cno
);
7998 Typ
: constant Entity_Id
:= Etype
(R_Cno
);
8002 Make_Raise_Constraint_Error
(Loc
,
8003 Reason
=> CE_Range_Check_Failed
));
8004 Set_Analyzed
(R_Cno
);
8005 Set_Etype
(R_Cno
, Typ
);
8006 Set_Raises_Constraint_Error
(R_Cno
);
8007 Set_Is_Static_Expression
(R_Cno
, Stat
);
8009 -- Now deal with possible local raise handling
8011 Possible_Local_Raise
(R_Cno
, Standard_Constraint_Error
);
8012 end Install_Static_Check
;
8014 -------------------------
8015 -- Is_Check_Suppressed --
8016 -------------------------
8018 function Is_Check_Suppressed
(E
: Entity_Id
; C
: Check_Id
) return Boolean is
8019 Ptr
: Suppress_Stack_Entry_Ptr
;
8022 -- First search the local entity suppress stack. We search this from the
8023 -- top of the stack down so that we get the innermost entry that applies
8024 -- to this case if there are nested entries.
8026 Ptr
:= Local_Suppress_Stack_Top
;
8027 while Ptr
/= null loop
8028 if (Ptr
.Entity
= Empty
or else Ptr
.Entity
= E
)
8029 and then (Ptr
.Check
= All_Checks
or else Ptr
.Check
= C
)
8031 return Ptr
.Suppress
;
8037 -- Now search the global entity suppress table for a matching entry.
8038 -- We also search this from the top down so that if there are multiple
8039 -- pragmas for the same entity, the last one applies (not clear what
8040 -- or whether the RM specifies this handling, but it seems reasonable).
8042 Ptr
:= Global_Suppress_Stack_Top
;
8043 while Ptr
/= null loop
8044 if (Ptr
.Entity
= Empty
or else Ptr
.Entity
= E
)
8045 and then (Ptr
.Check
= All_Checks
or else Ptr
.Check
= C
)
8047 return Ptr
.Suppress
;
8053 -- If we did not find a matching entry, then use the normal scope
8054 -- suppress value after all (actually this will be the global setting
8055 -- since it clearly was not overridden at any point). For a predefined
8056 -- check, we test the specific flag. For a user defined check, we check
8057 -- the All_Checks flag. The Overflow flag requires special handling to
8058 -- deal with the General vs Assertion case
8060 if C
= Overflow_Check
then
8061 return Overflow_Checks_Suppressed
(Empty
);
8062 elsif C
in Predefined_Check_Id
then
8063 return Scope_Suppress
.Suppress
(C
);
8065 return Scope_Suppress
.Suppress
(All_Checks
);
8067 end Is_Check_Suppressed
;
8069 ---------------------
8070 -- Kill_All_Checks --
8071 ---------------------
8073 procedure Kill_All_Checks
is
8075 if Debug_Flag_CC
then
8076 w
("Kill_All_Checks");
8079 -- We reset the number of saved checks to zero, and also modify all
8080 -- stack entries for statement ranges to indicate that the number of
8081 -- checks at each level is now zero.
8083 Num_Saved_Checks
:= 0;
8085 -- Note: the Int'Min here avoids any possibility of J being out of
8086 -- range when called from e.g. Conditional_Statements_Begin.
8088 for J
in 1 .. Int
'Min (Saved_Checks_TOS
, Saved_Checks_Stack
'Last) loop
8089 Saved_Checks_Stack
(J
) := 0;
8091 end Kill_All_Checks
;
8097 procedure Kill_Checks
(V
: Entity_Id
) is
8099 if Debug_Flag_CC
then
8100 w
("Kill_Checks for entity", Int
(V
));
8103 for J
in 1 .. Num_Saved_Checks
loop
8104 if Saved_Checks
(J
).Entity
= V
then
8105 if Debug_Flag_CC
then
8106 w
(" Checks killed for saved check ", J
);
8109 Saved_Checks
(J
).Killed
:= True;
8114 ------------------------------
8115 -- Length_Checks_Suppressed --
8116 ------------------------------
8118 function Length_Checks_Suppressed
(E
: Entity_Id
) return Boolean is
8120 if Present
(E
) and then Checks_May_Be_Suppressed
(E
) then
8121 return Is_Check_Suppressed
(E
, Length_Check
);
8123 return Scope_Suppress
.Suppress
(Length_Check
);
8125 end Length_Checks_Suppressed
;
8127 -----------------------
8128 -- Make_Bignum_Block --
8129 -----------------------
8131 function Make_Bignum_Block
(Loc
: Source_Ptr
) return Node_Id
is
8132 M
: constant Entity_Id
:= Make_Defining_Identifier
(Loc
, Name_uM
);
8135 Make_Block_Statement
(Loc
,
8137 New_List
(Build_SS_Mark_Call
(Loc
, M
)),
8138 Handled_Statement_Sequence
=>
8139 Make_Handled_Sequence_Of_Statements
(Loc
,
8140 Statements
=> New_List
(Build_SS_Release_Call
(Loc
, M
))));
8141 end Make_Bignum_Block
;
8143 ----------------------------------
8144 -- Minimize_Eliminate_Overflows --
8145 ----------------------------------
8147 -- This is a recursive routine that is called at the top of an expression
8148 -- tree to properly process overflow checking for a whole subtree by making
8149 -- recursive calls to process operands. This processing may involve the use
8150 -- of bignum or long long integer arithmetic, which will change the types
8151 -- of operands and results. That's why we can't do this bottom up (since
8152 -- it would interfere with semantic analysis).
8154 -- What happens is that if MINIMIZED/ELIMINATED mode is in effect then
8155 -- the operator expansion routines, as well as the expansion routines for
8156 -- if/case expression, do nothing (for the moment) except call the routine
8157 -- to apply the overflow check (Apply_Arithmetic_Overflow_Check). That
8158 -- routine does nothing for non top-level nodes, so at the point where the
8159 -- call is made for the top level node, the entire expression subtree has
8160 -- not been expanded, or processed for overflow. All that has to happen as
8161 -- a result of the top level call to this routine.
8163 -- As noted above, the overflow processing works by making recursive calls
8164 -- for the operands, and figuring out what to do, based on the processing
8165 -- of these operands (e.g. if a bignum operand appears, the parent op has
8166 -- to be done in bignum mode), and the determined ranges of the operands.
8168 -- After possible rewriting of a constituent subexpression node, a call is
8169 -- made to either reexpand the node (if nothing has changed) or reanalyze
8170 -- the node (if it has been modified by the overflow check processing). The
8171 -- Analyzed_Flag is set to False before the reexpand/reanalyze. To avoid
8172 -- a recursive call into the whole overflow apparatus, an important rule
8173 -- for this call is that the overflow handling mode must be temporarily set
8176 procedure Minimize_Eliminate_Overflows
8180 Top_Level
: Boolean)
8182 Rtyp
: constant Entity_Id
:= Etype
(N
);
8183 pragma Assert
(Is_Signed_Integer_Type
(Rtyp
));
8184 -- Result type, must be a signed integer type
8186 Check_Mode
: constant Overflow_Mode_Type
:= Overflow_Check_Mode
;
8187 pragma Assert
(Check_Mode
in Minimized_Or_Eliminated
);
8189 Loc
: constant Source_Ptr
:= Sloc
(N
);
8192 -- Ranges of values for right operand (operator case)
8194 Llo
: Uint
:= No_Uint
; -- initialize to prevent warning
8195 Lhi
: Uint
:= No_Uint
; -- initialize to prevent warning
8196 -- Ranges of values for left operand (operator case)
8198 LLIB
: constant Entity_Id
:= Base_Type
(Standard_Long_Long_Integer
);
8199 -- Operands and results are of this type when we convert
8201 LLLo
: constant Uint
:= Intval
(Type_Low_Bound
(LLIB
));
8202 LLHi
: constant Uint
:= Intval
(Type_High_Bound
(LLIB
));
8203 -- Bounds of Long_Long_Integer
8205 Binary
: constant Boolean := Nkind
(N
) in N_Binary_Op
;
8206 -- Indicates binary operator case
8209 -- Used in call to Determine_Range
8211 Bignum_Operands
: Boolean;
8212 -- Set True if one or more operands is already of type Bignum, meaning
8213 -- that for sure (regardless of Top_Level setting) we are committed to
8214 -- doing the operation in Bignum mode (or in the case of a case or if
8215 -- expression, converting all the dependent expressions to Bignum).
8217 Long_Long_Integer_Operands
: Boolean;
8218 -- Set True if one or more operands is already of type Long_Long_Integer
8219 -- which means that if the result is known to be in the result type
8220 -- range, then we must convert such operands back to the result type.
8222 procedure Reanalyze
(Typ
: Entity_Id
; Suppress
: Boolean := False);
8223 -- This is called when we have modified the node and we therefore need
8224 -- to reanalyze it. It is important that we reset the mode to STRICT for
8225 -- this reanalysis, since if we leave it in MINIMIZED or ELIMINATED mode
8226 -- we would reenter this routine recursively which would not be good.
8227 -- The argument Suppress is set True if we also want to suppress
8228 -- overflow checking for the reexpansion (this is set when we know
8229 -- overflow is not possible). Typ is the type for the reanalysis.
8231 procedure Reexpand
(Suppress
: Boolean := False);
8232 -- This is like Reanalyze, but does not do the Analyze step, it only
8233 -- does a reexpansion. We do this reexpansion in STRICT mode, so that
8234 -- instead of reentering the MINIMIZED/ELIMINATED mode processing, we
8235 -- follow the normal expansion path (e.g. converting A**4 to A**2**2).
8236 -- Note that skipping reanalysis is not just an optimization, testing
8237 -- has showed up several complex cases in which reanalyzing an already
8238 -- analyzed node causes incorrect behavior.
8240 function In_Result_Range
return Boolean;
8241 -- Returns True iff Lo .. Hi are within range of the result type
8243 procedure Max
(A
: in out Uint
; B
: Uint
);
8244 -- If A is No_Uint, sets A to B, else to UI_Max (A, B)
8246 procedure Min
(A
: in out Uint
; B
: Uint
);
8247 -- If A is No_Uint, sets A to B, else to UI_Min (A, B)
8249 ---------------------
8250 -- In_Result_Range --
8251 ---------------------
8253 function In_Result_Range
return Boolean is
8255 if Lo
= No_Uint
or else Hi
= No_Uint
then
8258 elsif Is_OK_Static_Subtype
(Etype
(N
)) then
8259 return Lo
>= Expr_Value
(Type_Low_Bound
(Rtyp
))
8261 Hi
<= Expr_Value
(Type_High_Bound
(Rtyp
));
8264 return Lo
>= Expr_Value
(Type_Low_Bound
(Base_Type
(Rtyp
)))
8266 Hi
<= Expr_Value
(Type_High_Bound
(Base_Type
(Rtyp
)));
8268 end In_Result_Range
;
8274 procedure Max
(A
: in out Uint
; B
: Uint
) is
8276 if A
= No_Uint
or else B
> A
then
8285 procedure Min
(A
: in out Uint
; B
: Uint
) is
8287 if A
= No_Uint
or else B
< A
then
8296 procedure Reanalyze
(Typ
: Entity_Id
; Suppress
: Boolean := False) is
8297 Svg
: constant Overflow_Mode_Type
:=
8298 Scope_Suppress
.Overflow_Mode_General
;
8299 Sva
: constant Overflow_Mode_Type
:=
8300 Scope_Suppress
.Overflow_Mode_Assertions
;
8301 Svo
: constant Boolean :=
8302 Scope_Suppress
.Suppress
(Overflow_Check
);
8305 Scope_Suppress
.Overflow_Mode_General
:= Strict
;
8306 Scope_Suppress
.Overflow_Mode_Assertions
:= Strict
;
8309 Scope_Suppress
.Suppress
(Overflow_Check
) := True;
8312 Analyze_And_Resolve
(N
, Typ
);
8314 Scope_Suppress
.Suppress
(Overflow_Check
) := Svo
;
8315 Scope_Suppress
.Overflow_Mode_General
:= Svg
;
8316 Scope_Suppress
.Overflow_Mode_Assertions
:= Sva
;
8323 procedure Reexpand
(Suppress
: Boolean := False) is
8324 Svg
: constant Overflow_Mode_Type
:=
8325 Scope_Suppress
.Overflow_Mode_General
;
8326 Sva
: constant Overflow_Mode_Type
:=
8327 Scope_Suppress
.Overflow_Mode_Assertions
;
8328 Svo
: constant Boolean :=
8329 Scope_Suppress
.Suppress
(Overflow_Check
);
8332 Scope_Suppress
.Overflow_Mode_General
:= Strict
;
8333 Scope_Suppress
.Overflow_Mode_Assertions
:= Strict
;
8334 Set_Analyzed
(N
, False);
8337 Scope_Suppress
.Suppress
(Overflow_Check
) := True;
8342 Scope_Suppress
.Suppress
(Overflow_Check
) := Svo
;
8343 Scope_Suppress
.Overflow_Mode_General
:= Svg
;
8344 Scope_Suppress
.Overflow_Mode_Assertions
:= Sva
;
8347 -- Start of processing for Minimize_Eliminate_Overflows
8350 -- Case where we do not have a signed integer arithmetic operation
8352 if not Is_Signed_Integer_Arithmetic_Op
(N
) then
8354 -- Use the normal Determine_Range routine to get the range. We
8355 -- don't require operands to be valid, invalid values may result in
8356 -- rubbish results where the result has not been properly checked for
8357 -- overflow, that's fine.
8359 Determine_Range
(N
, OK
, Lo
, Hi
, Assume_Valid
=> False);
8361 -- If Determine_Range did not work (can this in fact happen? Not
8362 -- clear but might as well protect), use type bounds.
8365 Lo
:= Intval
(Type_Low_Bound
(Base_Type
(Etype
(N
))));
8366 Hi
:= Intval
(Type_High_Bound
(Base_Type
(Etype
(N
))));
8369 -- If we don't have a binary operator, all we have to do is to set
8370 -- the Hi/Lo range, so we are done.
8374 -- Processing for if expression
8376 elsif Nkind
(N
) = N_If_Expression
then
8378 Then_DE
: constant Node_Id
:= Next
(First
(Expressions
(N
)));
8379 Else_DE
: constant Node_Id
:= Next
(Then_DE
);
8382 Bignum_Operands
:= False;
8384 Minimize_Eliminate_Overflows
8385 (Then_DE
, Lo
, Hi
, Top_Level
=> False);
8387 if Lo
= No_Uint
then
8388 Bignum_Operands
:= True;
8391 Minimize_Eliminate_Overflows
8392 (Else_DE
, Rlo
, Rhi
, Top_Level
=> False);
8394 if Rlo
= No_Uint
then
8395 Bignum_Operands
:= True;
8397 Long_Long_Integer_Operands
:=
8398 Etype
(Then_DE
) = LLIB
or else Etype
(Else_DE
) = LLIB
;
8404 -- If at least one of our operands is now Bignum, we must rebuild
8405 -- the if expression to use Bignum operands. We will analyze the
8406 -- rebuilt if expression with overflow checks off, since once we
8407 -- are in bignum mode, we are all done with overflow checks.
8409 if Bignum_Operands
then
8411 Make_If_Expression
(Loc
,
8412 Expressions
=> New_List
(
8413 Remove_Head
(Expressions
(N
)),
8414 Convert_To_Bignum
(Then_DE
),
8415 Convert_To_Bignum
(Else_DE
)),
8416 Is_Elsif
=> Is_Elsif
(N
)));
8418 Reanalyze
(RTE
(RE_Bignum
), Suppress
=> True);
8420 -- If we have no Long_Long_Integer operands, then we are in result
8421 -- range, since it means that none of our operands felt the need
8422 -- to worry about overflow (otherwise it would have already been
8423 -- converted to long long integer or bignum). We reexpand to
8424 -- complete the expansion of the if expression (but we do not
8425 -- need to reanalyze).
8427 elsif not Long_Long_Integer_Operands
then
8428 Set_Do_Overflow_Check
(N
, False);
8431 -- Otherwise convert us to long long integer mode. Note that we
8432 -- don't need any further overflow checking at this level.
8435 Convert_To_And_Rewrite
(LLIB
, Then_DE
);
8436 Convert_To_And_Rewrite
(LLIB
, Else_DE
);
8437 Set_Etype
(N
, LLIB
);
8439 -- Now reanalyze with overflow checks off
8441 Set_Do_Overflow_Check
(N
, False);
8442 Reanalyze
(LLIB
, Suppress
=> True);
8448 -- Here for case expression
8450 elsif Nkind
(N
) = N_Case_Expression
then
8451 Bignum_Operands
:= False;
8452 Long_Long_Integer_Operands
:= False;
8458 -- Loop through expressions applying recursive call
8460 Alt
:= First
(Alternatives
(N
));
8461 while Present
(Alt
) loop
8463 Aexp
: constant Node_Id
:= Expression
(Alt
);
8466 Minimize_Eliminate_Overflows
8467 (Aexp
, Lo
, Hi
, Top_Level
=> False);
8469 if Lo
= No_Uint
then
8470 Bignum_Operands
:= True;
8471 elsif Etype
(Aexp
) = LLIB
then
8472 Long_Long_Integer_Operands
:= True;
8479 -- If we have no bignum or long long integer operands, it means
8480 -- that none of our dependent expressions could raise overflow.
8481 -- In this case, we simply return with no changes except for
8482 -- resetting the overflow flag, since we are done with overflow
8483 -- checks for this node. We will reexpand to get the needed
8484 -- expansion for the case expression, but we do not need to
8485 -- reanalyze, since nothing has changed.
8487 if not (Bignum_Operands
or Long_Long_Integer_Operands
) then
8488 Set_Do_Overflow_Check
(N
, False);
8489 Reexpand
(Suppress
=> True);
8491 -- Otherwise we are going to rebuild the case expression using
8492 -- either bignum or long long integer operands throughout.
8497 pragma Warnings
(Off
, Rtype
);
8502 New_Alts
:= New_List
;
8503 Alt
:= First
(Alternatives
(N
));
8504 while Present
(Alt
) loop
8505 if Bignum_Operands
then
8506 New_Exp
:= Convert_To_Bignum
(Expression
(Alt
));
8507 Rtype
:= RTE
(RE_Bignum
);
8509 New_Exp
:= Convert_To
(LLIB
, Expression
(Alt
));
8513 Append_To
(New_Alts
,
8514 Make_Case_Expression_Alternative
(Sloc
(Alt
),
8516 Discrete_Choices
=> Discrete_Choices
(Alt
),
8517 Expression
=> New_Exp
));
8523 Make_Case_Expression
(Loc
,
8524 Expression
=> Expression
(N
),
8525 Alternatives
=> New_Alts
));
8527 Reanalyze
(Rtype
, Suppress
=> True);
8535 -- If we have an arithmetic operator we make recursive calls on the
8536 -- operands to get the ranges (and to properly process the subtree
8537 -- that lies below us).
8539 Minimize_Eliminate_Overflows
8540 (Right_Opnd
(N
), Rlo
, Rhi
, Top_Level
=> False);
8543 Minimize_Eliminate_Overflows
8544 (Left_Opnd
(N
), Llo
, Lhi
, Top_Level
=> False);
8547 -- Record if we have Long_Long_Integer operands
8549 Long_Long_Integer_Operands
:=
8550 Etype
(Right_Opnd
(N
)) = LLIB
8551 or else (Binary
and then Etype
(Left_Opnd
(N
)) = LLIB
);
8553 -- If either operand is a bignum, then result will be a bignum and we
8554 -- don't need to do any range analysis. As previously discussed we could
8555 -- do range analysis in such cases, but it could mean working with giant
8556 -- numbers at compile time for very little gain (the number of cases
8557 -- in which we could slip back from bignum mode is small).
8559 if Rlo
= No_Uint
or else (Binary
and then Llo
= No_Uint
) then
8562 Bignum_Operands
:= True;
8564 -- Otherwise compute result range
8567 Bignum_Operands
:= False;
8575 Hi
:= UI_Max
(abs Rlo
, abs Rhi
);
8587 -- If the right operand can only be zero, set 0..0
8589 if Rlo
= 0 and then Rhi
= 0 then
8593 -- Possible bounds of division must come from dividing end
8594 -- values of the input ranges (four possibilities), provided
8595 -- zero is not included in the possible values of the right
8598 -- Otherwise, we just consider two intervals of values for
8599 -- the right operand: the interval of negative values (up to
8600 -- -1) and the interval of positive values (starting at 1).
8601 -- Since division by 1 is the identity, and division by -1
8602 -- is negation, we get all possible bounds of division in that
8603 -- case by considering:
8604 -- - all values from the division of end values of input
8606 -- - the end values of the left operand;
8607 -- - the negation of the end values of the left operand.
8611 Mrk
: constant Uintp
.Save_Mark
:= Mark
;
8612 -- Mark so we can release the RR and Ev values
8620 -- Discard extreme values of zero for the divisor, since
8621 -- they will simply result in an exception in any case.
8629 -- Compute possible bounds coming from dividing end
8630 -- values of the input ranges.
8637 Lo
:= UI_Min
(UI_Min
(Ev1
, Ev2
), UI_Min
(Ev3
, Ev4
));
8638 Hi
:= UI_Max
(UI_Max
(Ev1
, Ev2
), UI_Max
(Ev3
, Ev4
));
8640 -- If the right operand can be both negative or positive,
8641 -- include the end values of the left operand in the
8642 -- extreme values, as well as their negation.
8644 if Rlo
< 0 and then Rhi
> 0 then
8651 UI_Min
(UI_Min
(Ev1
, Ev2
), UI_Min
(Ev3
, Ev4
)));
8653 UI_Max
(UI_Max
(Ev1
, Ev2
), UI_Max
(Ev3
, Ev4
)));
8656 -- Release the RR and Ev values
8658 Release_And_Save
(Mrk
, Lo
, Hi
);
8666 -- Discard negative values for the exponent, since they will
8667 -- simply result in an exception in any case.
8675 -- Estimate number of bits in result before we go computing
8676 -- giant useless bounds. Basically the number of bits in the
8677 -- result is the number of bits in the base multiplied by the
8678 -- value of the exponent. If this is big enough that the result
8679 -- definitely won't fit in Long_Long_Integer, switch to bignum
8680 -- mode immediately, and avoid computing giant bounds.
8682 -- The comparison here is approximate, but conservative, it
8683 -- only clicks on cases that are sure to exceed the bounds.
8685 if Num_Bits
(UI_Max
(abs Llo
, abs Lhi
)) * Rhi
+ 1 > 100 then
8689 -- If right operand is zero then result is 1
8696 -- High bound comes either from exponentiation of largest
8697 -- positive value to largest exponent value, or from
8698 -- the exponentiation of most negative value to an
8712 if Rhi
mod 2 = 0 then
8715 Hi2
:= Llo
** (Rhi
- 1);
8721 Hi
:= UI_Max
(Hi1
, Hi2
);
8724 -- Result can only be negative if base can be negative
8727 if Rhi
mod 2 = 0 then
8728 Lo
:= Llo
** (Rhi
- 1);
8733 -- Otherwise low bound is minimum ** minimum
8750 Maxabs
: constant Uint
:= UI_Max
(abs Rlo
, abs Rhi
) - 1;
8751 -- This is the maximum absolute value of the result
8757 -- The result depends only on the sign and magnitude of
8758 -- the right operand, it does not depend on the sign or
8759 -- magnitude of the left operand.
8772 when N_Op_Multiply
=>
8774 -- Possible bounds of multiplication must come from multiplying
8775 -- end values of the input ranges (four possibilities).
8778 Mrk
: constant Uintp
.Save_Mark
:= Mark
;
8779 -- Mark so we can release the Ev values
8781 Ev1
: constant Uint
:= Llo
* Rlo
;
8782 Ev2
: constant Uint
:= Llo
* Rhi
;
8783 Ev3
: constant Uint
:= Lhi
* Rlo
;
8784 Ev4
: constant Uint
:= Lhi
* Rhi
;
8787 Lo
:= UI_Min
(UI_Min
(Ev1
, Ev2
), UI_Min
(Ev3
, Ev4
));
8788 Hi
:= UI_Max
(UI_Max
(Ev1
, Ev2
), UI_Max
(Ev3
, Ev4
));
8790 -- Release the Ev values
8792 Release_And_Save
(Mrk
, Lo
, Hi
);
8795 -- Plus operator (affirmation)
8805 Maxabs
: constant Uint
:= UI_Max
(abs Rlo
, abs Rhi
) - 1;
8806 -- This is the maximum absolute value of the result. Note
8807 -- that the result range does not depend on the sign of the
8814 -- Case of left operand negative, which results in a range
8815 -- of -Maxabs .. 0 for those negative values. If there are
8816 -- no negative values then Lo value of result is always 0.
8822 -- Case of left operand positive
8831 when N_Op_Subtract
=>
8835 -- Nothing else should be possible
8838 raise Program_Error
;
8842 -- Here for the case where we have not rewritten anything (no bignum
8843 -- operands or long long integer operands), and we know the result.
8844 -- If we know we are in the result range, and we do not have Bignum
8845 -- operands or Long_Long_Integer operands, we can just reexpand with
8846 -- overflow checks turned off (since we know we cannot have overflow).
8847 -- As always the reexpansion is required to complete expansion of the
8848 -- operator, but we do not need to reanalyze, and we prevent recursion
8849 -- by suppressing the check.
8851 if not (Bignum_Operands
or Long_Long_Integer_Operands
)
8852 and then In_Result_Range
8854 Set_Do_Overflow_Check
(N
, False);
8855 Reexpand
(Suppress
=> True);
8858 -- Here we know that we are not in the result range, and in the general
8859 -- case we will move into either the Bignum or Long_Long_Integer domain
8860 -- to compute the result. However, there is one exception. If we are
8861 -- at the top level, and we do not have Bignum or Long_Long_Integer
8862 -- operands, we will have to immediately convert the result back to
8863 -- the result type, so there is no point in Bignum/Long_Long_Integer
8867 and then not (Bignum_Operands
or Long_Long_Integer_Operands
)
8869 -- One further refinement. If we are at the top level, but our parent
8870 -- is a type conversion, then go into bignum or long long integer node
8871 -- since the result will be converted to that type directly without
8872 -- going through the result type, and we may avoid an overflow. This
8873 -- is the case for example of Long_Long_Integer (A ** 4), where A is
8874 -- of type Integer, and the result A ** 4 fits in Long_Long_Integer
8875 -- but does not fit in Integer.
8877 and then Nkind
(Parent
(N
)) /= N_Type_Conversion
8879 -- Here keep original types, but we need to complete analysis
8881 -- One subtlety. We can't just go ahead and do an analyze operation
8882 -- here because it will cause recursion into the whole MINIMIZED/
8883 -- ELIMINATED overflow processing which is not what we want. Here
8884 -- we are at the top level, and we need a check against the result
8885 -- mode (i.e. we want to use STRICT mode). So do exactly that.
8886 -- Also, we have not modified the node, so this is a case where
8887 -- we need to reexpand, but not reanalyze.
8892 -- Cases where we do the operation in Bignum mode. This happens either
8893 -- because one of our operands is in Bignum mode already, or because
8894 -- the computed bounds are outside the bounds of Long_Long_Integer,
8895 -- which in some cases can be indicated by Hi and Lo being No_Uint.
8897 -- Note: we could do better here and in some cases switch back from
8898 -- Bignum mode to normal mode, e.g. big mod 2 must be in the range
8899 -- 0 .. 1, but the cases are rare and it is not worth the effort.
8900 -- Failing to do this switching back is only an efficiency issue.
8902 elsif Lo
= No_Uint
or else Lo
< LLLo
or else Hi
> LLHi
then
8904 -- OK, we are definitely outside the range of Long_Long_Integer. The
8905 -- question is whether to move to Bignum mode, or stay in the domain
8906 -- of Long_Long_Integer, signalling that an overflow check is needed.
8908 -- Obviously in MINIMIZED mode we stay with LLI, since we are not in
8909 -- the Bignum business. In ELIMINATED mode, we will normally move
8910 -- into Bignum mode, but there is an exception if neither of our
8911 -- operands is Bignum now, and we are at the top level (Top_Level
8912 -- set True). In this case, there is no point in moving into Bignum
8913 -- mode to prevent overflow if the caller will immediately convert
8914 -- the Bignum value back to LLI with an overflow check. It's more
8915 -- efficient to stay in LLI mode with an overflow check (if needed)
8917 if Check_Mode
= Minimized
8918 or else (Top_Level
and not Bignum_Operands
)
8920 if Do_Overflow_Check
(N
) then
8921 Enable_Overflow_Check
(N
);
8924 -- The result now has to be in Long_Long_Integer mode, so adjust
8925 -- the possible range to reflect this. Note these calls also
8926 -- change No_Uint values from the top level case to LLI bounds.
8931 -- Otherwise we are in ELIMINATED mode and we switch to Bignum mode
8934 pragma Assert
(Check_Mode
= Eliminated
);
8943 Fent
:= RTE
(RE_Big_Abs
);
8946 Fent
:= RTE
(RE_Big_Add
);
8949 Fent
:= RTE
(RE_Big_Div
);
8952 Fent
:= RTE
(RE_Big_Exp
);
8955 Fent
:= RTE
(RE_Big_Neg
);
8958 Fent
:= RTE
(RE_Big_Mod
);
8960 when N_Op_Multiply
=>
8961 Fent
:= RTE
(RE_Big_Mul
);
8964 Fent
:= RTE
(RE_Big_Rem
);
8966 when N_Op_Subtract
=>
8967 Fent
:= RTE
(RE_Big_Sub
);
8969 -- Anything else is an internal error, this includes the
8970 -- N_Op_Plus case, since how can plus cause the result
8971 -- to be out of range if the operand is in range?
8974 raise Program_Error
;
8977 -- Construct argument list for Bignum call, converting our
8978 -- operands to Bignum form if they are not already there.
8983 Append_To
(Args
, Convert_To_Bignum
(Left_Opnd
(N
)));
8986 Append_To
(Args
, Convert_To_Bignum
(Right_Opnd
(N
)));
8988 -- Now rewrite the arithmetic operator with a call to the
8989 -- corresponding bignum function.
8992 Make_Function_Call
(Loc
,
8993 Name
=> New_Occurrence_Of
(Fent
, Loc
),
8994 Parameter_Associations
=> Args
));
8995 Reanalyze
(RTE
(RE_Bignum
), Suppress
=> True);
8997 -- Indicate result is Bignum mode
9005 -- Otherwise we are in range of Long_Long_Integer, so no overflow
9006 -- check is required, at least not yet.
9009 Set_Do_Overflow_Check
(N
, False);
9012 -- Here we are not in Bignum territory, but we may have long long
9013 -- integer operands that need special handling. First a special check:
9014 -- If an exponentiation operator exponent is of type Long_Long_Integer,
9015 -- it means we converted it to prevent overflow, but exponentiation
9016 -- requires a Natural right operand, so convert it back to Natural.
9017 -- This conversion may raise an exception which is fine.
9019 if Nkind
(N
) = N_Op_Expon
and then Etype
(Right_Opnd
(N
)) = LLIB
then
9020 Convert_To_And_Rewrite
(Standard_Natural
, Right_Opnd
(N
));
9023 -- Here we will do the operation in Long_Long_Integer. We do this even
9024 -- if we know an overflow check is required, better to do this in long
9025 -- long integer mode, since we are less likely to overflow.
9027 -- Convert right or only operand to Long_Long_Integer, except that
9028 -- we do not touch the exponentiation right operand.
9030 if Nkind
(N
) /= N_Op_Expon
then
9031 Convert_To_And_Rewrite
(LLIB
, Right_Opnd
(N
));
9034 -- Convert left operand to Long_Long_Integer for binary case
9037 Convert_To_And_Rewrite
(LLIB
, Left_Opnd
(N
));
9040 -- Reset node to unanalyzed
9042 Set_Analyzed
(N
, False);
9043 Set_Etype
(N
, Empty
);
9044 Set_Entity
(N
, Empty
);
9046 -- Now analyze this new node. This reanalysis will complete processing
9047 -- for the node. In particular we will complete the expansion of an
9048 -- exponentiation operator (e.g. changing A ** 2 to A * A), and also
9049 -- we will complete any division checks (since we have not changed the
9050 -- setting of the Do_Division_Check flag).
9052 -- We do this reanalysis in STRICT mode to avoid recursion into the
9053 -- MINIMIZED/ELIMINATED handling, since we are now done with that.
9056 SG
: constant Overflow_Mode_Type
:=
9057 Scope_Suppress
.Overflow_Mode_General
;
9058 SA
: constant Overflow_Mode_Type
:=
9059 Scope_Suppress
.Overflow_Mode_Assertions
;
9062 Scope_Suppress
.Overflow_Mode_General
:= Strict
;
9063 Scope_Suppress
.Overflow_Mode_Assertions
:= Strict
;
9065 if not Do_Overflow_Check
(N
) then
9066 Reanalyze
(LLIB
, Suppress
=> True);
9071 Scope_Suppress
.Overflow_Mode_General
:= SG
;
9072 Scope_Suppress
.Overflow_Mode_Assertions
:= SA
;
9074 end Minimize_Eliminate_Overflows
;
9076 -------------------------
9077 -- Overflow_Check_Mode --
9078 -------------------------
9080 function Overflow_Check_Mode
return Overflow_Mode_Type
is
9082 if In_Assertion_Expr
= 0 then
9083 return Scope_Suppress
.Overflow_Mode_General
;
9085 return Scope_Suppress
.Overflow_Mode_Assertions
;
9087 end Overflow_Check_Mode
;
9089 --------------------------------
9090 -- Overflow_Checks_Suppressed --
9091 --------------------------------
9093 function Overflow_Checks_Suppressed
(E
: Entity_Id
) return Boolean is
9095 if Present
(E
) and then Checks_May_Be_Suppressed
(E
) then
9096 return Is_Check_Suppressed
(E
, Overflow_Check
);
9098 return Scope_Suppress
.Suppress
(Overflow_Check
);
9100 end Overflow_Checks_Suppressed
;
9102 ---------------------------------
9103 -- Predicate_Checks_Suppressed --
9104 ---------------------------------
9106 function Predicate_Checks_Suppressed
(E
: Entity_Id
) return Boolean is
9108 if Present
(E
) and then Checks_May_Be_Suppressed
(E
) then
9109 return Is_Check_Suppressed
(E
, Predicate_Check
);
9111 return Scope_Suppress
.Suppress
(Predicate_Check
);
9113 end Predicate_Checks_Suppressed
;
9115 -----------------------------
9116 -- Range_Checks_Suppressed --
9117 -----------------------------
9119 function Range_Checks_Suppressed
(E
: Entity_Id
) return Boolean is
9122 if Kill_Range_Checks
(E
) then
9125 elsif Checks_May_Be_Suppressed
(E
) then
9126 return Is_Check_Suppressed
(E
, Range_Check
);
9130 return Scope_Suppress
.Suppress
(Range_Check
);
9131 end Range_Checks_Suppressed
;
9133 -----------------------------------------
9134 -- Range_Or_Validity_Checks_Suppressed --
9135 -----------------------------------------
9137 -- Note: the coding would be simpler here if we simply made appropriate
9138 -- calls to Range/Validity_Checks_Suppressed, but that would result in
9139 -- duplicated checks which we prefer to avoid.
9141 function Range_Or_Validity_Checks_Suppressed
9142 (Expr
: Node_Id
) return Boolean
9145 -- Immediate return if scope checks suppressed for either check
9147 if Scope_Suppress
.Suppress
(Range_Check
)
9149 Scope_Suppress
.Suppress
(Validity_Check
)
9154 -- If no expression, that's odd, decide that checks are suppressed,
9155 -- since we don't want anyone trying to do checks in this case, which
9156 -- is most likely the result of some other error.
9162 -- Expression is present, so perform suppress checks on type
9165 Typ
: constant Entity_Id
:= Etype
(Expr
);
9167 if Checks_May_Be_Suppressed
(Typ
)
9168 and then (Is_Check_Suppressed
(Typ
, Range_Check
)
9170 Is_Check_Suppressed
(Typ
, Validity_Check
))
9176 -- If expression is an entity name, perform checks on this entity
9178 if Is_Entity_Name
(Expr
) then
9180 Ent
: constant Entity_Id
:= Entity
(Expr
);
9182 if Checks_May_Be_Suppressed
(Ent
) then
9183 return Is_Check_Suppressed
(Ent
, Range_Check
)
9184 or else Is_Check_Suppressed
(Ent
, Validity_Check
);
9189 -- If we fall through, no checks suppressed
9192 end Range_Or_Validity_Checks_Suppressed
;
9198 procedure Remove_Checks
(Expr
: Node_Id
) is
9199 function Process
(N
: Node_Id
) return Traverse_Result
;
9200 -- Process a single node during the traversal
9202 procedure Traverse
is new Traverse_Proc
(Process
);
9203 -- The traversal procedure itself
9209 function Process
(N
: Node_Id
) return Traverse_Result
is
9211 if Nkind
(N
) not in N_Subexpr
then
9215 Set_Do_Range_Check
(N
, False);
9219 Traverse
(Left_Opnd
(N
));
9222 when N_Attribute_Reference
=>
9223 Set_Do_Overflow_Check
(N
, False);
9225 when N_Function_Call
=>
9226 Set_Do_Tag_Check
(N
, False);
9229 Set_Do_Overflow_Check
(N
, False);
9233 Set_Do_Division_Check
(N
, False);
9236 Set_Do_Length_Check
(N
, False);
9239 Set_Do_Division_Check
(N
, False);
9242 Set_Do_Length_Check
(N
, False);
9245 Set_Do_Division_Check
(N
, False);
9248 Set_Do_Length_Check
(N
, False);
9255 Traverse
(Left_Opnd
(N
));
9258 when N_Selected_Component
=>
9259 Set_Do_Discriminant_Check
(N
, False);
9261 when N_Type_Conversion
=>
9262 Set_Do_Length_Check
(N
, False);
9263 Set_Do_Tag_Check
(N
, False);
9264 Set_Do_Overflow_Check
(N
, False);
9273 -- Start of processing for Remove_Checks
9279 ----------------------------
9280 -- Selected_Length_Checks --
9281 ----------------------------
9283 function Selected_Length_Checks
9285 Target_Typ
: Entity_Id
;
9286 Source_Typ
: Entity_Id
;
9287 Warn_Node
: Node_Id
) return Check_Result
9289 Loc
: constant Source_Ptr
:= Sloc
(Ck_Node
);
9292 Expr_Actual
: Node_Id
;
9294 Cond
: Node_Id
:= Empty
;
9295 Do_Access
: Boolean := False;
9296 Wnode
: Node_Id
:= Warn_Node
;
9297 Ret_Result
: Check_Result
:= (Empty
, Empty
);
9298 Num_Checks
: Natural := 0;
9300 procedure Add_Check
(N
: Node_Id
);
9301 -- Adds the action given to Ret_Result if N is non-Empty
9303 function Get_E_Length
(E
: Entity_Id
; Indx
: Nat
) return Node_Id
;
9304 function Get_N_Length
(N
: Node_Id
; Indx
: Nat
) return Node_Id
;
9305 -- Comments required ???
9307 function Same_Bounds
(L
: Node_Id
; R
: Node_Id
) return Boolean;
9308 -- True for equal literals and for nodes that denote the same constant
9309 -- entity, even if its value is not a static constant. This includes the
9310 -- case of a discriminal reference within an init proc. Removes some
9311 -- obviously superfluous checks.
9313 function Length_E_Cond
9314 (Exptyp
: Entity_Id
;
9316 Indx
: Nat
) return Node_Id
;
9317 -- Returns expression to compute:
9318 -- Typ'Length /= Exptyp'Length
9320 function Length_N_Cond
9323 Indx
: Nat
) return Node_Id
;
9324 -- Returns expression to compute:
9325 -- Typ'Length /= Expr'Length
9331 procedure Add_Check
(N
: Node_Id
) is
9335 -- For now, ignore attempt to place more than two checks ???
9336 -- This is really worrisome, are we really discarding checks ???
9338 if Num_Checks
= 2 then
9342 pragma Assert
(Num_Checks
<= 1);
9343 Num_Checks
:= Num_Checks
+ 1;
9344 Ret_Result
(Num_Checks
) := N
;
9352 function Get_E_Length
(E
: Entity_Id
; Indx
: Nat
) return Node_Id
is
9353 SE
: constant Entity_Id
:= Scope
(E
);
9355 E1
: Entity_Id
:= E
;
9358 if Ekind
(Scope
(E
)) = E_Record_Type
9359 and then Has_Discriminants
(Scope
(E
))
9361 N
:= Build_Discriminal_Subtype_Of_Component
(E
);
9364 Insert_Action
(Ck_Node
, N
);
9365 E1
:= Defining_Identifier
(N
);
9369 if Ekind
(E1
) = E_String_Literal_Subtype
then
9371 Make_Integer_Literal
(Loc
,
9372 Intval
=> String_Literal_Length
(E1
));
9374 elsif SE
/= Standard_Standard
9375 and then Ekind
(Scope
(SE
)) = E_Protected_Type
9376 and then Has_Discriminants
(Scope
(SE
))
9377 and then Has_Completion
(Scope
(SE
))
9378 and then not Inside_Init_Proc
9380 -- If the type whose length is needed is a private component
9381 -- constrained by a discriminant, we must expand the 'Length
9382 -- attribute into an explicit computation, using the discriminal
9383 -- of the current protected operation. This is because the actual
9384 -- type of the prival is constructed after the protected opera-
9385 -- tion has been fully expanded.
9388 Indx_Type
: Node_Id
;
9391 Do_Expand
: Boolean := False;
9394 Indx_Type
:= First_Index
(E
);
9396 for J
in 1 .. Indx
- 1 loop
9397 Next_Index
(Indx_Type
);
9400 Get_Index_Bounds
(Indx_Type
, Lo
, Hi
);
9402 if Nkind
(Lo
) = N_Identifier
9403 and then Ekind
(Entity
(Lo
)) = E_In_Parameter
9405 Lo
:= Get_Discriminal
(E
, Lo
);
9409 if Nkind
(Hi
) = N_Identifier
9410 and then Ekind
(Entity
(Hi
)) = E_In_Parameter
9412 Hi
:= Get_Discriminal
(E
, Hi
);
9417 if not Is_Entity_Name
(Lo
) then
9418 Lo
:= Duplicate_Subexpr_No_Checks
(Lo
);
9421 if not Is_Entity_Name
(Hi
) then
9422 Lo
:= Duplicate_Subexpr_No_Checks
(Hi
);
9428 Make_Op_Subtract
(Loc
,
9432 Right_Opnd
=> Make_Integer_Literal
(Loc
, 1));
9437 Make_Attribute_Reference
(Loc
,
9438 Attribute_Name
=> Name_Length
,
9440 New_Occurrence_Of
(E1
, Loc
));
9443 Set_Expressions
(N
, New_List
(
9444 Make_Integer_Literal
(Loc
, Indx
)));
9453 Make_Attribute_Reference
(Loc
,
9454 Attribute_Name
=> Name_Length
,
9456 New_Occurrence_Of
(E1
, Loc
));
9459 Set_Expressions
(N
, New_List
(
9460 Make_Integer_Literal
(Loc
, Indx
)));
9471 function Get_N_Length
(N
: Node_Id
; Indx
: Nat
) return Node_Id
is
9474 Make_Attribute_Reference
(Loc
,
9475 Attribute_Name
=> Name_Length
,
9477 Duplicate_Subexpr_No_Checks
(N
, Name_Req
=> True),
9478 Expressions
=> New_List
(
9479 Make_Integer_Literal
(Loc
, Indx
)));
9486 function Length_E_Cond
9487 (Exptyp
: Entity_Id
;
9489 Indx
: Nat
) return Node_Id
9494 Left_Opnd
=> Get_E_Length
(Typ
, Indx
),
9495 Right_Opnd
=> Get_E_Length
(Exptyp
, Indx
));
9502 function Length_N_Cond
9505 Indx
: Nat
) return Node_Id
9510 Left_Opnd
=> Get_E_Length
(Typ
, Indx
),
9511 Right_Opnd
=> Get_N_Length
(Expr
, Indx
));
9518 function Same_Bounds
(L
: Node_Id
; R
: Node_Id
) return Boolean is
9521 (Nkind
(L
) = N_Integer_Literal
9522 and then Nkind
(R
) = N_Integer_Literal
9523 and then Intval
(L
) = Intval
(R
))
9527 and then Ekind
(Entity
(L
)) = E_Constant
9528 and then ((Is_Entity_Name
(R
)
9529 and then Entity
(L
) = Entity
(R
))
9531 (Nkind
(R
) = N_Type_Conversion
9532 and then Is_Entity_Name
(Expression
(R
))
9533 and then Entity
(L
) = Entity
(Expression
(R
)))))
9537 and then Ekind
(Entity
(R
)) = E_Constant
9538 and then Nkind
(L
) = N_Type_Conversion
9539 and then Is_Entity_Name
(Expression
(L
))
9540 and then Entity
(R
) = Entity
(Expression
(L
)))
9544 and then Is_Entity_Name
(R
)
9545 and then Entity
(L
) = Entity
(R
)
9546 and then Ekind
(Entity
(L
)) = E_In_Parameter
9547 and then Inside_Init_Proc
);
9550 -- Start of processing for Selected_Length_Checks
9553 -- Checks will be applied only when generating code
9555 if not Expander_Active
then
9559 if Target_Typ
= Any_Type
9560 or else Target_Typ
= Any_Composite
9561 or else Raises_Constraint_Error
(Ck_Node
)
9570 T_Typ
:= Target_Typ
;
9572 if No
(Source_Typ
) then
9573 S_Typ
:= Etype
(Ck_Node
);
9575 S_Typ
:= Source_Typ
;
9578 if S_Typ
= Any_Type
or else S_Typ
= Any_Composite
then
9582 if Is_Access_Type
(T_Typ
) and then Is_Access_Type
(S_Typ
) then
9583 S_Typ
:= Designated_Type
(S_Typ
);
9584 T_Typ
:= Designated_Type
(T_Typ
);
9587 -- A simple optimization for the null case
9589 if Known_Null
(Ck_Node
) then
9594 if Is_Array_Type
(T_Typ
) and then Is_Array_Type
(S_Typ
) then
9595 if Is_Constrained
(T_Typ
) then
9597 -- The checking code to be generated will freeze the corresponding
9598 -- array type. However, we must freeze the type now, so that the
9599 -- freeze node does not appear within the generated if expression,
9602 Freeze_Before
(Ck_Node
, T_Typ
);
9604 Expr_Actual
:= Get_Referenced_Object
(Ck_Node
);
9605 Exptyp
:= Get_Actual_Subtype
(Ck_Node
);
9607 if Is_Access_Type
(Exptyp
) then
9608 Exptyp
:= Designated_Type
(Exptyp
);
9611 -- String_Literal case. This needs to be handled specially be-
9612 -- cause no index types are available for string literals. The
9613 -- condition is simply:
9615 -- T_Typ'Length = string-literal-length
9617 if Nkind
(Expr_Actual
) = N_String_Literal
9618 and then Ekind
(Etype
(Expr_Actual
)) = E_String_Literal_Subtype
9622 Left_Opnd
=> Get_E_Length
(T_Typ
, 1),
9624 Make_Integer_Literal
(Loc
,
9626 String_Literal_Length
(Etype
(Expr_Actual
))));
9628 -- General array case. Here we have a usable actual subtype for
9629 -- the expression, and the condition is built from the two types
9632 -- T_Typ'Length /= Exptyp'Length or else
9633 -- T_Typ'Length (2) /= Exptyp'Length (2) or else
9634 -- T_Typ'Length (3) /= Exptyp'Length (3) or else
9637 elsif Is_Constrained
(Exptyp
) then
9639 Ndims
: constant Nat
:= Number_Dimensions
(T_Typ
);
9652 -- At the library level, we need to ensure that the type of
9653 -- the object is elaborated before the check itself is
9654 -- emitted. This is only done if the object is in the
9655 -- current compilation unit, otherwise the type is frozen
9656 -- and elaborated in its unit.
9658 if Is_Itype
(Exptyp
)
9660 Ekind
(Cunit_Entity
(Current_Sem_Unit
)) = E_Package
9662 not In_Package_Body
(Cunit_Entity
(Current_Sem_Unit
))
9663 and then In_Open_Scopes
(Scope
(Exptyp
))
9665 Ref_Node
:= Make_Itype_Reference
(Sloc
(Ck_Node
));
9666 Set_Itype
(Ref_Node
, Exptyp
);
9667 Insert_Action
(Ck_Node
, Ref_Node
);
9670 L_Index
:= First_Index
(T_Typ
);
9671 R_Index
:= First_Index
(Exptyp
);
9673 for Indx
in 1 .. Ndims
loop
9674 if not (Nkind
(L_Index
) = N_Raise_Constraint_Error
9676 Nkind
(R_Index
) = N_Raise_Constraint_Error
)
9678 Get_Index_Bounds
(L_Index
, L_Low
, L_High
);
9679 Get_Index_Bounds
(R_Index
, R_Low
, R_High
);
9681 -- Deal with compile time length check. Note that we
9682 -- skip this in the access case, because the access
9683 -- value may be null, so we cannot know statically.
9686 and then Compile_Time_Known_Value
(L_Low
)
9687 and then Compile_Time_Known_Value
(L_High
)
9688 and then Compile_Time_Known_Value
(R_Low
)
9689 and then Compile_Time_Known_Value
(R_High
)
9691 if Expr_Value
(L_High
) >= Expr_Value
(L_Low
) then
9692 L_Length
:= Expr_Value
(L_High
) -
9693 Expr_Value
(L_Low
) + 1;
9695 L_Length
:= UI_From_Int
(0);
9698 if Expr_Value
(R_High
) >= Expr_Value
(R_Low
) then
9699 R_Length
:= Expr_Value
(R_High
) -
9700 Expr_Value
(R_Low
) + 1;
9702 R_Length
:= UI_From_Int
(0);
9705 if L_Length
> R_Length
then
9707 (Compile_Time_Constraint_Error
9708 (Wnode
, "too few elements for}??", T_Typ
));
9710 elsif L_Length
< R_Length
then
9712 (Compile_Time_Constraint_Error
9713 (Wnode
, "too many elements for}??", T_Typ
));
9716 -- The comparison for an individual index subtype
9717 -- is omitted if the corresponding index subtypes
9718 -- statically match, since the result is known to
9719 -- be true. Note that this test is worth while even
9720 -- though we do static evaluation, because non-static
9721 -- subtypes can statically match.
9724 Subtypes_Statically_Match
9725 (Etype
(L_Index
), Etype
(R_Index
))
9728 (Same_Bounds
(L_Low
, R_Low
)
9729 and then Same_Bounds
(L_High
, R_High
))
9732 (Cond
, Length_E_Cond
(Exptyp
, T_Typ
, Indx
));
9741 -- Handle cases where we do not get a usable actual subtype that
9742 -- is constrained. This happens for example in the function call
9743 -- and explicit dereference cases. In these cases, we have to get
9744 -- the length or range from the expression itself, making sure we
9745 -- do not evaluate it more than once.
9747 -- Here Ck_Node is the original expression, or more properly the
9748 -- result of applying Duplicate_Expr to the original tree, forcing
9749 -- the result to be a name.
9753 Ndims
: constant Nat
:= Number_Dimensions
(T_Typ
);
9756 -- Build the condition for the explicit dereference case
9758 for Indx
in 1 .. Ndims
loop
9760 (Cond
, Length_N_Cond
(Ck_Node
, T_Typ
, Indx
));
9767 -- Construct the test and insert into the tree
9769 if Present
(Cond
) then
9771 Cond
:= Guard_Access
(Cond
, Loc
, Ck_Node
);
9775 (Make_Raise_Constraint_Error
(Loc
,
9777 Reason
=> CE_Length_Check_Failed
));
9781 end Selected_Length_Checks
;
9783 ---------------------------
9784 -- Selected_Range_Checks --
9785 ---------------------------
9787 function Selected_Range_Checks
9789 Target_Typ
: Entity_Id
;
9790 Source_Typ
: Entity_Id
;
9791 Warn_Node
: Node_Id
) return Check_Result
9793 Loc
: constant Source_Ptr
:= Sloc
(Ck_Node
);
9796 Expr_Actual
: Node_Id
;
9798 Cond
: Node_Id
:= Empty
;
9799 Do_Access
: Boolean := False;
9800 Wnode
: Node_Id
:= Warn_Node
;
9801 Ret_Result
: Check_Result
:= (Empty
, Empty
);
9802 Num_Checks
: Integer := 0;
9804 procedure Add_Check
(N
: Node_Id
);
9805 -- Adds the action given to Ret_Result if N is non-Empty
9807 function Discrete_Range_Cond
9809 Typ
: Entity_Id
) return Node_Id
;
9810 -- Returns expression to compute:
9811 -- Low_Bound (Expr) < Typ'First
9813 -- High_Bound (Expr) > Typ'Last
9815 function Discrete_Expr_Cond
9817 Typ
: Entity_Id
) return Node_Id
;
9818 -- Returns expression to compute:
9823 function Get_E_First_Or_Last
9827 Nam
: Name_Id
) return Node_Id
;
9828 -- Returns an attribute reference
9829 -- E'First or E'Last
9830 -- with a source location of Loc.
9832 -- Nam is Name_First or Name_Last, according to which attribute is
9833 -- desired. If Indx is non-zero, it is passed as a literal in the
9834 -- Expressions of the attribute reference (identifying the desired
9835 -- array dimension).
9837 function Get_N_First
(N
: Node_Id
; Indx
: Nat
) return Node_Id
;
9838 function Get_N_Last
(N
: Node_Id
; Indx
: Nat
) return Node_Id
;
9839 -- Returns expression to compute:
9840 -- N'First or N'Last using Duplicate_Subexpr_No_Checks
9842 function Range_E_Cond
9843 (Exptyp
: Entity_Id
;
9847 -- Returns expression to compute:
9848 -- Exptyp'First < Typ'First or else Exptyp'Last > Typ'Last
9850 function Range_Equal_E_Cond
9851 (Exptyp
: Entity_Id
;
9853 Indx
: Nat
) return Node_Id
;
9854 -- Returns expression to compute:
9855 -- Exptyp'First /= Typ'First or else Exptyp'Last /= Typ'Last
9857 function Range_N_Cond
9860 Indx
: Nat
) return Node_Id
;
9861 -- Return expression to compute:
9862 -- Expr'First < Typ'First or else Expr'Last > Typ'Last
9868 procedure Add_Check
(N
: Node_Id
) is
9872 -- For now, ignore attempt to place more than 2 checks ???
9874 if Num_Checks
= 2 then
9878 pragma Assert
(Num_Checks
<= 1);
9879 Num_Checks
:= Num_Checks
+ 1;
9880 Ret_Result
(Num_Checks
) := N
;
9884 -------------------------
9885 -- Discrete_Expr_Cond --
9886 -------------------------
9888 function Discrete_Expr_Cond
9890 Typ
: Entity_Id
) return Node_Id
9898 Convert_To
(Base_Type
(Typ
),
9899 Duplicate_Subexpr_No_Checks
(Expr
)),
9901 Convert_To
(Base_Type
(Typ
),
9902 Get_E_First_Or_Last
(Loc
, Typ
, 0, Name_First
))),
9907 Convert_To
(Base_Type
(Typ
),
9908 Duplicate_Subexpr_No_Checks
(Expr
)),
9912 Get_E_First_Or_Last
(Loc
, Typ
, 0, Name_Last
))));
9913 end Discrete_Expr_Cond
;
9915 -------------------------
9916 -- Discrete_Range_Cond --
9917 -------------------------
9919 function Discrete_Range_Cond
9921 Typ
: Entity_Id
) return Node_Id
9923 LB
: Node_Id
:= Low_Bound
(Expr
);
9924 HB
: Node_Id
:= High_Bound
(Expr
);
9926 Left_Opnd
: Node_Id
;
9927 Right_Opnd
: Node_Id
;
9930 if Nkind
(LB
) = N_Identifier
9931 and then Ekind
(Entity
(LB
)) = E_Discriminant
9933 LB
:= New_Occurrence_Of
(Discriminal
(Entity
(LB
)), Loc
);
9940 (Base_Type
(Typ
), Duplicate_Subexpr_No_Checks
(LB
)),
9945 Get_E_First_Or_Last
(Loc
, Typ
, 0, Name_First
)));
9947 if Nkind
(HB
) = N_Identifier
9948 and then Ekind
(Entity
(HB
)) = E_Discriminant
9950 HB
:= New_Occurrence_Of
(Discriminal
(Entity
(HB
)), Loc
);
9957 (Base_Type
(Typ
), Duplicate_Subexpr_No_Checks
(HB
)),
9962 Get_E_First_Or_Last
(Loc
, Typ
, 0, Name_Last
)));
9964 return Make_Or_Else
(Loc
, Left_Opnd
, Right_Opnd
);
9965 end Discrete_Range_Cond
;
9967 -------------------------
9968 -- Get_E_First_Or_Last --
9969 -------------------------
9971 function Get_E_First_Or_Last
9975 Nam
: Name_Id
) return Node_Id
9980 Exprs
:= New_List
(Make_Integer_Literal
(Loc
, UI_From_Int
(Indx
)));
9985 return Make_Attribute_Reference
(Loc
,
9986 Prefix
=> New_Occurrence_Of
(E
, Loc
),
9987 Attribute_Name
=> Nam
,
9988 Expressions
=> Exprs
);
9989 end Get_E_First_Or_Last
;
9995 function Get_N_First
(N
: Node_Id
; Indx
: Nat
) return Node_Id
is
9998 Make_Attribute_Reference
(Loc
,
9999 Attribute_Name
=> Name_First
,
10001 Duplicate_Subexpr_No_Checks
(N
, Name_Req
=> True),
10002 Expressions
=> New_List
(
10003 Make_Integer_Literal
(Loc
, Indx
)));
10010 function Get_N_Last
(N
: Node_Id
; Indx
: Nat
) return Node_Id
is
10013 Make_Attribute_Reference
(Loc
,
10014 Attribute_Name
=> Name_Last
,
10016 Duplicate_Subexpr_No_Checks
(N
, Name_Req
=> True),
10017 Expressions
=> New_List
(
10018 Make_Integer_Literal
(Loc
, Indx
)));
10025 function Range_E_Cond
10026 (Exptyp
: Entity_Id
;
10028 Indx
: Nat
) return Node_Id
10036 Get_E_First_Or_Last
(Loc
, Exptyp
, Indx
, Name_First
),
10038 Get_E_First_Or_Last
(Loc
, Typ
, Indx
, Name_First
)),
10043 Get_E_First_Or_Last
(Loc
, Exptyp
, Indx
, Name_Last
),
10045 Get_E_First_Or_Last
(Loc
, Typ
, Indx
, Name_Last
)));
10048 ------------------------
10049 -- Range_Equal_E_Cond --
10050 ------------------------
10052 function Range_Equal_E_Cond
10053 (Exptyp
: Entity_Id
;
10055 Indx
: Nat
) return Node_Id
10063 Get_E_First_Or_Last
(Loc
, Exptyp
, Indx
, Name_First
),
10065 Get_E_First_Or_Last
(Loc
, Typ
, Indx
, Name_First
)),
10070 Get_E_First_Or_Last
(Loc
, Exptyp
, Indx
, Name_Last
),
10072 Get_E_First_Or_Last
(Loc
, Typ
, Indx
, Name_Last
)));
10073 end Range_Equal_E_Cond
;
10079 function Range_N_Cond
10082 Indx
: Nat
) return Node_Id
10090 Get_N_First
(Expr
, Indx
),
10092 Get_E_First_Or_Last
(Loc
, Typ
, Indx
, Name_First
)),
10097 Get_N_Last
(Expr
, Indx
),
10099 Get_E_First_Or_Last
(Loc
, Typ
, Indx
, Name_Last
)));
10102 -- Start of processing for Selected_Range_Checks
10105 -- Checks will be applied only when generating code. In GNATprove mode,
10106 -- we do not apply the checks, but we still call Selected_Range_Checks
10107 -- to possibly issue errors on SPARK code when a run-time error can be
10108 -- detected at compile time.
10110 if not Expander_Active
and not GNATprove_Mode
then
10114 if Target_Typ
= Any_Type
10115 or else Target_Typ
= Any_Composite
10116 or else Raises_Constraint_Error
(Ck_Node
)
10125 T_Typ
:= Target_Typ
;
10127 if No
(Source_Typ
) then
10128 S_Typ
:= Etype
(Ck_Node
);
10130 S_Typ
:= Source_Typ
;
10133 if S_Typ
= Any_Type
or else S_Typ
= Any_Composite
then
10137 -- The order of evaluating T_Typ before S_Typ seems to be critical
10138 -- because S_Typ can be derived from Etype (Ck_Node), if it's not passed
10139 -- in, and since Node can be an N_Range node, it might be invalid.
10140 -- Should there be an assert check somewhere for taking the Etype of
10141 -- an N_Range node ???
10143 if Is_Access_Type
(T_Typ
) and then Is_Access_Type
(S_Typ
) then
10144 S_Typ
:= Designated_Type
(S_Typ
);
10145 T_Typ
:= Designated_Type
(T_Typ
);
10148 -- A simple optimization for the null case
10150 if Known_Null
(Ck_Node
) then
10155 -- For an N_Range Node, check for a null range and then if not
10156 -- null generate a range check action.
10158 if Nkind
(Ck_Node
) = N_Range
then
10160 -- There's no point in checking a range against itself
10162 if Ck_Node
= Scalar_Range
(T_Typ
) then
10167 T_LB
: constant Node_Id
:= Type_Low_Bound
(T_Typ
);
10168 T_HB
: constant Node_Id
:= Type_High_Bound
(T_Typ
);
10169 Known_T_LB
: constant Boolean := Compile_Time_Known_Value
(T_LB
);
10170 Known_T_HB
: constant Boolean := Compile_Time_Known_Value
(T_HB
);
10172 LB
: Node_Id
:= Low_Bound
(Ck_Node
);
10173 HB
: Node_Id
:= High_Bound
(Ck_Node
);
10174 Known_LB
: Boolean := False;
10175 Known_HB
: Boolean := False;
10177 Null_Range
: Boolean;
10178 Out_Of_Range_L
: Boolean;
10179 Out_Of_Range_H
: Boolean;
10182 -- Compute what is known at compile time
10184 if Known_T_LB
and Known_T_HB
then
10185 if Compile_Time_Known_Value
(LB
) then
10188 -- There's no point in checking that a bound is within its
10189 -- own range so pretend that it is known in this case. First
10190 -- deal with low bound.
10192 elsif Ekind
(Etype
(LB
)) = E_Signed_Integer_Subtype
10193 and then Scalar_Range
(Etype
(LB
)) = Scalar_Range
(T_Typ
)
10199 -- Likewise for the high bound
10201 if Compile_Time_Known_Value
(HB
) then
10204 elsif Ekind
(Etype
(HB
)) = E_Signed_Integer_Subtype
10205 and then Scalar_Range
(Etype
(HB
)) = Scalar_Range
(T_Typ
)
10212 -- Check for case where everything is static and we can do the
10213 -- check at compile time. This is skipped if we have an access
10214 -- type, since the access value may be null.
10216 -- ??? This code can be improved since you only need to know that
10217 -- the two respective bounds (LB & T_LB or HB & T_HB) are known at
10218 -- compile time to emit pertinent messages.
10220 if Known_T_LB
and Known_T_HB
and Known_LB
and Known_HB
10223 -- Floating-point case
10225 if Is_Floating_Point_Type
(S_Typ
) then
10226 Null_Range
:= Expr_Value_R
(HB
) < Expr_Value_R
(LB
);
10228 (Expr_Value_R
(LB
) < Expr_Value_R
(T_LB
))
10230 (Expr_Value_R
(LB
) > Expr_Value_R
(T_HB
));
10233 (Expr_Value_R
(HB
) > Expr_Value_R
(T_HB
))
10235 (Expr_Value_R
(HB
) < Expr_Value_R
(T_LB
));
10237 -- Fixed or discrete type case
10240 Null_Range
:= Expr_Value
(HB
) < Expr_Value
(LB
);
10242 (Expr_Value
(LB
) < Expr_Value
(T_LB
))
10244 (Expr_Value
(LB
) > Expr_Value
(T_HB
));
10247 (Expr_Value
(HB
) > Expr_Value
(T_HB
))
10249 (Expr_Value
(HB
) < Expr_Value
(T_LB
));
10252 if not Null_Range
then
10253 if Out_Of_Range_L
then
10254 if No
(Warn_Node
) then
10256 (Compile_Time_Constraint_Error
10257 (Low_Bound
(Ck_Node
),
10258 "static value out of range of}??", T_Typ
));
10262 (Compile_Time_Constraint_Error
10264 "static range out of bounds of}??", T_Typ
));
10268 if Out_Of_Range_H
then
10269 if No
(Warn_Node
) then
10271 (Compile_Time_Constraint_Error
10272 (High_Bound
(Ck_Node
),
10273 "static value out of range of}??", T_Typ
));
10277 (Compile_Time_Constraint_Error
10279 "static range out of bounds of}??", T_Typ
));
10286 LB
: Node_Id
:= Low_Bound
(Ck_Node
);
10287 HB
: Node_Id
:= High_Bound
(Ck_Node
);
10290 -- If either bound is a discriminant and we are within the
10291 -- record declaration, it is a use of the discriminant in a
10292 -- constraint of a component, and nothing can be checked
10293 -- here. The check will be emitted within the init proc.
10294 -- Before then, the discriminal has no real meaning.
10295 -- Similarly, if the entity is a discriminal, there is no
10296 -- check to perform yet.
10298 -- The same holds within a discriminated synchronized type,
10299 -- where the discriminant may constrain a component or an
10302 if Nkind
(LB
) = N_Identifier
10303 and then Denotes_Discriminant
(LB
, True)
10305 if Current_Scope
= Scope
(Entity
(LB
))
10306 or else Is_Concurrent_Type
(Current_Scope
)
10307 or else Ekind
(Entity
(LB
)) /= E_Discriminant
10312 New_Occurrence_Of
(Discriminal
(Entity
(LB
)), Loc
);
10316 if Nkind
(HB
) = N_Identifier
10317 and then Denotes_Discriminant
(HB
, True)
10319 if Current_Scope
= Scope
(Entity
(HB
))
10320 or else Is_Concurrent_Type
(Current_Scope
)
10321 or else Ekind
(Entity
(HB
)) /= E_Discriminant
10326 New_Occurrence_Of
(Discriminal
(Entity
(HB
)), Loc
);
10330 Cond
:= Discrete_Range_Cond
(Ck_Node
, T_Typ
);
10331 Set_Paren_Count
(Cond
, 1);
10334 Make_And_Then
(Loc
,
10338 Convert_To
(Base_Type
(Etype
(HB
)),
10339 Duplicate_Subexpr_No_Checks
(HB
)),
10341 Convert_To
(Base_Type
(Etype
(LB
)),
10342 Duplicate_Subexpr_No_Checks
(LB
))),
10343 Right_Opnd
=> Cond
);
10348 elsif Is_Scalar_Type
(S_Typ
) then
10350 -- This somewhat duplicates what Apply_Scalar_Range_Check does,
10351 -- except the above simply sets a flag in the node and lets
10352 -- gigi generate the check base on the Etype of the expression.
10353 -- Sometimes, however we want to do a dynamic check against an
10354 -- arbitrary target type, so we do that here.
10356 if Ekind
(Base_Type
(S_Typ
)) /= Ekind
(Base_Type
(T_Typ
)) then
10357 Cond
:= Discrete_Expr_Cond
(Ck_Node
, T_Typ
);
10359 -- For literals, we can tell if the constraint error will be
10360 -- raised at compile time, so we never need a dynamic check, but
10361 -- if the exception will be raised, then post the usual warning,
10362 -- and replace the literal with a raise constraint error
10363 -- expression. As usual, skip this for access types
10365 elsif Compile_Time_Known_Value
(Ck_Node
) and then not Do_Access
then
10367 LB
: constant Node_Id
:= Type_Low_Bound
(T_Typ
);
10368 UB
: constant Node_Id
:= Type_High_Bound
(T_Typ
);
10370 Out_Of_Range
: Boolean;
10371 Static_Bounds
: constant Boolean :=
10372 Compile_Time_Known_Value
(LB
)
10373 and Compile_Time_Known_Value
(UB
);
10376 -- Following range tests should use Sem_Eval routine ???
10378 if Static_Bounds
then
10379 if Is_Floating_Point_Type
(S_Typ
) then
10381 (Expr_Value_R
(Ck_Node
) < Expr_Value_R
(LB
))
10383 (Expr_Value_R
(Ck_Node
) > Expr_Value_R
(UB
));
10385 -- Fixed or discrete type
10389 Expr_Value
(Ck_Node
) < Expr_Value
(LB
)
10391 Expr_Value
(Ck_Node
) > Expr_Value
(UB
);
10394 -- Bounds of the type are static and the literal is out of
10395 -- range so output a warning message.
10397 if Out_Of_Range
then
10398 if No
(Warn_Node
) then
10400 (Compile_Time_Constraint_Error
10402 "static value out of range of}??", T_Typ
));
10406 (Compile_Time_Constraint_Error
10408 "static value out of range of}??", T_Typ
));
10413 Cond
:= Discrete_Expr_Cond
(Ck_Node
, T_Typ
);
10417 -- Here for the case of a non-static expression, we need a runtime
10418 -- check unless the source type range is guaranteed to be in the
10419 -- range of the target type.
10422 if not In_Subrange_Of
(S_Typ
, T_Typ
) then
10423 Cond
:= Discrete_Expr_Cond
(Ck_Node
, T_Typ
);
10428 if Is_Array_Type
(T_Typ
) and then Is_Array_Type
(S_Typ
) then
10429 if Is_Constrained
(T_Typ
) then
10431 Expr_Actual
:= Get_Referenced_Object
(Ck_Node
);
10432 Exptyp
:= Get_Actual_Subtype
(Expr_Actual
);
10434 if Is_Access_Type
(Exptyp
) then
10435 Exptyp
:= Designated_Type
(Exptyp
);
10438 -- String_Literal case. This needs to be handled specially be-
10439 -- cause no index types are available for string literals. The
10440 -- condition is simply:
10442 -- T_Typ'Length = string-literal-length
10444 if Nkind
(Expr_Actual
) = N_String_Literal
then
10447 -- General array case. Here we have a usable actual subtype for
10448 -- the expression, and the condition is built from the two types
10450 -- T_Typ'First < Exptyp'First or else
10451 -- T_Typ'Last > Exptyp'Last or else
10452 -- T_Typ'First(1) < Exptyp'First(1) or else
10453 -- T_Typ'Last(1) > Exptyp'Last(1) or else
10456 elsif Is_Constrained
(Exptyp
) then
10458 Ndims
: constant Nat
:= Number_Dimensions
(T_Typ
);
10464 L_Index
:= First_Index
(T_Typ
);
10465 R_Index
:= First_Index
(Exptyp
);
10467 for Indx
in 1 .. Ndims
loop
10468 if not (Nkind
(L_Index
) = N_Raise_Constraint_Error
10470 Nkind
(R_Index
) = N_Raise_Constraint_Error
)
10472 -- Deal with compile time length check. Note that we
10473 -- skip this in the access case, because the access
10474 -- value may be null, so we cannot know statically.
10477 Subtypes_Statically_Match
10478 (Etype
(L_Index
), Etype
(R_Index
))
10480 -- If the target type is constrained then we
10481 -- have to check for exact equality of bounds
10482 -- (required for qualified expressions).
10484 if Is_Constrained
(T_Typ
) then
10487 Range_Equal_E_Cond
(Exptyp
, T_Typ
, Indx
));
10490 (Cond
, Range_E_Cond
(Exptyp
, T_Typ
, Indx
));
10500 -- Handle cases where we do not get a usable actual subtype that
10501 -- is constrained. This happens for example in the function call
10502 -- and explicit dereference cases. In these cases, we have to get
10503 -- the length or range from the expression itself, making sure we
10504 -- do not evaluate it more than once.
10506 -- Here Ck_Node is the original expression, or more properly the
10507 -- result of applying Duplicate_Expr to the original tree,
10508 -- forcing the result to be a name.
10512 Ndims
: constant Nat
:= Number_Dimensions
(T_Typ
);
10515 -- Build the condition for the explicit dereference case
10517 for Indx
in 1 .. Ndims
loop
10519 (Cond
, Range_N_Cond
(Ck_Node
, T_Typ
, Indx
));
10525 -- For a conversion to an unconstrained array type, generate an
10526 -- Action to check that the bounds of the source value are within
10527 -- the constraints imposed by the target type (RM 4.6(38)). No
10528 -- check is needed for a conversion to an access to unconstrained
10529 -- array type, as 4.6(24.15/2) requires the designated subtypes
10530 -- of the two access types to statically match.
10532 if Nkind
(Parent
(Ck_Node
)) = N_Type_Conversion
10533 and then not Do_Access
10536 Opnd_Index
: Node_Id
;
10537 Targ_Index
: Node_Id
;
10538 Opnd_Range
: Node_Id
;
10541 Opnd_Index
:= First_Index
(Get_Actual_Subtype
(Ck_Node
));
10542 Targ_Index
:= First_Index
(T_Typ
);
10543 while Present
(Opnd_Index
) loop
10545 -- If the index is a range, use its bounds. If it is an
10546 -- entity (as will be the case if it is a named subtype
10547 -- or an itype created for a slice) retrieve its range.
10549 if Is_Entity_Name
(Opnd_Index
)
10550 and then Is_Type
(Entity
(Opnd_Index
))
10552 Opnd_Range
:= Scalar_Range
(Entity
(Opnd_Index
));
10554 Opnd_Range
:= Opnd_Index
;
10557 if Nkind
(Opnd_Range
) = N_Range
then
10559 (Low_Bound
(Opnd_Range
), Etype
(Targ_Index
),
10560 Assume_Valid
=> True)
10563 (High_Bound
(Opnd_Range
), Etype
(Targ_Index
),
10564 Assume_Valid
=> True)
10568 -- If null range, no check needed
10571 Compile_Time_Known_Value
(High_Bound
(Opnd_Range
))
10573 Compile_Time_Known_Value
(Low_Bound
(Opnd_Range
))
10575 Expr_Value
(High_Bound
(Opnd_Range
)) <
10576 Expr_Value
(Low_Bound
(Opnd_Range
))
10580 elsif Is_Out_Of_Range
10581 (Low_Bound
(Opnd_Range
), Etype
(Targ_Index
),
10582 Assume_Valid
=> True)
10585 (High_Bound
(Opnd_Range
), Etype
(Targ_Index
),
10586 Assume_Valid
=> True)
10589 (Compile_Time_Constraint_Error
10590 (Wnode
, "value out of range of}??", T_Typ
));
10595 Discrete_Range_Cond
10596 (Opnd_Range
, Etype
(Targ_Index
)));
10600 Next_Index
(Opnd_Index
);
10601 Next_Index
(Targ_Index
);
10608 -- Construct the test and insert into the tree
10610 if Present
(Cond
) then
10612 Cond
:= Guard_Access
(Cond
, Loc
, Ck_Node
);
10616 (Make_Raise_Constraint_Error
(Loc
,
10618 Reason
=> CE_Range_Check_Failed
));
10622 end Selected_Range_Checks
;
10624 -------------------------------
10625 -- Storage_Checks_Suppressed --
10626 -------------------------------
10628 function Storage_Checks_Suppressed
(E
: Entity_Id
) return Boolean is
10630 if Present
(E
) and then Checks_May_Be_Suppressed
(E
) then
10631 return Is_Check_Suppressed
(E
, Storage_Check
);
10633 return Scope_Suppress
.Suppress
(Storage_Check
);
10635 end Storage_Checks_Suppressed
;
10637 ---------------------------
10638 -- Tag_Checks_Suppressed --
10639 ---------------------------
10641 function Tag_Checks_Suppressed
(E
: Entity_Id
) return Boolean is
10644 and then Checks_May_Be_Suppressed
(E
)
10646 return Is_Check_Suppressed
(E
, Tag_Check
);
10648 return Scope_Suppress
.Suppress
(Tag_Check
);
10650 end Tag_Checks_Suppressed
;
10652 ---------------------------------------
10653 -- Validate_Alignment_Check_Warnings --
10654 ---------------------------------------
10656 procedure Validate_Alignment_Check_Warnings
is
10658 for J
in Alignment_Warnings
.First
.. Alignment_Warnings
.Last
loop
10660 AWR
: Alignment_Warnings_Record
10661 renames Alignment_Warnings
.Table
(J
);
10663 if Known_Alignment
(AWR
.E
)
10664 and then AWR
.A
mod Alignment
(AWR
.E
) = 0
10666 Delete_Warning_And_Continuations
(AWR
.W
);
10670 end Validate_Alignment_Check_Warnings
;
10672 --------------------------
10673 -- Validity_Check_Range --
10674 --------------------------
10676 procedure Validity_Check_Range
10678 Related_Id
: Entity_Id
:= Empty
)
10681 if Validity_Checks_On
and Validity_Check_Operands
then
10682 if Nkind
(N
) = N_Range
then
10684 (Expr
=> Low_Bound
(N
),
10685 Related_Id
=> Related_Id
,
10686 Is_Low_Bound
=> True);
10689 (Expr
=> High_Bound
(N
),
10690 Related_Id
=> Related_Id
,
10691 Is_High_Bound
=> True);
10694 end Validity_Check_Range
;
10696 --------------------------------
10697 -- Validity_Checks_Suppressed --
10698 --------------------------------
10700 function Validity_Checks_Suppressed
(E
: Entity_Id
) return Boolean is
10702 if Present
(E
) and then Checks_May_Be_Suppressed
(E
) then
10703 return Is_Check_Suppressed
(E
, Validity_Check
);
10705 return Scope_Suppress
.Suppress
(Validity_Check
);
10707 end Validity_Checks_Suppressed
;