61e1ad4fed977be58d1c22f8832b832c07baf30b
[platform/upstream/gcc.git] / gcc / ada / checks.adb
1 ------------------------------------------------------------------------------
2 --                                                                          --
3 --                         GNAT COMPILER COMPONENTS                         --
4 --                                                                          --
5 --                               C H E C K S                                --
6 --                                                                          --
7 --                                 B o d y                                  --
8 --                                                                          --
9 --          Copyright (C) 1992-2016, Free Software Foundation, Inc.         --
10 --                                                                          --
11 -- GNAT is free software;  you can  redistribute it  and/or modify it under --
12 -- terms of the  GNU General Public License as published  by the Free Soft- --
13 -- ware  Foundation;  either version 3,  or (at your option) any later ver- --
14 -- sion.  GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY;  without even the  implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License --
17 -- for  more details.  You should have  received  a copy of the GNU General --
18 -- Public License  distributed with GNAT; see file COPYING3.  If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license.          --
20 --                                                                          --
21 -- GNAT was originally developed  by the GNAT team at  New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc.      --
23 --                                                                          --
24 ------------------------------------------------------------------------------
25
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;
39 with Lib;      use Lib;
40 with Nlists;   use Nlists;
41 with Nmake;    use Nmake;
42 with Opt;      use Opt;
43 with Output;   use Output;
44 with Restrict; use Restrict;
45 with Rident;   use Rident;
46 with Rtsfind;  use Rtsfind;
47 with Sem;      use Sem;
48 with Sem_Aux;  use Sem_Aux;
49 with Sem_Ch3;  use Sem_Ch3;
50 with Sem_Ch8;  use Sem_Ch8;
51 with Sem_Eval; use Sem_Eval;
52 with Sem_Res;  use Sem_Res;
53 with Sem_Util; use Sem_Util;
54 with Sem_Warn; use Sem_Warn;
55 with Sinfo;    use Sinfo;
56 with Sinput;   use Sinput;
57 with Snames;   use Snames;
58 with Sprint;   use Sprint;
59 with Stand;    use Stand;
60 with Stringt;  use Stringt;
61 with Targparm; use Targparm;
62 with Tbuild;   use Tbuild;
63 with Ttypes;   use Ttypes;
64 with Validsw;  use Validsw;
65
66 package body Checks is
67
68    --  General note: many of these routines are concerned with generating
69    --  checking code to make sure that constraint error is raised at runtime.
70    --  Clearly this code is only needed if the expander is active, since
71    --  otherwise we will not be generating code or going into the runtime
72    --  execution anyway.
73
74    --  We therefore disconnect most of these checks if the expander is
75    --  inactive. This has the additional benefit that we do not need to
76    --  worry about the tree being messed up by previous errors (since errors
77    --  turn off expansion anyway).
78
79    --  There are a few exceptions to the above rule. For instance routines
80    --  such as Apply_Scalar_Range_Check that do not insert any code can be
81    --  safely called even when the Expander is inactive (but Errors_Detected
82    --  is 0). The benefit of executing this code when expansion is off, is
83    --  the ability to emit constraint error warning for static expressions
84    --  even when we are not generating code.
85
86    --  The above is modified in gnatprove mode to ensure that proper check
87    --  flags are always placed, even if expansion is off.
88
89    -------------------------------------
90    -- Suppression of Redundant Checks --
91    -------------------------------------
92
93    --  This unit implements a limited circuit for removal of redundant
94    --  checks. The processing is based on a tracing of simple sequential
95    --  flow. For any sequence of statements, we save expressions that are
96    --  marked to be checked, and then if the same expression appears later
97    --  with the same check, then under certain circumstances, the second
98    --  check can be suppressed.
99
100    --  Basically, we can suppress the check if we know for certain that
101    --  the previous expression has been elaborated (together with its
102    --  check), and we know that the exception frame is the same, and that
103    --  nothing has happened to change the result of the exception.
104
105    --  Let us examine each of these three conditions in turn to describe
106    --  how we ensure that this condition is met.
107
108    --  First, we need to know for certain that the previous expression has
109    --  been executed. This is done principally by the mechanism of calling
110    --  Conditional_Statements_Begin at the start of any statement sequence
111    --  and Conditional_Statements_End at the end. The End call causes all
112    --  checks remembered since the Begin call to be discarded. This does
113    --  miss a few cases, notably the case of a nested BEGIN-END block with
114    --  no exception handlers. But the important thing is to be conservative.
115    --  The other protection is that all checks are discarded if a label
116    --  is encountered, since then the assumption of sequential execution
117    --  is violated, and we don't know enough about the flow.
118
119    --  Second, we need to know that the exception frame is the same. We
120    --  do this by killing all remembered checks when we enter a new frame.
121    --  Again, that's over-conservative, but generally the cases we can help
122    --  with are pretty local anyway (like the body of a loop for example).
123
124    --  Third, we must be sure to forget any checks which are no longer valid.
125    --  This is done by two mechanisms, first the Kill_Checks_Variable call is
126    --  used to note any changes to local variables. We only attempt to deal
127    --  with checks involving local variables, so we do not need to worry
128    --  about global variables. Second, a call to any non-global procedure
129    --  causes us to abandon all stored checks, since such a all may affect
130    --  the values of any local variables.
131
132    --  The following define the data structures used to deal with remembering
133    --  checks so that redundant checks can be eliminated as described above.
134
135    --  Right now, the only expressions that we deal with are of the form of
136    --  simple local objects (either declared locally, or IN parameters) or
137    --  such objects plus/minus a compile time known constant. We can do
138    --  more later on if it seems worthwhile, but this catches many simple
139    --  cases in practice.
140
141    --  The following record type reflects a single saved check. An entry
142    --  is made in the stack of saved checks if and only if the expression
143    --  has been elaborated with the indicated checks.
144
145    type Saved_Check is record
146       Killed : Boolean;
147       --  Set True if entry is killed by Kill_Checks
148
149       Entity : Entity_Id;
150       --  The entity involved in the expression that is checked
151
152       Offset : Uint;
153       --  A compile time value indicating the result of adding or
154       --  subtracting a compile time value. This value is to be
155       --  added to the value of the Entity. A value of zero is
156       --  used for the case of a simple entity reference.
157
158       Check_Type : Character;
159       --  This is set to 'R' for a range check (in which case Target_Type
160       --  is set to the target type for the range check) or to 'O' for an
161       --  overflow check (in which case Target_Type is set to Empty).
162
163       Target_Type : Entity_Id;
164       --  Used only if Do_Range_Check is set. Records the target type for
165       --  the check. We need this, because a check is a duplicate only if
166       --  it has the same target type (or more accurately one with a
167       --  range that is smaller or equal to the stored target type of a
168       --  saved check).
169    end record;
170
171    --  The following table keeps track of saved checks. Rather than use an
172    --  extensible table, we just use a table of fixed size, and we discard
173    --  any saved checks that do not fit. That's very unlikely to happen and
174    --  this is only an optimization in any case.
175
176    Saved_Checks : array (Int range 1 .. 200) of Saved_Check;
177    --  Array of saved checks
178
179    Num_Saved_Checks : Nat := 0;
180    --  Number of saved checks
181
182    --  The following stack keeps track of statement ranges. It is treated
183    --  as a stack. When Conditional_Statements_Begin is called, an entry
184    --  is pushed onto this stack containing the value of Num_Saved_Checks
185    --  at the time of the call. Then when Conditional_Statements_End is
186    --  called, this value is popped off and used to reset Num_Saved_Checks.
187
188    --  Note: again, this is a fixed length stack with a size that should
189    --  always be fine. If the value of the stack pointer goes above the
190    --  limit, then we just forget all saved checks.
191
192    Saved_Checks_Stack : array (Int range 1 .. 100) of Nat;
193    Saved_Checks_TOS : Nat := 0;
194
195    -----------------------
196    -- Local Subprograms --
197    -----------------------
198
199    procedure Apply_Arithmetic_Overflow_Strict (N : Node_Id);
200    --  Used to apply arithmetic overflow checks for all cases except operators
201    --  on signed arithmetic types in MINIMIZED/ELIMINATED case (for which we
202    --  call Apply_Arithmetic_Overflow_Minimized_Eliminated below). N can be a
203    --  signed integer arithmetic operator (but not an if or case expression).
204    --  It is also called for types other than signed integers.
205
206    procedure Apply_Arithmetic_Overflow_Minimized_Eliminated (Op : Node_Id);
207    --  Used to apply arithmetic overflow checks for the case where the overflow
208    --  checking mode is MINIMIZED or ELIMINATED and we have a signed integer
209    --  arithmetic op (which includes the case of if and case expressions). Note
210    --  that Do_Overflow_Check may or may not be set for node Op. In these modes
211    --  we have work to do even if overflow checking is suppressed.
212
213    procedure Apply_Division_Check
214      (N   : Node_Id;
215       Rlo : Uint;
216       Rhi : Uint;
217       ROK : Boolean);
218    --  N is an N_Op_Div, N_Op_Rem, or N_Op_Mod node. This routine applies
219    --  division checks as required if the Do_Division_Check flag is set.
220    --  Rlo and Rhi give the possible range of the right operand, these values
221    --  can be referenced and trusted only if ROK is set True.
222
223    procedure Apply_Float_Conversion_Check
224      (Ck_Node    : Node_Id;
225       Target_Typ : Entity_Id);
226    --  The checks on a conversion from a floating-point type to an integer
227    --  type are delicate. They have to be performed before conversion, they
228    --  have to raise an exception when the operand is a NaN, and rounding must
229    --  be taken into account to determine the safe bounds of the operand.
230
231    procedure Apply_Selected_Length_Checks
232      (Ck_Node    : Node_Id;
233       Target_Typ : Entity_Id;
234       Source_Typ : Entity_Id;
235       Do_Static  : Boolean);
236    --  This is the subprogram that does all the work for Apply_Length_Check
237    --  and Apply_Static_Length_Check. Expr, Target_Typ and Source_Typ are as
238    --  described for the above routines. The Do_Static flag indicates that
239    --  only a static check is to be done.
240
241    procedure Apply_Selected_Range_Checks
242      (Ck_Node    : Node_Id;
243       Target_Typ : Entity_Id;
244       Source_Typ : Entity_Id;
245       Do_Static  : Boolean);
246    --  This is the subprogram that does all the work for Apply_Range_Check.
247    --  Expr, Target_Typ and Source_Typ are as described for the above
248    --  routine. The Do_Static flag indicates that only a static check is
249    --  to be done.
250
251    type Check_Type is new Check_Id range Access_Check .. Division_Check;
252    function Check_Needed (Nod : Node_Id; Check : Check_Type) return Boolean;
253    --  This function is used to see if an access or division by zero check is
254    --  needed. The check is to be applied to a single variable appearing in the
255    --  source, and N is the node for the reference. If N is not of this form,
256    --  True is returned with no further processing. If N is of the right form,
257    --  then further processing determines if the given Check is needed.
258    --
259    --  The particular circuit is to see if we have the case of a check that is
260    --  not needed because it appears in the right operand of a short circuited
261    --  conditional where the left operand guards the check. For example:
262    --
263    --    if Var = 0 or else Q / Var > 12 then
264    --       ...
265    --    end if;
266    --
267    --  In this example, the division check is not required. At the same time
268    --  we can issue warnings for suspicious use of non-short-circuited forms,
269    --  such as:
270    --
271    --    if Var = 0 or Q / Var > 12 then
272    --       ...
273    --    end if;
274
275    procedure Find_Check
276      (Expr        : Node_Id;
277       Check_Type  : Character;
278       Target_Type : Entity_Id;
279       Entry_OK    : out Boolean;
280       Check_Num   : out Nat;
281       Ent         : out Entity_Id;
282       Ofs         : out Uint);
283    --  This routine is used by Enable_Range_Check and Enable_Overflow_Check
284    --  to see if a check is of the form for optimization, and if so, to see
285    --  if it has already been performed. Expr is the expression to check,
286    --  and Check_Type is 'R' for a range check, 'O' for an overflow check.
287    --  Target_Type is the target type for a range check, and Empty for an
288    --  overflow check. If the entry is not of the form for optimization,
289    --  then Entry_OK is set to False, and the remaining out parameters
290    --  are undefined. If the entry is OK, then Ent/Ofs are set to the
291    --  entity and offset from the expression. Check_Num is the number of
292    --  a matching saved entry in Saved_Checks, or zero if no such entry
293    --  is located.
294
295    function Get_Discriminal (E : Entity_Id; Bound : Node_Id) return Node_Id;
296    --  If a discriminal is used in constraining a prival, Return reference
297    --  to the discriminal of the protected body (which renames the parameter
298    --  of the enclosing protected operation). This clumsy transformation is
299    --  needed because privals are created too late and their actual subtypes
300    --  are not available when analysing the bodies of the protected operations.
301    --  This function is called whenever the bound is an entity and the scope
302    --  indicates a protected operation. If the bound is an in-parameter of
303    --  a protected operation that is not a prival, the function returns the
304    --  bound itself.
305    --  To be cleaned up???
306
307    function Guard_Access
308      (Cond    : Node_Id;
309       Loc     : Source_Ptr;
310       Ck_Node : Node_Id) return Node_Id;
311    --  In the access type case, guard the test with a test to ensure
312    --  that the access value is non-null, since the checks do not
313    --  not apply to null access values.
314
315    procedure Install_Static_Check (R_Cno : Node_Id; Loc : Source_Ptr);
316    --  Called by Apply_{Length,Range}_Checks to rewrite the tree with the
317    --  Constraint_Error node.
318
319    function Is_Signed_Integer_Arithmetic_Op (N : Node_Id) return Boolean;
320    --  Returns True if node N is for an arithmetic operation with signed
321    --  integer operands. This includes unary and binary operators, and also
322    --  if and case expression nodes where the dependent expressions are of
323    --  a signed integer type. These are the kinds of nodes for which special
324    --  handling applies in MINIMIZED or ELIMINATED overflow checking mode.
325
326    function Range_Or_Validity_Checks_Suppressed
327      (Expr : Node_Id) return Boolean;
328    --  Returns True if either range or validity checks or both are suppressed
329    --  for the type of the given expression, or, if the expression is the name
330    --  of an entity, if these checks are suppressed for the entity.
331
332    function Selected_Length_Checks
333      (Ck_Node    : Node_Id;
334       Target_Typ : Entity_Id;
335       Source_Typ : Entity_Id;
336       Warn_Node  : Node_Id) return Check_Result;
337    --  Like Apply_Selected_Length_Checks, except it doesn't modify
338    --  anything, just returns a list of nodes as described in the spec of
339    --  this package for the Range_Check function.
340
341    function Selected_Range_Checks
342      (Ck_Node    : Node_Id;
343       Target_Typ : Entity_Id;
344       Source_Typ : Entity_Id;
345       Warn_Node  : Node_Id) return Check_Result;
346    --  Like Apply_Selected_Range_Checks, except it doesn't modify anything,
347    --  just returns a list of nodes as described in the spec of this package
348    --  for the Range_Check function.
349
350    ------------------------------
351    -- Access_Checks_Suppressed --
352    ------------------------------
353
354    function Access_Checks_Suppressed (E : Entity_Id) return Boolean is
355    begin
356       if Present (E) and then Checks_May_Be_Suppressed (E) then
357          return Is_Check_Suppressed (E, Access_Check);
358       else
359          return Scope_Suppress.Suppress (Access_Check);
360       end if;
361    end Access_Checks_Suppressed;
362
363    -------------------------------------
364    -- Accessibility_Checks_Suppressed --
365    -------------------------------------
366
367    function Accessibility_Checks_Suppressed (E : Entity_Id) return Boolean is
368    begin
369       if Present (E) and then Checks_May_Be_Suppressed (E) then
370          return Is_Check_Suppressed (E, Accessibility_Check);
371       else
372          return Scope_Suppress.Suppress (Accessibility_Check);
373       end if;
374    end Accessibility_Checks_Suppressed;
375
376    -----------------------------
377    -- Activate_Division_Check --
378    -----------------------------
379
380    procedure Activate_Division_Check (N : Node_Id) is
381    begin
382       Set_Do_Division_Check (N, True);
383       Possible_Local_Raise (N, Standard_Constraint_Error);
384    end Activate_Division_Check;
385
386    -----------------------------
387    -- Activate_Overflow_Check --
388    -----------------------------
389
390    procedure Activate_Overflow_Check (N : Node_Id) is
391       Typ : constant Entity_Id := Etype (N);
392
393    begin
394       --  Floating-point case. If Etype is not set (this can happen when we
395       --  activate a check on a node that has not yet been analyzed), then
396       --  we assume we do not have a floating-point type (as per our spec).
397
398       if Present (Typ) and then Is_Floating_Point_Type (Typ) then
399
400          --  Ignore call if we have no automatic overflow checks on the target
401          --  and Check_Float_Overflow mode is not set. These are the cases in
402          --  which we expect to generate infinities and NaN's with no check.
403
404          if not (Machine_Overflows_On_Target or Check_Float_Overflow) then
405             return;
406
407          --  Ignore for unary operations ("+", "-", abs) since these can never
408          --  result in overflow for floating-point cases.
409
410          elsif Nkind (N) in N_Unary_Op then
411             return;
412
413          --  Otherwise we will set the flag
414
415          else
416             null;
417          end if;
418
419       --  Discrete case
420
421       else
422          --  Nothing to do for Rem/Mod/Plus (overflow not possible, the check
423          --  for zero-divide is a divide check, not an overflow check).
424
425          if Nkind_In (N, N_Op_Rem, N_Op_Mod, N_Op_Plus) then
426             return;
427          end if;
428       end if;
429
430       --  Fall through for cases where we do set the flag
431
432       Set_Do_Overflow_Check (N, True);
433       Possible_Local_Raise (N, Standard_Constraint_Error);
434    end Activate_Overflow_Check;
435
436    --------------------------
437    -- Activate_Range_Check --
438    --------------------------
439
440    procedure Activate_Range_Check (N : Node_Id) is
441    begin
442       Set_Do_Range_Check (N, True);
443       Possible_Local_Raise (N, Standard_Constraint_Error);
444    end Activate_Range_Check;
445
446    ---------------------------------
447    -- Alignment_Checks_Suppressed --
448    ---------------------------------
449
450    function Alignment_Checks_Suppressed (E : Entity_Id) return Boolean is
451    begin
452       if Present (E) and then Checks_May_Be_Suppressed (E) then
453          return Is_Check_Suppressed (E, Alignment_Check);
454       else
455          return Scope_Suppress.Suppress (Alignment_Check);
456       end if;
457    end Alignment_Checks_Suppressed;
458
459    ----------------------------------
460    -- Allocation_Checks_Suppressed --
461    ----------------------------------
462
463    --  Note: at the current time there are no calls to this function, because
464    --  the relevant check is in the run-time, so it is not a check that the
465    --  compiler can suppress anyway, but we still have to recognize the check
466    --  name Allocation_Check since it is part of the standard.
467
468    function Allocation_Checks_Suppressed (E : Entity_Id) return Boolean is
469    begin
470       if Present (E) and then Checks_May_Be_Suppressed (E) then
471          return Is_Check_Suppressed (E, Allocation_Check);
472       else
473          return Scope_Suppress.Suppress (Allocation_Check);
474       end if;
475    end Allocation_Checks_Suppressed;
476
477    -------------------------
478    -- Append_Range_Checks --
479    -------------------------
480
481    procedure Append_Range_Checks
482      (Checks       : Check_Result;
483       Stmts        : List_Id;
484       Suppress_Typ : Entity_Id;
485       Static_Sloc  : Source_Ptr;
486       Flag_Node    : Node_Id)
487    is
488       Internal_Flag_Node   : constant Node_Id    := Flag_Node;
489       Internal_Static_Sloc : constant Source_Ptr := Static_Sloc;
490
491       Checks_On : constant Boolean :=
492         (not Index_Checks_Suppressed (Suppress_Typ))
493          or else (not Range_Checks_Suppressed (Suppress_Typ));
494
495    begin
496       --  For now we just return if Checks_On is false, however this should
497       --  be enhanced to check for an always True value in the condition
498       --  and to generate a compilation warning???
499
500       if not Checks_On then
501          return;
502       end if;
503
504       for J in 1 .. 2 loop
505          exit when No (Checks (J));
506
507          if Nkind (Checks (J)) = N_Raise_Constraint_Error
508            and then Present (Condition (Checks (J)))
509          then
510             if not Has_Dynamic_Range_Check (Internal_Flag_Node) then
511                Append_To (Stmts, Checks (J));
512                Set_Has_Dynamic_Range_Check (Internal_Flag_Node);
513             end if;
514
515          else
516             Append_To
517               (Stmts,
518                 Make_Raise_Constraint_Error (Internal_Static_Sloc,
519                   Reason => CE_Range_Check_Failed));
520          end if;
521       end loop;
522    end Append_Range_Checks;
523
524    ------------------------
525    -- Apply_Access_Check --
526    ------------------------
527
528    procedure Apply_Access_Check (N : Node_Id) is
529       P : constant Node_Id := Prefix (N);
530
531    begin
532       --  We do not need checks if we are not generating code (i.e. the
533       --  expander is not active). This is not just an optimization, there
534       --  are cases (e.g. with pragma Debug) where generating the checks
535       --  can cause real trouble).
536
537       if not Expander_Active then
538          return;
539       end if;
540
541       --  No check if short circuiting makes check unnecessary
542
543       if not Check_Needed (P, Access_Check) then
544          return;
545       end if;
546
547       --  No check if accessing the Offset_To_Top component of a dispatch
548       --  table. They are safe by construction.
549
550       if Tagged_Type_Expansion
551         and then Present (Etype (P))
552         and then RTU_Loaded (Ada_Tags)
553         and then RTE_Available (RE_Offset_To_Top_Ptr)
554         and then Etype (P) = RTE (RE_Offset_To_Top_Ptr)
555       then
556          return;
557       end if;
558
559       --  Otherwise go ahead and install the check
560
561       Install_Null_Excluding_Check (P);
562    end Apply_Access_Check;
563
564    -------------------------------
565    -- Apply_Accessibility_Check --
566    -------------------------------
567
568    procedure Apply_Accessibility_Check
569      (N           : Node_Id;
570       Typ         : Entity_Id;
571       Insert_Node : Node_Id)
572    is
573       Loc         : constant Source_Ptr := Sloc (N);
574       Param_Ent   : Entity_Id           := Param_Entity (N);
575       Param_Level : Node_Id;
576       Type_Level  : Node_Id;
577
578    begin
579       if Ada_Version >= Ada_2012
580          and then not Present (Param_Ent)
581          and then Is_Entity_Name (N)
582          and then Ekind_In (Entity (N), E_Constant, E_Variable)
583          and then Present (Effective_Extra_Accessibility (Entity (N)))
584       then
585          Param_Ent := Entity (N);
586          while Present (Renamed_Object (Param_Ent)) loop
587
588             --  Renamed_Object must return an Entity_Name here
589             --  because of preceding "Present (E_E_A (...))" test.
590
591             Param_Ent := Entity (Renamed_Object (Param_Ent));
592          end loop;
593       end if;
594
595       if Inside_A_Generic then
596          return;
597
598       --  Only apply the run-time check if the access parameter has an
599       --  associated extra access level parameter and when the level of the
600       --  type is less deep than the level of the access parameter, and
601       --  accessibility checks are not suppressed.
602
603       elsif Present (Param_Ent)
604          and then Present (Extra_Accessibility (Param_Ent))
605          and then UI_Gt (Object_Access_Level (N),
606                          Deepest_Type_Access_Level (Typ))
607          and then not Accessibility_Checks_Suppressed (Param_Ent)
608          and then not Accessibility_Checks_Suppressed (Typ)
609       then
610          Param_Level :=
611            New_Occurrence_Of (Extra_Accessibility (Param_Ent), Loc);
612
613          Type_Level :=
614            Make_Integer_Literal (Loc, Deepest_Type_Access_Level (Typ));
615
616          --  Raise Program_Error if the accessibility level of the access
617          --  parameter is deeper than the level of the target access type.
618
619          Insert_Action (Insert_Node,
620            Make_Raise_Program_Error (Loc,
621              Condition =>
622                Make_Op_Gt (Loc,
623                  Left_Opnd  => Param_Level,
624                  Right_Opnd => Type_Level),
625              Reason => PE_Accessibility_Check_Failed));
626
627          Analyze_And_Resolve (N);
628       end if;
629    end Apply_Accessibility_Check;
630
631    --------------------------------
632    -- Apply_Address_Clause_Check --
633    --------------------------------
634
635    procedure Apply_Address_Clause_Check (E : Entity_Id; N : Node_Id) is
636       pragma Assert (Nkind (N) = N_Freeze_Entity);
637
638       AC  : constant Node_Id    := Address_Clause (E);
639       Loc : constant Source_Ptr := Sloc (AC);
640       Typ : constant Entity_Id  := Etype (E);
641
642       Expr : Node_Id;
643       --  Address expression (not necessarily the same as Aexp, for example
644       --  when Aexp is a reference to a constant, in which case Expr gets
645       --  reset to reference the value expression of the constant).
646
647    begin
648       --  See if alignment check needed. Note that we never need a check if the
649       --  maximum alignment is one, since the check will always succeed.
650
651       --  Note: we do not check for checks suppressed here, since that check
652       --  was done in Sem_Ch13 when the address clause was processed. We are
653       --  only called if checks were not suppressed. The reason for this is
654       --  that we have to delay the call to Apply_Alignment_Check till freeze
655       --  time (so that all types etc are elaborated), but we have to check
656       --  the status of check suppressing at the point of the address clause.
657
658       if No (AC)
659         or else not Check_Address_Alignment (AC)
660         or else Maximum_Alignment = 1
661       then
662          return;
663       end if;
664
665       --  Obtain expression from address clause
666
667       Expr := Address_Value (Expression (AC));
668
669       --  See if we know that Expr has an acceptable value at compile time. If
670       --  it hasn't or we don't know, we defer issuing the warning until the
671       --  end of the compilation to take into account back end annotations.
672
673       if Compile_Time_Known_Value (Expr)
674         and then (Known_Alignment (E) or else Known_Alignment (Typ))
675       then
676          declare
677             AL : Uint := Alignment (Typ);
678
679          begin
680             --  The object alignment might be more restrictive than the type
681             --  alignment.
682
683             if Known_Alignment (E) then
684                AL := Alignment (E);
685             end if;
686
687             if Expr_Value (Expr) mod AL = 0 then
688                return;
689             end if;
690          end;
691
692       --  If the expression has the form X'Address, then we can find out if the
693       --  object X has an alignment that is compatible with the object E. If it
694       --  hasn't or we don't know, we defer issuing the warning until the end
695       --  of the compilation to take into account back end annotations.
696
697       elsif Nkind (Expr) = N_Attribute_Reference
698         and then Attribute_Name (Expr) = Name_Address
699         and then
700           Has_Compatible_Alignment (E, Prefix (Expr), False) = Known_Compatible
701       then
702          return;
703       end if;
704
705       --  Here we do not know if the value is acceptable. Strictly we don't
706       --  have to do anything, since if the alignment is bad, we have an
707       --  erroneous program. However we are allowed to check for erroneous
708       --  conditions and we decide to do this by default if the check is not
709       --  suppressed.
710
711       --  However, don't do the check if elaboration code is unwanted
712
713       if Restriction_Active (No_Elaboration_Code) then
714          return;
715
716       --  Generate a check to raise PE if alignment may be inappropriate
717
718       else
719          --  If the original expression is a non-static constant, use the name
720          --  of the constant itself rather than duplicating its initialization
721          --  expression, which was extracted above.
722
723          --  Note: Expr is empty if the address-clause is applied to in-mode
724          --  actuals (allowed by 13.1(22)).
725
726          if not Present (Expr)
727            or else
728              (Is_Entity_Name (Expression (AC))
729                and then Ekind (Entity (Expression (AC))) = E_Constant
730                and then Nkind (Parent (Entity (Expression (AC)))) =
731                           N_Object_Declaration)
732          then
733             Expr := New_Copy_Tree (Expression (AC));
734          else
735             Remove_Side_Effects (Expr);
736          end if;
737
738          if No (Actions (N)) then
739             Set_Actions (N, New_List);
740          end if;
741
742          Prepend_To (Actions (N),
743            Make_Raise_Program_Error (Loc,
744              Condition =>
745                Make_Op_Ne (Loc,
746                  Left_Opnd  =>
747                    Make_Op_Mod (Loc,
748                      Left_Opnd  =>
749                        Unchecked_Convert_To
750                          (RTE (RE_Integer_Address), Expr),
751                      Right_Opnd =>
752                        Make_Attribute_Reference (Loc,
753                          Prefix         => New_Occurrence_Of (E, Loc),
754                          Attribute_Name => Name_Alignment)),
755                  Right_Opnd => Make_Integer_Literal (Loc, Uint_0)),
756              Reason    => PE_Misaligned_Address_Value));
757
758          Warning_Msg := No_Error_Msg;
759          Analyze (First (Actions (N)), Suppress => All_Checks);
760
761          --  If the above raise action generated a warning message (for example
762          --  from Warn_On_Non_Local_Exception mode with the active restriction
763          --  No_Exception_Propagation).
764
765          if Warning_Msg /= No_Error_Msg then
766
767             --  If the expression has a known at compile time value, then
768             --  once we know the alignment of the type, we can check if the
769             --  exception will be raised or not, and if not, we don't need
770             --  the warning so we will kill the warning later on.
771
772             if Compile_Time_Known_Value (Expr) then
773                Alignment_Warnings.Append
774                  ((E => E, A => Expr_Value (Expr), W => Warning_Msg));
775
776             --  Add explanation of the warning generated by the check
777
778             else
779                Error_Msg_N
780                  ("\address value may be incompatible with alignment of "
781                   & "object?X?", AC);
782             end if;
783          end if;
784
785          return;
786       end if;
787
788    exception
789
790       --  If we have some missing run time component in configurable run time
791       --  mode then just skip the check (it is not required in any case).
792
793       when RE_Not_Available =>
794          return;
795    end Apply_Address_Clause_Check;
796
797    -------------------------------------
798    -- Apply_Arithmetic_Overflow_Check --
799    -------------------------------------
800
801    procedure Apply_Arithmetic_Overflow_Check (N : Node_Id) is
802    begin
803       --  Use old routine in almost all cases (the only case we are treating
804       --  specially is the case of a signed integer arithmetic op with the
805       --  overflow checking mode set to MINIMIZED or ELIMINATED).
806
807       if Overflow_Check_Mode = Strict
808         or else not Is_Signed_Integer_Arithmetic_Op (N)
809       then
810          Apply_Arithmetic_Overflow_Strict (N);
811
812       --  Otherwise use the new routine for the case of a signed integer
813       --  arithmetic op, with Do_Overflow_Check set to True, and the checking
814       --  mode is MINIMIZED or ELIMINATED.
815
816       else
817          Apply_Arithmetic_Overflow_Minimized_Eliminated (N);
818       end if;
819    end Apply_Arithmetic_Overflow_Check;
820
821    --------------------------------------
822    -- Apply_Arithmetic_Overflow_Strict --
823    --------------------------------------
824
825    --  This routine is called only if the type is an integer type, and a
826    --  software arithmetic overflow check may be needed for op (add, subtract,
827    --  or multiply). This check is performed only if Software_Overflow_Checking
828    --  is enabled and Do_Overflow_Check is set. In this case we expand the
829    --  operation into a more complex sequence of tests that ensures that
830    --  overflow is properly caught.
831
832    --  This is used in CHECKED modes. It is identical to the code for this
833    --  cases before the big overflow earthquake, thus ensuring that in this
834    --  modes we have compatible behavior (and reliability) to what was there
835    --  before. It is also called for types other than signed integers, and if
836    --  the Do_Overflow_Check flag is off.
837
838    --  Note: we also call this routine if we decide in the MINIMIZED case
839    --  to give up and just generate an overflow check without any fuss.
840
841    procedure Apply_Arithmetic_Overflow_Strict (N : Node_Id) is
842       Loc  : constant Source_Ptr := Sloc (N);
843       Typ  : constant Entity_Id  := Etype (N);
844       Rtyp : constant Entity_Id  := Root_Type (Typ);
845
846    begin
847       --  Nothing to do if Do_Overflow_Check not set or overflow checks
848       --  suppressed.
849
850       if not Do_Overflow_Check (N) then
851          return;
852       end if;
853
854       --  An interesting special case. If the arithmetic operation appears as
855       --  the operand of a type conversion:
856
857       --    type1 (x op y)
858
859       --  and all the following conditions apply:
860
861       --    arithmetic operation is for a signed integer type
862       --    target type type1 is a static integer subtype
863       --    range of x and y are both included in the range of type1
864       --    range of x op y is included in the range of type1
865       --    size of type1 is at least twice the result size of op
866
867       --  then we don't do an overflow check in any case. Instead, we transform
868       --  the operation so that we end up with:
869
870       --    type1 (type1 (x) op type1 (y))
871
872       --  This avoids intermediate overflow before the conversion. It is
873       --  explicitly permitted by RM 3.5.4(24):
874
875       --    For the execution of a predefined operation of a signed integer
876       --    type, the implementation need not raise Constraint_Error if the
877       --    result is outside the base range of the type, so long as the
878       --    correct result is produced.
879
880       --  It's hard to imagine that any programmer counts on the exception
881       --  being raised in this case, and in any case it's wrong coding to
882       --  have this expectation, given the RM permission. Furthermore, other
883       --  Ada compilers do allow such out of range results.
884
885       --  Note that we do this transformation even if overflow checking is
886       --  off, since this is precisely about giving the "right" result and
887       --  avoiding the need for an overflow check.
888
889       --  Note: this circuit is partially redundant with respect to the similar
890       --  processing in Exp_Ch4.Expand_N_Type_Conversion, but the latter deals
891       --  with cases that do not come through here. We still need the following
892       --  processing even with the Exp_Ch4 code in place, since we want to be
893       --  sure not to generate the arithmetic overflow check in these cases
894       --  (Exp_Ch4 would have a hard time removing them once generated).
895
896       if Is_Signed_Integer_Type (Typ)
897         and then Nkind (Parent (N)) = N_Type_Conversion
898       then
899          Conversion_Optimization : declare
900             Target_Type : constant Entity_Id :=
901               Base_Type (Entity (Subtype_Mark (Parent (N))));
902
903             Llo, Lhi : Uint;
904             Rlo, Rhi : Uint;
905             LOK, ROK : Boolean;
906
907             Vlo : Uint;
908             Vhi : Uint;
909             VOK : Boolean;
910
911             Tlo : Uint;
912             Thi : Uint;
913
914          begin
915             if Is_Integer_Type (Target_Type)
916               and then RM_Size (Root_Type (Target_Type)) >= 2 * RM_Size (Rtyp)
917             then
918                Tlo := Expr_Value (Type_Low_Bound  (Target_Type));
919                Thi := Expr_Value (Type_High_Bound (Target_Type));
920
921                Determine_Range
922                  (Left_Opnd  (N), LOK, Llo, Lhi, Assume_Valid => True);
923                Determine_Range
924                  (Right_Opnd (N), ROK, Rlo, Rhi, Assume_Valid => True);
925
926                if (LOK and ROK)
927                  and then Tlo <= Llo and then Lhi <= Thi
928                  and then Tlo <= Rlo and then Rhi <= Thi
929                then
930                   Determine_Range (N, VOK, Vlo, Vhi, Assume_Valid => True);
931
932                   if VOK and then Tlo <= Vlo and then Vhi <= Thi then
933                      Rewrite (Left_Opnd (N),
934                        Make_Type_Conversion (Loc,
935                          Subtype_Mark => New_Occurrence_Of (Target_Type, Loc),
936                          Expression   => Relocate_Node (Left_Opnd (N))));
937
938                      Rewrite (Right_Opnd (N),
939                        Make_Type_Conversion (Loc,
940                         Subtype_Mark => New_Occurrence_Of (Target_Type, Loc),
941                         Expression   => Relocate_Node (Right_Opnd (N))));
942
943                      --  Rewrite the conversion operand so that the original
944                      --  node is retained, in order to avoid the warning for
945                      --  redundant conversions in Resolve_Type_Conversion.
946
947                      Rewrite (N, Relocate_Node (N));
948
949                      Set_Etype (N, Target_Type);
950
951                      Analyze_And_Resolve (Left_Opnd  (N), Target_Type);
952                      Analyze_And_Resolve (Right_Opnd (N), Target_Type);
953
954                      --  Given that the target type is twice the size of the
955                      --  source type, overflow is now impossible, so we can
956                      --  safely kill the overflow check and return.
957
958                      Set_Do_Overflow_Check (N, False);
959                      return;
960                   end if;
961                end if;
962             end if;
963          end Conversion_Optimization;
964       end if;
965
966       --  Now see if an overflow check is required
967
968       declare
969          Siz   : constant Int := UI_To_Int (Esize (Rtyp));
970          Dsiz  : constant Int := Siz * 2;
971          Opnod : Node_Id;
972          Ctyp  : Entity_Id;
973          Opnd  : Node_Id;
974          Cent  : RE_Id;
975
976       begin
977          --  Skip check if back end does overflow checks, or the overflow flag
978          --  is not set anyway, or we are not doing code expansion, or the
979          --  parent node is a type conversion whose operand is an arithmetic
980          --  operation on signed integers on which the expander can promote
981          --  later the operands to type Integer (see Expand_N_Type_Conversion).
982
983          if Backend_Overflow_Checks_On_Target
984            or else not Do_Overflow_Check (N)
985            or else not Expander_Active
986            or else (Present (Parent (N))
987                      and then Nkind (Parent (N)) = N_Type_Conversion
988                      and then Integer_Promotion_Possible (Parent (N)))
989          then
990             return;
991          end if;
992
993          --  Otherwise, generate the full general code for front end overflow
994          --  detection, which works by doing arithmetic in a larger type:
995
996          --    x op y
997
998          --  is expanded into
999
1000          --    Typ (Checktyp (x) op Checktyp (y));
1001
1002          --  where Typ is the type of the original expression, and Checktyp is
1003          --  an integer type of sufficient length to hold the largest possible
1004          --  result.
1005
1006          --  If the size of check type exceeds the size of Long_Long_Integer,
1007          --  we use a different approach, expanding to:
1008
1009          --    typ (xxx_With_Ovflo_Check (Integer_64 (x), Integer (y)))
1010
1011          --  where xxx is Add, Multiply or Subtract as appropriate
1012
1013          --  Find check type if one exists
1014
1015          if Dsiz <= Standard_Integer_Size then
1016             Ctyp := Standard_Integer;
1017
1018          elsif Dsiz <= Standard_Long_Long_Integer_Size then
1019             Ctyp := Standard_Long_Long_Integer;
1020
1021          --  No check type exists, use runtime call
1022
1023          else
1024             if Nkind (N) = N_Op_Add then
1025                Cent := RE_Add_With_Ovflo_Check;
1026
1027             elsif Nkind (N) = N_Op_Multiply then
1028                Cent := RE_Multiply_With_Ovflo_Check;
1029
1030             else
1031                pragma Assert (Nkind (N) = N_Op_Subtract);
1032                Cent := RE_Subtract_With_Ovflo_Check;
1033             end if;
1034
1035             Rewrite (N,
1036               OK_Convert_To (Typ,
1037                 Make_Function_Call (Loc,
1038                   Name => New_Occurrence_Of (RTE (Cent), Loc),
1039                   Parameter_Associations => New_List (
1040                     OK_Convert_To (RTE (RE_Integer_64), Left_Opnd  (N)),
1041                     OK_Convert_To (RTE (RE_Integer_64), Right_Opnd (N))))));
1042
1043             Analyze_And_Resolve (N, Typ);
1044             return;
1045          end if;
1046
1047          --  If we fall through, we have the case where we do the arithmetic
1048          --  in the next higher type and get the check by conversion. In these
1049          --  cases Ctyp is set to the type to be used as the check type.
1050
1051          Opnod := Relocate_Node (N);
1052
1053          Opnd := OK_Convert_To (Ctyp, Left_Opnd (Opnod));
1054
1055          Analyze (Opnd);
1056          Set_Etype (Opnd, Ctyp);
1057          Set_Analyzed (Opnd, True);
1058          Set_Left_Opnd (Opnod, Opnd);
1059
1060          Opnd := OK_Convert_To (Ctyp, Right_Opnd (Opnod));
1061
1062          Analyze (Opnd);
1063          Set_Etype (Opnd, Ctyp);
1064          Set_Analyzed (Opnd, True);
1065          Set_Right_Opnd (Opnod, Opnd);
1066
1067          --  The type of the operation changes to the base type of the check
1068          --  type, and we reset the overflow check indication, since clearly no
1069          --  overflow is possible now that we are using a double length type.
1070          --  We also set the Analyzed flag to avoid a recursive attempt to
1071          --  expand the node.
1072
1073          Set_Etype             (Opnod, Base_Type (Ctyp));
1074          Set_Do_Overflow_Check (Opnod, False);
1075          Set_Analyzed          (Opnod, True);
1076
1077          --  Now build the outer conversion
1078
1079          Opnd := OK_Convert_To (Typ, Opnod);
1080          Analyze (Opnd);
1081          Set_Etype (Opnd, Typ);
1082
1083          --  In the discrete type case, we directly generate the range check
1084          --  for the outer operand. This range check will implement the
1085          --  required overflow check.
1086
1087          if Is_Discrete_Type (Typ) then
1088             Rewrite (N, Opnd);
1089             Generate_Range_Check
1090               (Expression (N), Typ, CE_Overflow_Check_Failed);
1091
1092          --  For other types, we enable overflow checking on the conversion,
1093          --  after setting the node as analyzed to prevent recursive attempts
1094          --  to expand the conversion node.
1095
1096          else
1097             Set_Analyzed (Opnd, True);
1098             Enable_Overflow_Check (Opnd);
1099             Rewrite (N, Opnd);
1100          end if;
1101
1102       exception
1103          when RE_Not_Available =>
1104             return;
1105       end;
1106    end Apply_Arithmetic_Overflow_Strict;
1107
1108    ----------------------------------------------------
1109    -- Apply_Arithmetic_Overflow_Minimized_Eliminated --
1110    ----------------------------------------------------
1111
1112    procedure Apply_Arithmetic_Overflow_Minimized_Eliminated (Op : Node_Id) is
1113       pragma Assert (Is_Signed_Integer_Arithmetic_Op (Op));
1114
1115       Loc : constant Source_Ptr := Sloc (Op);
1116       P   : constant Node_Id    := Parent (Op);
1117
1118       LLIB : constant Entity_Id := Base_Type (Standard_Long_Long_Integer);
1119       --  Operands and results are of this type when we convert
1120
1121       Result_Type : constant Entity_Id := Etype (Op);
1122       --  Original result type
1123
1124       Check_Mode : constant Overflow_Mode_Type := Overflow_Check_Mode;
1125       pragma Assert (Check_Mode in Minimized_Or_Eliminated);
1126
1127       Lo, Hi : Uint;
1128       --  Ranges of values for result
1129
1130    begin
1131       --  Nothing to do if our parent is one of the following:
1132
1133       --    Another signed integer arithmetic op
1134       --    A membership operation
1135       --    A comparison operation
1136
1137       --  In all these cases, we will process at the higher level (and then
1138       --  this node will be processed during the downwards recursion that
1139       --  is part of the processing in Minimize_Eliminate_Overflows).
1140
1141       if Is_Signed_Integer_Arithmetic_Op (P)
1142         or else Nkind (P) in N_Membership_Test
1143         or else Nkind (P) in N_Op_Compare
1144
1145         --  This is also true for an alternative in a case expression
1146
1147         or else Nkind (P) = N_Case_Expression_Alternative
1148
1149         --  This is also true for a range operand in a membership test
1150
1151         or else (Nkind (P) = N_Range
1152                   and then Nkind (Parent (P)) in N_Membership_Test)
1153       then
1154          --  If_Expressions and Case_Expressions are treated as arithmetic
1155          --  ops, but if they appear in an assignment or similar contexts
1156          --  there is no overflow check that starts from that parent node,
1157          --  so apply check now.
1158
1159          if Nkind_In (P, N_If_Expression, N_Case_Expression)
1160            and then not Is_Signed_Integer_Arithmetic_Op (Parent (P))
1161          then
1162             null;
1163          else
1164             return;
1165          end if;
1166       end if;
1167
1168       --  Otherwise, we have a top level arithmetic operation node, and this
1169       --  is where we commence the special processing for MINIMIZED/ELIMINATED
1170       --  modes. This is the case where we tell the machinery not to move into
1171       --  Bignum mode at this top level (of course the top level operation
1172       --  will still be in Bignum mode if either of its operands are of type
1173       --  Bignum).
1174
1175       Minimize_Eliminate_Overflows (Op, Lo, Hi, Top_Level => True);
1176
1177       --  That call may but does not necessarily change the result type of Op.
1178       --  It is the job of this routine to undo such changes, so that at the
1179       --  top level, we have the proper type. This "undoing" is a point at
1180       --  which a final overflow check may be applied.
1181
1182       --  If the result type was not fiddled we are all set. We go to base
1183       --  types here because things may have been rewritten to generate the
1184       --  base type of the operand types.
1185
1186       if Base_Type (Etype (Op)) = Base_Type (Result_Type) then
1187          return;
1188
1189       --  Bignum case
1190
1191       elsif Is_RTE (Etype (Op), RE_Bignum) then
1192
1193          --  We need a sequence that looks like:
1194
1195          --    Rnn : Result_Type;
1196
1197          --    declare
1198          --       M : Mark_Id := SS_Mark;
1199          --    begin
1200          --       Rnn := Long_Long_Integer'Base (From_Bignum (Op));
1201          --       SS_Release (M);
1202          --    end;
1203
1204          --  This block is inserted (using Insert_Actions), and then the node
1205          --  is replaced with a reference to Rnn.
1206
1207          --  If our parent is a conversion node then there is no point in
1208          --  generating a conversion to Result_Type. Instead, we let the parent
1209          --  handle this. Note that this special case is not just about
1210          --  optimization. Consider
1211
1212          --      A,B,C : Integer;
1213          --      ...
1214          --      X := Long_Long_Integer'Base (A * (B ** C));
1215
1216          --  Now the product may fit in Long_Long_Integer but not in Integer.
1217          --  In MINIMIZED/ELIMINATED mode, we don't want to introduce an
1218          --  overflow exception for this intermediate value.
1219
1220          declare
1221             Blk : constant Node_Id  := Make_Bignum_Block (Loc);
1222             Rnn : constant Entity_Id := Make_Temporary (Loc, 'R', Op);
1223             RHS : Node_Id;
1224
1225             Rtype : Entity_Id;
1226
1227          begin
1228             RHS := Convert_From_Bignum (Op);
1229
1230             if Nkind (P) /= N_Type_Conversion then
1231                Convert_To_And_Rewrite (Result_Type, RHS);
1232                Rtype := Result_Type;
1233
1234                --  Interesting question, do we need a check on that conversion
1235                --  operation. Answer, not if we know the result is in range.
1236                --  At the moment we are not taking advantage of this. To be
1237                --  looked at later ???
1238
1239             else
1240                Rtype := LLIB;
1241             end if;
1242
1243             Insert_Before
1244               (First (Statements (Handled_Statement_Sequence (Blk))),
1245                Make_Assignment_Statement (Loc,
1246                  Name       => New_Occurrence_Of (Rnn, Loc),
1247                  Expression => RHS));
1248
1249             Insert_Actions (Op, New_List (
1250               Make_Object_Declaration (Loc,
1251                 Defining_Identifier => Rnn,
1252                 Object_Definition   => New_Occurrence_Of (Rtype, Loc)),
1253               Blk));
1254
1255             Rewrite (Op, New_Occurrence_Of (Rnn, Loc));
1256             Analyze_And_Resolve (Op);
1257          end;
1258
1259       --  Here we know the result is Long_Long_Integer'Base, or that it has
1260       --  been rewritten because the parent operation is a conversion. See
1261       --  Apply_Arithmetic_Overflow_Strict.Conversion_Optimization.
1262
1263       else
1264          pragma Assert
1265            (Etype (Op) = LLIB or else Nkind (Parent (Op)) = N_Type_Conversion);
1266
1267          --  All we need to do here is to convert the result to the proper
1268          --  result type. As explained above for the Bignum case, we can
1269          --  omit this if our parent is a type conversion.
1270
1271          if Nkind (P) /= N_Type_Conversion then
1272             Convert_To_And_Rewrite (Result_Type, Op);
1273          end if;
1274
1275          Analyze_And_Resolve (Op);
1276       end if;
1277    end Apply_Arithmetic_Overflow_Minimized_Eliminated;
1278
1279    ----------------------------
1280    -- Apply_Constraint_Check --
1281    ----------------------------
1282
1283    procedure Apply_Constraint_Check
1284      (N          : Node_Id;
1285       Typ        : Entity_Id;
1286       No_Sliding : Boolean := False)
1287    is
1288       Desig_Typ : Entity_Id;
1289
1290    begin
1291       --  No checks inside a generic (check the instantiations)
1292
1293       if Inside_A_Generic then
1294          return;
1295       end if;
1296
1297       --  Apply required constraint checks
1298
1299       if Is_Scalar_Type (Typ) then
1300          Apply_Scalar_Range_Check (N, Typ);
1301
1302       elsif Is_Array_Type (Typ) then
1303
1304          --  A useful optimization: an aggregate with only an others clause
1305          --  always has the right bounds.
1306
1307          if Nkind (N) = N_Aggregate
1308            and then No (Expressions (N))
1309            and then Nkind
1310             (First (Choices (First (Component_Associations (N)))))
1311               = N_Others_Choice
1312          then
1313             return;
1314          end if;
1315
1316          if Is_Constrained (Typ) then
1317             Apply_Length_Check (N, Typ);
1318
1319             if No_Sliding then
1320                Apply_Range_Check (N, Typ);
1321             end if;
1322          else
1323             Apply_Range_Check (N, Typ);
1324          end if;
1325
1326       elsif (Is_Record_Type (Typ) or else Is_Private_Type (Typ))
1327         and then Has_Discriminants (Base_Type (Typ))
1328         and then Is_Constrained (Typ)
1329       then
1330          Apply_Discriminant_Check (N, Typ);
1331
1332       elsif Is_Access_Type (Typ) then
1333
1334          Desig_Typ := Designated_Type (Typ);
1335
1336          --  No checks necessary if expression statically null
1337
1338          if Known_Null (N) then
1339             if Can_Never_Be_Null (Typ) then
1340                Install_Null_Excluding_Check (N);
1341             end if;
1342
1343          --  No sliding possible on access to arrays
1344
1345          elsif Is_Array_Type (Desig_Typ) then
1346             if Is_Constrained (Desig_Typ) then
1347                Apply_Length_Check (N, Typ);
1348             end if;
1349
1350             Apply_Range_Check (N, Typ);
1351
1352          elsif Has_Discriminants (Base_Type (Desig_Typ))
1353             and then Is_Constrained (Desig_Typ)
1354          then
1355             Apply_Discriminant_Check (N, Typ);
1356          end if;
1357
1358          --  Apply the 2005 Null_Excluding check. Note that we do not apply
1359          --  this check if the constraint node is illegal, as shown by having
1360          --  an error posted. This additional guard prevents cascaded errors
1361          --  and compiler aborts on illegal programs involving Ada 2005 checks.
1362
1363          if Can_Never_Be_Null (Typ)
1364            and then not Can_Never_Be_Null (Etype (N))
1365            and then not Error_Posted (N)
1366          then
1367             Install_Null_Excluding_Check (N);
1368          end if;
1369       end if;
1370    end Apply_Constraint_Check;
1371
1372    ------------------------------
1373    -- Apply_Discriminant_Check --
1374    ------------------------------
1375
1376    procedure Apply_Discriminant_Check
1377      (N   : Node_Id;
1378       Typ : Entity_Id;
1379       Lhs : Node_Id := Empty)
1380    is
1381       Loc       : constant Source_Ptr := Sloc (N);
1382       Do_Access : constant Boolean    := Is_Access_Type (Typ);
1383       S_Typ     : Entity_Id  := Etype (N);
1384       Cond      : Node_Id;
1385       T_Typ     : Entity_Id;
1386
1387       function Denotes_Explicit_Dereference (Obj : Node_Id) return Boolean;
1388       --  A heap object with an indefinite subtype is constrained by its
1389       --  initial value, and assigning to it requires a constraint_check.
1390       --  The target may be an explicit dereference, or a renaming of one.
1391
1392       function Is_Aliased_Unconstrained_Component return Boolean;
1393       --  It is possible for an aliased component to have a nominal
1394       --  unconstrained subtype (through instantiation). If this is a
1395       --  discriminated component assigned in the expansion of an aggregate
1396       --  in an initialization, the check must be suppressed. This unusual
1397       --  situation requires a predicate of its own.
1398
1399       ----------------------------------
1400       -- Denotes_Explicit_Dereference --
1401       ----------------------------------
1402
1403       function Denotes_Explicit_Dereference (Obj : Node_Id) return Boolean is
1404       begin
1405          return
1406            Nkind (Obj) = N_Explicit_Dereference
1407              or else
1408                (Is_Entity_Name (Obj)
1409                  and then Present (Renamed_Object (Entity (Obj)))
1410                  and then Nkind (Renamed_Object (Entity (Obj))) =
1411                                               N_Explicit_Dereference);
1412       end Denotes_Explicit_Dereference;
1413
1414       ----------------------------------------
1415       -- Is_Aliased_Unconstrained_Component --
1416       ----------------------------------------
1417
1418       function Is_Aliased_Unconstrained_Component return Boolean is
1419          Comp : Entity_Id;
1420          Pref : Node_Id;
1421
1422       begin
1423          if Nkind (Lhs) /= N_Selected_Component then
1424             return False;
1425          else
1426             Comp := Entity (Selector_Name (Lhs));
1427             Pref := Prefix (Lhs);
1428          end if;
1429
1430          if Ekind (Comp) /= E_Component
1431            or else not Is_Aliased (Comp)
1432          then
1433             return False;
1434          end if;
1435
1436          return not Comes_From_Source (Pref)
1437            and then In_Instance
1438            and then not Is_Constrained (Etype (Comp));
1439       end Is_Aliased_Unconstrained_Component;
1440
1441    --  Start of processing for Apply_Discriminant_Check
1442
1443    begin
1444       if Do_Access then
1445          T_Typ := Designated_Type (Typ);
1446       else
1447          T_Typ := Typ;
1448       end if;
1449
1450       --  Nothing to do if discriminant checks are suppressed or else no code
1451       --  is to be generated
1452
1453       if not Expander_Active
1454         or else Discriminant_Checks_Suppressed (T_Typ)
1455       then
1456          return;
1457       end if;
1458
1459       --  No discriminant checks necessary for an access when expression is
1460       --  statically Null. This is not only an optimization, it is fundamental
1461       --  because otherwise discriminant checks may be generated in init procs
1462       --  for types containing an access to a not-yet-frozen record, causing a
1463       --  deadly forward reference.
1464
1465       --  Also, if the expression is of an access type whose designated type is
1466       --  incomplete, then the access value must be null and we suppress the
1467       --  check.
1468
1469       if Known_Null (N) then
1470          return;
1471
1472       elsif Is_Access_Type (S_Typ) then
1473          S_Typ := Designated_Type (S_Typ);
1474
1475          if Ekind (S_Typ) = E_Incomplete_Type then
1476             return;
1477          end if;
1478       end if;
1479
1480       --  If an assignment target is present, then we need to generate the
1481       --  actual subtype if the target is a parameter or aliased object with
1482       --  an unconstrained nominal subtype.
1483
1484       --  Ada 2005 (AI-363): For Ada 2005, we limit the building of the actual
1485       --  subtype to the parameter and dereference cases, since other aliased
1486       --  objects are unconstrained (unless the nominal subtype is explicitly
1487       --  constrained).
1488
1489       if Present (Lhs)
1490         and then (Present (Param_Entity (Lhs))
1491                    or else (Ada_Version < Ada_2005
1492                              and then not Is_Constrained (T_Typ)
1493                              and then Is_Aliased_View (Lhs)
1494                              and then not Is_Aliased_Unconstrained_Component)
1495                    or else (Ada_Version >= Ada_2005
1496                              and then not Is_Constrained (T_Typ)
1497                              and then Denotes_Explicit_Dereference (Lhs)
1498                              and then Nkind (Original_Node (Lhs)) /=
1499                                         N_Function_Call))
1500       then
1501          T_Typ := Get_Actual_Subtype (Lhs);
1502       end if;
1503
1504       --  Nothing to do if the type is unconstrained (this is the case where
1505       --  the actual subtype in the RM sense of N is unconstrained and no check
1506       --  is required).
1507
1508       if not Is_Constrained (T_Typ) then
1509          return;
1510
1511       --  Ada 2005: nothing to do if the type is one for which there is a
1512       --  partial view that is constrained.
1513
1514       elsif Ada_Version >= Ada_2005
1515         and then Object_Type_Has_Constrained_Partial_View
1516                    (Typ  => Base_Type (T_Typ),
1517                     Scop => Current_Scope)
1518       then
1519          return;
1520       end if;
1521
1522       --  Nothing to do if the type is an Unchecked_Union
1523
1524       if Is_Unchecked_Union (Base_Type (T_Typ)) then
1525          return;
1526       end if;
1527
1528       --  Suppress checks if the subtypes are the same. The check must be
1529       --  preserved in an assignment to a formal, because the constraint is
1530       --  given by the actual.
1531
1532       if Nkind (Original_Node (N)) /= N_Allocator
1533         and then (No (Lhs)
1534                    or else not Is_Entity_Name (Lhs)
1535                    or else No (Param_Entity (Lhs)))
1536       then
1537          if (Etype (N) = Typ
1538               or else (Do_Access and then Designated_Type (Typ) = S_Typ))
1539            and then not Is_Aliased_View (Lhs)
1540          then
1541             return;
1542          end if;
1543
1544       --  We can also eliminate checks on allocators with a subtype mark that
1545       --  coincides with the context type. The context type may be a subtype
1546       --  without a constraint (common case, a generic actual).
1547
1548       elsif Nkind (Original_Node (N)) = N_Allocator
1549         and then Is_Entity_Name (Expression (Original_Node (N)))
1550       then
1551          declare
1552             Alloc_Typ : constant Entity_Id :=
1553               Entity (Expression (Original_Node (N)));
1554
1555          begin
1556             if Alloc_Typ = T_Typ
1557               or else (Nkind (Parent (T_Typ)) = N_Subtype_Declaration
1558                         and then Is_Entity_Name (
1559                           Subtype_Indication (Parent (T_Typ)))
1560                         and then Alloc_Typ = Base_Type (T_Typ))
1561
1562             then
1563                return;
1564             end if;
1565          end;
1566       end if;
1567
1568       --  See if we have a case where the types are both constrained, and all
1569       --  the constraints are constants. In this case, we can do the check
1570       --  successfully at compile time.
1571
1572       --  We skip this check for the case where the node is rewritten as
1573       --  an allocator, because it already carries the context subtype,
1574       --  and extracting the discriminants from the aggregate is messy.
1575
1576       if Is_Constrained (S_Typ)
1577         and then Nkind (Original_Node (N)) /= N_Allocator
1578       then
1579          declare
1580             DconT : Elmt_Id;
1581             Discr : Entity_Id;
1582             DconS : Elmt_Id;
1583             ItemS : Node_Id;
1584             ItemT : Node_Id;
1585
1586          begin
1587             --  S_Typ may not have discriminants in the case where it is a
1588             --  private type completed by a default discriminated type. In that
1589             --  case, we need to get the constraints from the underlying type.
1590             --  If the underlying type is unconstrained (i.e. has no default
1591             --  discriminants) no check is needed.
1592
1593             if Has_Discriminants (S_Typ) then
1594                Discr := First_Discriminant (S_Typ);
1595                DconS := First_Elmt (Discriminant_Constraint (S_Typ));
1596
1597             else
1598                Discr := First_Discriminant (Underlying_Type (S_Typ));
1599                DconS :=
1600                  First_Elmt
1601                    (Discriminant_Constraint (Underlying_Type (S_Typ)));
1602
1603                if No (DconS) then
1604                   return;
1605                end if;
1606
1607                --  A further optimization: if T_Typ is derived from S_Typ
1608                --  without imposing a constraint, no check is needed.
1609
1610                if Nkind (Original_Node (Parent (T_Typ))) =
1611                  N_Full_Type_Declaration
1612                then
1613                   declare
1614                      Type_Def : constant Node_Id :=
1615                        Type_Definition (Original_Node (Parent (T_Typ)));
1616                   begin
1617                      if Nkind (Type_Def) = N_Derived_Type_Definition
1618                        and then Is_Entity_Name (Subtype_Indication (Type_Def))
1619                        and then Entity (Subtype_Indication (Type_Def)) = S_Typ
1620                      then
1621                         return;
1622                      end if;
1623                   end;
1624                end if;
1625             end if;
1626
1627             --  Constraint may appear in full view of type
1628
1629             if Ekind (T_Typ) = E_Private_Subtype
1630               and then Present (Full_View (T_Typ))
1631             then
1632                DconT :=
1633                  First_Elmt (Discriminant_Constraint (Full_View (T_Typ)));
1634             else
1635                DconT :=
1636                  First_Elmt (Discriminant_Constraint (T_Typ));
1637             end if;
1638
1639             while Present (Discr) loop
1640                ItemS := Node (DconS);
1641                ItemT := Node (DconT);
1642
1643                --  For a discriminated component type constrained by the
1644                --  current instance of an enclosing type, there is no
1645                --  applicable discriminant check.
1646
1647                if Nkind (ItemT) = N_Attribute_Reference
1648                  and then Is_Access_Type (Etype (ItemT))
1649                  and then Is_Entity_Name (Prefix (ItemT))
1650                  and then Is_Type (Entity (Prefix (ItemT)))
1651                then
1652                   return;
1653                end if;
1654
1655                --  If the expressions for the discriminants are identical
1656                --  and it is side-effect free (for now just an entity),
1657                --  this may be a shared constraint, e.g. from a subtype
1658                --  without a constraint introduced as a generic actual.
1659                --  Examine other discriminants if any.
1660
1661                if ItemS = ItemT
1662                  and then Is_Entity_Name (ItemS)
1663                then
1664                   null;
1665
1666                elsif not Is_OK_Static_Expression (ItemS)
1667                  or else not Is_OK_Static_Expression (ItemT)
1668                then
1669                   exit;
1670
1671                elsif Expr_Value (ItemS) /= Expr_Value (ItemT) then
1672                   if Do_Access then   --  needs run-time check.
1673                      exit;
1674                   else
1675                      Apply_Compile_Time_Constraint_Error
1676                        (N, "incorrect value for discriminant&??",
1677                         CE_Discriminant_Check_Failed, Ent => Discr);
1678                      return;
1679                   end if;
1680                end if;
1681
1682                Next_Elmt (DconS);
1683                Next_Elmt (DconT);
1684                Next_Discriminant (Discr);
1685             end loop;
1686
1687             if No (Discr) then
1688                return;
1689             end if;
1690          end;
1691       end if;
1692
1693       --  Here we need a discriminant check. First build the expression
1694       --  for the comparisons of the discriminants:
1695
1696       --    (n.disc1 /= typ.disc1) or else
1697       --    (n.disc2 /= typ.disc2) or else
1698       --     ...
1699       --    (n.discn /= typ.discn)
1700
1701       Cond := Build_Discriminant_Checks (N, T_Typ);
1702
1703       --  If Lhs is set and is a parameter, then the condition is guarded by:
1704       --  lhs'constrained and then (condition built above)
1705
1706       if Present (Param_Entity (Lhs)) then
1707          Cond :=
1708            Make_And_Then (Loc,
1709              Left_Opnd =>
1710                Make_Attribute_Reference (Loc,
1711                  Prefix => New_Occurrence_Of (Param_Entity (Lhs), Loc),
1712                  Attribute_Name => Name_Constrained),
1713              Right_Opnd => Cond);
1714       end if;
1715
1716       if Do_Access then
1717          Cond := Guard_Access (Cond, Loc, N);
1718       end if;
1719
1720       Insert_Action (N,
1721         Make_Raise_Constraint_Error (Loc,
1722           Condition => Cond,
1723           Reason    => CE_Discriminant_Check_Failed));
1724    end Apply_Discriminant_Check;
1725
1726    -------------------------
1727    -- Apply_Divide_Checks --
1728    -------------------------
1729
1730    procedure Apply_Divide_Checks (N : Node_Id) is
1731       Loc   : constant Source_Ptr := Sloc (N);
1732       Typ   : constant Entity_Id  := Etype (N);
1733       Left  : constant Node_Id    := Left_Opnd (N);
1734       Right : constant Node_Id    := Right_Opnd (N);
1735
1736       Mode : constant Overflow_Mode_Type := Overflow_Check_Mode;
1737       --  Current overflow checking mode
1738
1739       LLB : Uint;
1740       Llo : Uint;
1741       Lhi : Uint;
1742       LOK : Boolean;
1743       Rlo : Uint;
1744       Rhi : Uint;
1745       ROK : Boolean;
1746
1747       pragma Warnings (Off, Lhi);
1748       --  Don't actually use this value
1749
1750    begin
1751       --  If we are operating in MINIMIZED or ELIMINATED mode, and we are
1752       --  operating on signed integer types, then the only thing this routine
1753       --  does is to call Apply_Arithmetic_Overflow_Minimized_Eliminated. That
1754       --  procedure will (possibly later on during recursive downward calls),
1755       --  ensure that any needed overflow/division checks are properly applied.
1756
1757       if Mode in Minimized_Or_Eliminated
1758         and then Is_Signed_Integer_Type (Typ)
1759       then
1760          Apply_Arithmetic_Overflow_Minimized_Eliminated (N);
1761          return;
1762       end if;
1763
1764       --  Proceed here in SUPPRESSED or CHECKED modes
1765
1766       if Expander_Active
1767         and then not Backend_Divide_Checks_On_Target
1768         and then Check_Needed (Right, Division_Check)
1769       then
1770          Determine_Range (Right, ROK, Rlo, Rhi, Assume_Valid => True);
1771
1772          --  Deal with division check
1773
1774          if Do_Division_Check (N)
1775            and then not Division_Checks_Suppressed (Typ)
1776          then
1777             Apply_Division_Check (N, Rlo, Rhi, ROK);
1778          end if;
1779
1780          --  Deal with overflow check
1781
1782          if Do_Overflow_Check (N)
1783            and then not Overflow_Checks_Suppressed (Etype (N))
1784          then
1785             Set_Do_Overflow_Check (N, False);
1786
1787             --  Test for extremely annoying case of xxx'First divided by -1
1788             --  for division of signed integer types (only overflow case).
1789
1790             if Nkind (N) = N_Op_Divide
1791               and then Is_Signed_Integer_Type (Typ)
1792             then
1793                Determine_Range (Left, LOK, Llo, Lhi, Assume_Valid => True);
1794                LLB := Expr_Value (Type_Low_Bound (Base_Type (Typ)));
1795
1796                if ((not ROK) or else (Rlo <= (-1) and then (-1) <= Rhi))
1797                      and then
1798                   ((not LOK) or else (Llo = LLB))
1799                then
1800                   Insert_Action (N,
1801                     Make_Raise_Constraint_Error (Loc,
1802                       Condition =>
1803                         Make_And_Then (Loc,
1804                           Left_Opnd  =>
1805                             Make_Op_Eq (Loc,
1806                               Left_Opnd  =>
1807                                 Duplicate_Subexpr_Move_Checks (Left),
1808                               Right_Opnd => Make_Integer_Literal (Loc, LLB)),
1809
1810                           Right_Opnd =>
1811                             Make_Op_Eq (Loc,
1812                               Left_Opnd  => Duplicate_Subexpr (Right),
1813                               Right_Opnd => Make_Integer_Literal (Loc, -1))),
1814
1815                       Reason => CE_Overflow_Check_Failed));
1816                end if;
1817             end if;
1818          end if;
1819       end if;
1820    end Apply_Divide_Checks;
1821
1822    --------------------------
1823    -- Apply_Division_Check --
1824    --------------------------
1825
1826    procedure Apply_Division_Check
1827      (N   : Node_Id;
1828       Rlo : Uint;
1829       Rhi : Uint;
1830       ROK : Boolean)
1831    is
1832       pragma Assert (Do_Division_Check (N));
1833
1834       Loc   : constant Source_Ptr := Sloc (N);
1835       Right : constant Node_Id    := Right_Opnd (N);
1836
1837    begin
1838       if Expander_Active
1839         and then not Backend_Divide_Checks_On_Target
1840         and then Check_Needed (Right, Division_Check)
1841       then
1842          --  See if division by zero possible, and if so generate test. This
1843          --  part of the test is not controlled by the -gnato switch, since
1844          --  it is a Division_Check and not an Overflow_Check.
1845
1846          if Do_Division_Check (N) then
1847             Set_Do_Division_Check (N, False);
1848
1849             if (not ROK) or else (Rlo <= 0 and then 0 <= Rhi) then
1850                Insert_Action (N,
1851                  Make_Raise_Constraint_Error (Loc,
1852                    Condition =>
1853                      Make_Op_Eq (Loc,
1854                        Left_Opnd  => Duplicate_Subexpr_Move_Checks (Right),
1855                        Right_Opnd => Make_Integer_Literal (Loc, 0)),
1856                    Reason => CE_Divide_By_Zero));
1857             end if;
1858          end if;
1859       end if;
1860    end Apply_Division_Check;
1861
1862    ----------------------------------
1863    -- Apply_Float_Conversion_Check --
1864    ----------------------------------
1865
1866    --  Let F and I be the source and target types of the conversion. The RM
1867    --  specifies that a floating-point value X is rounded to the nearest
1868    --  integer, with halfway cases being rounded away from zero. The rounded
1869    --  value of X is checked against I'Range.
1870
1871    --  The catch in the above paragraph is that there is no good way to know
1872    --  whether the round-to-integer operation resulted in overflow. A remedy is
1873    --  to perform a range check in the floating-point domain instead, however:
1874
1875    --      (1)  The bounds may not be known at compile time
1876    --      (2)  The check must take into account rounding or truncation.
1877    --      (3)  The range of type I may not be exactly representable in F.
1878    --      (4)  For the rounding case, The end-points I'First - 0.5 and
1879    --           I'Last + 0.5 may or may not be in range, depending on the
1880    --           sign of  I'First and I'Last.
1881    --      (5)  X may be a NaN, which will fail any comparison
1882
1883    --  The following steps correctly convert X with rounding:
1884
1885    --      (1) If either I'First or I'Last is not known at compile time, use
1886    --          I'Base instead of I in the next three steps and perform a
1887    --          regular range check against I'Range after conversion.
1888    --      (2) If I'First - 0.5 is representable in F then let Lo be that
1889    --          value and define Lo_OK as (I'First > 0). Otherwise, let Lo be
1890    --          F'Machine (I'First) and let Lo_OK be (Lo >= I'First).
1891    --          In other words, take one of the closest floating-point numbers
1892    --          (which is an integer value) to I'First, and see if it is in
1893    --          range or not.
1894    --      (3) If I'Last + 0.5 is representable in F then let Hi be that value
1895    --          and define Hi_OK as (I'Last < 0). Otherwise, let Hi be
1896    --          F'Machine (I'Last) and let Hi_OK be (Hi <= I'Last).
1897    --      (4) Raise CE when (Lo_OK and X < Lo) or (not Lo_OK and X <= Lo)
1898    --                     or (Hi_OK and X > Hi) or (not Hi_OK and X >= Hi)
1899
1900    --  For the truncating case, replace steps (2) and (3) as follows:
1901    --      (2) If I'First > 0, then let Lo be F'Pred (I'First) and let Lo_OK
1902    --          be False. Otherwise, let Lo be F'Succ (I'First - 1) and let
1903    --          Lo_OK be True.
1904    --      (3) If I'Last < 0, then let Hi be F'Succ (I'Last) and let Hi_OK
1905    --          be False. Otherwise let Hi be F'Pred (I'Last + 1) and let
1906    --          Hi_OK be True.
1907
1908    procedure Apply_Float_Conversion_Check
1909      (Ck_Node    : Node_Id;
1910       Target_Typ : Entity_Id)
1911    is
1912       LB          : constant Node_Id    := Type_Low_Bound (Target_Typ);
1913       HB          : constant Node_Id    := Type_High_Bound (Target_Typ);
1914       Loc         : constant Source_Ptr := Sloc (Ck_Node);
1915       Expr_Type   : constant Entity_Id  := Base_Type (Etype (Ck_Node));
1916       Target_Base : constant Entity_Id  :=
1917         Implementation_Base_Type (Target_Typ);
1918
1919       Par : constant Node_Id := Parent (Ck_Node);
1920       pragma Assert (Nkind (Par) = N_Type_Conversion);
1921       --  Parent of check node, must be a type conversion
1922
1923       Truncate  : constant Boolean := Float_Truncate (Par);
1924       Max_Bound : constant Uint :=
1925         UI_Expon
1926           (Machine_Radix_Value (Expr_Type),
1927            Machine_Mantissa_Value (Expr_Type) - 1) - 1;
1928
1929       --  Largest bound, so bound plus or minus half is a machine number of F
1930
1931       Ifirst, Ilast : Uint;
1932       --  Bounds of integer type
1933
1934       Lo, Hi : Ureal;
1935       --  Bounds to check in floating-point domain
1936
1937       Lo_OK, Hi_OK : Boolean;
1938       --  True iff Lo resp. Hi belongs to I'Range
1939
1940       Lo_Chk, Hi_Chk : Node_Id;
1941       --  Expressions that are False iff check fails
1942
1943       Reason : RT_Exception_Code;
1944
1945    begin
1946       --  We do not need checks if we are not generating code (i.e. the full
1947       --  expander is not active). In SPARK mode, we specifically don't want
1948       --  the frontend to expand these checks, which are dealt with directly
1949       --  in the formal verification backend.
1950
1951       if not Expander_Active then
1952          return;
1953       end if;
1954
1955       if not Compile_Time_Known_Value (LB)
1956           or not Compile_Time_Known_Value (HB)
1957       then
1958          declare
1959             --  First check that the value falls in the range of the base type,
1960             --  to prevent overflow during conversion and then perform a
1961             --  regular range check against the (dynamic) bounds.
1962
1963             pragma Assert (Target_Base /= Target_Typ);
1964
1965             Temp : constant Entity_Id := Make_Temporary (Loc, 'T', Par);
1966
1967          begin
1968             Apply_Float_Conversion_Check (Ck_Node, Target_Base);
1969             Set_Etype (Temp, Target_Base);
1970
1971             Insert_Action (Parent (Par),
1972               Make_Object_Declaration (Loc,
1973                 Defining_Identifier => Temp,
1974                 Object_Definition => New_Occurrence_Of (Target_Typ, Loc),
1975                 Expression => New_Copy_Tree (Par)),
1976                 Suppress => All_Checks);
1977
1978             Insert_Action (Par,
1979               Make_Raise_Constraint_Error (Loc,
1980                 Condition =>
1981                   Make_Not_In (Loc,
1982                     Left_Opnd  => New_Occurrence_Of (Temp, Loc),
1983                     Right_Opnd => New_Occurrence_Of (Target_Typ, Loc)),
1984                 Reason => CE_Range_Check_Failed));
1985             Rewrite (Par, New_Occurrence_Of (Temp, Loc));
1986
1987             return;
1988          end;
1989       end if;
1990
1991       --  Get the (static) bounds of the target type
1992
1993       Ifirst := Expr_Value (LB);
1994       Ilast  := Expr_Value (HB);
1995
1996       --  A simple optimization: if the expression is a universal literal,
1997       --  we can do the comparison with the bounds and the conversion to
1998       --  an integer type statically. The range checks are unchanged.
1999
2000       if Nkind (Ck_Node) = N_Real_Literal
2001         and then Etype (Ck_Node) = Universal_Real
2002         and then Is_Integer_Type (Target_Typ)
2003         and then Nkind (Parent (Ck_Node)) = N_Type_Conversion
2004       then
2005          declare
2006             Int_Val : constant Uint := UR_To_Uint (Realval (Ck_Node));
2007
2008          begin
2009             if Int_Val <= Ilast and then Int_Val >= Ifirst then
2010
2011                --  Conversion is safe
2012
2013                Rewrite (Parent (Ck_Node),
2014                  Make_Integer_Literal (Loc, UI_To_Int (Int_Val)));
2015                Analyze_And_Resolve (Parent (Ck_Node), Target_Typ);
2016                return;
2017             end if;
2018          end;
2019       end if;
2020
2021       --  Check against lower bound
2022
2023       if Truncate and then Ifirst > 0 then
2024          Lo := Pred (Expr_Type, UR_From_Uint (Ifirst));
2025          Lo_OK := False;
2026
2027       elsif Truncate then
2028          Lo := Succ (Expr_Type, UR_From_Uint (Ifirst - 1));
2029          Lo_OK := True;
2030
2031       elsif abs (Ifirst) < Max_Bound then
2032          Lo := UR_From_Uint (Ifirst) - Ureal_Half;
2033          Lo_OK := (Ifirst > 0);
2034
2035       else
2036          Lo := Machine (Expr_Type, UR_From_Uint (Ifirst), Round_Even, Ck_Node);
2037          Lo_OK := (Lo >= UR_From_Uint (Ifirst));
2038       end if;
2039
2040       if Lo_OK then
2041
2042          --  Lo_Chk := (X >= Lo)
2043
2044          Lo_Chk := Make_Op_Ge (Loc,
2045                      Left_Opnd => Duplicate_Subexpr_No_Checks (Ck_Node),
2046                      Right_Opnd => Make_Real_Literal (Loc, Lo));
2047
2048       else
2049          --  Lo_Chk := (X > Lo)
2050
2051          Lo_Chk := Make_Op_Gt (Loc,
2052                      Left_Opnd => Duplicate_Subexpr_No_Checks (Ck_Node),
2053                      Right_Opnd => Make_Real_Literal (Loc, Lo));
2054       end if;
2055
2056       --  Check against higher bound
2057
2058       if Truncate and then Ilast < 0 then
2059          Hi := Succ (Expr_Type, UR_From_Uint (Ilast));
2060          Hi_OK := False;
2061
2062       elsif Truncate then
2063          Hi := Pred (Expr_Type, UR_From_Uint (Ilast + 1));
2064          Hi_OK := True;
2065
2066       elsif abs (Ilast) < Max_Bound then
2067          Hi := UR_From_Uint (Ilast) + Ureal_Half;
2068          Hi_OK := (Ilast < 0);
2069       else
2070          Hi := Machine (Expr_Type, UR_From_Uint (Ilast), Round_Even, Ck_Node);
2071          Hi_OK := (Hi <= UR_From_Uint (Ilast));
2072       end if;
2073
2074       if Hi_OK then
2075
2076          --  Hi_Chk := (X <= Hi)
2077
2078          Hi_Chk := Make_Op_Le (Loc,
2079                      Left_Opnd => Duplicate_Subexpr_No_Checks (Ck_Node),
2080                      Right_Opnd => Make_Real_Literal (Loc, Hi));
2081
2082       else
2083          --  Hi_Chk := (X < Hi)
2084
2085          Hi_Chk := Make_Op_Lt (Loc,
2086                      Left_Opnd => Duplicate_Subexpr_No_Checks (Ck_Node),
2087                      Right_Opnd => Make_Real_Literal (Loc, Hi));
2088       end if;
2089
2090       --  If the bounds of the target type are the same as those of the base
2091       --  type, the check is an overflow check as a range check is not
2092       --  performed in these cases.
2093
2094       if Expr_Value (Type_Low_Bound (Target_Base)) = Ifirst
2095         and then Expr_Value (Type_High_Bound (Target_Base)) = Ilast
2096       then
2097          Reason := CE_Overflow_Check_Failed;
2098       else
2099          Reason := CE_Range_Check_Failed;
2100       end if;
2101
2102       --  Raise CE if either conditions does not hold
2103
2104       Insert_Action (Ck_Node,
2105         Make_Raise_Constraint_Error (Loc,
2106           Condition => Make_Op_Not (Loc, Make_And_Then (Loc, Lo_Chk, Hi_Chk)),
2107           Reason    => Reason));
2108    end Apply_Float_Conversion_Check;
2109
2110    ------------------------
2111    -- Apply_Length_Check --
2112    ------------------------
2113
2114    procedure Apply_Length_Check
2115      (Ck_Node    : Node_Id;
2116       Target_Typ : Entity_Id;
2117       Source_Typ : Entity_Id := Empty)
2118    is
2119    begin
2120       Apply_Selected_Length_Checks
2121         (Ck_Node, Target_Typ, Source_Typ, Do_Static => False);
2122    end Apply_Length_Check;
2123
2124    -------------------------------------
2125    -- Apply_Parameter_Aliasing_Checks --
2126    -------------------------------------
2127
2128    procedure Apply_Parameter_Aliasing_Checks
2129      (Call : Node_Id;
2130       Subp : Entity_Id)
2131    is
2132       Loc : constant Source_Ptr := Sloc (Call);
2133
2134       function May_Cause_Aliasing
2135         (Formal_1 : Entity_Id;
2136          Formal_2 : Entity_Id) return Boolean;
2137       --  Determine whether two formal parameters can alias each other
2138       --  depending on their modes.
2139
2140       function Original_Actual (N : Node_Id) return Node_Id;
2141       --  The expander may replace an actual with a temporary for the sake of
2142       --  side effect removal. The temporary may hide a potential aliasing as
2143       --  it does not share the address of the actual. This routine attempts
2144       --  to retrieve the original actual.
2145
2146       procedure Overlap_Check
2147         (Actual_1 : Node_Id;
2148          Actual_2 : Node_Id;
2149          Formal_1 : Entity_Id;
2150          Formal_2 : Entity_Id;
2151          Check    : in out Node_Id);
2152       --  Create a check to determine whether Actual_1 overlaps with Actual_2.
2153       --  If detailed exception messages are enabled, the check is augmented to
2154       --  provide information about the names of the corresponding formals. See
2155       --  the body for details. Actual_1 and Actual_2 denote the two actuals to
2156       --  be tested. Formal_1 and Formal_2 denote the corresponding formals.
2157       --  Check contains all and-ed simple tests generated so far or remains
2158       --  unchanged in the case of detailed exception messaged.
2159
2160       ------------------------
2161       -- May_Cause_Aliasing --
2162       ------------------------
2163
2164       function May_Cause_Aliasing
2165         (Formal_1 : Entity_Id;
2166          Formal_2 : Entity_Id) return Boolean
2167       is
2168       begin
2169          --  The following combination cannot lead to aliasing
2170
2171          --     Formal 1    Formal 2
2172          --     IN          IN
2173
2174          if Ekind (Formal_1) = E_In_Parameter
2175               and then
2176             Ekind (Formal_2) = E_In_Parameter
2177          then
2178             return False;
2179
2180          --  The following combinations may lead to aliasing
2181
2182          --     Formal 1    Formal 2
2183          --     IN          OUT
2184          --     IN          IN OUT
2185          --     OUT         IN
2186          --     OUT         IN OUT
2187          --     OUT         OUT
2188
2189          else
2190             return True;
2191          end if;
2192       end May_Cause_Aliasing;
2193
2194       ---------------------
2195       -- Original_Actual --
2196       ---------------------
2197
2198       function Original_Actual (N : Node_Id) return Node_Id is
2199       begin
2200          if Nkind (N) = N_Type_Conversion then
2201             return Expression (N);
2202
2203          --  The expander created a temporary to capture the result of a type
2204          --  conversion where the expression is the real actual.
2205
2206          elsif Nkind (N) = N_Identifier
2207            and then Present (Original_Node (N))
2208            and then Nkind (Original_Node (N)) = N_Type_Conversion
2209          then
2210             return Expression (Original_Node (N));
2211          end if;
2212
2213          return N;
2214       end Original_Actual;
2215
2216       -------------------
2217       -- Overlap_Check --
2218       -------------------
2219
2220       procedure Overlap_Check
2221         (Actual_1 : Node_Id;
2222          Actual_2 : Node_Id;
2223          Formal_1 : Entity_Id;
2224          Formal_2 : Entity_Id;
2225          Check    : in out Node_Id)
2226       is
2227          Cond      : Node_Id;
2228          ID_Casing : constant Casing_Type :=
2229                        Identifier_Casing (Source_Index (Current_Sem_Unit));
2230
2231       begin
2232          --  Generate:
2233          --    Actual_1'Overlaps_Storage (Actual_2)
2234
2235          Cond :=
2236            Make_Attribute_Reference (Loc,
2237              Prefix         => New_Copy_Tree (Original_Actual (Actual_1)),
2238              Attribute_Name => Name_Overlaps_Storage,
2239              Expressions    =>
2240                New_List (New_Copy_Tree (Original_Actual (Actual_2))));
2241
2242          --  Generate the following check when detailed exception messages are
2243          --  enabled:
2244
2245          --    if Actual_1'Overlaps_Storage (Actual_2) then
2246          --       raise Program_Error with <detailed message>;
2247          --    end if;
2248
2249          if Exception_Extra_Info then
2250             Start_String;
2251
2252             --  Do not generate location information for internal calls
2253
2254             if Comes_From_Source (Call) then
2255                Store_String_Chars (Build_Location_String (Loc));
2256                Store_String_Char (' ');
2257             end if;
2258
2259             Store_String_Chars ("aliased parameters, actuals for """);
2260
2261             Get_Name_String (Chars (Formal_1));
2262             Set_Casing (ID_Casing);
2263             Store_String_Chars (Name_Buffer (1 .. Name_Len));
2264
2265             Store_String_Chars (""" and """);
2266
2267             Get_Name_String (Chars (Formal_2));
2268             Set_Casing (ID_Casing);
2269             Store_String_Chars (Name_Buffer (1 .. Name_Len));
2270
2271             Store_String_Chars (""" overlap");
2272
2273             Insert_Action (Call,
2274               Make_If_Statement (Loc,
2275                 Condition       => Cond,
2276                 Then_Statements => New_List (
2277                   Make_Raise_Statement (Loc,
2278                     Name       =>
2279                       New_Occurrence_Of (Standard_Program_Error, Loc),
2280                     Expression => Make_String_Literal (Loc, End_String)))));
2281
2282          --  Create a sequence of overlapping checks by and-ing them all
2283          --  together.
2284
2285          else
2286             if No (Check) then
2287                Check := Cond;
2288             else
2289                Check :=
2290                  Make_And_Then (Loc,
2291                    Left_Opnd  => Check,
2292                    Right_Opnd => Cond);
2293             end if;
2294          end if;
2295       end Overlap_Check;
2296
2297       --  Local variables
2298
2299       Actual_1   : Node_Id;
2300       Actual_2   : Node_Id;
2301       Check      : Node_Id;
2302       Formal_1   : Entity_Id;
2303       Formal_2   : Entity_Id;
2304       Orig_Act_1 : Node_Id;
2305       Orig_Act_2 : Node_Id;
2306
2307    --  Start of processing for Apply_Parameter_Aliasing_Checks
2308
2309    begin
2310       Check := Empty;
2311
2312       Actual_1 := First_Actual (Call);
2313       Formal_1 := First_Formal (Subp);
2314       while Present (Actual_1) and then Present (Formal_1) loop
2315          Orig_Act_1 := Original_Actual (Actual_1);
2316
2317          --  Ensure that the actual is an object that is not passed by value.
2318          --  Elementary types are always passed by value, therefore actuals of
2319          --  such types cannot lead to aliasing. An aggregate is an object in
2320          --  Ada 2012, but an actual that is an aggregate cannot overlap with
2321          --  another actual. A type that is By_Reference (such as an array of
2322          --  controlled types) is not subject to the check because any update
2323          --  will be done in place and a subsequent read will always see the
2324          --  correct value, see RM 6.2 (12/3).
2325
2326          if Nkind (Orig_Act_1) = N_Aggregate
2327            or else (Nkind (Orig_Act_1) = N_Qualified_Expression
2328                      and then Nkind (Expression (Orig_Act_1)) = N_Aggregate)
2329          then
2330             null;
2331
2332          elsif Is_Object_Reference (Orig_Act_1)
2333            and then not Is_Elementary_Type (Etype (Orig_Act_1))
2334            and then not Is_By_Reference_Type (Etype (Orig_Act_1))
2335          then
2336             Actual_2 := Next_Actual (Actual_1);
2337             Formal_2 := Next_Formal (Formal_1);
2338             while Present (Actual_2) and then Present (Formal_2) loop
2339                Orig_Act_2 := Original_Actual (Actual_2);
2340
2341                --  The other actual we are testing against must also denote
2342                --  a non pass-by-value object. Generate the check only when
2343                --  the mode of the two formals may lead to aliasing.
2344
2345                if Is_Object_Reference (Orig_Act_2)
2346                  and then not Is_Elementary_Type (Etype (Orig_Act_2))
2347                  and then May_Cause_Aliasing (Formal_1, Formal_2)
2348                then
2349                   Overlap_Check
2350                     (Actual_1 => Actual_1,
2351                      Actual_2 => Actual_2,
2352                      Formal_1 => Formal_1,
2353                      Formal_2 => Formal_2,
2354                      Check    => Check);
2355                end if;
2356
2357                Next_Actual (Actual_2);
2358                Next_Formal (Formal_2);
2359             end loop;
2360          end if;
2361
2362          Next_Actual (Actual_1);
2363          Next_Formal (Formal_1);
2364       end loop;
2365
2366       --  Place a simple check right before the call
2367
2368       if Present (Check) and then not Exception_Extra_Info then
2369          Insert_Action (Call,
2370            Make_Raise_Program_Error (Loc,
2371              Condition => Check,
2372              Reason    => PE_Aliased_Parameters));
2373       end if;
2374    end Apply_Parameter_Aliasing_Checks;
2375
2376    -------------------------------------
2377    -- Apply_Parameter_Validity_Checks --
2378    -------------------------------------
2379
2380    procedure Apply_Parameter_Validity_Checks (Subp : Entity_Id) is
2381       Subp_Decl : Node_Id;
2382
2383       procedure Add_Validity_Check
2384         (Formal     : Entity_Id;
2385          Prag_Nam   : Name_Id;
2386          For_Result : Boolean := False);
2387       --  Add a single 'Valid[_Scalar] check which verifies the initialization
2388       --  of Formal. Prag_Nam denotes the pre or post condition pragma name.
2389       --  Set flag For_Result when to verify the result of a function.
2390
2391       ------------------------
2392       -- Add_Validity_Check --
2393       ------------------------
2394
2395       procedure Add_Validity_Check
2396         (Formal     : Entity_Id;
2397          Prag_Nam   : Name_Id;
2398          For_Result : Boolean := False)
2399       is
2400          procedure Build_Pre_Post_Condition (Expr : Node_Id);
2401          --  Create a pre/postcondition pragma that tests expression Expr
2402
2403          ------------------------------
2404          -- Build_Pre_Post_Condition --
2405          ------------------------------
2406
2407          procedure Build_Pre_Post_Condition (Expr : Node_Id) is
2408             Loc   : constant Source_Ptr := Sloc (Subp);
2409             Decls : List_Id;
2410             Prag  : Node_Id;
2411
2412          begin
2413             Prag :=
2414               Make_Pragma (Loc,
2415                 Pragma_Identifier            =>
2416                   Make_Identifier (Loc, Prag_Nam),
2417                 Pragma_Argument_Associations => New_List (
2418                   Make_Pragma_Argument_Association (Loc,
2419                     Chars      => Name_Check,
2420                     Expression => Expr)));
2421
2422             --  Add a message unless exception messages are suppressed
2423
2424             if not Exception_Locations_Suppressed then
2425                Append_To (Pragma_Argument_Associations (Prag),
2426                  Make_Pragma_Argument_Association (Loc,
2427                    Chars      => Name_Message,
2428                    Expression =>
2429                      Make_String_Literal (Loc,
2430                        Strval => "failed "
2431                                  & Get_Name_String (Prag_Nam)
2432                                  & " from "
2433                                  & Build_Location_String (Loc))));
2434             end if;
2435
2436             --  Insert the pragma in the tree
2437
2438             if Nkind (Parent (Subp_Decl)) = N_Compilation_Unit then
2439                Add_Global_Declaration (Prag);
2440                Analyze (Prag);
2441
2442             --  PPC pragmas associated with subprogram bodies must be inserted
2443             --  in the declarative part of the body.
2444
2445             elsif Nkind (Subp_Decl) = N_Subprogram_Body then
2446                Decls := Declarations (Subp_Decl);
2447
2448                if No (Decls) then
2449                   Decls := New_List;
2450                   Set_Declarations (Subp_Decl, Decls);
2451                end if;
2452
2453                Prepend_To (Decls, Prag);
2454                Analyze (Prag);
2455
2456             --  For subprogram declarations insert the PPC pragma right after
2457             --  the declarative node.
2458
2459             else
2460                Insert_After_And_Analyze (Subp_Decl, Prag);
2461             end if;
2462          end Build_Pre_Post_Condition;
2463
2464          --  Local variables
2465
2466          Loc   : constant Source_Ptr := Sloc (Subp);
2467          Typ   : constant Entity_Id  := Etype (Formal);
2468          Check : Node_Id;
2469          Nam   : Name_Id;
2470
2471       --  Start of processing for Add_Validity_Check
2472
2473       begin
2474          --  For scalars, generate 'Valid test
2475
2476          if Is_Scalar_Type (Typ) then
2477             Nam := Name_Valid;
2478
2479          --  For any non-scalar with scalar parts, generate 'Valid_Scalars test
2480
2481          elsif Scalar_Part_Present (Typ) then
2482             Nam := Name_Valid_Scalars;
2483
2484          --  No test needed for other cases (no scalars to test)
2485
2486          else
2487             return;
2488          end if;
2489
2490          --  Step 1: Create the expression to verify the validity of the
2491          --  context.
2492
2493          Check := New_Occurrence_Of (Formal, Loc);
2494
2495          --  When processing a function result, use 'Result. Generate
2496          --    Context'Result
2497
2498          if For_Result then
2499             Check :=
2500               Make_Attribute_Reference (Loc,
2501                 Prefix         => Check,
2502                 Attribute_Name => Name_Result);
2503          end if;
2504
2505          --  Generate:
2506          --    Context['Result]'Valid[_Scalars]
2507
2508          Check :=
2509            Make_Attribute_Reference (Loc,
2510              Prefix         => Check,
2511              Attribute_Name => Nam);
2512
2513          --  Step 2: Create a pre or post condition pragma
2514
2515          Build_Pre_Post_Condition (Check);
2516       end Add_Validity_Check;
2517
2518       --  Local variables
2519
2520       Formal    : Entity_Id;
2521       Subp_Spec : Node_Id;
2522
2523    --  Start of processing for Apply_Parameter_Validity_Checks
2524
2525    begin
2526       --  Extract the subprogram specification and declaration nodes
2527
2528       Subp_Spec := Parent (Subp);
2529
2530       if Nkind (Subp_Spec) = N_Defining_Program_Unit_Name then
2531          Subp_Spec := Parent (Subp_Spec);
2532       end if;
2533
2534       Subp_Decl := Parent (Subp_Spec);
2535
2536       if not Comes_From_Source (Subp)
2537
2538          --  Do not process formal subprograms because the corresponding actual
2539          --  will receive the proper checks when the instance is analyzed.
2540
2541         or else Is_Formal_Subprogram (Subp)
2542
2543         --  Do not process imported subprograms since pre and postconditions
2544         --  are never verified on routines coming from a different language.
2545
2546         or else Is_Imported (Subp)
2547         or else Is_Intrinsic_Subprogram (Subp)
2548
2549         --  The PPC pragmas generated by this routine do not correspond to
2550         --  source aspects, therefore they cannot be applied to abstract
2551         --  subprograms.
2552
2553         or else Nkind (Subp_Decl) = N_Abstract_Subprogram_Declaration
2554
2555         --  Do not consider subprogram renaminds because the renamed entity
2556         --  already has the proper PPC pragmas.
2557
2558         or else Nkind (Subp_Decl) = N_Subprogram_Renaming_Declaration
2559
2560         --  Do not process null procedures because there is no benefit of
2561         --  adding the checks to a no action routine.
2562
2563         or else (Nkind (Subp_Spec) = N_Procedure_Specification
2564                   and then Null_Present (Subp_Spec))
2565       then
2566          return;
2567       end if;
2568
2569       --  Inspect all the formals applying aliasing and scalar initialization
2570       --  checks where applicable.
2571
2572       Formal := First_Formal (Subp);
2573       while Present (Formal) loop
2574
2575          --  Generate the following scalar initialization checks for each
2576          --  formal parameter:
2577
2578          --    mode IN     - Pre       => Formal'Valid[_Scalars]
2579          --    mode IN OUT - Pre, Post => Formal'Valid[_Scalars]
2580          --    mode    OUT -      Post => Formal'Valid[_Scalars]
2581
2582          if Check_Validity_Of_Parameters then
2583             if Ekind_In (Formal, E_In_Parameter, E_In_Out_Parameter) then
2584                Add_Validity_Check (Formal, Name_Precondition, False);
2585             end if;
2586
2587             if Ekind_In (Formal, E_In_Out_Parameter, E_Out_Parameter) then
2588                Add_Validity_Check (Formal, Name_Postcondition, False);
2589             end if;
2590          end if;
2591
2592          Next_Formal (Formal);
2593       end loop;
2594
2595       --  Generate following scalar initialization check for function result:
2596
2597       --    Post => Subp'Result'Valid[_Scalars]
2598
2599       if Check_Validity_Of_Parameters and then Ekind (Subp) = E_Function then
2600          Add_Validity_Check (Subp, Name_Postcondition, True);
2601       end if;
2602    end Apply_Parameter_Validity_Checks;
2603
2604    ---------------------------
2605    -- Apply_Predicate_Check --
2606    ---------------------------
2607
2608    procedure Apply_Predicate_Check
2609      (N   : Node_Id;
2610       Typ : Entity_Id;
2611       Fun : Entity_Id := Empty)
2612    is
2613       S : Entity_Id;
2614
2615    begin
2616       if Predicate_Checks_Suppressed (Empty) then
2617          return;
2618
2619       elsif Predicates_Ignored (Typ) then
2620          return;
2621
2622       elsif Present (Predicate_Function (Typ)) then
2623          S := Current_Scope;
2624          while Present (S) and then not Is_Subprogram (S) loop
2625             S := Scope (S);
2626          end loop;
2627
2628          --  A predicate check does not apply within internally generated
2629          --  subprograms, such as TSS functions.
2630
2631          if Within_Internal_Subprogram then
2632             return;
2633
2634          --  If the check appears within the predicate function itself, it
2635          --  means that the user specified a check whose formal is the
2636          --  predicated subtype itself, rather than some covering type. This
2637          --  is likely to be a common error, and thus deserves a warning.
2638
2639          elsif Present (S) and then S = Predicate_Function (Typ) then
2640             Error_Msg_NE
2641               ("predicate check includes a call to& that requires a "
2642                & "predicate check??", Parent (N), Fun);
2643             Error_Msg_N
2644               ("\this will result in infinite recursion??", Parent (N));
2645
2646             if Is_First_Subtype (Typ) then
2647                Error_Msg_NE
2648                  ("\use an explicit subtype of& to carry the predicate",
2649                   Parent (N), Typ);
2650             end if;
2651
2652             Insert_Action (N,
2653               Make_Raise_Storage_Error (Sloc (N),
2654                 Reason => SE_Infinite_Recursion));
2655
2656          --  Here for normal case of predicate active
2657
2658          else
2659             --  If the type has a static predicate and the expression is known
2660             --  at compile time, see if the expression satisfies the predicate.
2661
2662             Check_Expression_Against_Static_Predicate (N, Typ);
2663
2664             if not Expander_Active then
2665                return;
2666             end if;
2667
2668             --  For an entity of the type, generate a call to the predicate
2669             --  function, unless its type is an actual subtype, which is not
2670             --  visible outside of the enclosing subprogram.
2671
2672             if Is_Entity_Name (N)
2673               and then not Is_Actual_Subtype (Typ)
2674             then
2675                Insert_Action (N,
2676                  Make_Predicate_Check
2677                    (Typ, New_Occurrence_Of (Entity (N), Sloc (N))));
2678
2679             --  If the expression is not an entity it may have side effects,
2680             --  and the following call will create an object declaration for
2681             --  it. We disable checks during its analysis, to prevent an
2682             --  infinite recursion.
2683
2684             else
2685                Insert_Action (N,
2686                  Make_Predicate_Check
2687                    (Typ, Duplicate_Subexpr (N)), Suppress => All_Checks);
2688             end if;
2689          end if;
2690       end if;
2691    end Apply_Predicate_Check;
2692
2693    -----------------------
2694    -- Apply_Range_Check --
2695    -----------------------
2696
2697    procedure Apply_Range_Check
2698      (Ck_Node    : Node_Id;
2699       Target_Typ : Entity_Id;
2700       Source_Typ : Entity_Id := Empty)
2701    is
2702    begin
2703       Apply_Selected_Range_Checks
2704         (Ck_Node, Target_Typ, Source_Typ, Do_Static => False);
2705    end Apply_Range_Check;
2706
2707    ------------------------------
2708    -- Apply_Scalar_Range_Check --
2709    ------------------------------
2710
2711    --  Note that Apply_Scalar_Range_Check never turns the Do_Range_Check flag
2712    --  off if it is already set on.
2713
2714    procedure Apply_Scalar_Range_Check
2715      (Expr       : Node_Id;
2716       Target_Typ : Entity_Id;
2717       Source_Typ : Entity_Id := Empty;
2718       Fixed_Int  : Boolean   := False)
2719    is
2720       Parnt   : constant Node_Id := Parent (Expr);
2721       S_Typ   : Entity_Id;
2722       Arr     : Node_Id   := Empty;  -- initialize to prevent warning
2723       Arr_Typ : Entity_Id := Empty;  -- initialize to prevent warning
2724       OK      : Boolean;
2725
2726       Is_Subscr_Ref : Boolean;
2727       --  Set true if Expr is a subscript
2728
2729       Is_Unconstrained_Subscr_Ref : Boolean;
2730       --  Set true if Expr is a subscript of an unconstrained array. In this
2731       --  case we do not attempt to do an analysis of the value against the
2732       --  range of the subscript, since we don't know the actual subtype.
2733
2734       Int_Real : Boolean;
2735       --  Set to True if Expr should be regarded as a real value even though
2736       --  the type of Expr might be discrete.
2737
2738       procedure Bad_Value (Warn : Boolean := False);
2739       --  Procedure called if value is determined to be out of range. Warn is
2740       --  True to force a warning instead of an error, even when SPARK_Mode is
2741       --  On.
2742
2743       ---------------
2744       -- Bad_Value --
2745       ---------------
2746
2747       procedure Bad_Value (Warn : Boolean := False) is
2748       begin
2749          Apply_Compile_Time_Constraint_Error
2750            (Expr, "value not in range of}??", CE_Range_Check_Failed,
2751             Ent  => Target_Typ,
2752             Typ  => Target_Typ,
2753             Warn => Warn);
2754       end Bad_Value;
2755
2756    --  Start of processing for Apply_Scalar_Range_Check
2757
2758    begin
2759       --  Return if check obviously not needed
2760
2761       if
2762          --  Not needed inside generic
2763
2764          Inside_A_Generic
2765
2766          --  Not needed if previous error
2767
2768          or else Target_Typ = Any_Type
2769          or else Nkind (Expr) = N_Error
2770
2771          --  Not needed for non-scalar type
2772
2773          or else not Is_Scalar_Type (Target_Typ)
2774
2775          --  Not needed if we know node raises CE already
2776
2777          or else Raises_Constraint_Error (Expr)
2778       then
2779          return;
2780       end if;
2781
2782       --  Now, see if checks are suppressed
2783
2784       Is_Subscr_Ref :=
2785         Is_List_Member (Expr) and then Nkind (Parnt) = N_Indexed_Component;
2786
2787       if Is_Subscr_Ref then
2788          Arr := Prefix (Parnt);
2789          Arr_Typ := Get_Actual_Subtype_If_Available (Arr);
2790
2791          if Is_Access_Type (Arr_Typ) then
2792             Arr_Typ := Designated_Type (Arr_Typ);
2793          end if;
2794       end if;
2795
2796       if not Do_Range_Check (Expr) then
2797
2798          --  Subscript reference. Check for Index_Checks suppressed
2799
2800          if Is_Subscr_Ref then
2801
2802             --  Check array type and its base type
2803
2804             if Index_Checks_Suppressed (Arr_Typ)
2805               or else Index_Checks_Suppressed (Base_Type (Arr_Typ))
2806             then
2807                return;
2808
2809             --  Check array itself if it is an entity name
2810
2811             elsif Is_Entity_Name (Arr)
2812               and then Index_Checks_Suppressed (Entity (Arr))
2813             then
2814                return;
2815
2816             --  Check expression itself if it is an entity name
2817
2818             elsif Is_Entity_Name (Expr)
2819               and then Index_Checks_Suppressed (Entity (Expr))
2820             then
2821                return;
2822             end if;
2823
2824          --  All other cases, check for Range_Checks suppressed
2825
2826          else
2827             --  Check target type and its base type
2828
2829             if Range_Checks_Suppressed (Target_Typ)
2830               or else Range_Checks_Suppressed (Base_Type (Target_Typ))
2831             then
2832                return;
2833
2834             --  Check expression itself if it is an entity name
2835
2836             elsif Is_Entity_Name (Expr)
2837               and then Range_Checks_Suppressed (Entity (Expr))
2838             then
2839                return;
2840
2841             --  If Expr is part of an assignment statement, then check left
2842             --  side of assignment if it is an entity name.
2843
2844             elsif Nkind (Parnt) = N_Assignment_Statement
2845               and then Is_Entity_Name (Name (Parnt))
2846               and then Range_Checks_Suppressed (Entity (Name (Parnt)))
2847             then
2848                return;
2849             end if;
2850          end if;
2851       end if;
2852
2853       --  Do not set range checks if they are killed
2854
2855       if Nkind (Expr) = N_Unchecked_Type_Conversion
2856         and then Kill_Range_Check (Expr)
2857       then
2858          return;
2859       end if;
2860
2861       --  Do not set range checks for any values from System.Scalar_Values
2862       --  since the whole idea of such values is to avoid checking them.
2863
2864       if Is_Entity_Name (Expr)
2865         and then Is_RTU (Scope (Entity (Expr)), System_Scalar_Values)
2866       then
2867          return;
2868       end if;
2869
2870       --  Now see if we need a check
2871
2872       if No (Source_Typ) then
2873          S_Typ := Etype (Expr);
2874       else
2875          S_Typ := Source_Typ;
2876       end if;
2877
2878       if not Is_Scalar_Type (S_Typ) or else S_Typ = Any_Type then
2879          return;
2880       end if;
2881
2882       Is_Unconstrained_Subscr_Ref :=
2883         Is_Subscr_Ref and then not Is_Constrained (Arr_Typ);
2884
2885       --  Special checks for floating-point type
2886
2887       if Is_Floating_Point_Type (S_Typ) then
2888
2889          --  Always do a range check if the source type includes infinities and
2890          --  the target type does not include infinities. We do not do this if
2891          --  range checks are killed.
2892          --  If the expression is a literal and the bounds of the type are
2893          --  static constants it may be possible to optimize the check.
2894
2895          if Has_Infinities (S_Typ)
2896            and then not Has_Infinities (Target_Typ)
2897          then
2898             --  If the expression is a literal and the bounds of the type are
2899             --  static constants it may be possible to optimize the check.
2900
2901             if Nkind (Expr) = N_Real_Literal then
2902                declare
2903                   Tlo : constant Node_Id := Type_Low_Bound  (Target_Typ);
2904                   Thi : constant Node_Id := Type_High_Bound (Target_Typ);
2905
2906                begin
2907                   if Compile_Time_Known_Value (Tlo)
2908                     and then Compile_Time_Known_Value (Thi)
2909                     and then Expr_Value_R (Expr) >= Expr_Value_R (Tlo)
2910                     and then Expr_Value_R (Expr) <= Expr_Value_R (Thi)
2911                   then
2912                      return;
2913                   else
2914                      Enable_Range_Check (Expr);
2915                   end if;
2916                end;
2917
2918             else
2919                Enable_Range_Check (Expr);
2920             end if;
2921          end if;
2922       end if;
2923
2924       --  Return if we know expression is definitely in the range of the target
2925       --  type as determined by Determine_Range. Right now we only do this for
2926       --  discrete types, and not fixed-point or floating-point types.
2927
2928       --  The additional less-precise tests below catch these cases
2929
2930       --  Note: skip this if we are given a source_typ, since the point of
2931       --  supplying a Source_Typ is to stop us looking at the expression.
2932       --  We could sharpen this test to be out parameters only ???
2933
2934       if Is_Discrete_Type (Target_Typ)
2935         and then Is_Discrete_Type (Etype (Expr))
2936         and then not Is_Unconstrained_Subscr_Ref
2937         and then No (Source_Typ)
2938       then
2939          declare
2940             Tlo : constant Node_Id := Type_Low_Bound  (Target_Typ);
2941             Thi : constant Node_Id := Type_High_Bound (Target_Typ);
2942             Lo  : Uint;
2943             Hi  : Uint;
2944
2945          begin
2946             if Compile_Time_Known_Value (Tlo)
2947               and then Compile_Time_Known_Value (Thi)
2948             then
2949                declare
2950                   Lov : constant Uint := Expr_Value (Tlo);
2951                   Hiv : constant Uint := Expr_Value (Thi);
2952
2953                begin
2954                   --  If range is null, we for sure have a constraint error
2955                   --  (we don't even need to look at the value involved,
2956                   --  since all possible values will raise CE).
2957
2958                   if Lov > Hiv then
2959
2960                      --  When SPARK_Mode is On, force a warning instead of
2961                      --  an error in that case, as this likely corresponds
2962                      --  to deactivated code.
2963
2964                      Bad_Value (Warn => SPARK_Mode = On);
2965
2966                      --  In GNATprove mode, we enable the range check so that
2967                      --  GNATprove will issue a message if it cannot be proved.
2968
2969                      if GNATprove_Mode then
2970                         Enable_Range_Check (Expr);
2971                      end if;
2972
2973                      return;
2974                   end if;
2975
2976                   --  Otherwise determine range of value
2977
2978                   Determine_Range (Expr, OK, Lo, Hi, Assume_Valid => True);
2979
2980                   if OK then
2981
2982                      --  If definitely in range, all OK
2983
2984                      if Lo >= Lov and then Hi <= Hiv then
2985                         return;
2986
2987                      --  If definitely not in range, warn
2988
2989                      elsif Lov > Hi or else Hiv < Lo then
2990                         Bad_Value;
2991                         return;
2992
2993                      --  Otherwise we don't know
2994
2995                      else
2996                         null;
2997                      end if;
2998                   end if;
2999                end;
3000             end if;
3001          end;
3002       end if;
3003
3004       Int_Real :=
3005         Is_Floating_Point_Type (S_Typ)
3006           or else (Is_Fixed_Point_Type (S_Typ) and then not Fixed_Int);
3007
3008       --  Check if we can determine at compile time whether Expr is in the
3009       --  range of the target type. Note that if S_Typ is within the bounds
3010       --  of Target_Typ then this must be the case. This check is meaningful
3011       --  only if this is not a conversion between integer and real types.
3012
3013       if not Is_Unconstrained_Subscr_Ref
3014         and then Is_Discrete_Type (S_Typ) = Is_Discrete_Type (Target_Typ)
3015         and then
3016           (In_Subrange_Of (S_Typ, Target_Typ, Fixed_Int)
3017
3018              --  Also check if the expression itself is in the range of the
3019              --  target type if it is a known at compile time value. We skip
3020              --  this test if S_Typ is set since for OUT and IN OUT parameters
3021              --  the Expr itself is not relevant to the checking.
3022
3023              or else
3024                (No (Source_Typ)
3025                   and then Is_In_Range (Expr, Target_Typ,
3026                                         Assume_Valid => True,
3027                                         Fixed_Int    => Fixed_Int,
3028                                         Int_Real     => Int_Real)))
3029       then
3030          return;
3031
3032       elsif Is_Out_Of_Range (Expr, Target_Typ,
3033                              Assume_Valid => True,
3034                              Fixed_Int    => Fixed_Int,
3035                              Int_Real     => Int_Real)
3036       then
3037          Bad_Value;
3038          return;
3039
3040       --  Floating-point case
3041       --  In the floating-point case, we only do range checks if the type is
3042       --  constrained. We definitely do NOT want range checks for unconstrained
3043       --  types, since we want to have infinities, except when
3044       --  Check_Float_Overflow is set.
3045
3046       elsif Is_Floating_Point_Type (S_Typ) then
3047          if Is_Constrained (S_Typ) or else Check_Float_Overflow then
3048             Enable_Range_Check (Expr);
3049          end if;
3050
3051       --  For all other cases we enable a range check unconditionally
3052
3053       else
3054          Enable_Range_Check (Expr);
3055          return;
3056       end if;
3057    end Apply_Scalar_Range_Check;
3058
3059    ----------------------------------
3060    -- Apply_Selected_Length_Checks --
3061    ----------------------------------
3062
3063    procedure Apply_Selected_Length_Checks
3064      (Ck_Node    : Node_Id;
3065       Target_Typ : Entity_Id;
3066       Source_Typ : Entity_Id;
3067       Do_Static  : Boolean)
3068    is
3069       Cond     : Node_Id;
3070       R_Result : Check_Result;
3071       R_Cno    : Node_Id;
3072
3073       Loc         : constant Source_Ptr := Sloc (Ck_Node);
3074       Checks_On   : constant Boolean :=
3075         (not Index_Checks_Suppressed (Target_Typ))
3076           or else (not Length_Checks_Suppressed (Target_Typ));
3077
3078    begin
3079       --  Note: this means that we lose some useful warnings if the expander
3080       --  is not active, and we also lose these warnings in SPARK mode ???
3081
3082       if not Expander_Active then
3083          return;
3084       end if;
3085
3086       R_Result :=
3087         Selected_Length_Checks (Ck_Node, Target_Typ, Source_Typ, Empty);
3088
3089       for J in 1 .. 2 loop
3090          R_Cno := R_Result (J);
3091          exit when No (R_Cno);
3092
3093          --  A length check may mention an Itype which is attached to a
3094          --  subsequent node. At the top level in a package this can cause
3095          --  an order-of-elaboration problem, so we make sure that the itype
3096          --  is referenced now.
3097
3098          if Ekind (Current_Scope) = E_Package
3099            and then Is_Compilation_Unit (Current_Scope)
3100          then
3101             Ensure_Defined (Target_Typ, Ck_Node);
3102
3103             if Present (Source_Typ) then
3104                Ensure_Defined (Source_Typ, Ck_Node);
3105
3106             elsif Is_Itype (Etype (Ck_Node)) then
3107                Ensure_Defined (Etype (Ck_Node), Ck_Node);
3108             end if;
3109          end if;
3110
3111          --  If the item is a conditional raise of constraint error, then have
3112          --  a look at what check is being performed and ???
3113
3114          if Nkind (R_Cno) = N_Raise_Constraint_Error
3115            and then Present (Condition (R_Cno))
3116          then
3117             Cond := Condition (R_Cno);
3118
3119             --  Case where node does not now have a dynamic check
3120
3121             if not Has_Dynamic_Length_Check (Ck_Node) then
3122
3123                --  If checks are on, just insert the check
3124
3125                if Checks_On then
3126                   Insert_Action (Ck_Node, R_Cno);
3127
3128                   if not Do_Static then
3129                      Set_Has_Dynamic_Length_Check (Ck_Node);
3130                   end if;
3131
3132                --  If checks are off, then analyze the length check after
3133                --  temporarily attaching it to the tree in case the relevant
3134                --  condition can be evaluated at compile time. We still want a
3135                --  compile time warning in this case.
3136
3137                else
3138                   Set_Parent (R_Cno, Ck_Node);
3139                   Analyze (R_Cno);
3140                end if;
3141             end if;
3142
3143             --  Output a warning if the condition is known to be True
3144
3145             if Is_Entity_Name (Cond)
3146               and then Entity (Cond) = Standard_True
3147             then
3148                Apply_Compile_Time_Constraint_Error
3149                  (Ck_Node, "wrong length for array of}??",
3150                   CE_Length_Check_Failed,
3151                   Ent => Target_Typ,
3152                   Typ => Target_Typ);
3153
3154             --  If we were only doing a static check, or if checks are not
3155             --  on, then we want to delete the check, since it is not needed.
3156             --  We do this by replacing the if statement by a null statement
3157
3158             elsif Do_Static or else not Checks_On then
3159                Remove_Warning_Messages (R_Cno);
3160                Rewrite (R_Cno, Make_Null_Statement (Loc));
3161             end if;
3162
3163          else
3164             Install_Static_Check (R_Cno, Loc);
3165          end if;
3166       end loop;
3167    end Apply_Selected_Length_Checks;
3168
3169    ---------------------------------
3170    -- Apply_Selected_Range_Checks --
3171    ---------------------------------
3172
3173    procedure Apply_Selected_Range_Checks
3174      (Ck_Node    : Node_Id;
3175       Target_Typ : Entity_Id;
3176       Source_Typ : Entity_Id;
3177       Do_Static  : Boolean)
3178    is
3179       Loc       : constant Source_Ptr := Sloc (Ck_Node);
3180       Checks_On : constant Boolean :=
3181                     not Index_Checks_Suppressed (Target_Typ)
3182                       or else
3183                     not Range_Checks_Suppressed (Target_Typ);
3184
3185       Cond     : Node_Id;
3186       R_Cno    : Node_Id;
3187       R_Result : Check_Result;
3188
3189    begin
3190       if not Expander_Active or not Checks_On then
3191          return;
3192       end if;
3193
3194       R_Result :=
3195         Selected_Range_Checks (Ck_Node, Target_Typ, Source_Typ, Empty);
3196
3197       for J in 1 .. 2 loop
3198          R_Cno := R_Result (J);
3199          exit when No (R_Cno);
3200
3201          --  The range check requires runtime evaluation. Depending on what its
3202          --  triggering condition is, the check may be converted into a compile
3203          --  time constraint check.
3204
3205          if Nkind (R_Cno) = N_Raise_Constraint_Error
3206            and then Present (Condition (R_Cno))
3207          then
3208             Cond := Condition (R_Cno);
3209
3210             --  Insert the range check before the related context. Note that
3211             --  this action analyses the triggering condition.
3212
3213             Insert_Action (Ck_Node, R_Cno);
3214
3215             --  This old code doesn't make sense, why is the context flagged as
3216             --  requiring dynamic range checks now in the middle of generating
3217             --  them ???
3218
3219             if not Do_Static then
3220                Set_Has_Dynamic_Range_Check (Ck_Node);
3221             end if;
3222
3223             --  The triggering condition evaluates to True, the range check
3224             --  can be converted into a compile time constraint check.
3225
3226             if Is_Entity_Name (Cond)
3227               and then Entity (Cond) = Standard_True
3228             then
3229                --  Since an N_Range is technically not an expression, we have
3230                --  to set one of the bounds to C_E and then just flag the
3231                --  N_Range. The warning message will point to the lower bound
3232                --  and complain about a range, which seems OK.
3233
3234                if Nkind (Ck_Node) = N_Range then
3235                   Apply_Compile_Time_Constraint_Error
3236                     (Low_Bound (Ck_Node),
3237                      "static range out of bounds of}??",
3238                      CE_Range_Check_Failed,
3239                      Ent => Target_Typ,
3240                      Typ => Target_Typ);
3241
3242                   Set_Raises_Constraint_Error (Ck_Node);
3243
3244                else
3245                   Apply_Compile_Time_Constraint_Error
3246                     (Ck_Node,
3247                      "static value out of range of}??",
3248                      CE_Range_Check_Failed,
3249                      Ent => Target_Typ,
3250                      Typ => Target_Typ);
3251                end if;
3252
3253             --  If we were only doing a static check, or if checks are not
3254             --  on, then we want to delete the check, since it is not needed.
3255             --  We do this by replacing the if statement by a null statement
3256
3257             elsif Do_Static then
3258                Remove_Warning_Messages (R_Cno);
3259                Rewrite (R_Cno, Make_Null_Statement (Loc));
3260             end if;
3261
3262          --  The range check raises Constraint_Error explicitly
3263
3264          else
3265             Install_Static_Check (R_Cno, Loc);
3266          end if;
3267       end loop;
3268    end Apply_Selected_Range_Checks;
3269
3270    -------------------------------
3271    -- Apply_Static_Length_Check --
3272    -------------------------------
3273
3274    procedure Apply_Static_Length_Check
3275      (Expr       : Node_Id;
3276       Target_Typ : Entity_Id;
3277       Source_Typ : Entity_Id := Empty)
3278    is
3279    begin
3280       Apply_Selected_Length_Checks
3281         (Expr, Target_Typ, Source_Typ, Do_Static => True);
3282    end Apply_Static_Length_Check;
3283
3284    -------------------------------------
3285    -- Apply_Subscript_Validity_Checks --
3286    -------------------------------------
3287
3288    procedure Apply_Subscript_Validity_Checks (Expr : Node_Id) is
3289       Sub : Node_Id;
3290
3291    begin
3292       pragma Assert (Nkind (Expr) = N_Indexed_Component);
3293
3294       --  Loop through subscripts
3295
3296       Sub := First (Expressions (Expr));
3297       while Present (Sub) loop
3298
3299          --  Check one subscript. Note that we do not worry about enumeration
3300          --  type with holes, since we will convert the value to a Pos value
3301          --  for the subscript, and that convert will do the necessary validity
3302          --  check.
3303
3304          Ensure_Valid (Sub, Holes_OK => True);
3305
3306          --  Move to next subscript
3307
3308          Sub := Next (Sub);
3309       end loop;
3310    end Apply_Subscript_Validity_Checks;
3311
3312    ----------------------------------
3313    -- Apply_Type_Conversion_Checks --
3314    ----------------------------------
3315
3316    procedure Apply_Type_Conversion_Checks (N : Node_Id) is
3317       Target_Type : constant Entity_Id := Etype (N);
3318       Target_Base : constant Entity_Id := Base_Type (Target_Type);
3319       Expr        : constant Node_Id   := Expression (N);
3320
3321       Expr_Type : constant Entity_Id := Underlying_Type (Etype (Expr));
3322       --  Note: if Etype (Expr) is a private type without discriminants, its
3323       --  full view might have discriminants with defaults, so we need the
3324       --  full view here to retrieve the constraints.
3325
3326    begin
3327       if Inside_A_Generic then
3328          return;
3329
3330       --  Skip these checks if serious errors detected, there are some nasty
3331       --  situations of incomplete trees that blow things up.
3332
3333       elsif Serious_Errors_Detected > 0 then
3334          return;
3335
3336       --  Never generate discriminant checks for Unchecked_Union types
3337
3338       elsif Present (Expr_Type)
3339         and then Is_Unchecked_Union (Expr_Type)
3340       then
3341          return;
3342
3343       --  Scalar type conversions of the form Target_Type (Expr) require a
3344       --  range check if we cannot be sure that Expr is in the base type of
3345       --  Target_Typ and also that Expr is in the range of Target_Typ. These
3346       --  are not quite the same condition from an implementation point of
3347       --  view, but clearly the second includes the first.
3348
3349       elsif Is_Scalar_Type (Target_Type) then
3350          declare
3351             Conv_OK  : constant Boolean := Conversion_OK (N);
3352             --  If the Conversion_OK flag on the type conversion is set and no
3353             --  floating-point type is involved in the type conversion then
3354             --  fixed-point values must be read as integral values.
3355
3356             Float_To_Int : constant Boolean :=
3357               Is_Floating_Point_Type (Expr_Type)
3358               and then Is_Integer_Type (Target_Type);
3359
3360          begin
3361             if not Overflow_Checks_Suppressed (Target_Base)
3362               and then not Overflow_Checks_Suppressed (Target_Type)
3363               and then not
3364                 In_Subrange_Of (Expr_Type, Target_Base, Fixed_Int => Conv_OK)
3365               and then not Float_To_Int
3366             then
3367                Activate_Overflow_Check (N);
3368             end if;
3369
3370             if not Range_Checks_Suppressed (Target_Type)
3371               and then not Range_Checks_Suppressed (Expr_Type)
3372             then
3373                if Float_To_Int then
3374                   Apply_Float_Conversion_Check (Expr, Target_Type);
3375                else
3376                   Apply_Scalar_Range_Check
3377                     (Expr, Target_Type, Fixed_Int => Conv_OK);
3378
3379                   --  If the target type has predicates, we need to indicate
3380                   --  the need for a check, even if Determine_Range finds that
3381                   --  the value is within bounds. This may be the case e.g for
3382                   --  a division with a constant denominator.
3383
3384                   if Has_Predicates (Target_Type) then
3385                      Enable_Range_Check (Expr);
3386                   end if;
3387                end if;
3388             end if;
3389          end;
3390
3391       elsif Comes_From_Source (N)
3392         and then not Discriminant_Checks_Suppressed (Target_Type)
3393         and then Is_Record_Type (Target_Type)
3394         and then Is_Derived_Type (Target_Type)
3395         and then not Is_Tagged_Type (Target_Type)
3396         and then not Is_Constrained (Target_Type)
3397         and then Present (Stored_Constraint (Target_Type))
3398       then
3399          --  An unconstrained derived type may have inherited discriminant.
3400          --  Build an actual discriminant constraint list using the stored
3401          --  constraint, to verify that the expression of the parent type
3402          --  satisfies the constraints imposed by the (unconstrained) derived
3403          --  type. This applies to value conversions, not to view conversions
3404          --  of tagged types.
3405
3406          declare
3407             Loc         : constant Source_Ptr := Sloc (N);
3408             Cond        : Node_Id;
3409             Constraint  : Elmt_Id;
3410             Discr_Value : Node_Id;
3411             Discr       : Entity_Id;
3412
3413             New_Constraints : constant Elist_Id := New_Elmt_List;
3414             Old_Constraints : constant Elist_Id :=
3415               Discriminant_Constraint (Expr_Type);
3416
3417          begin
3418             Constraint := First_Elmt (Stored_Constraint (Target_Type));
3419             while Present (Constraint) loop
3420                Discr_Value := Node (Constraint);
3421
3422                if Is_Entity_Name (Discr_Value)
3423                  and then Ekind (Entity (Discr_Value)) = E_Discriminant
3424                then
3425                   Discr := Corresponding_Discriminant (Entity (Discr_Value));
3426
3427                   if Present (Discr)
3428                     and then Scope (Discr) = Base_Type (Expr_Type)
3429                   then
3430                      --  Parent is constrained by new discriminant. Obtain
3431                      --  Value of original discriminant in expression. If the
3432                      --  new discriminant has been used to constrain more than
3433                      --  one of the stored discriminants, this will provide the
3434                      --  required consistency check.
3435
3436                      Append_Elmt
3437                        (Make_Selected_Component (Loc,
3438                           Prefix        =>
3439                             Duplicate_Subexpr_No_Checks
3440                               (Expr, Name_Req => True),
3441                           Selector_Name =>
3442                             Make_Identifier (Loc, Chars (Discr))),
3443                         New_Constraints);
3444
3445                   else
3446                      --  Discriminant of more remote ancestor ???
3447
3448                      return;
3449                   end if;
3450
3451                --  Derived type definition has an explicit value for this
3452                --  stored discriminant.
3453
3454                else
3455                   Append_Elmt
3456                     (Duplicate_Subexpr_No_Checks (Discr_Value),
3457                      New_Constraints);
3458                end if;
3459
3460                Next_Elmt (Constraint);
3461             end loop;
3462
3463             --  Use the unconstrained expression type to retrieve the
3464             --  discriminants of the parent, and apply momentarily the
3465             --  discriminant constraint synthesized above.
3466
3467             Set_Discriminant_Constraint (Expr_Type, New_Constraints);
3468             Cond := Build_Discriminant_Checks (Expr, Expr_Type);
3469             Set_Discriminant_Constraint (Expr_Type, Old_Constraints);
3470
3471             Insert_Action (N,
3472               Make_Raise_Constraint_Error (Loc,
3473                 Condition => Cond,
3474                 Reason    => CE_Discriminant_Check_Failed));
3475          end;
3476
3477       --  For arrays, checks are set now, but conversions are applied during
3478       --  expansion, to take into accounts changes of representation. The
3479       --  checks become range checks on the base type or length checks on the
3480       --  subtype, depending on whether the target type is unconstrained or
3481       --  constrained. Note that the range check is put on the expression of a
3482       --  type conversion, while the length check is put on the type conversion
3483       --  itself.
3484
3485       elsif Is_Array_Type (Target_Type) then
3486          if Is_Constrained (Target_Type) then
3487             Set_Do_Length_Check (N);
3488          else
3489             Set_Do_Range_Check (Expr);
3490          end if;
3491       end if;
3492    end Apply_Type_Conversion_Checks;
3493
3494    ----------------------------------------------
3495    -- Apply_Universal_Integer_Attribute_Checks --
3496    ----------------------------------------------
3497
3498    procedure Apply_Universal_Integer_Attribute_Checks (N : Node_Id) is
3499       Loc : constant Source_Ptr := Sloc (N);
3500       Typ : constant Entity_Id  := Etype (N);
3501
3502    begin
3503       if Inside_A_Generic then
3504          return;
3505
3506       --  Nothing to do if checks are suppressed
3507
3508       elsif Range_Checks_Suppressed (Typ)
3509         and then Overflow_Checks_Suppressed (Typ)
3510       then
3511          return;
3512
3513       --  Nothing to do if the attribute does not come from source. The
3514       --  internal attributes we generate of this type do not need checks,
3515       --  and furthermore the attempt to check them causes some circular
3516       --  elaboration orders when dealing with packed types.
3517
3518       elsif not Comes_From_Source (N) then
3519          return;
3520
3521       --  If the prefix is a selected component that depends on a discriminant
3522       --  the check may improperly expose a discriminant instead of using
3523       --  the bounds of the object itself. Set the type of the attribute to
3524       --  the base type of the context, so that a check will be imposed when
3525       --  needed (e.g. if the node appears as an index).
3526
3527       elsif Nkind (Prefix (N)) = N_Selected_Component
3528         and then Ekind (Typ) = E_Signed_Integer_Subtype
3529         and then Depends_On_Discriminant (Scalar_Range (Typ))
3530       then
3531          Set_Etype (N, Base_Type (Typ));
3532
3533       --  Otherwise, replace the attribute node with a type conversion node
3534       --  whose expression is the attribute, retyped to universal integer, and
3535       --  whose subtype mark is the target type. The call to analyze this
3536       --  conversion will set range and overflow checks as required for proper
3537       --  detection of an out of range value.
3538
3539       else
3540          Set_Etype    (N, Universal_Integer);
3541          Set_Analyzed (N, True);
3542
3543          Rewrite (N,
3544            Make_Type_Conversion (Loc,
3545              Subtype_Mark => New_Occurrence_Of (Typ, Loc),
3546              Expression   => Relocate_Node (N)));
3547
3548          Analyze_And_Resolve (N, Typ);
3549          return;
3550       end if;
3551    end Apply_Universal_Integer_Attribute_Checks;
3552
3553    -------------------------------------
3554    -- Atomic_Synchronization_Disabled --
3555    -------------------------------------
3556
3557    --  Note: internally Disable/Enable_Atomic_Synchronization is implemented
3558    --  using a bogus check called Atomic_Synchronization. This is to make it
3559    --  more convenient to get exactly the same semantics as [Un]Suppress.
3560
3561    function Atomic_Synchronization_Disabled (E : Entity_Id) return Boolean is
3562    begin
3563       --  If debug flag d.e is set, always return False, i.e. all atomic sync
3564       --  looks enabled, since it is never disabled.
3565
3566       if Debug_Flag_Dot_E then
3567          return False;
3568
3569       --  If debug flag d.d is set then always return True, i.e. all atomic
3570       --  sync looks disabled, since it always tests True.
3571
3572       elsif Debug_Flag_Dot_D then
3573          return True;
3574
3575       --  If entity present, then check result for that entity
3576
3577       elsif Present (E) and then Checks_May_Be_Suppressed (E) then
3578          return Is_Check_Suppressed (E, Atomic_Synchronization);
3579
3580       --  Otherwise result depends on current scope setting
3581
3582       else
3583          return Scope_Suppress.Suppress (Atomic_Synchronization);
3584       end if;
3585    end Atomic_Synchronization_Disabled;
3586
3587    -------------------------------
3588    -- Build_Discriminant_Checks --
3589    -------------------------------
3590
3591    function Build_Discriminant_Checks
3592      (N     : Node_Id;
3593       T_Typ : Entity_Id) return Node_Id
3594    is
3595       Loc      : constant Source_Ptr := Sloc (N);
3596       Cond     : Node_Id;
3597       Disc     : Elmt_Id;
3598       Disc_Ent : Entity_Id;
3599       Dref     : Node_Id;
3600       Dval     : Node_Id;
3601
3602       function Aggregate_Discriminant_Val (Disc : Entity_Id) return Node_Id;
3603
3604       ----------------------------------
3605       -- Aggregate_Discriminant_Value --
3606       ----------------------------------
3607
3608       function Aggregate_Discriminant_Val (Disc : Entity_Id) return Node_Id is
3609          Assoc : Node_Id;
3610
3611       begin
3612          --  The aggregate has been normalized with named associations. We use
3613          --  the Chars field to locate the discriminant to take into account
3614          --  discriminants in derived types, which carry the same name as those
3615          --  in the parent.
3616
3617          Assoc := First (Component_Associations (N));
3618          while Present (Assoc) loop
3619             if Chars (First (Choices (Assoc))) = Chars (Disc) then
3620                return Expression (Assoc);
3621             else
3622                Next (Assoc);
3623             end if;
3624          end loop;
3625
3626          --  Discriminant must have been found in the loop above
3627
3628          raise Program_Error;
3629       end Aggregate_Discriminant_Val;
3630
3631    --  Start of processing for Build_Discriminant_Checks
3632
3633    begin
3634       --  Loop through discriminants evolving the condition
3635
3636       Cond := Empty;
3637       Disc := First_Elmt (Discriminant_Constraint (T_Typ));
3638
3639       --  For a fully private type, use the discriminants of the parent type
3640
3641       if Is_Private_Type (T_Typ)
3642         and then No (Full_View (T_Typ))
3643       then
3644          Disc_Ent := First_Discriminant (Etype (Base_Type (T_Typ)));
3645       else
3646          Disc_Ent := First_Discriminant (T_Typ);
3647       end if;
3648
3649       while Present (Disc) loop
3650          Dval := Node (Disc);
3651
3652          if Nkind (Dval) = N_Identifier
3653            and then Ekind (Entity (Dval)) = E_Discriminant
3654          then
3655             Dval := New_Occurrence_Of (Discriminal (Entity (Dval)), Loc);
3656          else
3657             Dval := Duplicate_Subexpr_No_Checks (Dval);
3658          end if;
3659
3660          --  If we have an Unchecked_Union node, we can infer the discriminants
3661          --  of the node.
3662
3663          if Is_Unchecked_Union (Base_Type (T_Typ)) then
3664             Dref := New_Copy (
3665               Get_Discriminant_Value (
3666                 First_Discriminant (T_Typ),
3667                 T_Typ,
3668                 Stored_Constraint (T_Typ)));
3669
3670          elsif Nkind (N) = N_Aggregate then
3671             Dref :=
3672                Duplicate_Subexpr_No_Checks
3673                  (Aggregate_Discriminant_Val (Disc_Ent));
3674
3675          else
3676             Dref :=
3677               Make_Selected_Component (Loc,
3678                 Prefix        =>
3679                   Duplicate_Subexpr_No_Checks (N, Name_Req => True),
3680                 Selector_Name => Make_Identifier (Loc, Chars (Disc_Ent)));
3681
3682             Set_Is_In_Discriminant_Check (Dref);
3683          end if;
3684
3685          Evolve_Or_Else (Cond,
3686            Make_Op_Ne (Loc,
3687              Left_Opnd  => Dref,
3688              Right_Opnd => Dval));
3689
3690          Next_Elmt (Disc);
3691          Next_Discriminant (Disc_Ent);
3692       end loop;
3693
3694       return Cond;
3695    end Build_Discriminant_Checks;
3696
3697    ------------------
3698    -- Check_Needed --
3699    ------------------
3700
3701    function Check_Needed (Nod : Node_Id; Check : Check_Type) return Boolean is
3702       N : Node_Id;
3703       P : Node_Id;
3704       K : Node_Kind;
3705       L : Node_Id;
3706       R : Node_Id;
3707
3708       function Left_Expression (Op : Node_Id) return Node_Id;
3709       --  Return the relevant expression from the left operand of the given
3710       --  short circuit form: this is LO itself, except if LO is a qualified
3711       --  expression, a type conversion, or an expression with actions, in
3712       --  which case this is Left_Expression (Expression (LO)).
3713
3714       ---------------------
3715       -- Left_Expression --
3716       ---------------------
3717
3718       function Left_Expression (Op : Node_Id) return Node_Id is
3719          LE : Node_Id := Left_Opnd (Op);
3720       begin
3721          while Nkind_In (LE, N_Qualified_Expression,
3722                              N_Type_Conversion,
3723                              N_Expression_With_Actions)
3724          loop
3725             LE := Expression (LE);
3726          end loop;
3727
3728          return LE;
3729       end Left_Expression;
3730
3731    --  Start of processing for Check_Needed
3732
3733    begin
3734       --  Always check if not simple entity
3735
3736       if Nkind (Nod) not in N_Has_Entity
3737         or else not Comes_From_Source (Nod)
3738       then
3739          return True;
3740       end if;
3741
3742       --  Look up tree for short circuit
3743
3744       N := Nod;
3745       loop
3746          P := Parent (N);
3747          K := Nkind (P);
3748
3749          --  Done if out of subexpression (note that we allow generated stuff
3750          --  such as itype declarations in this context, to keep the loop going
3751          --  since we may well have generated such stuff in complex situations.
3752          --  Also done if no parent (probably an error condition, but no point
3753          --  in behaving nasty if we find it).
3754
3755          if No (P)
3756            or else (K not in N_Subexpr and then Comes_From_Source (P))
3757          then
3758             return True;
3759
3760          --  Or/Or Else case, where test is part of the right operand, or is
3761          --  part of one of the actions associated with the right operand, and
3762          --  the left operand is an equality test.
3763
3764          elsif K = N_Op_Or then
3765             exit when N = Right_Opnd (P)
3766               and then Nkind (Left_Expression (P)) = N_Op_Eq;
3767
3768          elsif K = N_Or_Else then
3769             exit when (N = Right_Opnd (P)
3770                         or else
3771                           (Is_List_Member (N)
3772                              and then List_Containing (N) = Actions (P)))
3773               and then Nkind (Left_Expression (P)) = N_Op_Eq;
3774
3775          --  Similar test for the And/And then case, where the left operand
3776          --  is an inequality test.
3777
3778          elsif K = N_Op_And then
3779             exit when N = Right_Opnd (P)
3780               and then Nkind (Left_Expression (P)) = N_Op_Ne;
3781
3782          elsif K = N_And_Then then
3783             exit when (N = Right_Opnd (P)
3784                         or else
3785                           (Is_List_Member (N)
3786                             and then List_Containing (N) = Actions (P)))
3787               and then Nkind (Left_Expression (P)) = N_Op_Ne;
3788          end if;
3789
3790          N := P;
3791       end loop;
3792
3793       --  If we fall through the loop, then we have a conditional with an
3794       --  appropriate test as its left operand, so look further.
3795
3796       L := Left_Expression (P);
3797
3798       --  L is an "=" or "/=" operator: extract its operands
3799
3800       R := Right_Opnd (L);
3801       L := Left_Opnd (L);
3802
3803       --  Left operand of test must match original variable
3804
3805       if Nkind (L) not in N_Has_Entity or else Entity (L) /= Entity (Nod) then
3806          return True;
3807       end if;
3808
3809       --  Right operand of test must be key value (zero or null)
3810
3811       case Check is
3812          when Access_Check =>
3813             if not Known_Null (R) then
3814                return True;
3815             end if;
3816
3817          when Division_Check =>
3818             if not Compile_Time_Known_Value (R)
3819               or else Expr_Value (R) /= Uint_0
3820             then
3821                return True;
3822             end if;
3823
3824          when others =>
3825             raise Program_Error;
3826       end case;
3827
3828       --  Here we have the optimizable case, warn if not short-circuited
3829
3830       if K = N_Op_And or else K = N_Op_Or then
3831          Error_Msg_Warn := SPARK_Mode /= On;
3832
3833          case Check is
3834             when Access_Check =>
3835                if GNATprove_Mode then
3836                   Error_Msg_N
3837                     ("Constraint_Error might have been raised (access check)",
3838                      Parent (Nod));
3839                else
3840                   Error_Msg_N
3841                     ("Constraint_Error may be raised (access check)??",
3842                      Parent (Nod));
3843                end if;
3844
3845             when Division_Check =>
3846                if GNATprove_Mode then
3847                   Error_Msg_N
3848                     ("Constraint_Error might have been raised (zero divide)",
3849                      Parent (Nod));
3850                else
3851                   Error_Msg_N
3852                     ("Constraint_Error may be raised (zero divide)??",
3853                      Parent (Nod));
3854                end if;
3855
3856             when others =>
3857                raise Program_Error;
3858          end case;
3859
3860          if K = N_Op_And then
3861             Error_Msg_N -- CODEFIX
3862               ("use `AND THEN` instead of AND??", P);
3863          else
3864             Error_Msg_N -- CODEFIX
3865               ("use `OR ELSE` instead of OR??", P);
3866          end if;
3867
3868          --  If not short-circuited, we need the check
3869
3870          return True;
3871
3872       --  If short-circuited, we can omit the check
3873
3874       else
3875          return False;
3876       end if;
3877    end Check_Needed;
3878
3879    -----------------------------------
3880    -- Check_Valid_Lvalue_Subscripts --
3881    -----------------------------------
3882
3883    procedure Check_Valid_Lvalue_Subscripts (Expr : Node_Id) is
3884    begin
3885       --  Skip this if range checks are suppressed
3886
3887       if Range_Checks_Suppressed (Etype (Expr)) then
3888          return;
3889
3890       --  Only do this check for expressions that come from source. We assume
3891       --  that expander generated assignments explicitly include any necessary
3892       --  checks. Note that this is not just an optimization, it avoids
3893       --  infinite recursions.
3894
3895       elsif not Comes_From_Source (Expr) then
3896          return;
3897
3898       --  For a selected component, check the prefix
3899
3900       elsif Nkind (Expr) = N_Selected_Component then
3901          Check_Valid_Lvalue_Subscripts (Prefix (Expr));
3902          return;
3903
3904       --  Case of indexed component
3905
3906       elsif Nkind (Expr) = N_Indexed_Component then
3907          Apply_Subscript_Validity_Checks (Expr);
3908
3909          --  Prefix may itself be or contain an indexed component, and these
3910          --  subscripts need checking as well.
3911
3912          Check_Valid_Lvalue_Subscripts (Prefix (Expr));
3913       end if;
3914    end Check_Valid_Lvalue_Subscripts;
3915
3916    ----------------------------------
3917    -- Null_Exclusion_Static_Checks --
3918    ----------------------------------
3919
3920    procedure Null_Exclusion_Static_Checks (N : Node_Id) is
3921       Error_Node : Node_Id;
3922       Expr       : Node_Id;
3923       Has_Null   : constant Boolean := Has_Null_Exclusion (N);
3924       K          : constant Node_Kind := Nkind (N);
3925       Typ        : Entity_Id;
3926
3927    begin
3928       pragma Assert
3929         (Nkind_In (K, N_Component_Declaration,
3930                       N_Discriminant_Specification,
3931                       N_Function_Specification,
3932                       N_Object_Declaration,
3933                       N_Parameter_Specification));
3934
3935       if K = N_Function_Specification then
3936          Typ := Etype (Defining_Entity (N));
3937       else
3938          Typ := Etype (Defining_Identifier (N));
3939       end if;
3940
3941       case K is
3942          when N_Component_Declaration =>
3943             if Present (Access_Definition (Component_Definition (N))) then
3944                Error_Node := Component_Definition (N);
3945             else
3946                Error_Node := Subtype_Indication (Component_Definition (N));
3947             end if;
3948
3949          when N_Discriminant_Specification =>
3950             Error_Node    := Discriminant_Type (N);
3951
3952          when N_Function_Specification =>
3953             Error_Node    := Result_Definition (N);
3954
3955          when N_Object_Declaration =>
3956             Error_Node    := Object_Definition (N);
3957
3958          when N_Parameter_Specification =>
3959             Error_Node    := Parameter_Type (N);
3960
3961          when others =>
3962             raise Program_Error;
3963       end case;
3964
3965       if Has_Null then
3966
3967          --  Enforce legality rule 3.10 (13): A null exclusion can only be
3968          --  applied to an access [sub]type.
3969
3970          if not Is_Access_Type (Typ) then
3971             Error_Msg_N
3972               ("`NOT NULL` allowed only for an access type", Error_Node);
3973
3974          --  Enforce legality rule RM 3.10(14/1): A null exclusion can only
3975          --  be applied to a [sub]type that does not exclude null already.
3976
3977          elsif Can_Never_Be_Null (Typ)
3978            and then Comes_From_Source (Typ)
3979          then
3980             Error_Msg_NE
3981               ("`NOT NULL` not allowed (& already excludes null)",
3982                Error_Node, Typ);
3983          end if;
3984       end if;
3985
3986       --  Check that null-excluding objects are always initialized, except for
3987       --  deferred constants, for which the expression will appear in the full
3988       --  declaration.
3989
3990       if K = N_Object_Declaration
3991         and then No (Expression (N))
3992         and then not Constant_Present (N)
3993         and then not No_Initialization (N)
3994       then
3995          --  Add an expression that assigns null. This node is needed by
3996          --  Apply_Compile_Time_Constraint_Error, which will replace this with
3997          --  a Constraint_Error node.
3998
3999          Set_Expression (N, Make_Null (Sloc (N)));
4000          Set_Etype (Expression (N), Etype (Defining_Identifier (N)));
4001
4002          Apply_Compile_Time_Constraint_Error
4003            (N      => Expression (N),
4004             Msg    =>
4005               "(Ada 2005) null-excluding objects must be initialized??",
4006             Reason => CE_Null_Not_Allowed);
4007       end if;
4008
4009       --  Check that a null-excluding component, formal or object is not being
4010       --  assigned a null value. Otherwise generate a warning message and
4011       --  replace Expression (N) by an N_Constraint_Error node.
4012
4013       if K /= N_Function_Specification then
4014          Expr := Expression (N);
4015
4016          if Present (Expr) and then Known_Null (Expr) then
4017             case K is
4018                when N_Component_Declaration      |
4019                     N_Discriminant_Specification =>
4020                   Apply_Compile_Time_Constraint_Error
4021                     (N      => Expr,
4022                      Msg    => "(Ada 2005) null not allowed "
4023                                & "in null-excluding components??",
4024                      Reason => CE_Null_Not_Allowed);
4025
4026                when N_Object_Declaration =>
4027                   Apply_Compile_Time_Constraint_Error
4028                     (N      => Expr,
4029                      Msg    => "(Ada 2005) null not allowed "
4030                                & "in null-excluding objects??",
4031                      Reason => CE_Null_Not_Allowed);
4032
4033                when N_Parameter_Specification =>
4034                   Apply_Compile_Time_Constraint_Error
4035                     (N      => Expr,
4036                      Msg    => "(Ada 2005) null not allowed "
4037                                & "in null-excluding formals??",
4038                      Reason => CE_Null_Not_Allowed);
4039
4040                when others =>
4041                   null;
4042             end case;
4043          end if;
4044       end if;
4045    end Null_Exclusion_Static_Checks;
4046
4047    ----------------------------------
4048    -- Conditional_Statements_Begin --
4049    ----------------------------------
4050
4051    procedure Conditional_Statements_Begin is
4052    begin
4053       Saved_Checks_TOS := Saved_Checks_TOS + 1;
4054
4055       --  If stack overflows, kill all checks, that way we know to simply reset
4056       --  the number of saved checks to zero on return. This should never occur
4057       --  in practice.
4058
4059       if Saved_Checks_TOS > Saved_Checks_Stack'Last then
4060          Kill_All_Checks;
4061
4062       --  In the normal case, we just make a new stack entry saving the current
4063       --  number of saved checks for a later restore.
4064
4065       else
4066          Saved_Checks_Stack (Saved_Checks_TOS) := Num_Saved_Checks;
4067
4068          if Debug_Flag_CC then
4069             w ("Conditional_Statements_Begin: Num_Saved_Checks = ",
4070                Num_Saved_Checks);
4071          end if;
4072       end if;
4073    end Conditional_Statements_Begin;
4074
4075    --------------------------------
4076    -- Conditional_Statements_End --
4077    --------------------------------
4078
4079    procedure Conditional_Statements_End is
4080    begin
4081       pragma Assert (Saved_Checks_TOS > 0);
4082
4083       --  If the saved checks stack overflowed, then we killed all checks, so
4084       --  setting the number of saved checks back to zero is correct. This
4085       --  should never occur in practice.
4086
4087       if Saved_Checks_TOS > Saved_Checks_Stack'Last then
4088          Num_Saved_Checks := 0;
4089
4090       --  In the normal case, restore the number of saved checks from the top
4091       --  stack entry.
4092
4093       else
4094          Num_Saved_Checks := Saved_Checks_Stack (Saved_Checks_TOS);
4095
4096          if Debug_Flag_CC then
4097             w ("Conditional_Statements_End: Num_Saved_Checks = ",
4098                Num_Saved_Checks);
4099          end if;
4100       end if;
4101
4102       Saved_Checks_TOS := Saved_Checks_TOS - 1;
4103    end Conditional_Statements_End;
4104
4105    -------------------------
4106    -- Convert_From_Bignum --
4107    -------------------------
4108
4109    function Convert_From_Bignum (N : Node_Id) return Node_Id is
4110       Loc : constant Source_Ptr := Sloc (N);
4111
4112    begin
4113       pragma Assert (Is_RTE (Etype (N), RE_Bignum));
4114
4115       --  Construct call From Bignum
4116
4117       return
4118         Make_Function_Call (Loc,
4119           Name                   =>
4120             New_Occurrence_Of (RTE (RE_From_Bignum), Loc),
4121           Parameter_Associations => New_List (Relocate_Node (N)));
4122    end Convert_From_Bignum;
4123
4124    -----------------------
4125    -- Convert_To_Bignum --
4126    -----------------------
4127
4128    function Convert_To_Bignum (N : Node_Id) return Node_Id is
4129       Loc : constant Source_Ptr := Sloc (N);
4130
4131    begin
4132       --  Nothing to do if Bignum already except call Relocate_Node
4133
4134       if Is_RTE (Etype (N), RE_Bignum) then
4135          return Relocate_Node (N);
4136
4137       --  Otherwise construct call to To_Bignum, converting the operand to the
4138       --  required Long_Long_Integer form.
4139
4140       else
4141          pragma Assert (Is_Signed_Integer_Type (Etype (N)));
4142          return
4143            Make_Function_Call (Loc,
4144              Name                   =>
4145                New_Occurrence_Of (RTE (RE_To_Bignum), Loc),
4146              Parameter_Associations => New_List (
4147                Convert_To (Standard_Long_Long_Integer, Relocate_Node (N))));
4148       end if;
4149    end Convert_To_Bignum;
4150
4151    ---------------------
4152    -- Determine_Range --
4153    ---------------------
4154
4155    Cache_Size : constant := 2 ** 10;
4156    type Cache_Index is range 0 .. Cache_Size - 1;
4157    --  Determine size of below cache (power of 2 is more efficient)
4158
4159    Determine_Range_Cache_N    : array (Cache_Index) of Node_Id;
4160    Determine_Range_Cache_V    : array (Cache_Index) of Boolean;
4161    Determine_Range_Cache_Lo   : array (Cache_Index) of Uint;
4162    Determine_Range_Cache_Hi   : array (Cache_Index) of Uint;
4163    Determine_Range_Cache_Lo_R : array (Cache_Index) of Ureal;
4164    Determine_Range_Cache_Hi_R : array (Cache_Index) of Ureal;
4165    --  The above arrays are used to implement a small direct cache for
4166    --  Determine_Range and Determine_Range_R calls. Because of the way these
4167    --  subprograms recursively traces subexpressions, and because overflow
4168    --  checking calls the routine on the way up the tree, a quadratic behavior
4169    --  can otherwise be encountered in large expressions. The cache entry for
4170    --  node N is stored in the (N mod Cache_Size) entry, and can be validated
4171    --  by checking the actual node value stored there. The Range_Cache_V array
4172    --  records the setting of Assume_Valid for the cache entry.
4173
4174    procedure Determine_Range
4175      (N            : Node_Id;
4176       OK           : out Boolean;
4177       Lo           : out Uint;
4178       Hi           : out Uint;
4179       Assume_Valid : Boolean := False)
4180    is
4181       Typ : Entity_Id := Etype (N);
4182       --  Type to use, may get reset to base type for possibly invalid entity
4183
4184       Lo_Left : Uint;
4185       Hi_Left : Uint;
4186       --  Lo and Hi bounds of left operand
4187
4188       Lo_Right : Uint;
4189       Hi_Right : Uint;
4190       --  Lo and Hi bounds of right (or only) operand
4191
4192       Bound : Node_Id;
4193       --  Temp variable used to hold a bound node
4194
4195       Hbound : Uint;
4196       --  High bound of base type of expression
4197
4198       Lor : Uint;
4199       Hir : Uint;
4200       --  Refined values for low and high bounds, after tightening
4201
4202       OK1 : Boolean;
4203       --  Used in lower level calls to indicate if call succeeded
4204
4205       Cindex : Cache_Index;
4206       --  Used to search cache
4207
4208       Btyp : Entity_Id;
4209       --  Base type
4210
4211       function OK_Operands return Boolean;
4212       --  Used for binary operators. Determines the ranges of the left and
4213       --  right operands, and if they are both OK, returns True, and puts
4214       --  the results in Lo_Right, Hi_Right, Lo_Left, Hi_Left.
4215
4216       -----------------
4217       -- OK_Operands --
4218       -----------------
4219
4220       function OK_Operands return Boolean is
4221       begin
4222          Determine_Range
4223            (Left_Opnd  (N), OK1, Lo_Left,  Hi_Left, Assume_Valid);
4224
4225          if not OK1 then
4226             return False;
4227          end if;
4228
4229          Determine_Range
4230            (Right_Opnd (N), OK1, Lo_Right, Hi_Right, Assume_Valid);
4231          return OK1;
4232       end OK_Operands;
4233
4234    --  Start of processing for Determine_Range
4235
4236    begin
4237       --  Prevent junk warnings by initializing range variables
4238
4239       Lo  := No_Uint;
4240       Hi  := No_Uint;
4241       Lor := No_Uint;
4242       Hir := No_Uint;
4243
4244       --  For temporary constants internally generated to remove side effects
4245       --  we must use the corresponding expression to determine the range of
4246       --  the expression. But note that the expander can also generate
4247       --  constants in other cases, including deferred constants.
4248
4249       if Is_Entity_Name (N)
4250         and then Nkind (Parent (Entity (N))) = N_Object_Declaration
4251         and then Ekind (Entity (N)) = E_Constant
4252         and then Is_Internal_Name (Chars (Entity (N)))
4253       then
4254          if Present (Expression (Parent (Entity (N)))) then
4255             Determine_Range
4256               (Expression (Parent (Entity (N))), OK, Lo, Hi, Assume_Valid);
4257
4258          elsif Present (Full_View (Entity (N))) then
4259             Determine_Range
4260               (Expression (Parent (Full_View (Entity (N)))),
4261                OK, Lo, Hi, Assume_Valid);
4262
4263          else
4264             OK := False;
4265          end if;
4266          return;
4267       end if;
4268
4269       --  If type is not defined, we can't determine its range
4270
4271       if No (Typ)
4272
4273         --  We don't deal with anything except discrete types
4274
4275         or else not Is_Discrete_Type (Typ)
4276
4277         --  Ignore type for which an error has been posted, since range in
4278         --  this case may well be a bogosity deriving from the error. Also
4279         --  ignore if error posted on the reference node.
4280
4281         or else Error_Posted (N) or else Error_Posted (Typ)
4282       then
4283          OK := False;
4284          return;
4285       end if;
4286
4287       --  For all other cases, we can determine the range
4288
4289       OK := True;
4290
4291       --  If value is compile time known, then the possible range is the one
4292       --  value that we know this expression definitely has.
4293
4294       if Compile_Time_Known_Value (N) then
4295          Lo := Expr_Value (N);
4296          Hi := Lo;
4297          return;
4298       end if;
4299
4300       --  Return if already in the cache
4301
4302       Cindex := Cache_Index (N mod Cache_Size);
4303
4304       if Determine_Range_Cache_N (Cindex) = N
4305            and then
4306          Determine_Range_Cache_V (Cindex) = Assume_Valid
4307       then
4308          Lo := Determine_Range_Cache_Lo (Cindex);
4309          Hi := Determine_Range_Cache_Hi (Cindex);
4310          return;
4311       end if;
4312
4313       --  Otherwise, start by finding the bounds of the type of the expression,
4314       --  the value cannot be outside this range (if it is, then we have an
4315       --  overflow situation, which is a separate check, we are talking here
4316       --  only about the expression value).
4317
4318       --  First a check, never try to find the bounds of a generic type, since
4319       --  these bounds are always junk values, and it is only valid to look at
4320       --  the bounds in an instance.
4321
4322       if Is_Generic_Type (Typ) then
4323          OK := False;
4324          return;
4325       end if;
4326
4327       --  First step, change to use base type unless we know the value is valid
4328
4329       if (Is_Entity_Name (N) and then Is_Known_Valid (Entity (N)))
4330         or else Assume_No_Invalid_Values
4331         or else Assume_Valid
4332       then
4333          null;
4334       else
4335          Typ := Underlying_Type (Base_Type (Typ));
4336       end if;
4337
4338       --  Retrieve the base type. Handle the case where the base type is a
4339       --  private enumeration type.
4340
4341       Btyp := Base_Type (Typ);
4342
4343       if Is_Private_Type (Btyp) and then Present (Full_View (Btyp)) then
4344          Btyp := Full_View (Btyp);
4345       end if;
4346
4347       --  We use the actual bound unless it is dynamic, in which case use the
4348       --  corresponding base type bound if possible. If we can't get a bound
4349       --  then we figure we can't determine the range (a peculiar case, that
4350       --  perhaps cannot happen, but there is no point in bombing in this
4351       --  optimization circuit.
4352
4353       --  First the low bound
4354
4355       Bound := Type_Low_Bound (Typ);
4356
4357       if Compile_Time_Known_Value (Bound) then
4358          Lo := Expr_Value (Bound);
4359
4360       elsif Compile_Time_Known_Value (Type_Low_Bound (Btyp)) then
4361          Lo := Expr_Value (Type_Low_Bound (Btyp));
4362
4363       else
4364          OK := False;
4365          return;
4366       end if;
4367
4368       --  Now the high bound
4369
4370       Bound := Type_High_Bound (Typ);
4371
4372       --  We need the high bound of the base type later on, and this should
4373       --  always be compile time known. Again, it is not clear that this
4374       --  can ever be false, but no point in bombing.
4375
4376       if Compile_Time_Known_Value (Type_High_Bound (Btyp)) then
4377          Hbound := Expr_Value (Type_High_Bound (Btyp));
4378          Hi := Hbound;
4379
4380       else
4381          OK := False;
4382          return;
4383       end if;
4384
4385       --  If we have a static subtype, then that may have a tighter bound so
4386       --  use the upper bound of the subtype instead in this case.
4387
4388       if Compile_Time_Known_Value (Bound) then
4389          Hi := Expr_Value (Bound);
4390       end if;
4391
4392       --  We may be able to refine this value in certain situations. If any
4393       --  refinement is possible, then Lor and Hir are set to possibly tighter
4394       --  bounds, and OK1 is set to True.
4395
4396       case Nkind (N) is
4397
4398          --  For unary plus, result is limited by range of operand
4399
4400          when N_Op_Plus =>
4401             Determine_Range
4402               (Right_Opnd (N), OK1, Lor, Hir, Assume_Valid);
4403
4404          --  For unary minus, determine range of operand, and negate it
4405
4406          when N_Op_Minus =>
4407             Determine_Range
4408               (Right_Opnd (N), OK1, Lo_Right, Hi_Right, Assume_Valid);
4409
4410             if OK1 then
4411                Lor := -Hi_Right;
4412                Hir := -Lo_Right;
4413             end if;
4414
4415          --  For binary addition, get range of each operand and do the
4416          --  addition to get the result range.
4417
4418          when N_Op_Add =>
4419             if OK_Operands then
4420                Lor := Lo_Left + Lo_Right;
4421                Hir := Hi_Left + Hi_Right;
4422             end if;
4423
4424          --  Division is tricky. The only case we consider is where the right
4425          --  operand is a positive constant, and in this case we simply divide
4426          --  the bounds of the left operand
4427
4428          when N_Op_Divide =>
4429             if OK_Operands then
4430                if Lo_Right = Hi_Right
4431                  and then Lo_Right > 0
4432                then
4433                   Lor := Lo_Left / Lo_Right;
4434                   Hir := Hi_Left / Lo_Right;
4435                else
4436                   OK1 := False;
4437                end if;
4438             end if;
4439
4440          --  For binary subtraction, get range of each operand and do the worst
4441          --  case subtraction to get the result range.
4442
4443          when N_Op_Subtract =>
4444             if OK_Operands then
4445                Lor := Lo_Left - Hi_Right;
4446                Hir := Hi_Left - Lo_Right;
4447             end if;
4448
4449          --  For MOD, if right operand is a positive constant, then result must
4450          --  be in the allowable range of mod results.
4451
4452          when N_Op_Mod =>
4453             if OK_Operands then
4454                if Lo_Right = Hi_Right
4455                  and then Lo_Right /= 0
4456                then
4457                   if Lo_Right > 0 then
4458                      Lor := Uint_0;
4459                      Hir := Lo_Right - 1;
4460
4461                   else -- Lo_Right < 0
4462                      Lor := Lo_Right + 1;
4463                      Hir := Uint_0;
4464                   end if;
4465
4466                else
4467                   OK1 := False;
4468                end if;
4469             end if;
4470
4471          --  For REM, if right operand is a positive constant, then result must
4472          --  be in the allowable range of mod results.
4473
4474          when N_Op_Rem =>
4475             if OK_Operands then
4476                if Lo_Right = Hi_Right
4477                  and then Lo_Right /= 0
4478                then
4479                   declare
4480                      Dval : constant Uint := (abs Lo_Right) - 1;
4481
4482                   begin
4483                      --  The sign of the result depends on the sign of the
4484                      --  dividend (but not on the sign of the divisor, hence
4485                      --  the abs operation above).
4486
4487                      if Lo_Left < 0 then
4488                         Lor := -Dval;
4489                      else
4490                         Lor := Uint_0;
4491                      end if;
4492
4493                      if Hi_Left < 0 then
4494                         Hir := Uint_0;
4495                      else
4496                         Hir := Dval;
4497                      end if;
4498                   end;
4499
4500                else
4501                   OK1 := False;
4502                end if;
4503             end if;
4504
4505          --  Attribute reference cases
4506
4507          when N_Attribute_Reference =>
4508             case Attribute_Name (N) is
4509
4510                --  For Pos/Val attributes, we can refine the range using the
4511                --  possible range of values of the attribute expression.
4512
4513                when Name_Pos | Name_Val =>
4514                   Determine_Range
4515                     (First (Expressions (N)), OK1, Lor, Hir, Assume_Valid);
4516
4517                --  For Length attribute, use the bounds of the corresponding
4518                --  index type to refine the range.
4519
4520                when Name_Length =>
4521                   declare
4522                      Atyp : Entity_Id := Etype (Prefix (N));
4523                      Inum : Nat;
4524                      Indx : Node_Id;
4525
4526                      LL, LU : Uint;
4527                      UL, UU : Uint;
4528
4529                   begin
4530                      if Is_Access_Type (Atyp) then
4531                         Atyp := Designated_Type (Atyp);
4532                      end if;
4533
4534                      --  For string literal, we know exact value
4535
4536                      if Ekind (Atyp) = E_String_Literal_Subtype then
4537                         OK := True;
4538                         Lo := String_Literal_Length (Atyp);
4539                         Hi := String_Literal_Length (Atyp);
4540                         return;
4541                      end if;
4542
4543                      --  Otherwise check for expression given
4544
4545                      if No (Expressions (N)) then
4546                         Inum := 1;
4547                      else
4548                         Inum :=
4549                           UI_To_Int (Expr_Value (First (Expressions (N))));
4550                      end if;
4551
4552                      Indx := First_Index (Atyp);
4553                      for J in 2 .. Inum loop
4554                         Indx := Next_Index (Indx);
4555                      end loop;
4556
4557                      --  If the index type is a formal type or derived from
4558                      --  one, the bounds are not static.
4559
4560                      if Is_Generic_Type (Root_Type (Etype (Indx))) then
4561                         OK := False;
4562                         return;
4563                      end if;
4564
4565                      Determine_Range
4566                        (Type_Low_Bound (Etype (Indx)), OK1, LL, LU,
4567                         Assume_Valid);
4568
4569                      if OK1 then
4570                         Determine_Range
4571                           (Type_High_Bound (Etype (Indx)), OK1, UL, UU,
4572                            Assume_Valid);
4573
4574                         if OK1 then
4575
4576                            --  The maximum value for Length is the biggest
4577                            --  possible gap between the values of the bounds.
4578                            --  But of course, this value cannot be negative.
4579
4580                            Hir := UI_Max (Uint_0, UU - LL + 1);
4581
4582                            --  For constrained arrays, the minimum value for
4583                            --  Length is taken from the actual value of the
4584                            --  bounds, since the index will be exactly of this
4585                            --  subtype.
4586
4587                            if Is_Constrained (Atyp) then
4588                               Lor := UI_Max (Uint_0, UL - LU + 1);
4589
4590                            --  For an unconstrained array, the minimum value
4591                            --  for length is always zero.
4592
4593                            else
4594                               Lor := Uint_0;
4595                            end if;
4596                         end if;
4597                      end if;
4598                   end;
4599
4600                --  No special handling for other attributes
4601                --  Probably more opportunities exist here???
4602
4603                when others =>
4604                   OK1 := False;
4605
4606             end case;
4607
4608          --  For type conversion from one discrete type to another, we can
4609          --  refine the range using the converted value.
4610
4611          when N_Type_Conversion =>
4612             Determine_Range (Expression (N), OK1, Lor, Hir, Assume_Valid);
4613
4614          --  Nothing special to do for all other expression kinds
4615
4616          when others =>
4617             OK1 := False;
4618             Lor := No_Uint;
4619             Hir := No_Uint;
4620       end case;
4621
4622       --  At this stage, if OK1 is true, then we know that the actual result of
4623       --  the computed expression is in the range Lor .. Hir. We can use this
4624       --  to restrict the possible range of results.
4625
4626       if OK1 then
4627
4628          --  If the refined value of the low bound is greater than the type
4629          --  low bound, then reset it to the more restrictive value. However,
4630          --  we do NOT do this for the case of a modular type where the
4631          --  possible upper bound on the value is above the base type high
4632          --  bound, because that means the result could wrap.
4633
4634          if Lor > Lo
4635            and then not (Is_Modular_Integer_Type (Typ) and then Hir > Hbound)
4636          then
4637             Lo := Lor;
4638          end if;
4639
4640          --  Similarly, if the refined value of the high bound is less than the
4641          --  value so far, then reset it to the more restrictive value. Again,
4642          --  we do not do this if the refined low bound is negative for a
4643          --  modular type, since this would wrap.
4644
4645          if Hir < Hi
4646            and then not (Is_Modular_Integer_Type (Typ) and then Lor < Uint_0)
4647          then
4648             Hi := Hir;
4649          end if;
4650       end if;
4651
4652       --  Set cache entry for future call and we are all done
4653
4654       Determine_Range_Cache_N  (Cindex) := N;
4655       Determine_Range_Cache_V  (Cindex) := Assume_Valid;
4656       Determine_Range_Cache_Lo (Cindex) := Lo;
4657       Determine_Range_Cache_Hi (Cindex) := Hi;
4658       return;
4659
4660    --  If any exception occurs, it means that we have some bug in the compiler,
4661    --  possibly triggered by a previous error, or by some unforeseen peculiar
4662    --  occurrence. However, this is only an optimization attempt, so there is
4663    --  really no point in crashing the compiler. Instead we just decide, too
4664    --  bad, we can't figure out a range in this case after all.
4665
4666    exception
4667       when others =>
4668
4669          --  Debug flag K disables this behavior (useful for debugging)
4670
4671          if Debug_Flag_K then
4672             raise;
4673          else
4674             OK := False;
4675             Lo := No_Uint;
4676             Hi := No_Uint;
4677             return;
4678          end if;
4679    end Determine_Range;
4680
4681    -----------------------
4682    -- Determine_Range_R --
4683    -----------------------
4684
4685    procedure Determine_Range_R
4686      (N            : Node_Id;
4687       OK           : out Boolean;
4688       Lo           : out Ureal;
4689       Hi           : out Ureal;
4690       Assume_Valid : Boolean := False)
4691    is
4692       Typ : Entity_Id := Etype (N);
4693       --  Type to use, may get reset to base type for possibly invalid entity
4694
4695       Lo_Left : Ureal;
4696       Hi_Left : Ureal;
4697       --  Lo and Hi bounds of left operand
4698
4699       Lo_Right : Ureal;
4700       Hi_Right : Ureal;
4701       --  Lo and Hi bounds of right (or only) operand
4702
4703       Bound : Node_Id;
4704       --  Temp variable used to hold a bound node
4705
4706       Hbound : Ureal;
4707       --  High bound of base type of expression
4708
4709       Lor : Ureal;
4710       Hir : Ureal;
4711       --  Refined values for low and high bounds, after tightening
4712
4713       OK1 : Boolean;
4714       --  Used in lower level calls to indicate if call succeeded
4715
4716       Cindex : Cache_Index;
4717       --  Used to search cache
4718
4719       Btyp : Entity_Id;
4720       --  Base type
4721
4722       function OK_Operands return Boolean;
4723       --  Used for binary operators. Determines the ranges of the left and
4724       --  right operands, and if they are both OK, returns True, and puts
4725       --  the results in Lo_Right, Hi_Right, Lo_Left, Hi_Left.
4726
4727       function Round_Machine (B : Ureal) return Ureal;
4728       --  B is a real bound. Round it using mode Round_Even.
4729
4730       -----------------
4731       -- OK_Operands --
4732       -----------------
4733
4734       function OK_Operands return Boolean is
4735       begin
4736          Determine_Range_R
4737            (Left_Opnd  (N), OK1, Lo_Left,  Hi_Left, Assume_Valid);
4738
4739          if not OK1 then
4740             return False;
4741          end if;
4742
4743          Determine_Range_R
4744            (Right_Opnd (N), OK1, Lo_Right, Hi_Right, Assume_Valid);
4745          return OK1;
4746       end OK_Operands;
4747
4748       -------------------
4749       -- Round_Machine --
4750       -------------------
4751
4752       function Round_Machine (B : Ureal) return Ureal is
4753       begin
4754          return Machine (Typ, B, Round_Even, N);
4755       end Round_Machine;
4756
4757    --  Start of processing for Determine_Range_R
4758
4759    begin
4760       --  Prevent junk warnings by initializing range variables
4761
4762       Lo  := No_Ureal;
4763       Hi  := No_Ureal;
4764       Lor := No_Ureal;
4765       Hir := No_Ureal;
4766
4767       --  For temporary constants internally generated to remove side effects
4768       --  we must use the corresponding expression to determine the range of
4769       --  the expression. But note that the expander can also generate
4770       --  constants in other cases, including deferred constants.
4771
4772       if Is_Entity_Name (N)
4773         and then Nkind (Parent (Entity (N))) = N_Object_Declaration
4774         and then Ekind (Entity (N)) = E_Constant
4775         and then Is_Internal_Name (Chars (Entity (N)))
4776       then
4777          if Present (Expression (Parent (Entity (N)))) then
4778             Determine_Range_R
4779               (Expression (Parent (Entity (N))), OK, Lo, Hi, Assume_Valid);
4780
4781          elsif Present (Full_View (Entity (N))) then
4782             Determine_Range_R
4783               (Expression (Parent (Full_View (Entity (N)))),
4784                OK, Lo, Hi, Assume_Valid);
4785
4786          else
4787             OK := False;
4788          end if;
4789
4790          return;
4791       end if;
4792
4793       --  If type is not defined, we can't determine its range
4794
4795       if No (Typ)
4796
4797         --  We don't deal with anything except IEEE floating-point types
4798
4799         or else not Is_Floating_Point_Type (Typ)
4800         or else Float_Rep (Typ) /= IEEE_Binary
4801
4802         --  Ignore type for which an error has been posted, since range in
4803         --  this case may well be a bogosity deriving from the error. Also
4804         --  ignore if error posted on the reference node.
4805
4806         or else Error_Posted (N) or else Error_Posted (Typ)
4807       then
4808          OK := False;
4809          return;
4810       end if;
4811
4812       --  For all other cases, we can determine the range
4813
4814       OK := True;
4815
4816       --  If value is compile time known, then the possible range is the one
4817       --  value that we know this expression definitely has.
4818
4819       if Compile_Time_Known_Value (N) then
4820          Lo := Expr_Value_R (N);
4821          Hi := Lo;
4822          return;
4823       end if;
4824
4825       --  Return if already in the cache
4826
4827       Cindex := Cache_Index (N mod Cache_Size);
4828
4829       if Determine_Range_Cache_N (Cindex) = N
4830            and then
4831          Determine_Range_Cache_V (Cindex) = Assume_Valid
4832       then
4833          Lo := Determine_Range_Cache_Lo_R (Cindex);
4834          Hi := Determine_Range_Cache_Hi_R (Cindex);
4835          return;
4836       end if;
4837
4838       --  Otherwise, start by finding the bounds of the type of the expression,
4839       --  the value cannot be outside this range (if it is, then we have an
4840       --  overflow situation, which is a separate check, we are talking here
4841       --  only about the expression value).
4842
4843       --  First a check, never try to find the bounds of a generic type, since
4844       --  these bounds are always junk values, and it is only valid to look at
4845       --  the bounds in an instance.
4846
4847       if Is_Generic_Type (Typ) then
4848          OK := False;
4849          return;
4850       end if;
4851
4852       --  First step, change to use base type unless we know the value is valid
4853
4854       if (Is_Entity_Name (N) and then Is_Known_Valid (Entity (N)))
4855         or else Assume_No_Invalid_Values
4856         or else Assume_Valid
4857       then
4858          null;
4859       else
4860          Typ := Underlying_Type (Base_Type (Typ));
4861       end if;
4862
4863       --  Retrieve the base type. Handle the case where the base type is a
4864       --  private type.
4865
4866       Btyp := Base_Type (Typ);
4867
4868       if Is_Private_Type (Btyp) and then Present (Full_View (Btyp)) then
4869          Btyp := Full_View (Btyp);
4870       end if;
4871
4872       --  We use the actual bound unless it is dynamic, in which case use the
4873       --  corresponding base type bound if possible. If we can't get a bound
4874       --  then we figure we can't determine the range (a peculiar case, that
4875       --  perhaps cannot happen, but there is no point in bombing in this
4876       --  optimization circuit).
4877
4878       --  First the low bound
4879
4880       Bound := Type_Low_Bound (Typ);
4881
4882       if Compile_Time_Known_Value (Bound) then
4883          Lo := Expr_Value_R (Bound);
4884
4885       elsif Compile_Time_Known_Value (Type_Low_Bound (Btyp)) then
4886          Lo := Expr_Value_R (Type_Low_Bound (Btyp));
4887
4888       else
4889          OK := False;
4890          return;
4891       end if;
4892
4893       --  Now the high bound
4894
4895       Bound := Type_High_Bound (Typ);
4896
4897       --  We need the high bound of the base type later on, and this should
4898       --  always be compile time known. Again, it is not clear that this
4899       --  can ever be false, but no point in bombing.
4900
4901       if Compile_Time_Known_Value (Type_High_Bound (Btyp)) then
4902          Hbound := Expr_Value_R (Type_High_Bound (Btyp));
4903          Hi := Hbound;
4904
4905       else
4906          OK := False;
4907          return;
4908       end if;
4909
4910       --  If we have a static subtype, then that may have a tighter bound so
4911       --  use the upper bound of the subtype instead in this case.
4912
4913       if Compile_Time_Known_Value (Bound) then
4914          Hi := Expr_Value_R (Bound);
4915       end if;
4916
4917       --  We may be able to refine this value in certain situations. If any
4918       --  refinement is possible, then Lor and Hir are set to possibly tighter
4919       --  bounds, and OK1 is set to True.
4920
4921       case Nkind (N) is
4922
4923          --  For unary plus, result is limited by range of operand
4924
4925          when N_Op_Plus =>
4926             Determine_Range_R
4927               (Right_Opnd (N), OK1, Lor, Hir, Assume_Valid);
4928
4929          --  For unary minus, determine range of operand, and negate it
4930
4931          when N_Op_Minus =>
4932             Determine_Range_R
4933               (Right_Opnd (N), OK1, Lo_Right, Hi_Right, Assume_Valid);
4934
4935             if OK1 then
4936                Lor := -Hi_Right;
4937                Hir := -Lo_Right;
4938             end if;
4939
4940          --  For binary addition, get range of each operand and do the
4941          --  addition to get the result range.
4942
4943          when N_Op_Add =>
4944             if OK_Operands then
4945                Lor := Round_Machine (Lo_Left + Lo_Right);
4946                Hir := Round_Machine (Hi_Left + Hi_Right);
4947             end if;
4948
4949          --  For binary subtraction, get range of each operand and do the worst
4950          --  case subtraction to get the result range.
4951
4952          when N_Op_Subtract =>
4953             if OK_Operands then
4954                Lor := Round_Machine (Lo_Left - Hi_Right);
4955                Hir := Round_Machine (Hi_Left - Lo_Right);
4956             end if;
4957
4958          --  For multiplication, get range of each operand and do the
4959          --  four multiplications to get the result range.
4960
4961          when N_Op_Multiply =>
4962             if OK_Operands then
4963                declare
4964                   M1 : constant Ureal := Round_Machine (Lo_Left * Lo_Right);
4965                   M2 : constant Ureal := Round_Machine (Lo_Left * Hi_Right);
4966                   M3 : constant Ureal := Round_Machine (Hi_Left * Lo_Right);
4967                   M4 : constant Ureal := Round_Machine (Hi_Left * Hi_Right);
4968                begin
4969                   Lor := UR_Min (UR_Min (M1, M2), UR_Min (M3, M4));
4970                   Hir := UR_Max (UR_Max (M1, M2), UR_Max (M3, M4));
4971                end;
4972             end if;
4973
4974          --  For division, consider separately the cases where the right
4975          --  operand is positive or negative. Otherwise, the right operand
4976          --  can be arbitrarily close to zero, so the result is likely to
4977          --  be unbounded in one direction, do not attempt to compute it.
4978
4979          when N_Op_Divide =>
4980             if OK_Operands then
4981
4982                --  Right operand is positive
4983
4984                if Lo_Right > Ureal_0 then
4985
4986                   --  If the low bound of the left operand is negative, obtain
4987                   --  the overall low bound by dividing it by the smallest
4988                   --  value of the right operand, and otherwise by the largest
4989                   --  value of the right operand.
4990
4991                   if Lo_Left < Ureal_0 then
4992                      Lor := Round_Machine (Lo_Left / Lo_Right);
4993                   else
4994                      Lor := Round_Machine (Lo_Left / Hi_Right);
4995                   end if;
4996
4997                   --  If the high bound of the left operand is negative, obtain
4998                   --  the overall high bound by dividing it by the largest
4999                   --  value of the right operand, and otherwise by the
5000                   --  smallest value of the right operand.
5001
5002                   if Hi_Left < Ureal_0 then
5003                      Hir := Round_Machine (Hi_Left / Hi_Right);
5004                   else
5005                      Hir := Round_Machine (Hi_Left / Lo_Right);
5006                   end if;
5007
5008                --  Right operand is negative
5009
5010                elsif Hi_Right < Ureal_0 then
5011
5012                   --  If the low bound of the left operand is negative, obtain
5013                   --  the overall low bound by dividing it by the largest
5014                   --  value of the right operand, and otherwise by the smallest
5015                   --  value of the right operand.
5016
5017                   if Lo_Left < Ureal_0 then
5018                      Lor := Round_Machine (Lo_Left / Hi_Right);
5019                   else
5020                      Lor := Round_Machine (Lo_Left / Lo_Right);
5021                   end if;
5022
5023                   --  If the high bound of the left operand is negative, obtain
5024                   --  the overall high bound by dividing it by the smallest
5025                   --  value of the right operand, and otherwise by the
5026                   --  largest value of the right operand.
5027
5028                   if Hi_Left < Ureal_0 then
5029                      Hir := Round_Machine (Hi_Left / Lo_Right);
5030                   else
5031                      Hir := Round_Machine (Hi_Left / Hi_Right);
5032                   end if;
5033
5034                else
5035                   OK1 := False;
5036                end if;
5037             end if;
5038
5039          --  For type conversion from one floating-point type to another, we
5040          --  can refine the range using the converted value.
5041
5042          when N_Type_Conversion =>
5043             Determine_Range_R (Expression (N), OK1, Lor, Hir, Assume_Valid);
5044
5045          --  Nothing special to do for all other expression kinds
5046
5047          when others =>
5048             OK1 := False;
5049             Lor := No_Ureal;
5050             Hir := No_Ureal;
5051       end case;
5052
5053       --  At this stage, if OK1 is true, then we know that the actual result of
5054       --  the computed expression is in the range Lor .. Hir. We can use this
5055       --  to restrict the possible range of results.
5056
5057       if OK1 then
5058
5059          --  If the refined value of the low bound is greater than the type
5060          --  low bound, then reset it to the more restrictive value.
5061
5062          if Lor > Lo then
5063             Lo := Lor;
5064          end if;
5065
5066          --  Similarly, if the refined value of the high bound is less than the
5067          --  value so far, then reset it to the more restrictive value.
5068
5069          if Hir < Hi then
5070             Hi := Hir;
5071          end if;
5072       end if;
5073
5074       --  Set cache entry for future call and we are all done
5075
5076       Determine_Range_Cache_N    (Cindex) := N;
5077       Determine_Range_Cache_V    (Cindex) := Assume_Valid;
5078       Determine_Range_Cache_Lo_R (Cindex) := Lo;
5079       Determine_Range_Cache_Hi_R (Cindex) := Hi;
5080       return;
5081
5082    --  If any exception occurs, it means that we have some bug in the compiler,
5083    --  possibly triggered by a previous error, or by some unforeseen peculiar
5084    --  occurrence. However, this is only an optimization attempt, so there is
5085    --  really no point in crashing the compiler. Instead we just decide, too
5086    --  bad, we can't figure out a range in this case after all.
5087
5088    exception
5089       when others =>
5090
5091          --  Debug flag K disables this behavior (useful for debugging)
5092
5093          if Debug_Flag_K then
5094             raise;
5095          else
5096             OK := False;
5097             Lo := No_Ureal;
5098             Hi := No_Ureal;
5099             return;
5100          end if;
5101    end Determine_Range_R;
5102
5103    ------------------------------------
5104    -- Discriminant_Checks_Suppressed --
5105    ------------------------------------
5106
5107    function Discriminant_Checks_Suppressed (E : Entity_Id) return Boolean is
5108    begin
5109       if Present (E) then
5110          if Is_Unchecked_Union (E) then
5111             return True;
5112          elsif Checks_May_Be_Suppressed (E) then
5113             return Is_Check_Suppressed (E, Discriminant_Check);
5114          end if;
5115       end if;
5116
5117       return Scope_Suppress.Suppress (Discriminant_Check);
5118    end Discriminant_Checks_Suppressed;
5119
5120    --------------------------------
5121    -- Division_Checks_Suppressed --
5122    --------------------------------
5123
5124    function Division_Checks_Suppressed (E : Entity_Id) return Boolean is
5125    begin
5126       if Present (E) and then Checks_May_Be_Suppressed (E) then
5127          return Is_Check_Suppressed (E, Division_Check);
5128       else
5129          return Scope_Suppress.Suppress (Division_Check);
5130       end if;
5131    end Division_Checks_Suppressed;
5132
5133    --------------------------------------
5134    -- Duplicated_Tag_Checks_Suppressed --
5135    --------------------------------------
5136
5137    function Duplicated_Tag_Checks_Suppressed (E : Entity_Id) return Boolean is
5138    begin
5139       if Present (E) and then Checks_May_Be_Suppressed (E) then
5140          return Is_Check_Suppressed (E, Duplicated_Tag_Check);
5141       else
5142          return Scope_Suppress.Suppress (Duplicated_Tag_Check);
5143       end if;
5144    end Duplicated_Tag_Checks_Suppressed;
5145
5146    -----------------------------------
5147    -- Elaboration_Checks_Suppressed --
5148    -----------------------------------
5149
5150    function Elaboration_Checks_Suppressed (E : Entity_Id) return Boolean is
5151    begin
5152       --  The complication in this routine is that if we are in the dynamic
5153       --  model of elaboration, we also check All_Checks, since All_Checks
5154       --  does not set Elaboration_Check explicitly.
5155
5156       if Present (E) then
5157          if Kill_Elaboration_Checks (E) then
5158             return True;
5159
5160          elsif Checks_May_Be_Suppressed (E) then
5161             if Is_Check_Suppressed (E, Elaboration_Check) then
5162                return True;
5163             elsif Dynamic_Elaboration_Checks then
5164                return Is_Check_Suppressed (E, All_Checks);
5165             else
5166                return False;
5167             end if;
5168          end if;
5169       end if;
5170
5171       if Scope_Suppress.Suppress (Elaboration_Check) then
5172          return True;
5173       elsif Dynamic_Elaboration_Checks then
5174          return Scope_Suppress.Suppress (All_Checks);
5175       else
5176          return False;
5177       end if;
5178    end Elaboration_Checks_Suppressed;
5179
5180    ---------------------------
5181    -- Enable_Overflow_Check --
5182    ---------------------------
5183
5184    procedure Enable_Overflow_Check (N : Node_Id) is
5185       Typ  : constant Entity_Id          := Base_Type (Etype (N));
5186       Mode : constant Overflow_Mode_Type := Overflow_Check_Mode;
5187       Chk  : Nat;
5188       OK   : Boolean;
5189       Ent  : Entity_Id;
5190       Ofs  : Uint;
5191       Lo   : Uint;
5192       Hi   : Uint;
5193
5194       Do_Ovflow_Check : Boolean;
5195
5196    begin
5197       if Debug_Flag_CC then
5198          w ("Enable_Overflow_Check for node ", Int (N));
5199          Write_Str ("  Source location = ");
5200          wl (Sloc (N));
5201          pg (Union_Id (N));
5202       end if;
5203
5204       --  No check if overflow checks suppressed for type of node
5205
5206       if Overflow_Checks_Suppressed (Etype (N)) then
5207          return;
5208
5209       --  Nothing to do for unsigned integer types, which do not overflow
5210
5211       elsif Is_Modular_Integer_Type (Typ) then
5212          return;
5213       end if;
5214
5215       --  This is the point at which processing for STRICT mode diverges
5216       --  from processing for MINIMIZED/ELIMINATED modes. This divergence is
5217       --  probably more extreme that it needs to be, but what is going on here
5218       --  is that when we introduced MINIMIZED/ELIMINATED modes, we wanted
5219       --  to leave the processing for STRICT mode untouched. There were
5220       --  two reasons for this. First it avoided any incompatible change of
5221       --  behavior. Second, it guaranteed that STRICT mode continued to be
5222       --  legacy reliable.
5223
5224       --  The big difference is that in STRICT mode there is a fair amount of
5225       --  circuitry to try to avoid setting the Do_Overflow_Check flag if we
5226       --  know that no check is needed. We skip all that in the two new modes,
5227       --  since really overflow checking happens over a whole subtree, and we
5228       --  do the corresponding optimizations later on when applying the checks.
5229
5230       if Mode in Minimized_Or_Eliminated then
5231          if not (Overflow_Checks_Suppressed (Etype (N)))
5232            and then not (Is_Entity_Name (N)
5233                           and then Overflow_Checks_Suppressed (Entity (N)))
5234          then
5235             Activate_Overflow_Check (N);
5236          end if;
5237
5238          if Debug_Flag_CC then
5239             w ("Minimized/Eliminated mode");
5240          end if;
5241
5242          return;
5243       end if;
5244
5245       --  Remainder of processing is for STRICT case, and is unchanged from
5246       --  earlier versions preceding the addition of MINIMIZED/ELIMINATED.
5247
5248       --  Nothing to do if the range of the result is known OK. We skip this
5249       --  for conversions, since the caller already did the check, and in any
5250       --  case the condition for deleting the check for a type conversion is
5251       --  different.
5252
5253       if Nkind (N) /= N_Type_Conversion then
5254          Determine_Range (N, OK, Lo, Hi, Assume_Valid => True);
5255
5256          --  Note in the test below that we assume that the range is not OK
5257          --  if a bound of the range is equal to that of the type. That's not
5258          --  quite accurate but we do this for the following reasons:
5259
5260          --   a) The way that Determine_Range works, it will typically report
5261          --      the bounds of the value as being equal to the bounds of the
5262          --      type, because it either can't tell anything more precise, or
5263          --      does not think it is worth the effort to be more precise.
5264
5265          --   b) It is very unusual to have a situation in which this would
5266          --      generate an unnecessary overflow check (an example would be
5267          --      a subtype with a range 0 .. Integer'Last - 1 to which the
5268          --      literal value one is added).
5269
5270          --   c) The alternative is a lot of special casing in this routine
5271          --      which would partially duplicate Determine_Range processing.
5272
5273          if OK then
5274             Do_Ovflow_Check := True;
5275
5276             --  Note that the following checks are quite deliberately > and <
5277             --  rather than >= and <= as explained above.
5278
5279             if  Lo > Expr_Value (Type_Low_Bound  (Typ))
5280                   and then
5281                 Hi < Expr_Value (Type_High_Bound (Typ))
5282             then
5283                Do_Ovflow_Check := False;
5284
5285             --  Despite the comments above, it is worth dealing specially with
5286             --  division specially. The only case where integer division can
5287             --  overflow is (largest negative number) / (-1). So we will do
5288             --  an extra range analysis to see if this is possible.
5289
5290             elsif Nkind (N) = N_Op_Divide then
5291                Determine_Range
5292                  (Left_Opnd (N), OK, Lo, Hi, Assume_Valid => True);
5293
5294                if OK and then Lo > Expr_Value (Type_Low_Bound (Typ)) then
5295                   Do_Ovflow_Check := False;
5296
5297                else
5298                   Determine_Range
5299                     (Right_Opnd (N), OK, Lo, Hi, Assume_Valid => True);
5300
5301                   if OK and then (Lo > Uint_Minus_1
5302                                     or else
5303                                   Hi < Uint_Minus_1)
5304                   then
5305                      Do_Ovflow_Check := False;
5306                   end if;
5307                end if;
5308             end if;
5309
5310             --  If no overflow check required, we are done
5311
5312             if not Do_Ovflow_Check then
5313                if Debug_Flag_CC then
5314                   w ("No overflow check required");
5315                end if;
5316
5317                return;
5318             end if;
5319          end if;
5320       end if;
5321
5322       --  If not in optimizing mode, set flag and we are done. We are also done
5323       --  (and just set the flag) if the type is not a discrete type, since it
5324       --  is not worth the effort to eliminate checks for other than discrete
5325       --  types. In addition, we take this same path if we have stored the
5326       --  maximum number of checks possible already (a very unlikely situation,
5327       --  but we do not want to blow up).
5328
5329       if Optimization_Level = 0
5330         or else not Is_Discrete_Type (Etype (N))
5331         or else Num_Saved_Checks = Saved_Checks'Last
5332       then
5333          Activate_Overflow_Check (N);
5334
5335          if Debug_Flag_CC then
5336             w ("Optimization off");
5337          end if;
5338
5339          return;
5340       end if;
5341
5342       --  Otherwise evaluate and check the expression
5343
5344       Find_Check
5345         (Expr        => N,
5346          Check_Type  => 'O',
5347          Target_Type => Empty,
5348          Entry_OK    => OK,
5349          Check_Num   => Chk,
5350          Ent         => Ent,
5351          Ofs         => Ofs);
5352
5353       if Debug_Flag_CC then
5354          w ("Called Find_Check");
5355          w ("  OK = ", OK);
5356
5357          if OK then
5358             w ("  Check_Num = ", Chk);
5359             w ("  Ent       = ", Int (Ent));
5360             Write_Str ("  Ofs       = ");
5361             pid (Ofs);
5362          end if;
5363       end if;
5364
5365       --  If check is not of form to optimize, then set flag and we are done
5366
5367       if not OK then
5368          Activate_Overflow_Check (N);
5369          return;
5370       end if;
5371
5372       --  If check is already performed, then return without setting flag
5373
5374       if Chk /= 0 then
5375          if Debug_Flag_CC then
5376             w ("Check suppressed!");
5377          end if;
5378
5379          return;
5380       end if;
5381
5382       --  Here we will make a new entry for the new check
5383
5384       Activate_Overflow_Check (N);
5385       Num_Saved_Checks := Num_Saved_Checks + 1;
5386       Saved_Checks (Num_Saved_Checks) :=
5387         (Killed      => False,
5388          Entity      => Ent,
5389          Offset      => Ofs,
5390          Check_Type  => 'O',
5391          Target_Type => Empty);
5392
5393       if Debug_Flag_CC then
5394          w ("Make new entry, check number = ", Num_Saved_Checks);
5395          w ("  Entity = ", Int (Ent));
5396          Write_Str ("  Offset = ");
5397          pid (Ofs);
5398          w ("  Check_Type = O");
5399          w ("  Target_Type = Empty");
5400       end if;
5401
5402    --  If we get an exception, then something went wrong, probably because of
5403    --  an error in the structure of the tree due to an incorrect program. Or
5404    --  it may be a bug in the optimization circuit. In either case the safest
5405    --  thing is simply to set the check flag unconditionally.
5406
5407    exception
5408       when others =>
5409          Activate_Overflow_Check (N);
5410
5411          if Debug_Flag_CC then
5412             w ("  exception occurred, overflow flag set");
5413          end if;
5414
5415          return;
5416    end Enable_Overflow_Check;
5417
5418    ------------------------
5419    -- Enable_Range_Check --
5420    ------------------------
5421
5422    procedure Enable_Range_Check (N : Node_Id) is
5423       Chk  : Nat;
5424       OK   : Boolean;
5425       Ent  : Entity_Id;
5426       Ofs  : Uint;
5427       Ttyp : Entity_Id;
5428       P    : Node_Id;
5429
5430    begin
5431       --  Return if unchecked type conversion with range check killed. In this
5432       --  case we never set the flag (that's what Kill_Range_Check is about).
5433
5434       if Nkind (N) = N_Unchecked_Type_Conversion
5435         and then Kill_Range_Check (N)
5436       then
5437          return;
5438       end if;
5439
5440       --  Do not set range check flag if parent is assignment statement or
5441       --  object declaration with Suppress_Assignment_Checks flag set
5442
5443       if Nkind_In (Parent (N), N_Assignment_Statement, N_Object_Declaration)
5444         and then Suppress_Assignment_Checks (Parent (N))
5445       then
5446          return;
5447       end if;
5448
5449       --  Check for various cases where we should suppress the range check
5450
5451       --  No check if range checks suppressed for type of node
5452
5453       if Present (Etype (N)) and then Range_Checks_Suppressed (Etype (N)) then
5454          return;
5455
5456       --  No check if node is an entity name, and range checks are suppressed
5457       --  for this entity, or for the type of this entity.
5458
5459       elsif Is_Entity_Name (N)
5460         and then (Range_Checks_Suppressed (Entity (N))
5461                    or else Range_Checks_Suppressed (Etype (Entity (N))))
5462       then
5463          return;
5464
5465       --  No checks if index of array, and index checks are suppressed for
5466       --  the array object or the type of the array.
5467
5468       elsif Nkind (Parent (N)) = N_Indexed_Component then
5469          declare
5470             Pref : constant Node_Id := Prefix (Parent (N));
5471          begin
5472             if Is_Entity_Name (Pref)
5473               and then Index_Checks_Suppressed (Entity (Pref))
5474             then
5475                return;
5476             elsif Index_Checks_Suppressed (Etype (Pref)) then
5477                return;
5478             end if;
5479          end;
5480       end if;
5481
5482       --  Debug trace output
5483
5484       if Debug_Flag_CC then
5485          w ("Enable_Range_Check for node ", Int (N));
5486          Write_Str ("  Source location = ");
5487          wl (Sloc (N));
5488          pg (Union_Id (N));
5489       end if;
5490
5491       --  If not in optimizing mode, set flag and we are done. We are also done
5492       --  (and just set the flag) if the type is not a discrete type, since it
5493       --  is not worth the effort to eliminate checks for other than discrete
5494       --  types. In addition, we take this same path if we have stored the
5495       --  maximum number of checks possible already (a very unlikely situation,
5496       --  but we do not want to blow up).
5497
5498       if Optimization_Level = 0
5499         or else No (Etype (N))
5500         or else not Is_Discrete_Type (Etype (N))
5501         or else Num_Saved_Checks = Saved_Checks'Last
5502       then
5503          Activate_Range_Check (N);
5504
5505          if Debug_Flag_CC then
5506             w ("Optimization off");
5507          end if;
5508
5509          return;
5510       end if;
5511
5512       --  Otherwise find out the target type
5513
5514       P := Parent (N);
5515
5516       --  For assignment, use left side subtype
5517
5518       if Nkind (P) = N_Assignment_Statement
5519         and then Expression (P) = N
5520       then
5521          Ttyp := Etype (Name (P));
5522
5523       --  For indexed component, use subscript subtype
5524
5525       elsif Nkind (P) = N_Indexed_Component then
5526          declare
5527             Atyp : Entity_Id;
5528             Indx : Node_Id;
5529             Subs : Node_Id;
5530
5531          begin
5532             Atyp := Etype (Prefix (P));
5533
5534             if Is_Access_Type (Atyp) then
5535                Atyp := Designated_Type (Atyp);
5536
5537                --  If the prefix is an access to an unconstrained array,
5538                --  perform check unconditionally: it depends on the bounds of
5539                --  an object and we cannot currently recognize whether the test
5540                --  may be redundant.
5541
5542                if not Is_Constrained (Atyp) then
5543                   Activate_Range_Check (N);
5544                   return;
5545                end if;
5546
5547             --  Ditto if prefix is simply an unconstrained array. We used
5548             --  to think this case was OK, if the prefix was not an explicit
5549             --  dereference, but we have now seen a case where this is not
5550             --  true, so it is safer to just suppress the optimization in this
5551             --  case. The back end is getting better at eliminating redundant
5552             --  checks in any case, so the loss won't be important.
5553
5554             elsif Is_Array_Type (Atyp)
5555               and then not Is_Constrained (Atyp)
5556             then
5557                Activate_Range_Check (N);
5558                return;
5559             end if;
5560
5561             Indx := First_Index (Atyp);
5562             Subs := First (Expressions (P));
5563             loop
5564                if Subs = N then
5565                   Ttyp := Etype (Indx);
5566                   exit;
5567                end if;
5568
5569                Next_Index (Indx);
5570                Next (Subs);
5571             end loop;
5572          end;
5573
5574       --  For now, ignore all other cases, they are not so interesting
5575
5576       else
5577          if Debug_Flag_CC then
5578             w ("  target type not found, flag set");
5579          end if;
5580
5581          Activate_Range_Check (N);
5582          return;
5583       end if;
5584
5585       --  Evaluate and check the expression
5586
5587       Find_Check
5588         (Expr        => N,
5589          Check_Type  => 'R',
5590          Target_Type => Ttyp,
5591          Entry_OK    => OK,
5592          Check_Num   => Chk,
5593          Ent         => Ent,
5594          Ofs         => Ofs);
5595
5596       if Debug_Flag_CC then
5597          w ("Called Find_Check");
5598          w ("Target_Typ = ", Int (Ttyp));
5599          w ("  OK = ", OK);
5600
5601          if OK then
5602             w ("  Check_Num = ", Chk);
5603             w ("  Ent       = ", Int (Ent));
5604             Write_Str ("  Ofs       = ");
5605             pid (Ofs);
5606          end if;
5607       end if;
5608
5609       --  If check is not of form to optimize, then set flag and we are done
5610
5611       if not OK then
5612          if Debug_Flag_CC then
5613             w ("  expression not of optimizable type, flag set");
5614          end if;
5615
5616          Activate_Range_Check (N);
5617          return;
5618       end if;
5619
5620       --  If check is already performed, then return without setting flag
5621
5622       if Chk /= 0 then
5623          if Debug_Flag_CC then
5624             w ("Check suppressed!");
5625          end if;
5626
5627          return;
5628       end if;
5629
5630       --  Here we will make a new entry for the new check
5631
5632       Activate_Range_Check (N);
5633       Num_Saved_Checks := Num_Saved_Checks + 1;
5634       Saved_Checks (Num_Saved_Checks) :=
5635         (Killed      => False,
5636          Entity      => Ent,
5637          Offset      => Ofs,
5638          Check_Type  => 'R',
5639          Target_Type => Ttyp);
5640
5641       if Debug_Flag_CC then
5642          w ("Make new entry, check number = ", Num_Saved_Checks);
5643          w ("  Entity = ", Int (Ent));
5644          Write_Str ("  Offset = ");
5645          pid (Ofs);
5646          w ("  Check_Type = R");
5647          w ("  Target_Type = ", Int (Ttyp));
5648          pg (Union_Id (Ttyp));
5649       end if;
5650
5651    --  If we get an exception, then something went wrong, probably because of
5652    --  an error in the structure of the tree due to an incorrect program. Or
5653    --  it may be a bug in the optimization circuit. In either case the safest
5654    --  thing is simply to set the check flag unconditionally.
5655
5656    exception
5657       when others =>
5658          Activate_Range_Check (N);
5659
5660          if Debug_Flag_CC then
5661             w ("  exception occurred, range flag set");
5662          end if;
5663
5664          return;
5665    end Enable_Range_Check;
5666
5667    ------------------
5668    -- Ensure_Valid --
5669    ------------------
5670
5671    procedure Ensure_Valid
5672      (Expr          : Node_Id;
5673       Holes_OK      : Boolean   := False;
5674       Related_Id    : Entity_Id := Empty;
5675       Is_Low_Bound  : Boolean   := False;
5676       Is_High_Bound : Boolean   := False)
5677    is
5678       Typ : constant Entity_Id  := Etype (Expr);
5679
5680    begin
5681       --  Ignore call if we are not doing any validity checking
5682
5683       if not Validity_Checks_On then
5684          return;
5685
5686       --  Ignore call if range or validity checks suppressed on entity or type
5687
5688       elsif Range_Or_Validity_Checks_Suppressed (Expr) then
5689          return;
5690
5691       --  No check required if expression is from the expander, we assume the
5692       --  expander will generate whatever checks are needed. Note that this is
5693       --  not just an optimization, it avoids infinite recursions.
5694
5695       --  Unchecked conversions must be checked, unless they are initialized
5696       --  scalar values, as in a component assignment in an init proc.
5697
5698       --  In addition, we force a check if Force_Validity_Checks is set
5699
5700       elsif not Comes_From_Source (Expr)
5701         and then not Force_Validity_Checks
5702         and then (Nkind (Expr) /= N_Unchecked_Type_Conversion
5703                     or else Kill_Range_Check (Expr))
5704       then
5705          return;
5706
5707       --  No check required if expression is known to have valid value
5708
5709       elsif Expr_Known_Valid (Expr) then
5710          return;
5711
5712       --  No check needed within a generated predicate function. Validity
5713       --  of input value will have been checked earlier.
5714
5715       elsif Ekind (Current_Scope) = E_Function
5716         and then Is_Predicate_Function (Current_Scope)
5717       then
5718          return;
5719
5720       --  Ignore case of enumeration with holes where the flag is set not to
5721       --  worry about holes, since no special validity check is needed
5722
5723       elsif Is_Enumeration_Type (Typ)
5724         and then Has_Non_Standard_Rep (Typ)
5725         and then Holes_OK
5726       then
5727          return;
5728
5729       --  No check required on the left-hand side of an assignment
5730
5731       elsif Nkind (Parent (Expr)) = N_Assignment_Statement
5732         and then Expr = Name (Parent (Expr))
5733       then
5734          return;
5735
5736       --  No check on a universal real constant. The context will eventually
5737       --  convert it to a machine number for some target type, or report an
5738       --  illegality.
5739
5740       elsif Nkind (Expr) = N_Real_Literal
5741         and then Etype (Expr) = Universal_Real
5742       then
5743          return;
5744
5745       --  If the expression denotes a component of a packed boolean array,
5746       --  no possible check applies. We ignore the old ACATS chestnuts that
5747       --  involve Boolean range True..True.
5748
5749       --  Note: validity checks are generated for expressions that yield a
5750       --  scalar type, when it is possible to create a value that is outside of
5751       --  the type. If this is a one-bit boolean no such value exists. This is
5752       --  an optimization, and it also prevents compiler blowing up during the
5753       --  elaboration of improperly expanded packed array references.
5754
5755       elsif Nkind (Expr) = N_Indexed_Component
5756         and then Is_Bit_Packed_Array (Etype (Prefix (Expr)))
5757         and then Root_Type (Etype (Expr)) = Standard_Boolean
5758       then
5759          return;
5760
5761       --  For an expression with actions, we want to insert the validity check
5762       --  on the final Expression.
5763
5764       elsif Nkind (Expr) = N_Expression_With_Actions then
5765          Ensure_Valid (Expression (Expr));
5766          return;
5767
5768       --  An annoying special case. If this is an out parameter of a scalar
5769       --  type, then the value is not going to be accessed, therefore it is
5770       --  inappropriate to do any validity check at the call site.
5771
5772       else
5773          --  Only need to worry about scalar types
5774
5775          if Is_Scalar_Type (Typ) then
5776             declare
5777                P : Node_Id;
5778                N : Node_Id;
5779                E : Entity_Id;
5780                F : Entity_Id;
5781                A : Node_Id;
5782                L : List_Id;
5783
5784             begin
5785                --  Find actual argument (which may be a parameter association)
5786                --  and the parent of the actual argument (the call statement)
5787
5788                N := Expr;
5789                P := Parent (Expr);
5790
5791                if Nkind (P) = N_Parameter_Association then
5792                   N := P;
5793                   P := Parent (N);
5794                end if;
5795
5796                --  Only need to worry if we are argument of a procedure call
5797                --  since functions don't have out parameters. If this is an
5798                --  indirect or dispatching call, get signature from the
5799                --  subprogram type.
5800
5801                if Nkind (P) = N_Procedure_Call_Statement then
5802                   L := Parameter_Associations (P);
5803
5804                   if Is_Entity_Name (Name (P)) then
5805                      E := Entity (Name (P));
5806                   else
5807                      pragma Assert (Nkind (Name (P)) = N_Explicit_Dereference);
5808                      E := Etype (Name (P));
5809                   end if;
5810
5811                   --  Only need to worry if there are indeed actuals, and if
5812                   --  this could be a procedure call, otherwise we cannot get a
5813                   --  match (either we are not an argument, or the mode of the
5814                   --  formal is not OUT). This test also filters out the
5815                   --  generic case.
5816
5817                   if Is_Non_Empty_List (L) and then Is_Subprogram (E) then
5818
5819                      --  This is the loop through parameters, looking for an
5820                      --  OUT parameter for which we are the argument.
5821
5822                      F := First_Formal (E);
5823                      A := First (L);
5824                      while Present (F) loop
5825                         if Ekind (F) = E_Out_Parameter and then A = N then
5826                            return;
5827                         end if;
5828
5829                         Next_Formal (F);
5830                         Next (A);
5831                      end loop;
5832                   end if;
5833                end if;
5834             end;
5835          end if;
5836       end if;
5837
5838       --  If this is a boolean expression, only its elementary operands need
5839       --  checking: if they are valid, a boolean or short-circuit operation
5840       --  with them will be valid as well.
5841
5842       if Base_Type (Typ) = Standard_Boolean
5843         and then
5844          (Nkind (Expr) in N_Op or else Nkind (Expr) in N_Short_Circuit)
5845       then
5846          return;
5847       end if;
5848
5849       --  If we fall through, a validity check is required
5850
5851       Insert_Valid_Check (Expr, Related_Id, Is_Low_Bound, Is_High_Bound);
5852
5853       if Is_Entity_Name (Expr)
5854         and then Safe_To_Capture_Value (Expr, Entity (Expr))
5855       then
5856          Set_Is_Known_Valid (Entity (Expr));
5857       end if;
5858    end Ensure_Valid;
5859
5860    ----------------------
5861    -- Expr_Known_Valid --
5862    ----------------------
5863
5864    function Expr_Known_Valid (Expr : Node_Id) return Boolean is
5865       Typ : constant Entity_Id := Etype (Expr);
5866
5867    begin
5868       --  Non-scalar types are always considered valid, since they never give
5869       --  rise to the issues of erroneous or bounded error behavior that are
5870       --  the concern. In formal reference manual terms the notion of validity
5871       --  only applies to scalar types. Note that even when packed arrays are
5872       --  represented using modular types, they are still arrays semantically,
5873       --  so they are also always valid (in particular, the unused bits can be
5874       --  random rubbish without affecting the validity of the array value).
5875
5876       if not Is_Scalar_Type (Typ) or else Is_Packed_Array_Impl_Type (Typ) then
5877          return True;
5878
5879       --  If no validity checking, then everything is considered valid
5880
5881       elsif not Validity_Checks_On then
5882          return True;
5883
5884       --  Floating-point types are considered valid unless floating-point
5885       --  validity checks have been specifically turned on.
5886
5887       elsif Is_Floating_Point_Type (Typ)
5888         and then not Validity_Check_Floating_Point
5889       then
5890          return True;
5891
5892       --  If the expression is the value of an object that is known to be
5893       --  valid, then clearly the expression value itself is valid.
5894
5895       elsif Is_Entity_Name (Expr)
5896         and then Is_Known_Valid (Entity (Expr))
5897
5898         --  Exclude volatile variables
5899
5900         and then not Treat_As_Volatile (Entity (Expr))
5901       then
5902          return True;
5903
5904       --  References to discriminants are always considered valid. The value
5905       --  of a discriminant gets checked when the object is built. Within the
5906       --  record, we consider it valid, and it is important to do so, since
5907       --  otherwise we can try to generate bogus validity checks which
5908       --  reference discriminants out of scope. Discriminants of concurrent
5909       --  types are excluded for the same reason.
5910
5911       elsif Is_Entity_Name (Expr)
5912         and then Denotes_Discriminant (Expr, Check_Concurrent => True)
5913       then
5914          return True;
5915
5916       --  If the type is one for which all values are known valid, then we are
5917       --  sure that the value is valid except in the slightly odd case where
5918       --  the expression is a reference to a variable whose size has been
5919       --  explicitly set to a value greater than the object size.
5920
5921       elsif Is_Known_Valid (Typ) then
5922          if Is_Entity_Name (Expr)
5923            and then Ekind (Entity (Expr)) = E_Variable
5924            and then Esize (Entity (Expr)) > Esize (Typ)
5925          then
5926             return False;
5927          else
5928             return True;
5929          end if;
5930
5931       --  Integer and character literals always have valid values, where
5932       --  appropriate these will be range checked in any case.
5933
5934       elsif Nkind_In (Expr, N_Integer_Literal, N_Character_Literal) then
5935          return True;
5936
5937       --  If we have a type conversion or a qualification of a known valid
5938       --  value, then the result will always be valid.
5939
5940       elsif Nkind_In (Expr, N_Type_Conversion, N_Qualified_Expression) then
5941          return Expr_Known_Valid (Expression (Expr));
5942
5943       --  Case of expression is a non-floating-point operator. In this case we
5944       --  can assume the result is valid the generated code for the operator
5945       --  will include whatever checks are needed (e.g. range checks) to ensure
5946       --  validity. This assumption does not hold for the floating-point case,
5947       --  since floating-point operators can generate Infinite or NaN results
5948       --  which are considered invalid.
5949
5950       --  Historical note: in older versions, the exemption of floating-point
5951       --  types from this assumption was done only in cases where the parent
5952       --  was an assignment, function call or parameter association. Presumably
5953       --  the idea was that in other contexts, the result would be checked
5954       --  elsewhere, but this list of cases was missing tests (at least the
5955       --  N_Object_Declaration case, as shown by a reported missing validity
5956       --  check), and it is not clear why function calls but not procedure
5957       --  calls were tested for. It really seems more accurate and much
5958       --  safer to recognize that expressions which are the result of a
5959       --  floating-point operator can never be assumed to be valid.
5960
5961       elsif Nkind (Expr) in N_Op and then not Is_Floating_Point_Type (Typ) then
5962          return True;
5963
5964       --  The result of a membership test is always valid, since it is true or
5965       --  false, there are no other possibilities.
5966
5967       elsif Nkind (Expr) in N_Membership_Test then
5968          return True;
5969
5970       --  For all other cases, we do not know the expression is valid
5971
5972       else
5973          return False;
5974       end if;
5975    end Expr_Known_Valid;
5976
5977    ----------------
5978    -- Find_Check --
5979    ----------------
5980
5981    procedure Find_Check
5982      (Expr        : Node_Id;
5983       Check_Type  : Character;
5984       Target_Type : Entity_Id;
5985       Entry_OK    : out Boolean;
5986       Check_Num   : out Nat;
5987       Ent         : out Entity_Id;
5988       Ofs         : out Uint)
5989    is
5990       function Within_Range_Of
5991         (Target_Type : Entity_Id;
5992          Check_Type  : Entity_Id) return Boolean;
5993       --  Given a requirement for checking a range against Target_Type, and
5994       --  and a range Check_Type against which a check has already been made,
5995       --  determines if the check against check type is sufficient to ensure
5996       --  that no check against Target_Type is required.
5997
5998       ---------------------
5999       -- Within_Range_Of --
6000       ---------------------
6001
6002       function Within_Range_Of
6003         (Target_Type : Entity_Id;
6004          Check_Type  : Entity_Id) return Boolean
6005       is
6006       begin
6007          if Target_Type = Check_Type then
6008             return True;
6009
6010          else
6011             declare
6012                Tlo : constant Node_Id := Type_Low_Bound  (Target_Type);
6013                Thi : constant Node_Id := Type_High_Bound (Target_Type);
6014                Clo : constant Node_Id := Type_Low_Bound  (Check_Type);
6015                Chi : constant Node_Id := Type_High_Bound (Check_Type);
6016
6017             begin
6018                if (Tlo = Clo
6019                      or else (Compile_Time_Known_Value (Tlo)
6020                                 and then
6021                               Compile_Time_Known_Value (Clo)
6022                                 and then
6023                               Expr_Value (Clo) >= Expr_Value (Tlo)))
6024                  and then
6025                   (Thi = Chi
6026                      or else (Compile_Time_Known_Value (Thi)
6027                                 and then
6028                               Compile_Time_Known_Value (Chi)
6029                                 and then
6030                               Expr_Value (Chi) <= Expr_Value (Clo)))
6031                then
6032                   return True;
6033                else
6034                   return False;
6035                end if;
6036             end;
6037          end if;
6038       end Within_Range_Of;
6039
6040    --  Start of processing for Find_Check
6041
6042    begin
6043       --  Establish default, in case no entry is found
6044
6045       Check_Num := 0;
6046
6047       --  Case of expression is simple entity reference
6048
6049       if Is_Entity_Name (Expr) then
6050          Ent := Entity (Expr);
6051          Ofs := Uint_0;
6052
6053       --  Case of expression is entity + known constant
6054
6055       elsif Nkind (Expr) = N_Op_Add
6056         and then Compile_Time_Known_Value (Right_Opnd (Expr))
6057         and then Is_Entity_Name (Left_Opnd (Expr))
6058       then
6059          Ent := Entity (Left_Opnd (Expr));
6060          Ofs := Expr_Value (Right_Opnd (Expr));
6061
6062       --  Case of expression is entity - known constant
6063
6064       elsif Nkind (Expr) = N_Op_Subtract
6065         and then Compile_Time_Known_Value (Right_Opnd (Expr))
6066         and then Is_Entity_Name (Left_Opnd (Expr))
6067       then
6068          Ent := Entity (Left_Opnd (Expr));
6069          Ofs := UI_Negate (Expr_Value (Right_Opnd (Expr)));
6070
6071       --  Any other expression is not of the right form
6072
6073       else
6074          Ent := Empty;
6075          Ofs := Uint_0;
6076          Entry_OK := False;
6077          return;
6078       end if;
6079
6080       --  Come here with expression of appropriate form, check if entity is an
6081       --  appropriate one for our purposes.
6082
6083       if (Ekind (Ent) = E_Variable
6084             or else Is_Constant_Object (Ent))
6085         and then not Is_Library_Level_Entity (Ent)
6086       then
6087          Entry_OK := True;
6088       else
6089          Entry_OK := False;
6090          return;
6091       end if;
6092
6093       --  See if there is matching check already
6094
6095       for J in reverse 1 .. Num_Saved_Checks loop
6096          declare
6097             SC : Saved_Check renames Saved_Checks (J);
6098          begin
6099             if SC.Killed = False
6100               and then SC.Entity = Ent
6101               and then SC.Offset = Ofs
6102               and then SC.Check_Type = Check_Type
6103               and then Within_Range_Of (Target_Type, SC.Target_Type)
6104             then
6105                Check_Num := J;
6106                return;
6107             end if;
6108          end;
6109       end loop;
6110
6111       --  If we fall through entry was not found
6112
6113       return;
6114    end Find_Check;
6115
6116    ---------------------------------
6117    -- Generate_Discriminant_Check --
6118    ---------------------------------
6119
6120    --  Note: the code for this procedure is derived from the
6121    --  Emit_Discriminant_Check Routine in trans.c.
6122
6123    procedure Generate_Discriminant_Check (N : Node_Id) is
6124       Loc  : constant Source_Ptr := Sloc (N);
6125       Pref : constant Node_Id    := Prefix (N);
6126       Sel  : constant Node_Id    := Selector_Name (N);
6127
6128       Orig_Comp : constant Entity_Id :=
6129         Original_Record_Component (Entity (Sel));
6130       --  The original component to be checked
6131
6132       Discr_Fct : constant Entity_Id :=
6133         Discriminant_Checking_Func (Orig_Comp);
6134       --  The discriminant checking function
6135
6136       Discr : Entity_Id;
6137       --  One discriminant to be checked in the type
6138
6139       Real_Discr : Entity_Id;
6140       --  Actual discriminant in the call
6141
6142       Pref_Type : Entity_Id;
6143       --  Type of relevant prefix (ignoring private/access stuff)
6144
6145       Args : List_Id;
6146       --  List of arguments for function call
6147
6148       Formal : Entity_Id;
6149       --  Keep track of the formal corresponding to the actual we build for
6150       --  each discriminant, in order to be able to perform the necessary type
6151       --  conversions.
6152
6153       Scomp : Node_Id;
6154       --  Selected component reference for checking function argument
6155
6156    begin
6157       Pref_Type := Etype (Pref);
6158
6159       --  Force evaluation of the prefix, so that it does not get evaluated
6160       --  twice (once for the check, once for the actual reference). Such a
6161       --  double evaluation is always a potential source of inefficiency, and
6162       --  is functionally incorrect in the volatile case, or when the prefix
6163       --  may have side effects. A nonvolatile entity or a component of a
6164       --  nonvolatile entity requires no evaluation.
6165
6166       if Is_Entity_Name (Pref) then
6167          if Treat_As_Volatile (Entity (Pref)) then
6168             Force_Evaluation (Pref, Name_Req => True);
6169          end if;
6170
6171       elsif Treat_As_Volatile (Etype (Pref)) then
6172          Force_Evaluation (Pref, Name_Req => True);
6173
6174       elsif Nkind (Pref) = N_Selected_Component
6175         and then Is_Entity_Name (Prefix (Pref))
6176       then
6177          null;
6178
6179       else
6180          Force_Evaluation (Pref, Name_Req => True);
6181       end if;
6182
6183       --  For a tagged type, use the scope of the original component to
6184       --  obtain the type, because ???
6185
6186       if Is_Tagged_Type (Scope (Orig_Comp)) then
6187          Pref_Type := Scope (Orig_Comp);
6188
6189       --  For an untagged derived type, use the discriminants of the parent
6190       --  which have been renamed in the derivation, possibly by a one-to-many
6191       --  discriminant constraint. For untagged type, initially get the Etype
6192       --  of the prefix
6193
6194       else
6195          if Is_Derived_Type (Pref_Type)
6196            and then Number_Discriminants (Pref_Type) /=
6197                     Number_Discriminants (Etype (Base_Type (Pref_Type)))
6198          then
6199             Pref_Type := Etype (Base_Type (Pref_Type));
6200          end if;
6201       end if;
6202
6203       --  We definitely should have a checking function, This routine should
6204       --  not be called if no discriminant checking function is present.
6205
6206       pragma Assert (Present (Discr_Fct));
6207
6208       --  Create the list of the actual parameters for the call. This list
6209       --  is the list of the discriminant fields of the record expression to
6210       --  be discriminant checked.
6211
6212       Args   := New_List;
6213       Formal := First_Formal (Discr_Fct);
6214       Discr  := First_Discriminant (Pref_Type);
6215       while Present (Discr) loop
6216
6217          --  If we have a corresponding discriminant field, and a parent
6218          --  subtype is present, then we want to use the corresponding
6219          --  discriminant since this is the one with the useful value.
6220
6221          if Present (Corresponding_Discriminant (Discr))
6222            and then Ekind (Pref_Type) = E_Record_Type
6223            and then Present (Parent_Subtype (Pref_Type))
6224          then
6225             Real_Discr := Corresponding_Discriminant (Discr);
6226          else
6227             Real_Discr := Discr;
6228          end if;
6229
6230          --  Construct the reference to the discriminant
6231
6232          Scomp :=
6233            Make_Selected_Component (Loc,
6234              Prefix =>
6235                Unchecked_Convert_To (Pref_Type,
6236                  Duplicate_Subexpr (Pref)),
6237              Selector_Name => New_Occurrence_Of (Real_Discr, Loc));
6238
6239          --  Manually analyze and resolve this selected component. We really
6240          --  want it just as it appears above, and do not want the expander
6241          --  playing discriminal games etc with this reference. Then we append
6242          --  the argument to the list we are gathering.
6243
6244          Set_Etype (Scomp, Etype (Real_Discr));
6245          Set_Analyzed (Scomp, True);
6246          Append_To (Args, Convert_To (Etype (Formal), Scomp));
6247
6248          Next_Formal_With_Extras (Formal);
6249          Next_Discriminant (Discr);
6250       end loop;
6251
6252       --  Now build and insert the call
6253
6254       Insert_Action (N,
6255         Make_Raise_Constraint_Error (Loc,
6256           Condition =>
6257             Make_Function_Call (Loc,
6258               Name                   => New_Occurrence_Of (Discr_Fct, Loc),
6259               Parameter_Associations => Args),
6260           Reason => CE_Discriminant_Check_Failed));
6261    end Generate_Discriminant_Check;
6262
6263    ---------------------------
6264    -- Generate_Index_Checks --
6265    ---------------------------
6266
6267    procedure Generate_Index_Checks (N : Node_Id) is
6268
6269       function Entity_Of_Prefix return Entity_Id;
6270       --  Returns the entity of the prefix of N (or Empty if not found)
6271
6272       ----------------------
6273       -- Entity_Of_Prefix --
6274       ----------------------
6275
6276       function Entity_Of_Prefix return Entity_Id is
6277          P : Node_Id;
6278
6279       begin
6280          P := Prefix (N);
6281          while not Is_Entity_Name (P) loop
6282             if not Nkind_In (P, N_Selected_Component,
6283                                 N_Indexed_Component)
6284             then
6285                return Empty;
6286             end if;
6287
6288             P := Prefix (P);
6289          end loop;
6290
6291          return Entity (P);
6292       end Entity_Of_Prefix;
6293
6294       --  Local variables
6295
6296       Loc   : constant Source_Ptr := Sloc (N);
6297       A     : constant Node_Id    := Prefix (N);
6298       A_Ent : constant Entity_Id  := Entity_Of_Prefix;
6299       Sub   : Node_Id;
6300
6301    --  Start of processing for Generate_Index_Checks
6302
6303    begin
6304       --  Ignore call if the prefix is not an array since we have a serious
6305       --  error in the sources. Ignore it also if index checks are suppressed
6306       --  for array object or type.
6307
6308       if not Is_Array_Type (Etype (A))
6309         or else (Present (A_Ent) and then Index_Checks_Suppressed (A_Ent))
6310         or else Index_Checks_Suppressed (Etype (A))
6311       then
6312          return;
6313
6314       --  The indexed component we are dealing with contains 'Loop_Entry in its
6315       --  prefix. This case arises when analysis has determined that constructs
6316       --  such as
6317
6318       --     Prefix'Loop_Entry (Expr)
6319       --     Prefix'Loop_Entry (Expr1, Expr2, ... ExprN)
6320
6321       --  require rewriting for error detection purposes. A side effect of this
6322       --  action is the generation of index checks that mention 'Loop_Entry.
6323       --  Delay the generation of the check until 'Loop_Entry has been properly
6324       --  expanded. This is done in Expand_Loop_Entry_Attributes.
6325
6326       elsif Nkind (Prefix (N)) = N_Attribute_Reference
6327         and then Attribute_Name (Prefix (N)) = Name_Loop_Entry
6328       then
6329          return;
6330       end if;
6331
6332       --  Generate a raise of constraint error with the appropriate reason and
6333       --  a condition of the form:
6334
6335       --    Base_Type (Sub) not in Array'Range (Subscript)
6336
6337       --  Note that the reason we generate the conversion to the base type here
6338       --  is that we definitely want the range check to take place, even if it
6339       --  looks like the subtype is OK. Optimization considerations that allow
6340       --  us to omit the check have already been taken into account in the
6341       --  setting of the Do_Range_Check flag earlier on.
6342
6343       Sub := First (Expressions (N));
6344
6345       --  Handle string literals
6346
6347       if Ekind (Etype (A)) = E_String_Literal_Subtype then
6348          if Do_Range_Check (Sub) then
6349             Set_Do_Range_Check (Sub, False);
6350
6351             --  For string literals we obtain the bounds of the string from the
6352             --  associated subtype.
6353
6354             Insert_Action (N,
6355               Make_Raise_Constraint_Error (Loc,
6356                 Condition =>
6357                    Make_Not_In (Loc,
6358                      Left_Opnd  =>
6359                        Convert_To (Base_Type (Etype (Sub)),
6360                          Duplicate_Subexpr_Move_Checks (Sub)),
6361                      Right_Opnd =>
6362                        Make_Attribute_Reference (Loc,
6363                          Prefix         => New_Occurrence_Of (Etype (A), Loc),
6364                          Attribute_Name => Name_Range)),
6365                 Reason => CE_Index_Check_Failed));
6366          end if;
6367
6368       --  General case
6369
6370       else
6371          declare
6372             A_Idx   : Node_Id := Empty;
6373             A_Range : Node_Id;
6374             Ind     : Nat;
6375             Num     : List_Id;
6376             Range_N : Node_Id;
6377
6378          begin
6379             A_Idx := First_Index (Etype (A));
6380             Ind   := 1;
6381             while Present (Sub) loop
6382                if Do_Range_Check (Sub) then
6383                   Set_Do_Range_Check (Sub, False);
6384
6385                   --  Force evaluation except for the case of a simple name of
6386                   --  a nonvolatile entity.
6387
6388                   if not Is_Entity_Name (Sub)
6389                     or else Treat_As_Volatile (Entity (Sub))
6390                   then
6391                      Force_Evaluation (Sub);
6392                   end if;
6393
6394                   if Nkind (A_Idx) = N_Range then
6395                      A_Range := A_Idx;
6396
6397                   elsif Nkind (A_Idx) = N_Identifier
6398                     or else Nkind (A_Idx) = N_Expanded_Name
6399                   then
6400                      A_Range := Scalar_Range (Entity (A_Idx));
6401
6402                   else pragma Assert (Nkind (A_Idx) = N_Subtype_Indication);
6403                      A_Range := Range_Expression (Constraint (A_Idx));
6404                   end if;
6405
6406                   --  For array objects with constant bounds we can generate
6407                   --  the index check using the bounds of the type of the index
6408
6409                   if Present (A_Ent)
6410                     and then Ekind (A_Ent) = E_Variable
6411                     and then Is_Constant_Bound (Low_Bound (A_Range))
6412                     and then Is_Constant_Bound (High_Bound (A_Range))
6413                   then
6414                      Range_N :=
6415                        Make_Attribute_Reference (Loc,
6416                          Prefix         =>
6417                            New_Occurrence_Of (Etype (A_Idx), Loc),
6418                          Attribute_Name => Name_Range);
6419
6420                   --  For arrays with non-constant bounds we cannot generate
6421                   --  the index check using the bounds of the type of the index
6422                   --  since it may reference discriminants of some enclosing
6423                   --  type. We obtain the bounds directly from the prefix
6424                   --  object.
6425
6426                   else
6427                      if Ind = 1 then
6428                         Num := No_List;
6429                      else
6430                         Num := New_List (Make_Integer_Literal (Loc, Ind));
6431                      end if;
6432
6433                      Range_N :=
6434                        Make_Attribute_Reference (Loc,
6435                          Prefix =>
6436                            Duplicate_Subexpr_Move_Checks (A, Name_Req => True),
6437                          Attribute_Name => Name_Range,
6438                          Expressions    => Num);
6439                   end if;
6440
6441                   Insert_Action (N,
6442                     Make_Raise_Constraint_Error (Loc,
6443                       Condition =>
6444                          Make_Not_In (Loc,
6445                            Left_Opnd  =>
6446                              Convert_To (Base_Type (Etype (Sub)),
6447                                Duplicate_Subexpr_Move_Checks (Sub)),
6448                            Right_Opnd => Range_N),
6449                       Reason => CE_Index_Check_Failed));
6450                end if;
6451
6452                A_Idx := Next_Index (A_Idx);
6453                Ind := Ind + 1;
6454                Next (Sub);
6455             end loop;
6456          end;
6457       end if;
6458    end Generate_Index_Checks;
6459
6460    --------------------------
6461    -- Generate_Range_Check --
6462    --------------------------
6463
6464    procedure Generate_Range_Check
6465      (N           : Node_Id;
6466       Target_Type : Entity_Id;
6467       Reason      : RT_Exception_Code)
6468    is
6469       Loc              : constant Source_Ptr := Sloc (N);
6470       Source_Type      : constant Entity_Id  := Etype (N);
6471       Source_Base_Type : constant Entity_Id  := Base_Type (Source_Type);
6472       Target_Base_Type : constant Entity_Id  := Base_Type (Target_Type);
6473
6474       procedure Convert_And_Check_Range;
6475       --  Convert the conversion operand to the target base type and save in
6476       --  a temporary. Then check the converted value against the range of the
6477       --  target subtype.
6478
6479       -----------------------------
6480       -- Convert_And_Check_Range --
6481       -----------------------------
6482
6483       procedure Convert_And_Check_Range is
6484          Tnn : constant Entity_Id := Make_Temporary (Loc, 'T', N);
6485
6486       begin
6487          --  We make a temporary to hold the value of the converted value
6488          --  (converted to the base type), and then do the test against this
6489          --  temporary. The conversion itself is replaced by an occurrence of
6490          --  Tnn and followed by the explicit range check. Note that checks
6491          --  are suppressed for this code, since we don't want a recursive
6492          --  range check popping up.
6493
6494          --     Tnn : constant Target_Base_Type := Target_Base_Type (N);
6495          --     [constraint_error when Tnn not in Target_Type]
6496
6497          Insert_Actions (N, New_List (
6498            Make_Object_Declaration (Loc,
6499              Defining_Identifier => Tnn,
6500              Object_Definition   => New_Occurrence_Of (Target_Base_Type, Loc),
6501              Constant_Present    => True,
6502              Expression          =>
6503                Make_Type_Conversion (Loc,
6504                  Subtype_Mark => New_Occurrence_Of (Target_Base_Type, Loc),
6505                  Expression   => Duplicate_Subexpr (N))),
6506
6507            Make_Raise_Constraint_Error (Loc,
6508              Condition =>
6509                Make_Not_In (Loc,
6510                  Left_Opnd  => New_Occurrence_Of (Tnn, Loc),
6511                  Right_Opnd => New_Occurrence_Of (Target_Type, Loc)),
6512              Reason => Reason)),
6513            Suppress => All_Checks);
6514
6515          Rewrite (N, New_Occurrence_Of (Tnn, Loc));
6516
6517          --  Set the type of N, because the declaration for Tnn might not
6518          --  be analyzed yet, as is the case if N appears within a record
6519          --  declaration, as a discriminant constraint or expression.
6520
6521          Set_Etype (N, Target_Base_Type);
6522       end Convert_And_Check_Range;
6523
6524    --  Start of processing for Generate_Range_Check
6525
6526    begin
6527       --  First special case, if the source type is already within the range
6528       --  of the target type, then no check is needed (probably we should have
6529       --  stopped Do_Range_Check from being set in the first place, but better
6530       --  late than never in preventing junk code and junk flag settings.
6531
6532       if In_Subrange_Of (Source_Type, Target_Type)
6533
6534         --  We do NOT apply this if the source node is a literal, since in this
6535         --  case the literal has already been labeled as having the subtype of
6536         --  the target.
6537
6538         and then not
6539           (Nkind_In (N, N_Integer_Literal, N_Real_Literal, N_Character_Literal)
6540              or else
6541                (Is_Entity_Name (N)
6542                  and then Ekind (Entity (N)) = E_Enumeration_Literal))
6543       then
6544          Set_Do_Range_Check (N, False);
6545          return;
6546       end if;
6547
6548       --  Here a check is needed. If the expander is not active, or if we are
6549       --  in GNATProve mode, then simply set the Do_Range_Check flag and we
6550       --  are done. In both these cases, we just want to see the range check
6551       --  flag set, we do not want to generate the explicit range check code.
6552
6553       if GNATprove_Mode or else not Expander_Active then
6554          Set_Do_Range_Check (N, True);
6555          return;
6556       end if;
6557
6558       --  Here we will generate an explicit range check, so we don't want to
6559       --  set the Do_Range check flag, since the range check is taken care of
6560       --  by the code we will generate.
6561
6562       Set_Do_Range_Check (N, False);
6563
6564       --  Force evaluation of the node, so that it does not get evaluated twice
6565       --  (once for the check, once for the actual reference). Such a double
6566       --  evaluation is always a potential source of inefficiency, and is
6567       --  functionally incorrect in the volatile case.
6568
6569       if not Is_Entity_Name (N) or else Treat_As_Volatile (Entity (N)) then
6570          Force_Evaluation (N);
6571       end if;
6572
6573       --  The easiest case is when Source_Base_Type and Target_Base_Type are
6574       --  the same since in this case we can simply do a direct check of the
6575       --  value of N against the bounds of Target_Type.
6576
6577       --    [constraint_error when N not in Target_Type]
6578
6579       --  Note: this is by far the most common case, for example all cases of
6580       --  checks on the RHS of assignments are in this category, but not all
6581       --  cases are like this. Notably conversions can involve two types.
6582
6583       if Source_Base_Type = Target_Base_Type then
6584
6585          --  Insert the explicit range check. Note that we suppress checks for
6586          --  this code, since we don't want a recursive range check popping up.
6587
6588          Insert_Action (N,
6589            Make_Raise_Constraint_Error (Loc,
6590              Condition =>
6591                Make_Not_In (Loc,
6592                  Left_Opnd  => Duplicate_Subexpr (N),
6593                  Right_Opnd => New_Occurrence_Of (Target_Type, Loc)),
6594              Reason => Reason),
6595            Suppress => All_Checks);
6596
6597       --  Next test for the case where the target type is within the bounds
6598       --  of the base type of the source type, since in this case we can
6599       --  simply convert these bounds to the base type of T to do the test.
6600
6601       --    [constraint_error when N not in
6602       --       Source_Base_Type (Target_Type'First)
6603       --         ..
6604       --       Source_Base_Type(Target_Type'Last))]
6605
6606       --  The conversions will always work and need no check
6607
6608       --  Unchecked_Convert_To is used instead of Convert_To to handle the case
6609       --  of converting from an enumeration value to an integer type, such as
6610       --  occurs for the case of generating a range check on Enum'Val(Exp)
6611       --  (which used to be handled by gigi). This is OK, since the conversion
6612       --  itself does not require a check.
6613
6614       elsif In_Subrange_Of (Target_Type, Source_Base_Type) then
6615
6616          --  Insert the explicit range check. Note that we suppress checks for
6617          --  this code, since we don't want a recursive range check popping up.
6618
6619          if Is_Discrete_Type (Source_Base_Type)
6620               and then
6621             Is_Discrete_Type (Target_Base_Type)
6622          then
6623             Insert_Action (N,
6624               Make_Raise_Constraint_Error (Loc,
6625                 Condition =>
6626                   Make_Not_In (Loc,
6627                     Left_Opnd  => Duplicate_Subexpr (N),
6628
6629                     Right_Opnd =>
6630                       Make_Range (Loc,
6631                         Low_Bound  =>
6632                           Unchecked_Convert_To (Source_Base_Type,
6633                             Make_Attribute_Reference (Loc,
6634                               Prefix         =>
6635                                 New_Occurrence_Of (Target_Type, Loc),
6636                               Attribute_Name => Name_First)),
6637
6638                         High_Bound =>
6639                           Unchecked_Convert_To (Source_Base_Type,
6640                             Make_Attribute_Reference (Loc,
6641                               Prefix         =>
6642                                 New_Occurrence_Of (Target_Type, Loc),
6643                               Attribute_Name => Name_Last)))),
6644                 Reason    => Reason),
6645               Suppress => All_Checks);
6646
6647          --  For conversions involving at least one type that is not discrete,
6648          --  first convert to target type and then generate the range check.
6649          --  This avoids problems with values that are close to a bound of the
6650          --  target type that would fail a range check when done in a larger
6651          --  source type before converting but would pass if converted with
6652          --  rounding and then checked (such as in float-to-float conversions).
6653
6654          else
6655             Convert_And_Check_Range;
6656          end if;
6657
6658       --  Note that at this stage we now that the Target_Base_Type is not in
6659       --  the range of the Source_Base_Type (since even the Target_Type itself
6660       --  is not in this range). It could still be the case that Source_Type is
6661       --  in range of the target base type since we have not checked that case.
6662
6663       --  If that is the case, we can freely convert the source to the target,
6664       --  and then test the target result against the bounds.
6665
6666       elsif In_Subrange_Of (Source_Type, Target_Base_Type) then
6667          Convert_And_Check_Range;
6668
6669       --  At this stage, we know that we have two scalar types, which are
6670       --  directly convertible, and where neither scalar type has a base
6671       --  range that is in the range of the other scalar type.
6672
6673       --  The only way this can happen is with a signed and unsigned type.
6674       --  So test for these two cases:
6675
6676       else
6677          --  Case of the source is unsigned and the target is signed
6678
6679          if Is_Unsigned_Type (Source_Base_Type)
6680            and then not Is_Unsigned_Type (Target_Base_Type)
6681          then
6682             --  If the source is unsigned and the target is signed, then we
6683             --  know that the source is not shorter than the target (otherwise
6684             --  the source base type would be in the target base type range).
6685
6686             --  In other words, the unsigned type is either the same size as
6687             --  the target, or it is larger. It cannot be smaller.
6688
6689             pragma Assert
6690               (Esize (Source_Base_Type) >= Esize (Target_Base_Type));
6691
6692             --  We only need to check the low bound if the low bound of the
6693             --  target type is non-negative. If the low bound of the target
6694             --  type is negative, then we know that we will fit fine.
6695
6696             --  If the high bound of the target type is negative, then we
6697             --  know we have a constraint error, since we can't possibly
6698             --  have a negative source.
6699
6700             --  With these two checks out of the way, we can do the check
6701             --  using the source type safely
6702
6703             --  This is definitely the most annoying case.
6704
6705             --    [constraint_error
6706             --       when (Target_Type'First >= 0
6707             --               and then
6708             --                 N < Source_Base_Type (Target_Type'First))
6709             --         or else Target_Type'Last < 0
6710             --         or else N > Source_Base_Type (Target_Type'Last)];
6711
6712             --  We turn off all checks since we know that the conversions
6713             --  will work fine, given the guards for negative values.
6714
6715             Insert_Action (N,
6716               Make_Raise_Constraint_Error (Loc,
6717                 Condition =>
6718                   Make_Or_Else (Loc,
6719                     Make_Or_Else (Loc,
6720                       Left_Opnd =>
6721                         Make_And_Then (Loc,
6722                           Left_Opnd => Make_Op_Ge (Loc,
6723                             Left_Opnd =>
6724                               Make_Attribute_Reference (Loc,
6725                                 Prefix =>
6726                                   New_Occurrence_Of (Target_Type, Loc),
6727                                 Attribute_Name => Name_First),
6728                             Right_Opnd => Make_Integer_Literal (Loc, Uint_0)),
6729
6730                           Right_Opnd =>
6731                             Make_Op_Lt (Loc,
6732                               Left_Opnd => Duplicate_Subexpr (N),
6733                               Right_Opnd =>
6734                                 Convert_To (Source_Base_Type,
6735                                   Make_Attribute_Reference (Loc,
6736                                     Prefix =>
6737                                       New_Occurrence_Of (Target_Type, Loc),
6738                                     Attribute_Name => Name_First)))),
6739
6740                       Right_Opnd =>
6741                         Make_Op_Lt (Loc,
6742                           Left_Opnd =>
6743                             Make_Attribute_Reference (Loc,
6744                               Prefix => New_Occurrence_Of (Target_Type, Loc),
6745                               Attribute_Name => Name_Last),
6746                             Right_Opnd => Make_Integer_Literal (Loc, Uint_0))),
6747
6748                     Right_Opnd =>
6749                       Make_Op_Gt (Loc,
6750                         Left_Opnd => Duplicate_Subexpr (N),
6751                         Right_Opnd =>
6752                           Convert_To (Source_Base_Type,
6753                             Make_Attribute_Reference (Loc,
6754                               Prefix => New_Occurrence_Of (Target_Type, Loc),
6755                               Attribute_Name => Name_Last)))),
6756
6757                 Reason => Reason),
6758               Suppress  => All_Checks);
6759
6760          --  Only remaining possibility is that the source is signed and
6761          --  the target is unsigned.
6762
6763          else
6764             pragma Assert (not Is_Unsigned_Type (Source_Base_Type)
6765                             and then Is_Unsigned_Type (Target_Base_Type));
6766
6767             --  If the source is signed and the target is unsigned, then we
6768             --  know that the target is not shorter than the source (otherwise
6769             --  the target base type would be in the source base type range).
6770
6771             --  In other words, the unsigned type is either the same size as
6772             --  the target, or it is larger. It cannot be smaller.
6773
6774             --  Clearly we have an error if the source value is negative since
6775             --  no unsigned type can have negative values. If the source type
6776             --  is non-negative, then the check can be done using the target
6777             --  type.
6778
6779             --    Tnn : constant Target_Base_Type (N) := Target_Type;
6780
6781             --    [constraint_error
6782             --       when N < 0 or else Tnn not in Target_Type];
6783
6784             --  We turn off all checks for the conversion of N to the target
6785             --  base type, since we generate the explicit check to ensure that
6786             --  the value is non-negative
6787
6788             declare
6789                Tnn : constant Entity_Id := Make_Temporary (Loc, 'T', N);
6790
6791             begin
6792                Insert_Actions (N, New_List (
6793                  Make_Object_Declaration (Loc,
6794                    Defining_Identifier => Tnn,
6795                    Object_Definition   =>
6796                      New_Occurrence_Of (Target_Base_Type, Loc),
6797                    Constant_Present    => True,
6798                    Expression          =>
6799                      Make_Unchecked_Type_Conversion (Loc,
6800                        Subtype_Mark =>
6801                          New_Occurrence_Of (Target_Base_Type, Loc),
6802                        Expression   => Duplicate_Subexpr (N))),
6803
6804                  Make_Raise_Constraint_Error (Loc,
6805                    Condition =>
6806                      Make_Or_Else (Loc,
6807                        Left_Opnd =>
6808                          Make_Op_Lt (Loc,
6809                            Left_Opnd  => Duplicate_Subexpr (N),
6810                            Right_Opnd => Make_Integer_Literal (Loc, Uint_0)),
6811
6812                        Right_Opnd =>
6813                          Make_Not_In (Loc,
6814                            Left_Opnd  => New_Occurrence_Of (Tnn, Loc),
6815                            Right_Opnd =>
6816                              New_Occurrence_Of (Target_Type, Loc))),
6817
6818                    Reason     => Reason)),
6819                  Suppress => All_Checks);
6820
6821                --  Set the Etype explicitly, because Insert_Actions may have
6822                --  placed the declaration in the freeze list for an enclosing
6823                --  construct, and thus it is not analyzed yet.
6824
6825                Set_Etype (Tnn, Target_Base_Type);
6826                Rewrite (N, New_Occurrence_Of (Tnn, Loc));
6827             end;
6828          end if;
6829       end if;
6830    end Generate_Range_Check;
6831
6832    ------------------
6833    -- Get_Check_Id --
6834    ------------------
6835
6836    function Get_Check_Id (N : Name_Id) return Check_Id is
6837    begin
6838       --  For standard check name, we can do a direct computation
6839
6840       if N in First_Check_Name .. Last_Check_Name then
6841          return Check_Id (N - (First_Check_Name - 1));
6842
6843       --  For non-standard names added by pragma Check_Name, search table
6844
6845       else
6846          for J in All_Checks + 1 .. Check_Names.Last loop
6847             if Check_Names.Table (J) = N then
6848                return J;
6849             end if;
6850          end loop;
6851       end if;
6852
6853       --  No matching name found
6854
6855       return No_Check_Id;
6856    end Get_Check_Id;
6857
6858    ---------------------
6859    -- Get_Discriminal --
6860    ---------------------
6861
6862    function Get_Discriminal (E : Entity_Id; Bound : Node_Id) return Node_Id is
6863       Loc : constant Source_Ptr := Sloc (E);
6864       D   : Entity_Id;
6865       Sc  : Entity_Id;
6866
6867    begin
6868       --  The bound can be a bona fide parameter of a protected operation,
6869       --  rather than a prival encoded as an in-parameter.
6870
6871       if No (Discriminal_Link (Entity (Bound))) then
6872          return Bound;
6873       end if;
6874
6875       --  Climb the scope stack looking for an enclosing protected type. If
6876       --  we run out of scopes, return the bound itself.
6877
6878       Sc := Scope (E);
6879       while Present (Sc) loop
6880          if Sc = Standard_Standard then
6881             return Bound;
6882          elsif Ekind (Sc) = E_Protected_Type then
6883             exit;
6884          end if;
6885
6886          Sc := Scope (Sc);
6887       end loop;
6888
6889       D := First_Discriminant (Sc);
6890       while Present (D) loop
6891          if Chars (D) = Chars (Bound) then
6892             return New_Occurrence_Of (Discriminal (D), Loc);
6893          end if;
6894
6895          Next_Discriminant (D);
6896       end loop;
6897
6898       return Bound;
6899    end Get_Discriminal;
6900
6901    ----------------------
6902    -- Get_Range_Checks --
6903    ----------------------
6904
6905    function Get_Range_Checks
6906      (Ck_Node    : Node_Id;
6907       Target_Typ : Entity_Id;
6908       Source_Typ : Entity_Id := Empty;
6909       Warn_Node  : Node_Id   := Empty) return Check_Result
6910    is
6911    begin
6912       return
6913         Selected_Range_Checks (Ck_Node, Target_Typ, Source_Typ, Warn_Node);
6914    end Get_Range_Checks;
6915
6916    ------------------
6917    -- Guard_Access --
6918    ------------------
6919
6920    function Guard_Access
6921      (Cond    : Node_Id;
6922       Loc     : Source_Ptr;
6923       Ck_Node : Node_Id) return Node_Id
6924    is
6925    begin
6926       if Nkind (Cond) = N_Or_Else then
6927          Set_Paren_Count (Cond, 1);
6928       end if;
6929
6930       if Nkind (Ck_Node) = N_Allocator then
6931          return Cond;
6932
6933       else
6934          return
6935            Make_And_Then (Loc,
6936              Left_Opnd =>
6937                Make_Op_Ne (Loc,
6938                  Left_Opnd  => Duplicate_Subexpr_No_Checks (Ck_Node),
6939                  Right_Opnd => Make_Null (Loc)),
6940              Right_Opnd => Cond);
6941       end if;
6942    end Guard_Access;
6943
6944    -----------------------------
6945    -- Index_Checks_Suppressed --
6946    -----------------------------
6947
6948    function Index_Checks_Suppressed (E : Entity_Id) return Boolean is
6949    begin
6950       if Present (E) and then Checks_May_Be_Suppressed (E) then
6951          return Is_Check_Suppressed (E, Index_Check);
6952       else
6953          return Scope_Suppress.Suppress (Index_Check);
6954       end if;
6955    end Index_Checks_Suppressed;
6956
6957    ----------------
6958    -- Initialize --
6959    ----------------
6960
6961    procedure Initialize is
6962    begin
6963       for J in Determine_Range_Cache_N'Range loop
6964          Determine_Range_Cache_N (J) := Empty;
6965       end loop;
6966
6967       Check_Names.Init;
6968
6969       for J in Int range 1 .. All_Checks loop
6970          Check_Names.Append (Name_Id (Int (First_Check_Name) + J - 1));
6971       end loop;
6972    end Initialize;
6973
6974    -------------------------
6975    -- Insert_Range_Checks --
6976    -------------------------
6977
6978    procedure Insert_Range_Checks
6979      (Checks       : Check_Result;
6980       Node         : Node_Id;
6981       Suppress_Typ : Entity_Id;
6982       Static_Sloc  : Source_Ptr := No_Location;
6983       Flag_Node    : Node_Id    := Empty;
6984       Do_Before    : Boolean    := False)
6985    is
6986       Internal_Flag_Node   : Node_Id    := Flag_Node;
6987       Internal_Static_Sloc : Source_Ptr := Static_Sloc;
6988
6989       Check_Node : Node_Id;
6990       Checks_On  : constant Boolean :=
6991         (not Index_Checks_Suppressed (Suppress_Typ))
6992          or else (not Range_Checks_Suppressed (Suppress_Typ));
6993
6994    begin
6995       --  For now we just return if Checks_On is false, however this should be
6996       --  enhanced to check for an always True value in the condition and to
6997       --  generate a compilation warning???
6998
6999       if not Expander_Active or not Checks_On then
7000          return;
7001       end if;
7002
7003       if Static_Sloc = No_Location then
7004          Internal_Static_Sloc := Sloc (Node);
7005       end if;
7006
7007       if No (Flag_Node) then
7008          Internal_Flag_Node := Node;
7009       end if;
7010
7011       for J in 1 .. 2 loop
7012          exit when No (Checks (J));
7013
7014          if Nkind (Checks (J)) = N_Raise_Constraint_Error
7015            and then Present (Condition (Checks (J)))
7016          then
7017             if not Has_Dynamic_Range_Check (Internal_Flag_Node) then
7018                Check_Node := Checks (J);
7019                Mark_Rewrite_Insertion (Check_Node);
7020
7021                if Do_Before then
7022                   Insert_Before_And_Analyze (Node, Check_Node);
7023                else
7024                   Insert_After_And_Analyze (Node, Check_Node);
7025                end if;
7026
7027                Set_Has_Dynamic_Range_Check (Internal_Flag_Node);
7028             end if;
7029
7030          else
7031             Check_Node :=
7032               Make_Raise_Constraint_Error (Internal_Static_Sloc,
7033                 Reason => CE_Range_Check_Failed);
7034             Mark_Rewrite_Insertion (Check_Node);
7035
7036             if Do_Before then
7037                Insert_Before_And_Analyze (Node, Check_Node);
7038             else
7039                Insert_After_And_Analyze (Node, Check_Node);
7040             end if;
7041          end if;
7042       end loop;
7043    end Insert_Range_Checks;
7044
7045    ------------------------
7046    -- Insert_Valid_Check --
7047    ------------------------
7048
7049    procedure Insert_Valid_Check
7050      (Expr          : Node_Id;
7051       Related_Id    : Entity_Id := Empty;
7052       Is_Low_Bound  : Boolean   := False;
7053       Is_High_Bound : Boolean   := False)
7054    is
7055       Loc : constant Source_Ptr := Sloc (Expr);
7056       Typ : constant Entity_Id  := Etype (Expr);
7057       Exp : Node_Id;
7058
7059    begin
7060       --  Do not insert if checks off, or if not checking validity or if
7061       --  expression is known to be valid.
7062
7063       if not Validity_Checks_On
7064         or else Range_Or_Validity_Checks_Suppressed (Expr)
7065         or else Expr_Known_Valid (Expr)
7066       then
7067          return;
7068       end if;
7069
7070       --  Do not insert checks within a predicate function. This will arise
7071       --  if the current unit and the predicate function are being compiled
7072       --  with validity checks enabled.
7073
7074       if Present (Predicate_Function (Typ))
7075         and then Current_Scope = Predicate_Function (Typ)
7076       then
7077          return;
7078       end if;
7079
7080       --  If the expression is a packed component of a modular type of the
7081       --  right size, the data is always valid.
7082
7083       if Nkind (Expr) = N_Selected_Component
7084         and then Present (Component_Clause (Entity (Selector_Name (Expr))))
7085         and then Is_Modular_Integer_Type (Typ)
7086         and then Modulus (Typ) = 2 ** Esize (Entity (Selector_Name (Expr)))
7087       then
7088          return;
7089       end if;
7090
7091       --  If we have a checked conversion, then validity check applies to
7092       --  the expression inside the conversion, not the result, since if
7093       --  the expression inside is valid, then so is the conversion result.
7094
7095       Exp := Expr;
7096       while Nkind (Exp) = N_Type_Conversion loop
7097          Exp := Expression (Exp);
7098       end loop;
7099
7100       --  We are about to insert the validity check for Exp. We save and
7101       --  reset the Do_Range_Check flag over this validity check, and then
7102       --  put it back for the final original reference (Exp may be rewritten).
7103
7104       declare
7105          DRC : constant Boolean := Do_Range_Check (Exp);
7106          PV  : Node_Id;
7107          CE  : Node_Id;
7108
7109       begin
7110          Set_Do_Range_Check (Exp, False);
7111
7112          --  Force evaluation to avoid multiple reads for atomic/volatile
7113
7114          --  Note: we set Name_Req to False. We used to set it to True, with
7115          --  the thinking that a name is required as the prefix of the 'Valid
7116          --  call, but in fact the check that the prefix of an attribute is
7117          --  a name is in the parser, and we just don't require it here.
7118          --  Moreover, when we set Name_Req to True, that interfered with the
7119          --  checking for Volatile, since we couldn't just capture the value.
7120
7121          if Is_Entity_Name (Exp)
7122            and then Is_Volatile (Entity (Exp))
7123          then
7124             --  Same reasoning as above for setting Name_Req to False
7125
7126             Force_Evaluation (Exp, Name_Req => False);
7127          end if;
7128
7129          --  Build the prefix for the 'Valid call
7130
7131          PV :=
7132            Duplicate_Subexpr_No_Checks
7133              (Exp           => Exp,
7134               Name_Req      => False,
7135               Related_Id    => Related_Id,
7136               Is_Low_Bound  => Is_Low_Bound,
7137               Is_High_Bound => Is_High_Bound);
7138
7139          --  A rather specialized test. If PV is an analyzed expression which
7140          --  is an indexed component of a packed array that has not been
7141          --  properly expanded, turn off its Analyzed flag to make sure it
7142          --  gets properly reexpanded. If the prefix is an access value,
7143          --  the dereference will be added later.
7144
7145          --  The reason this arises is that Duplicate_Subexpr_No_Checks did
7146          --  an analyze with the old parent pointer. This may point e.g. to
7147          --  a subprogram call, which deactivates this expansion.
7148
7149          if Analyzed (PV)
7150            and then Nkind (PV) = N_Indexed_Component
7151            and then Is_Array_Type (Etype (Prefix (PV)))
7152            and then Present (Packed_Array_Impl_Type (Etype (Prefix (PV))))
7153          then
7154             Set_Analyzed (PV, False);
7155          end if;
7156
7157          --  Build the raise CE node to check for validity. We build a type
7158          --  qualification for the prefix, since it may not be of the form of
7159          --  a name, and we don't care in this context!
7160
7161          CE :=
7162            Make_Raise_Constraint_Error (Loc,
7163              Condition =>
7164                Make_Op_Not (Loc,
7165                  Right_Opnd =>
7166                    Make_Attribute_Reference (Loc,
7167                      Prefix         => PV,
7168                      Attribute_Name => Name_Valid)),
7169              Reason    => CE_Invalid_Data);
7170
7171          --  Insert the validity check. Note that we do this with validity
7172          --  checks turned off, to avoid recursion, we do not want validity
7173          --  checks on the validity checking code itself.
7174
7175          Insert_Action (Expr, CE, Suppress => Validity_Check);
7176
7177          --  If the expression is a reference to an element of a bit-packed
7178          --  array, then it is rewritten as a renaming declaration. If the
7179          --  expression is an actual in a call, it has not been expanded,
7180          --  waiting for the proper point at which to do it. The same happens
7181          --  with renamings, so that we have to force the expansion now. This
7182          --  non-local complication is due to code in exp_ch2,adb, exp_ch4.adb
7183          --  and exp_ch6.adb.
7184
7185          if Is_Entity_Name (Exp)
7186            and then Nkind (Parent (Entity (Exp))) =
7187                                                  N_Object_Renaming_Declaration
7188          then
7189             declare
7190                Old_Exp : constant Node_Id := Name (Parent (Entity (Exp)));
7191             begin
7192                if Nkind (Old_Exp) = N_Indexed_Component
7193                  and then Is_Bit_Packed_Array (Etype (Prefix (Old_Exp)))
7194                then
7195                   Expand_Packed_Element_Reference (Old_Exp);
7196                end if;
7197             end;
7198          end if;
7199
7200          --  Put back the Do_Range_Check flag on the resulting (possibly
7201          --  rewritten) expression.
7202
7203          --  Note: it might be thought that a validity check is not required
7204          --  when a range check is present, but that's not the case, because
7205          --  the back end is allowed to assume for the range check that the
7206          --  operand is within its declared range (an assumption that validity
7207          --  checking is all about NOT assuming).
7208
7209          --  Note: no need to worry about Possible_Local_Raise here, it will
7210          --  already have been called if original node has Do_Range_Check set.
7211
7212          Set_Do_Range_Check (Exp, DRC);
7213       end;
7214    end Insert_Valid_Check;
7215
7216    -------------------------------------
7217    -- Is_Signed_Integer_Arithmetic_Op --
7218    -------------------------------------
7219
7220    function Is_Signed_Integer_Arithmetic_Op (N : Node_Id) return Boolean is
7221    begin
7222       case Nkind (N) is
7223          when N_Op_Abs   | N_Op_Add      | N_Op_Divide   | N_Op_Expon |
7224               N_Op_Minus | N_Op_Mod      | N_Op_Multiply | N_Op_Plus  |
7225               N_Op_Rem   | N_Op_Subtract =>
7226             return Is_Signed_Integer_Type (Etype (N));
7227
7228          when N_If_Expression | N_Case_Expression =>
7229             return Is_Signed_Integer_Type (Etype (N));
7230
7231          when others =>
7232             return False;
7233       end case;
7234    end Is_Signed_Integer_Arithmetic_Op;
7235
7236    ----------------------------------
7237    -- Install_Null_Excluding_Check --
7238    ----------------------------------
7239
7240    procedure Install_Null_Excluding_Check (N : Node_Id) is
7241       Loc : constant Source_Ptr := Sloc (Parent (N));
7242       Typ : constant Entity_Id  := Etype (N);
7243
7244       function Safe_To_Capture_In_Parameter_Value return Boolean;
7245       --  Determines if it is safe to capture Known_Non_Null status for an
7246       --  the entity referenced by node N. The caller ensures that N is indeed
7247       --  an entity name. It is safe to capture the non-null status for an IN
7248       --  parameter when the reference occurs within a declaration that is sure
7249       --  to be executed as part of the declarative region.
7250
7251       procedure Mark_Non_Null;
7252       --  After installation of check, if the node in question is an entity
7253       --  name, then mark this entity as non-null if possible.
7254
7255       function Safe_To_Capture_In_Parameter_Value return Boolean is
7256          E     : constant Entity_Id := Entity (N);
7257          S     : constant Entity_Id := Current_Scope;
7258          S_Par : Node_Id;
7259
7260       begin
7261          if Ekind (E) /= E_In_Parameter then
7262             return False;
7263          end if;
7264
7265          --  Two initial context checks. We must be inside a subprogram body
7266          --  with declarations and reference must not appear in nested scopes.
7267
7268          if (Ekind (S) /= E_Function and then Ekind (S) /= E_Procedure)
7269            or else Scope (E) /= S
7270          then
7271             return False;
7272          end if;
7273
7274          S_Par := Parent (Parent (S));
7275
7276          if Nkind (S_Par) /= N_Subprogram_Body
7277            or else No (Declarations (S_Par))
7278          then
7279             return False;
7280          end if;
7281
7282          declare
7283             N_Decl : Node_Id;
7284             P      : Node_Id;
7285
7286          begin
7287             --  Retrieve the declaration node of N (if any). Note that N
7288             --  may be a part of a complex initialization expression.
7289
7290             P := Parent (N);
7291             N_Decl := Empty;
7292             while Present (P) loop
7293
7294                --  If we have a short circuit form, and we are within the right
7295                --  hand expression, we return false, since the right hand side
7296                --  is not guaranteed to be elaborated.
7297
7298                if Nkind (P) in N_Short_Circuit
7299                  and then N = Right_Opnd (P)
7300                then
7301                   return False;
7302                end if;
7303
7304                --  Similarly, if we are in an if expression and not part of the
7305                --  condition, then we return False, since neither the THEN or
7306                --  ELSE dependent expressions will always be elaborated.
7307
7308                if Nkind (P) = N_If_Expression
7309                  and then N /= First (Expressions (P))
7310                then
7311                   return False;
7312                end if;
7313
7314                --  If within a case expression, and not part of the expression,
7315                --  then return False, since a particular dependent expression
7316                --  may not always be elaborated
7317
7318                if Nkind (P) = N_Case_Expression
7319                  and then N /= Expression (P)
7320                then
7321                   return False;
7322                end if;
7323
7324                --  While traversing the parent chain, if node N belongs to a
7325                --  statement, then it may never appear in a declarative region.
7326
7327                if Nkind (P) in N_Statement_Other_Than_Procedure_Call
7328                  or else Nkind (P) = N_Procedure_Call_Statement
7329                then
7330                   return False;
7331                end if;
7332
7333                --  If we are at a declaration, record it and exit
7334
7335                if Nkind (P) in N_Declaration
7336                  and then Nkind (P) not in N_Subprogram_Specification
7337                then
7338                   N_Decl := P;
7339                   exit;
7340                end if;
7341
7342                P := Parent (P);
7343             end loop;
7344
7345             if No (N_Decl) then
7346                return False;
7347             end if;
7348
7349             return List_Containing (N_Decl) = Declarations (S_Par);
7350          end;
7351       end Safe_To_Capture_In_Parameter_Value;
7352
7353       -------------------
7354       -- Mark_Non_Null --
7355       -------------------
7356
7357       procedure Mark_Non_Null is
7358       begin
7359          --  Only case of interest is if node N is an entity name
7360
7361          if Is_Entity_Name (N) then
7362
7363             --  For sure, we want to clear an indication that this is known to
7364             --  be null, since if we get past this check, it definitely is not.
7365
7366             Set_Is_Known_Null (Entity (N), False);
7367
7368             --  We can mark the entity as known to be non-null if either it is
7369             --  safe to capture the value, or in the case of an IN parameter,
7370             --  which is a constant, if the check we just installed is in the
7371             --  declarative region of the subprogram body. In this latter case,
7372             --  a check is decisive for the rest of the body if the expression
7373             --  is sure to be elaborated, since we know we have to elaborate
7374             --  all declarations before executing the body.
7375
7376             --  Couldn't this always be part of Safe_To_Capture_Value ???
7377
7378             if Safe_To_Capture_Value (N, Entity (N))
7379               or else Safe_To_Capture_In_Parameter_Value
7380             then
7381                Set_Is_Known_Non_Null (Entity (N));
7382             end if;
7383          end if;
7384       end Mark_Non_Null;
7385
7386    --  Start of processing for Install_Null_Excluding_Check
7387
7388    begin
7389       pragma Assert (Is_Access_Type (Typ));
7390
7391       --  No check inside a generic, check will be emitted in instance
7392
7393       if Inside_A_Generic then
7394          return;
7395       end if;
7396
7397       --  No check needed if known to be non-null
7398
7399       if Known_Non_Null (N) then
7400          return;
7401       end if;
7402
7403       --  If known to be null, here is where we generate a compile time check
7404
7405       if Known_Null (N) then
7406
7407          --  Avoid generating warning message inside init procs. In SPARK mode
7408          --  we can go ahead and call Apply_Compile_Time_Constraint_Error
7409          --  since it will be turned into an error in any case.
7410
7411          if (not Inside_Init_Proc or else SPARK_Mode = On)
7412
7413            --  Do not emit the warning within a conditional expression,
7414            --  where the expression might not be evaluated, and the warning
7415            --  appear as extraneous noise.
7416
7417            and then not Within_Case_Or_If_Expression (N)
7418          then
7419             Apply_Compile_Time_Constraint_Error
7420               (N, "null value not allowed here??", CE_Access_Check_Failed);
7421
7422          --  Remaining cases, where we silently insert the raise
7423
7424          else
7425             Insert_Action (N,
7426               Make_Raise_Constraint_Error (Loc,
7427                 Reason => CE_Access_Check_Failed));
7428          end if;
7429
7430          Mark_Non_Null;
7431          return;
7432       end if;
7433
7434       --  If entity is never assigned, for sure a warning is appropriate
7435
7436       if Is_Entity_Name (N) then
7437          Check_Unset_Reference (N);
7438       end if;
7439
7440       --  No check needed if checks are suppressed on the range. Note that we
7441       --  don't set Is_Known_Non_Null in this case (we could legitimately do
7442       --  so, since the program is erroneous, but we don't like to casually
7443       --  propagate such conclusions from erroneosity).
7444
7445       if Access_Checks_Suppressed (Typ) then
7446          return;
7447       end if;
7448
7449       --  No check needed for access to concurrent record types generated by
7450       --  the expander. This is not just an optimization (though it does indeed
7451       --  remove junk checks). It also avoids generation of junk warnings.
7452
7453       if Nkind (N) in N_Has_Chars
7454         and then Chars (N) = Name_uObject
7455         and then Is_Concurrent_Record_Type
7456                    (Directly_Designated_Type (Etype (N)))
7457       then
7458          return;
7459       end if;
7460
7461       --  No check needed in interface thunks since the runtime check is
7462       --  already performed at the caller side.
7463
7464       if Is_Thunk (Current_Scope) then
7465          return;
7466       end if;
7467
7468       --  No check needed for the Get_Current_Excep.all.all idiom generated by
7469       --  the expander within exception handlers, since we know that the value
7470       --  can never be null.
7471
7472       --  Is this really the right way to do this? Normally we generate such
7473       --  code in the expander with checks off, and that's how we suppress this
7474       --  kind of junk check ???
7475
7476       if Nkind (N) = N_Function_Call
7477         and then Nkind (Name (N)) = N_Explicit_Dereference
7478         and then Nkind (Prefix (Name (N))) = N_Identifier
7479         and then Is_RTE (Entity (Prefix (Name (N))), RE_Get_Current_Excep)
7480       then
7481          return;
7482       end if;
7483
7484       --  Otherwise install access check
7485
7486       Insert_Action (N,
7487         Make_Raise_Constraint_Error (Loc,
7488           Condition =>
7489             Make_Op_Eq (Loc,
7490               Left_Opnd  => Duplicate_Subexpr_Move_Checks (N),
7491               Right_Opnd => Make_Null (Loc)),
7492           Reason => CE_Access_Check_Failed));
7493
7494       Mark_Non_Null;
7495    end Install_Null_Excluding_Check;
7496
7497    --------------------------
7498    -- Install_Static_Check --
7499    --------------------------
7500
7501    procedure Install_Static_Check (R_Cno : Node_Id; Loc : Source_Ptr) is
7502       Stat : constant Boolean   := Is_OK_Static_Expression (R_Cno);
7503       Typ  : constant Entity_Id := Etype (R_Cno);
7504
7505    begin
7506       Rewrite (R_Cno,
7507         Make_Raise_Constraint_Error (Loc,
7508           Reason => CE_Range_Check_Failed));
7509       Set_Analyzed (R_Cno);
7510       Set_Etype (R_Cno, Typ);
7511       Set_Raises_Constraint_Error (R_Cno);
7512       Set_Is_Static_Expression (R_Cno, Stat);
7513
7514       --  Now deal with possible local raise handling
7515
7516       Possible_Local_Raise (R_Cno, Standard_Constraint_Error);
7517    end Install_Static_Check;
7518
7519    -------------------------
7520    -- Is_Check_Suppressed --
7521    -------------------------
7522
7523    function Is_Check_Suppressed (E : Entity_Id; C : Check_Id) return Boolean is
7524       Ptr : Suppress_Stack_Entry_Ptr;
7525
7526    begin
7527       --  First search the local entity suppress stack. We search this from the
7528       --  top of the stack down so that we get the innermost entry that applies
7529       --  to this case if there are nested entries.
7530
7531       Ptr := Local_Suppress_Stack_Top;
7532       while Ptr /= null loop
7533          if (Ptr.Entity = Empty or else Ptr.Entity = E)
7534            and then (Ptr.Check = All_Checks or else Ptr.Check = C)
7535          then
7536             return Ptr.Suppress;
7537          end if;
7538
7539          Ptr := Ptr.Prev;
7540       end loop;
7541
7542       --  Now search the global entity suppress table for a matching entry.
7543       --  We also search this from the top down so that if there are multiple
7544       --  pragmas for the same entity, the last one applies (not clear what
7545       --  or whether the RM specifies this handling, but it seems reasonable).
7546
7547       Ptr := Global_Suppress_Stack_Top;
7548       while Ptr /= null loop
7549          if (Ptr.Entity = Empty or else Ptr.Entity = E)
7550            and then (Ptr.Check = All_Checks or else Ptr.Check = C)
7551          then
7552             return Ptr.Suppress;
7553          end if;
7554
7555          Ptr := Ptr.Prev;
7556       end loop;
7557
7558       --  If we did not find a matching entry, then use the normal scope
7559       --  suppress value after all (actually this will be the global setting
7560       --  since it clearly was not overridden at any point). For a predefined
7561       --  check, we test the specific flag. For a user defined check, we check
7562       --  the All_Checks flag. The Overflow flag requires special handling to
7563       --  deal with the General vs Assertion case
7564
7565       if C = Overflow_Check then
7566          return Overflow_Checks_Suppressed (Empty);
7567       elsif C in Predefined_Check_Id then
7568          return Scope_Suppress.Suppress (C);
7569       else
7570          return Scope_Suppress.Suppress (All_Checks);
7571       end if;
7572    end Is_Check_Suppressed;
7573
7574    ---------------------
7575    -- Kill_All_Checks --
7576    ---------------------
7577
7578    procedure Kill_All_Checks is
7579    begin
7580       if Debug_Flag_CC then
7581          w ("Kill_All_Checks");
7582       end if;
7583
7584       --  We reset the number of saved checks to zero, and also modify all
7585       --  stack entries for statement ranges to indicate that the number of
7586       --  checks at each level is now zero.
7587
7588       Num_Saved_Checks := 0;
7589
7590       --  Note: the Int'Min here avoids any possibility of J being out of
7591       --  range when called from e.g. Conditional_Statements_Begin.
7592
7593       for J in 1 .. Int'Min (Saved_Checks_TOS, Saved_Checks_Stack'Last) loop
7594          Saved_Checks_Stack (J) := 0;
7595       end loop;
7596    end Kill_All_Checks;
7597
7598    -----------------
7599    -- Kill_Checks --
7600    -----------------
7601
7602    procedure Kill_Checks (V : Entity_Id) is
7603    begin
7604       if Debug_Flag_CC then
7605          w ("Kill_Checks for entity", Int (V));
7606       end if;
7607
7608       for J in 1 .. Num_Saved_Checks loop
7609          if Saved_Checks (J).Entity = V then
7610             if Debug_Flag_CC then
7611                w ("   Checks killed for saved check ", J);
7612             end if;
7613
7614             Saved_Checks (J).Killed := True;
7615          end if;
7616       end loop;
7617    end Kill_Checks;
7618
7619    ------------------------------
7620    -- Length_Checks_Suppressed --
7621    ------------------------------
7622
7623    function Length_Checks_Suppressed (E : Entity_Id) return Boolean is
7624    begin
7625       if Present (E) and then Checks_May_Be_Suppressed (E) then
7626          return Is_Check_Suppressed (E, Length_Check);
7627       else
7628          return Scope_Suppress.Suppress (Length_Check);
7629       end if;
7630    end Length_Checks_Suppressed;
7631
7632    -----------------------
7633    -- Make_Bignum_Block --
7634    -----------------------
7635
7636    function Make_Bignum_Block (Loc : Source_Ptr) return Node_Id is
7637       M : constant Entity_Id := Make_Defining_Identifier (Loc, Name_uM);
7638    begin
7639       return
7640         Make_Block_Statement (Loc,
7641           Declarations               =>
7642             New_List (Build_SS_Mark_Call (Loc, M)),
7643           Handled_Statement_Sequence =>
7644             Make_Handled_Sequence_Of_Statements (Loc,
7645               Statements => New_List (Build_SS_Release_Call (Loc, M))));
7646    end Make_Bignum_Block;
7647
7648    ----------------------------------
7649    -- Minimize_Eliminate_Overflows --
7650    ----------------------------------
7651
7652    --  This is a recursive routine that is called at the top of an expression
7653    --  tree to properly process overflow checking for a whole subtree by making
7654    --  recursive calls to process operands. This processing may involve the use
7655    --  of bignum or long long integer arithmetic, which will change the types
7656    --  of operands and results. That's why we can't do this bottom up (since
7657    --  it would interfere with semantic analysis).
7658
7659    --  What happens is that if MINIMIZED/ELIMINATED mode is in effect then
7660    --  the operator expansion routines, as well as the expansion routines for
7661    --  if/case expression, do nothing (for the moment) except call the routine
7662    --  to apply the overflow check (Apply_Arithmetic_Overflow_Check). That
7663    --  routine does nothing for non top-level nodes, so at the point where the
7664    --  call is made for the top level node, the entire expression subtree has
7665    --  not been expanded, or processed for overflow. All that has to happen as
7666    --  a result of the top level call to this routine.
7667
7668    --  As noted above, the overflow processing works by making recursive calls
7669    --  for the operands, and figuring out what to do, based on the processing
7670    --  of these operands (e.g. if a bignum operand appears, the parent op has
7671    --  to be done in bignum mode), and the determined ranges of the operands.
7672
7673    --  After possible rewriting of a constituent subexpression node, a call is
7674    --  made to either reexpand the node (if nothing has changed) or reanalyze
7675    --  the node (if it has been modified by the overflow check processing). The
7676    --  Analyzed_Flag is set to False before the reexpand/reanalyze. To avoid
7677    --  a recursive call into the whole overflow apparatus, an important rule
7678    --  for this call is that the overflow handling mode must be temporarily set
7679    --  to STRICT.
7680
7681    procedure Minimize_Eliminate_Overflows
7682      (N         : Node_Id;
7683       Lo        : out Uint;
7684       Hi        : out Uint;
7685       Top_Level : Boolean)
7686    is
7687       Rtyp : constant Entity_Id := Etype (N);
7688       pragma Assert (Is_Signed_Integer_Type (Rtyp));
7689       --  Result type, must be a signed integer type
7690
7691       Check_Mode : constant Overflow_Mode_Type := Overflow_Check_Mode;
7692       pragma Assert (Check_Mode in Minimized_Or_Eliminated);
7693
7694       Loc : constant Source_Ptr := Sloc (N);
7695
7696       Rlo, Rhi : Uint;
7697       --  Ranges of values for right operand (operator case)
7698
7699       Llo, Lhi : Uint;
7700       --  Ranges of values for left operand (operator case)
7701
7702       LLIB : constant Entity_Id := Base_Type (Standard_Long_Long_Integer);
7703       --  Operands and results are of this type when we convert
7704
7705       LLLo : constant Uint := Intval (Type_Low_Bound  (LLIB));
7706       LLHi : constant Uint := Intval (Type_High_Bound (LLIB));
7707       --  Bounds of Long_Long_Integer
7708
7709       Binary : constant Boolean := Nkind (N) in N_Binary_Op;
7710       --  Indicates binary operator case
7711
7712       OK : Boolean;
7713       --  Used in call to Determine_Range
7714
7715       Bignum_Operands : Boolean;
7716       --  Set True if one or more operands is already of type Bignum, meaning
7717       --  that for sure (regardless of Top_Level setting) we are committed to
7718       --  doing the operation in Bignum mode (or in the case of a case or if
7719       --  expression, converting all the dependent expressions to Bignum).
7720
7721       Long_Long_Integer_Operands : Boolean;
7722       --  Set True if one or more operands is already of type Long_Long_Integer
7723       --  which means that if the result is known to be in the result type
7724       --  range, then we must convert such operands back to the result type.
7725
7726       procedure Reanalyze (Typ : Entity_Id; Suppress : Boolean := False);
7727       --  This is called when we have modified the node and we therefore need
7728       --  to reanalyze it. It is important that we reset the mode to STRICT for
7729       --  this reanalysis, since if we leave it in MINIMIZED or ELIMINATED mode
7730       --  we would reenter this routine recursively which would not be good.
7731       --  The argument Suppress is set True if we also want to suppress
7732       --  overflow checking for the reexpansion (this is set when we know
7733       --  overflow is not possible). Typ is the type for the reanalysis.
7734
7735       procedure Reexpand (Suppress : Boolean := False);
7736       --  This is like Reanalyze, but does not do the Analyze step, it only
7737       --  does a reexpansion. We do this reexpansion in STRICT mode, so that
7738       --  instead of reentering the MINIMIZED/ELIMINATED mode processing, we
7739       --  follow the normal expansion path (e.g. converting A**4 to A**2**2).
7740       --  Note that skipping reanalysis is not just an optimization, testing
7741       --  has showed up several complex cases in which reanalyzing an already
7742       --  analyzed node causes incorrect behavior.
7743
7744       function In_Result_Range return Boolean;
7745       --  Returns True iff Lo .. Hi are within range of the result type
7746
7747       procedure Max (A : in out Uint; B : Uint);
7748       --  If A is No_Uint, sets A to B, else to UI_Max (A, B)
7749
7750       procedure Min (A : in out Uint; B : Uint);
7751       --  If A is No_Uint, sets A to B, else to UI_Min (A, B)
7752
7753       ---------------------
7754       -- In_Result_Range --
7755       ---------------------
7756
7757       function In_Result_Range return Boolean is
7758       begin
7759          if Lo = No_Uint or else Hi = No_Uint then
7760             return False;
7761
7762          elsif Is_OK_Static_Subtype (Etype (N)) then
7763             return Lo >= Expr_Value (Type_Low_Bound  (Rtyp))
7764                      and then
7765                    Hi <= Expr_Value (Type_High_Bound (Rtyp));
7766
7767          else
7768             return Lo >= Expr_Value (Type_Low_Bound  (Base_Type (Rtyp)))
7769                      and then
7770                    Hi <= Expr_Value (Type_High_Bound (Base_Type (Rtyp)));
7771          end if;
7772       end In_Result_Range;
7773
7774       ---------
7775       -- Max --
7776       ---------
7777
7778       procedure Max (A : in out Uint; B : Uint) is
7779       begin
7780          if A = No_Uint or else B > A then
7781             A := B;
7782          end if;
7783       end Max;
7784
7785       ---------
7786       -- Min --
7787       ---------
7788
7789       procedure Min (A : in out Uint; B : Uint) is
7790       begin
7791          if A = No_Uint or else B < A then
7792             A := B;
7793          end if;
7794       end Min;
7795
7796       ---------------
7797       -- Reanalyze --
7798       ---------------
7799
7800       procedure Reanalyze (Typ : Entity_Id; Suppress : Boolean := False) is
7801          Svg : constant Overflow_Mode_Type :=
7802                  Scope_Suppress.Overflow_Mode_General;
7803          Sva : constant Overflow_Mode_Type :=
7804                  Scope_Suppress.Overflow_Mode_Assertions;
7805          Svo : constant Boolean             :=
7806                  Scope_Suppress.Suppress (Overflow_Check);
7807
7808       begin
7809          Scope_Suppress.Overflow_Mode_General    := Strict;
7810          Scope_Suppress.Overflow_Mode_Assertions := Strict;
7811
7812          if Suppress then
7813             Scope_Suppress.Suppress (Overflow_Check) := True;
7814          end if;
7815
7816          Analyze_And_Resolve (N, Typ);
7817
7818          Scope_Suppress.Suppress (Overflow_Check) := Svo;
7819          Scope_Suppress.Overflow_Mode_General     := Svg;
7820          Scope_Suppress.Overflow_Mode_Assertions  := Sva;
7821       end Reanalyze;
7822
7823       --------------
7824       -- Reexpand --
7825       --------------
7826
7827       procedure Reexpand (Suppress : Boolean := False) is
7828          Svg : constant Overflow_Mode_Type :=
7829                  Scope_Suppress.Overflow_Mode_General;
7830          Sva : constant Overflow_Mode_Type :=
7831                  Scope_Suppress.Overflow_Mode_Assertions;
7832          Svo : constant Boolean             :=
7833                  Scope_Suppress.Suppress (Overflow_Check);
7834
7835       begin
7836          Scope_Suppress.Overflow_Mode_General    := Strict;
7837          Scope_Suppress.Overflow_Mode_Assertions := Strict;
7838          Set_Analyzed (N, False);
7839
7840          if Suppress then
7841             Scope_Suppress.Suppress (Overflow_Check) := True;
7842          end if;
7843
7844          Expand (N);
7845
7846          Scope_Suppress.Suppress (Overflow_Check) := Svo;
7847          Scope_Suppress.Overflow_Mode_General     := Svg;
7848          Scope_Suppress.Overflow_Mode_Assertions  := Sva;
7849       end Reexpand;
7850
7851    --  Start of processing for Minimize_Eliminate_Overflows
7852
7853    begin
7854       --  Case where we do not have a signed integer arithmetic operation
7855
7856       if not Is_Signed_Integer_Arithmetic_Op (N) then
7857
7858          --  Use the normal Determine_Range routine to get the range. We
7859          --  don't require operands to be valid, invalid values may result in
7860          --  rubbish results where the result has not been properly checked for
7861          --  overflow, that's fine.
7862
7863          Determine_Range (N, OK, Lo, Hi, Assume_Valid => False);
7864
7865          --  If Determine_Range did not work (can this in fact happen? Not
7866          --  clear but might as well protect), use type bounds.
7867
7868          if not OK then
7869             Lo := Intval (Type_Low_Bound  (Base_Type (Etype (N))));
7870             Hi := Intval (Type_High_Bound (Base_Type (Etype (N))));
7871          end if;
7872
7873          --  If we don't have a binary operator, all we have to do is to set
7874          --  the Hi/Lo range, so we are done.
7875
7876          return;
7877
7878       --  Processing for if expression
7879
7880       elsif Nkind (N) = N_If_Expression then
7881          declare
7882             Then_DE : constant Node_Id := Next (First (Expressions (N)));
7883             Else_DE : constant Node_Id := Next (Then_DE);
7884
7885          begin
7886             Bignum_Operands := False;
7887
7888             Minimize_Eliminate_Overflows
7889               (Then_DE, Lo, Hi, Top_Level => False);
7890
7891             if Lo = No_Uint then
7892                Bignum_Operands := True;
7893             end if;
7894
7895             Minimize_Eliminate_Overflows
7896               (Else_DE, Rlo, Rhi, Top_Level => False);
7897
7898             if Rlo = No_Uint then
7899                Bignum_Operands := True;
7900             else
7901                Long_Long_Integer_Operands :=
7902                  Etype (Then_DE) = LLIB or else Etype (Else_DE) = LLIB;
7903
7904                Min (Lo, Rlo);
7905                Max (Hi, Rhi);
7906             end if;
7907
7908             --  If at least one of our operands is now Bignum, we must rebuild
7909             --  the if expression to use Bignum operands. We will analyze the
7910             --  rebuilt if expression with overflow checks off, since once we
7911             --  are in bignum mode, we are all done with overflow checks.
7912
7913             if Bignum_Operands then
7914                Rewrite (N,
7915                  Make_If_Expression (Loc,
7916                    Expressions => New_List (
7917                      Remove_Head (Expressions (N)),
7918                      Convert_To_Bignum (Then_DE),
7919                      Convert_To_Bignum (Else_DE)),
7920                    Is_Elsif    => Is_Elsif (N)));
7921
7922                Reanalyze (RTE (RE_Bignum), Suppress => True);
7923
7924             --  If we have no Long_Long_Integer operands, then we are in result
7925             --  range, since it means that none of our operands felt the need
7926             --  to worry about overflow (otherwise it would have already been
7927             --  converted to long long integer or bignum). We reexpand to
7928             --  complete the expansion of the if expression (but we do not
7929             --  need to reanalyze).
7930
7931             elsif not Long_Long_Integer_Operands then
7932                Set_Do_Overflow_Check (N, False);
7933                Reexpand;
7934
7935             --  Otherwise convert us to long long integer mode. Note that we
7936             --  don't need any further overflow checking at this level.
7937
7938             else
7939                Convert_To_And_Rewrite (LLIB, Then_DE);
7940                Convert_To_And_Rewrite (LLIB, Else_DE);
7941                Set_Etype (N, LLIB);
7942
7943                --  Now reanalyze with overflow checks off
7944
7945                Set_Do_Overflow_Check (N, False);
7946                Reanalyze (LLIB, Suppress => True);
7947             end if;
7948          end;
7949
7950          return;
7951
7952       --  Here for case expression
7953
7954       elsif Nkind (N) = N_Case_Expression then
7955          Bignum_Operands := False;
7956          Long_Long_Integer_Operands := False;
7957
7958          declare
7959             Alt : Node_Id;
7960
7961          begin
7962             --  Loop through expressions applying recursive call
7963
7964             Alt := First (Alternatives (N));
7965             while Present (Alt) loop
7966                declare
7967                   Aexp : constant Node_Id := Expression (Alt);
7968
7969                begin
7970                   Minimize_Eliminate_Overflows
7971                     (Aexp, Lo, Hi, Top_Level => False);
7972
7973                   if Lo = No_Uint then
7974                      Bignum_Operands := True;
7975                   elsif Etype (Aexp) = LLIB then
7976                      Long_Long_Integer_Operands := True;
7977                   end if;
7978                end;
7979
7980                Next (Alt);
7981             end loop;
7982
7983             --  If we have no bignum or long long integer operands, it means
7984             --  that none of our dependent expressions could raise overflow.
7985             --  In this case, we simply return with no changes except for
7986             --  resetting the overflow flag, since we are done with overflow
7987             --  checks for this node. We will reexpand to get the needed
7988             --  expansion for the case expression, but we do not need to
7989             --  reanalyze, since nothing has changed.
7990
7991             if not (Bignum_Operands or Long_Long_Integer_Operands) then
7992                Set_Do_Overflow_Check (N, False);
7993                Reexpand (Suppress => True);
7994
7995             --  Otherwise we are going to rebuild the case expression using
7996             --  either bignum or long long integer operands throughout.
7997
7998             else
7999                declare
8000                   Rtype    : Entity_Id;
8001                   New_Alts : List_Id;
8002                   New_Exp  : Node_Id;
8003
8004                begin
8005                   New_Alts := New_List;
8006                   Alt := First (Alternatives (N));
8007                   while Present (Alt) loop
8008                      if Bignum_Operands then
8009                         New_Exp := Convert_To_Bignum (Expression (Alt));
8010                         Rtype   := RTE (RE_Bignum);
8011                      else
8012                         New_Exp := Convert_To (LLIB, Expression (Alt));
8013                         Rtype   := LLIB;
8014                      end if;
8015
8016                      Append_To (New_Alts,
8017                        Make_Case_Expression_Alternative (Sloc (Alt),
8018                          Actions          => No_List,
8019                          Discrete_Choices => Discrete_Choices (Alt),
8020                          Expression       => New_Exp));
8021
8022                      Next (Alt);
8023                   end loop;
8024
8025                   Rewrite (N,
8026                     Make_Case_Expression (Loc,
8027                       Expression   => Expression (N),
8028                       Alternatives => New_Alts));
8029
8030                   Reanalyze (Rtype, Suppress => True);
8031                end;
8032             end if;
8033          end;
8034
8035          return;
8036       end if;
8037
8038       --  If we have an arithmetic operator we make recursive calls on the
8039       --  operands to get the ranges (and to properly process the subtree
8040       --  that lies below us).
8041
8042       Minimize_Eliminate_Overflows
8043         (Right_Opnd (N), Rlo, Rhi, Top_Level => False);
8044
8045       if Binary then
8046          Minimize_Eliminate_Overflows
8047            (Left_Opnd (N), Llo, Lhi, Top_Level => False);
8048       end if;
8049
8050       --  Record if we have Long_Long_Integer operands
8051
8052       Long_Long_Integer_Operands :=
8053         Etype (Right_Opnd (N)) = LLIB
8054           or else (Binary and then Etype (Left_Opnd (N)) = LLIB);
8055
8056       --  If either operand is a bignum, then result will be a bignum and we
8057       --  don't need to do any range analysis. As previously discussed we could
8058       --  do range analysis in such cases, but it could mean working with giant
8059       --  numbers at compile time for very little gain (the number of cases
8060       --  in which we could slip back from bignum mode is small).
8061
8062       if Rlo = No_Uint or else (Binary and then Llo = No_Uint) then
8063          Lo := No_Uint;
8064          Hi := No_Uint;
8065          Bignum_Operands := True;
8066
8067       --  Otherwise compute result range
8068
8069       else
8070          Bignum_Operands := False;
8071
8072          case Nkind (N) is
8073
8074             --  Absolute value
8075
8076             when N_Op_Abs =>
8077                Lo := Uint_0;
8078                Hi := UI_Max (abs Rlo, abs Rhi);
8079
8080             --  Addition
8081
8082             when N_Op_Add =>
8083                Lo := Llo + Rlo;
8084                Hi := Lhi + Rhi;
8085
8086             --  Division
8087
8088             when N_Op_Divide =>
8089
8090                --  If the right operand can only be zero, set 0..0
8091
8092                if Rlo = 0 and then Rhi = 0 then
8093                   Lo := Uint_0;
8094                   Hi := Uint_0;
8095
8096                --  Possible bounds of division must come from dividing end
8097                --  values of the input ranges (four possibilities), provided
8098                --  zero is not included in the possible values of the right
8099                --  operand.
8100
8101                --  Otherwise, we just consider two intervals of values for
8102                --  the right operand: the interval of negative values (up to
8103                --  -1) and the interval of positive values (starting at 1).
8104                --  Since division by 1 is the identity, and division by -1
8105                --  is negation, we get all possible bounds of division in that
8106                --  case by considering:
8107                --    - all values from the division of end values of input
8108                --      ranges;
8109                --    - the end values of the left operand;
8110                --    - the negation of the end values of the left operand.
8111
8112                else
8113                   declare
8114                      Mrk : constant Uintp.Save_Mark := Mark;
8115                      --  Mark so we can release the RR and Ev values
8116
8117                      Ev1 : Uint;
8118                      Ev2 : Uint;
8119                      Ev3 : Uint;
8120                      Ev4 : Uint;
8121
8122                   begin
8123                      --  Discard extreme values of zero for the divisor, since
8124                      --  they will simply result in an exception in any case.
8125
8126                      if Rlo = 0 then
8127                         Rlo := Uint_1;
8128                      elsif Rhi = 0 then
8129                         Rhi := -Uint_1;
8130                      end if;
8131
8132                      --  Compute possible bounds coming from dividing end
8133                      --  values of the input ranges.
8134
8135                      Ev1 := Llo / Rlo;
8136                      Ev2 := Llo / Rhi;
8137                      Ev3 := Lhi / Rlo;
8138                      Ev4 := Lhi / Rhi;
8139
8140                      Lo := UI_Min (UI_Min (Ev1, Ev2), UI_Min (Ev3, Ev4));
8141                      Hi := UI_Max (UI_Max (Ev1, Ev2), UI_Max (Ev3, Ev4));
8142
8143                      --  If the right operand can be both negative or positive,
8144                      --  include the end values of the left operand in the
8145                      --  extreme values, as well as their negation.
8146
8147                      if Rlo < 0 and then Rhi > 0 then
8148                         Ev1 := Llo;
8149                         Ev2 := -Llo;
8150                         Ev3 := Lhi;
8151                         Ev4 := -Lhi;
8152
8153                         Min (Lo,
8154                              UI_Min (UI_Min (Ev1, Ev2), UI_Min (Ev3, Ev4)));
8155                         Max (Hi,
8156                              UI_Max (UI_Max (Ev1, Ev2), UI_Max (Ev3, Ev4)));
8157                      end if;
8158
8159                      --  Release the RR and Ev values
8160
8161                      Release_And_Save (Mrk, Lo, Hi);
8162                   end;
8163                end if;
8164
8165             --  Exponentiation
8166
8167             when N_Op_Expon =>
8168
8169                --  Discard negative values for the exponent, since they will
8170                --  simply result in an exception in any case.
8171
8172                if Rhi < 0 then
8173                   Rhi := Uint_0;
8174                elsif Rlo < 0 then
8175                   Rlo := Uint_0;
8176                end if;
8177
8178                --  Estimate number of bits in result before we go computing
8179                --  giant useless bounds. Basically the number of bits in the
8180                --  result is the number of bits in the base multiplied by the
8181                --  value of the exponent. If this is big enough that the result
8182                --  definitely won't fit in Long_Long_Integer, switch to bignum
8183                --  mode immediately, and avoid computing giant bounds.
8184
8185                --  The comparison here is approximate, but conservative, it
8186                --  only clicks on cases that are sure to exceed the bounds.
8187
8188                if Num_Bits (UI_Max (abs Llo, abs Lhi)) * Rhi + 1 > 100 then
8189                   Lo := No_Uint;
8190                   Hi := No_Uint;
8191
8192                --  If right operand is zero then result is 1
8193
8194                elsif Rhi = 0 then
8195                   Lo := Uint_1;
8196                   Hi := Uint_1;
8197
8198                else
8199                   --  High bound comes either from exponentiation of largest
8200                   --  positive value to largest exponent value, or from
8201                   --  the exponentiation of most negative value to an
8202                   --  even exponent.
8203
8204                   declare
8205                      Hi1, Hi2 : Uint;
8206
8207                   begin
8208                      if Lhi > 0 then
8209                         Hi1 := Lhi ** Rhi;
8210                      else
8211                         Hi1 := Uint_0;
8212                      end if;
8213
8214                      if Llo < 0 then
8215                         if Rhi mod 2 = 0 then
8216                            Hi2 := Llo ** Rhi;
8217                         else
8218                            Hi2 := Llo ** (Rhi - 1);
8219                         end if;
8220                      else
8221                         Hi2 := Uint_0;
8222                      end if;
8223
8224                      Hi := UI_Max (Hi1, Hi2);
8225                   end;
8226
8227                   --  Result can only be negative if base can be negative
8228
8229                   if Llo < 0 then
8230                      if Rhi mod 2 = 0 then
8231                         Lo := Llo ** (Rhi - 1);
8232                      else
8233                         Lo := Llo ** Rhi;
8234                      end if;
8235
8236                   --  Otherwise low bound is minimum ** minimum
8237
8238                   else
8239                      Lo := Llo ** Rlo;
8240                   end if;
8241                end if;
8242
8243             --  Negation
8244
8245             when N_Op_Minus =>
8246                Lo := -Rhi;
8247                Hi := -Rlo;
8248
8249             --  Mod
8250
8251             when N_Op_Mod =>
8252                declare
8253                   Maxabs : constant Uint := UI_Max (abs Rlo, abs Rhi) - 1;
8254                   --  This is the maximum absolute value of the result
8255
8256                begin
8257                   Lo := Uint_0;
8258                   Hi := Uint_0;
8259
8260                   --  The result depends only on the sign and magnitude of
8261                   --  the right operand, it does not depend on the sign or
8262                   --  magnitude of the left operand.
8263
8264                   if Rlo < 0 then
8265                      Lo := -Maxabs;
8266                   end if;
8267
8268                   if Rhi > 0 then
8269                      Hi := Maxabs;
8270                   end if;
8271                end;
8272
8273             --  Multiplication
8274
8275             when N_Op_Multiply =>
8276
8277                --  Possible bounds of multiplication must come from multiplying
8278                --  end values of the input ranges (four possibilities).
8279
8280                declare
8281                   Mrk : constant Uintp.Save_Mark := Mark;
8282                   --  Mark so we can release the Ev values
8283
8284                   Ev1 : constant Uint := Llo * Rlo;
8285                   Ev2 : constant Uint := Llo * Rhi;
8286                   Ev3 : constant Uint := Lhi * Rlo;
8287                   Ev4 : constant Uint := Lhi * Rhi;
8288
8289                begin
8290                   Lo := UI_Min (UI_Min (Ev1, Ev2), UI_Min (Ev3, Ev4));
8291                   Hi := UI_Max (UI_Max (Ev1, Ev2), UI_Max (Ev3, Ev4));
8292
8293                   --  Release the Ev values
8294
8295                   Release_And_Save (Mrk, Lo, Hi);
8296                end;
8297
8298             --  Plus operator (affirmation)
8299
8300             when N_Op_Plus =>
8301                Lo := Rlo;
8302                Hi := Rhi;
8303
8304             --  Remainder
8305
8306             when N_Op_Rem =>
8307                declare
8308                   Maxabs : constant Uint := UI_Max (abs Rlo, abs Rhi) - 1;
8309                   --  This is the maximum absolute value of the result. Note
8310                   --  that the result range does not depend on the sign of the
8311                   --  right operand.
8312
8313                begin
8314                   Lo := Uint_0;
8315                   Hi := Uint_0;
8316
8317                   --  Case of left operand negative, which results in a range
8318                   --  of -Maxabs .. 0 for those negative values. If there are
8319                   --  no negative values then Lo value of result is always 0.
8320
8321                   if Llo < 0 then
8322                      Lo := -Maxabs;
8323                   end if;
8324
8325                   --  Case of left operand positive
8326
8327                   if Lhi > 0 then
8328                      Hi := Maxabs;
8329                   end if;
8330                end;
8331
8332             --  Subtract
8333
8334             when N_Op_Subtract =>
8335                Lo := Llo - Rhi;
8336                Hi := Lhi - Rlo;
8337
8338             --  Nothing else should be possible
8339
8340             when others =>
8341                raise Program_Error;
8342          end case;
8343       end if;
8344
8345       --  Here for the case where we have not rewritten anything (no bignum
8346       --  operands or long long integer operands), and we know the result.
8347       --  If we know we are in the result range, and we do not have Bignum
8348       --  operands or Long_Long_Integer operands, we can just reexpand with
8349       --  overflow checks turned off (since we know we cannot have overflow).
8350       --  As always the reexpansion is required to complete expansion of the
8351       --  operator, but we do not need to reanalyze, and we prevent recursion
8352       --  by suppressing the check.
8353
8354       if not (Bignum_Operands or Long_Long_Integer_Operands)
8355         and then In_Result_Range
8356       then
8357          Set_Do_Overflow_Check (N, False);
8358          Reexpand (Suppress => True);
8359          return;
8360
8361       --  Here we know that we are not in the result range, and in the general
8362       --  case we will move into either the Bignum or Long_Long_Integer domain
8363       --  to compute the result. However, there is one exception. If we are
8364       --  at the top level, and we do not have Bignum or Long_Long_Integer
8365       --  operands, we will have to immediately convert the result back to
8366       --  the result type, so there is no point in Bignum/Long_Long_Integer
8367       --  fiddling.
8368
8369       elsif Top_Level
8370         and then not (Bignum_Operands or Long_Long_Integer_Operands)
8371
8372         --  One further refinement. If we are at the top level, but our parent
8373         --  is a type conversion, then go into bignum or long long integer node
8374         --  since the result will be converted to that type directly without
8375         --  going through the result type, and we may avoid an overflow. This
8376         --  is the case for example of Long_Long_Integer (A ** 4), where A is
8377         --  of type Integer, and the result A ** 4 fits in Long_Long_Integer
8378         --  but does not fit in Integer.
8379
8380         and then Nkind (Parent (N)) /= N_Type_Conversion
8381       then
8382          --  Here keep original types, but we need to complete analysis
8383
8384          --  One subtlety. We can't just go ahead and do an analyze operation
8385          --  here because it will cause recursion into the whole MINIMIZED/
8386          --  ELIMINATED overflow processing which is not what we want. Here
8387          --  we are at the top level, and we need a check against the result
8388          --  mode (i.e. we want to use STRICT mode). So do exactly that.
8389          --  Also, we have not modified the node, so this is a case where
8390          --  we need to reexpand, but not reanalyze.
8391
8392          Reexpand;
8393          return;
8394
8395       --  Cases where we do the operation in Bignum mode. This happens either
8396       --  because one of our operands is in Bignum mode already, or because
8397       --  the computed bounds are outside the bounds of Long_Long_Integer,
8398       --  which in some cases can be indicated by Hi and Lo being No_Uint.
8399
8400       --  Note: we could do better here and in some cases switch back from
8401       --  Bignum mode to normal mode, e.g. big mod 2 must be in the range
8402       --  0 .. 1, but the cases are rare and it is not worth the effort.
8403       --  Failing to do this switching back is only an efficiency issue.
8404
8405       elsif Lo = No_Uint or else Lo < LLLo or else Hi > LLHi then
8406
8407          --  OK, we are definitely outside the range of Long_Long_Integer. The
8408          --  question is whether to move to Bignum mode, or stay in the domain
8409          --  of Long_Long_Integer, signalling that an overflow check is needed.
8410
8411          --  Obviously in MINIMIZED mode we stay with LLI, since we are not in
8412          --  the Bignum business. In ELIMINATED mode, we will normally move
8413          --  into Bignum mode, but there is an exception if neither of our
8414          --  operands is Bignum now, and we are at the top level (Top_Level
8415          --  set True). In this case, there is no point in moving into Bignum
8416          --  mode to prevent overflow if the caller will immediately convert
8417          --  the Bignum value back to LLI with an overflow check. It's more
8418          --  efficient to stay in LLI mode with an overflow check (if needed)
8419
8420          if Check_Mode = Minimized
8421            or else (Top_Level and not Bignum_Operands)
8422          then
8423             if Do_Overflow_Check (N) then
8424                Enable_Overflow_Check (N);
8425             end if;
8426
8427             --  The result now has to be in Long_Long_Integer mode, so adjust
8428             --  the possible range to reflect this. Note these calls also
8429             --  change No_Uint values from the top level case to LLI bounds.
8430
8431             Max (Lo, LLLo);
8432             Min (Hi, LLHi);
8433
8434          --  Otherwise we are in ELIMINATED mode and we switch to Bignum mode
8435
8436          else
8437             pragma Assert (Check_Mode = Eliminated);
8438
8439             declare
8440                Fent : Entity_Id;
8441                Args : List_Id;
8442
8443             begin
8444                case Nkind (N) is
8445                   when N_Op_Abs      =>
8446                      Fent := RTE (RE_Big_Abs);
8447
8448                   when N_Op_Add      =>
8449                      Fent := RTE (RE_Big_Add);
8450
8451                   when N_Op_Divide   =>
8452                      Fent := RTE (RE_Big_Div);
8453
8454                   when N_Op_Expon    =>
8455                      Fent := RTE (RE_Big_Exp);
8456
8457                   when N_Op_Minus    =>
8458                      Fent := RTE (RE_Big_Neg);
8459
8460                   when N_Op_Mod      =>
8461                      Fent := RTE (RE_Big_Mod);
8462
8463                   when N_Op_Multiply =>
8464                      Fent := RTE (RE_Big_Mul);
8465
8466                   when N_Op_Rem      =>
8467                      Fent := RTE (RE_Big_Rem);
8468
8469                   when N_Op_Subtract =>
8470                      Fent := RTE (RE_Big_Sub);
8471
8472                   --  Anything else is an internal error, this includes the
8473                   --  N_Op_Plus case, since how can plus cause the result
8474                   --  to be out of range if the operand is in range?
8475
8476                   when others =>
8477                      raise Program_Error;
8478                end case;
8479
8480                --  Construct argument list for Bignum call, converting our
8481                --  operands to Bignum form if they are not already there.
8482
8483                Args := New_List;
8484
8485                if Binary then
8486                   Append_To (Args, Convert_To_Bignum (Left_Opnd (N)));
8487                end if;
8488
8489                Append_To (Args, Convert_To_Bignum (Right_Opnd (N)));
8490
8491                --  Now rewrite the arithmetic operator with a call to the
8492                --  corresponding bignum function.
8493
8494                Rewrite (N,
8495                  Make_Function_Call (Loc,
8496                    Name                   => New_Occurrence_Of (Fent, Loc),
8497                    Parameter_Associations => Args));
8498                Reanalyze (RTE (RE_Bignum), Suppress => True);
8499
8500                --  Indicate result is Bignum mode
8501
8502                Lo := No_Uint;
8503                Hi := No_Uint;
8504                return;
8505             end;
8506          end if;
8507
8508       --  Otherwise we are in range of Long_Long_Integer, so no overflow
8509       --  check is required, at least not yet.
8510
8511       else
8512          Set_Do_Overflow_Check (N, False);
8513       end if;
8514
8515       --  Here we are not in Bignum territory, but we may have long long
8516       --  integer operands that need special handling. First a special check:
8517       --  If an exponentiation operator exponent is of type Long_Long_Integer,
8518       --  it means we converted it to prevent overflow, but exponentiation
8519       --  requires a Natural right operand, so convert it back to Natural.
8520       --  This conversion may raise an exception which is fine.
8521
8522       if Nkind (N) = N_Op_Expon and then Etype (Right_Opnd (N)) = LLIB then
8523          Convert_To_And_Rewrite (Standard_Natural, Right_Opnd (N));
8524       end if;
8525
8526       --  Here we will do the operation in Long_Long_Integer. We do this even
8527       --  if we know an overflow check is required, better to do this in long
8528       --  long integer mode, since we are less likely to overflow.
8529
8530       --  Convert right or only operand to Long_Long_Integer, except that
8531       --  we do not touch the exponentiation right operand.
8532
8533       if Nkind (N) /= N_Op_Expon then
8534          Convert_To_And_Rewrite (LLIB, Right_Opnd (N));
8535       end if;
8536
8537       --  Convert left operand to Long_Long_Integer for binary case
8538
8539       if Binary then
8540          Convert_To_And_Rewrite (LLIB, Left_Opnd (N));
8541       end if;
8542
8543       --  Reset node to unanalyzed
8544
8545       Set_Analyzed (N, False);
8546       Set_Etype (N, Empty);
8547       Set_Entity (N, Empty);
8548
8549       --  Now analyze this new node. This reanalysis will complete processing
8550       --  for the node. In particular we will complete the expansion of an
8551       --  exponentiation operator (e.g. changing A ** 2 to A * A), and also
8552       --  we will complete any division checks (since we have not changed the
8553       --  setting of the Do_Division_Check flag).
8554
8555       --  We do this reanalysis in STRICT mode to avoid recursion into the
8556       --  MINIMIZED/ELIMINATED handling, since we are now done with that.
8557
8558       declare
8559          SG : constant Overflow_Mode_Type :=
8560                 Scope_Suppress.Overflow_Mode_General;
8561          SA : constant Overflow_Mode_Type :=
8562                 Scope_Suppress.Overflow_Mode_Assertions;
8563
8564       begin
8565          Scope_Suppress.Overflow_Mode_General    := Strict;
8566          Scope_Suppress.Overflow_Mode_Assertions := Strict;
8567
8568          if not Do_Overflow_Check (N) then
8569             Reanalyze (LLIB, Suppress => True);
8570          else
8571             Reanalyze (LLIB);
8572          end if;
8573
8574          Scope_Suppress.Overflow_Mode_General    := SG;
8575          Scope_Suppress.Overflow_Mode_Assertions := SA;
8576       end;
8577    end Minimize_Eliminate_Overflows;
8578
8579    -------------------------
8580    -- Overflow_Check_Mode --
8581    -------------------------
8582
8583    function Overflow_Check_Mode return Overflow_Mode_Type is
8584    begin
8585       if In_Assertion_Expr = 0 then
8586          return Scope_Suppress.Overflow_Mode_General;
8587       else
8588          return Scope_Suppress.Overflow_Mode_Assertions;
8589       end if;
8590    end Overflow_Check_Mode;
8591
8592    --------------------------------
8593    -- Overflow_Checks_Suppressed --
8594    --------------------------------
8595
8596    function Overflow_Checks_Suppressed (E : Entity_Id) return Boolean is
8597    begin
8598       if Present (E) and then Checks_May_Be_Suppressed (E) then
8599          return Is_Check_Suppressed (E, Overflow_Check);
8600       else
8601          return Scope_Suppress.Suppress (Overflow_Check);
8602       end if;
8603    end Overflow_Checks_Suppressed;
8604
8605    ---------------------------------
8606    -- Predicate_Checks_Suppressed --
8607    ---------------------------------
8608
8609    function Predicate_Checks_Suppressed (E : Entity_Id) return Boolean is
8610    begin
8611       if Present (E) and then Checks_May_Be_Suppressed (E) then
8612          return Is_Check_Suppressed (E, Predicate_Check);
8613       else
8614          return Scope_Suppress.Suppress (Predicate_Check);
8615       end if;
8616    end Predicate_Checks_Suppressed;
8617
8618    -----------------------------
8619    -- Range_Checks_Suppressed --
8620    -----------------------------
8621
8622    function Range_Checks_Suppressed (E : Entity_Id) return Boolean is
8623    begin
8624       if Present (E) then
8625          if Kill_Range_Checks (E) then
8626             return True;
8627
8628          elsif Checks_May_Be_Suppressed (E) then
8629             return Is_Check_Suppressed (E, Range_Check);
8630          end if;
8631       end if;
8632
8633       return Scope_Suppress.Suppress (Range_Check);
8634    end Range_Checks_Suppressed;
8635
8636    -----------------------------------------
8637    -- Range_Or_Validity_Checks_Suppressed --
8638    -----------------------------------------
8639
8640    --  Note: the coding would be simpler here if we simply made appropriate
8641    --  calls to Range/Validity_Checks_Suppressed, but that would result in
8642    --  duplicated checks which we prefer to avoid.
8643
8644    function Range_Or_Validity_Checks_Suppressed
8645      (Expr : Node_Id) return Boolean
8646    is
8647    begin
8648       --  Immediate return if scope checks suppressed for either check
8649
8650       if Scope_Suppress.Suppress (Range_Check)
8651            or
8652          Scope_Suppress.Suppress (Validity_Check)
8653       then
8654          return True;
8655       end if;
8656
8657       --  If no expression, that's odd, decide that checks are suppressed,
8658       --  since we don't want anyone trying to do checks in this case, which
8659       --  is most likely the result of some other error.
8660
8661       if No (Expr) then
8662          return True;
8663       end if;
8664
8665       --  Expression is present, so perform suppress checks on type
8666
8667       declare
8668          Typ : constant Entity_Id := Etype (Expr);
8669       begin
8670          if Checks_May_Be_Suppressed (Typ)
8671            and then (Is_Check_Suppressed (Typ, Range_Check)
8672                        or else
8673                      Is_Check_Suppressed (Typ, Validity_Check))
8674          then
8675             return True;
8676          end if;
8677       end;
8678
8679       --  If expression is an entity name, perform checks on this entity
8680
8681       if Is_Entity_Name (Expr) then
8682          declare
8683             Ent : constant Entity_Id := Entity (Expr);
8684          begin
8685             if Checks_May_Be_Suppressed (Ent) then
8686                return Is_Check_Suppressed (Ent, Range_Check)
8687                  or else Is_Check_Suppressed (Ent, Validity_Check);
8688             end if;
8689          end;
8690       end if;
8691
8692       --  If we fall through, no checks suppressed
8693
8694       return False;
8695    end Range_Or_Validity_Checks_Suppressed;
8696
8697    -------------------
8698    -- Remove_Checks --
8699    -------------------
8700
8701    procedure Remove_Checks (Expr : Node_Id) is
8702       function Process (N : Node_Id) return Traverse_Result;
8703       --  Process a single node during the traversal
8704
8705       procedure Traverse is new Traverse_Proc (Process);
8706       --  The traversal procedure itself
8707
8708       -------------
8709       -- Process --
8710       -------------
8711
8712       function Process (N : Node_Id) return Traverse_Result is
8713       begin
8714          if Nkind (N) not in N_Subexpr then
8715             return Skip;
8716          end if;
8717
8718          Set_Do_Range_Check (N, False);
8719
8720          case Nkind (N) is
8721             when N_And_Then =>
8722                Traverse (Left_Opnd (N));
8723                return Skip;
8724
8725             when N_Attribute_Reference =>
8726                Set_Do_Overflow_Check (N, False);
8727
8728             when N_Function_Call =>
8729                Set_Do_Tag_Check (N, False);
8730
8731             when N_Op =>
8732                Set_Do_Overflow_Check (N, False);
8733
8734                case Nkind (N) is
8735                   when N_Op_Divide =>
8736                      Set_Do_Division_Check (N, False);
8737
8738                   when N_Op_And =>
8739                      Set_Do_Length_Check (N, False);
8740
8741                   when N_Op_Mod =>
8742                      Set_Do_Division_Check (N, False);
8743
8744                   when N_Op_Or =>
8745                      Set_Do_Length_Check (N, False);
8746
8747                   when N_Op_Rem =>
8748                      Set_Do_Division_Check (N, False);
8749
8750                   when N_Op_Xor =>
8751                      Set_Do_Length_Check (N, False);
8752
8753                   when others =>
8754                      null;
8755                end case;
8756
8757             when N_Or_Else =>
8758                Traverse (Left_Opnd (N));
8759                return Skip;
8760
8761             when N_Selected_Component =>
8762                Set_Do_Discriminant_Check (N, False);
8763
8764             when N_Type_Conversion =>
8765                Set_Do_Length_Check   (N, False);
8766                Set_Do_Tag_Check      (N, False);
8767                Set_Do_Overflow_Check (N, False);
8768
8769             when others =>
8770                null;
8771          end case;
8772
8773          return OK;
8774       end Process;
8775
8776    --  Start of processing for Remove_Checks
8777
8778    begin
8779       Traverse (Expr);
8780    end Remove_Checks;
8781
8782    ----------------------------
8783    -- Selected_Length_Checks --
8784    ----------------------------
8785
8786    function Selected_Length_Checks
8787      (Ck_Node    : Node_Id;
8788       Target_Typ : Entity_Id;
8789       Source_Typ : Entity_Id;
8790       Warn_Node  : Node_Id) return Check_Result
8791    is
8792       Loc         : constant Source_Ptr := Sloc (Ck_Node);
8793       S_Typ       : Entity_Id;
8794       T_Typ       : Entity_Id;
8795       Expr_Actual : Node_Id;
8796       Exptyp      : Entity_Id;
8797       Cond        : Node_Id := Empty;
8798       Do_Access   : Boolean := False;
8799       Wnode       : Node_Id := Warn_Node;
8800       Ret_Result  : Check_Result := (Empty, Empty);
8801       Num_Checks  : Natural := 0;
8802
8803       procedure Add_Check (N : Node_Id);
8804       --  Adds the action given to Ret_Result if N is non-Empty
8805
8806       function Get_E_Length (E : Entity_Id; Indx : Nat) return Node_Id;
8807       function Get_N_Length (N : Node_Id; Indx : Nat) return Node_Id;
8808       --  Comments required ???
8809
8810       function Same_Bounds (L : Node_Id; R : Node_Id) return Boolean;
8811       --  True for equal literals and for nodes that denote the same constant
8812       --  entity, even if its value is not a static constant. This includes the
8813       --  case of a discriminal reference within an init proc. Removes some
8814       --  obviously superfluous checks.
8815
8816       function Length_E_Cond
8817         (Exptyp : Entity_Id;
8818          Typ    : Entity_Id;
8819          Indx   : Nat) return Node_Id;
8820       --  Returns expression to compute:
8821       --    Typ'Length /= Exptyp'Length
8822
8823       function Length_N_Cond
8824         (Expr : Node_Id;
8825          Typ  : Entity_Id;
8826          Indx : Nat) return Node_Id;
8827       --  Returns expression to compute:
8828       --    Typ'Length /= Expr'Length
8829
8830       ---------------
8831       -- Add_Check --
8832       ---------------
8833
8834       procedure Add_Check (N : Node_Id) is
8835       begin
8836          if Present (N) then
8837
8838             --  For now, ignore attempt to place more than two checks ???
8839             --  This is really worrisome, are we really discarding checks ???
8840
8841             if Num_Checks = 2 then
8842                return;
8843             end if;
8844
8845             pragma Assert (Num_Checks <= 1);
8846             Num_Checks := Num_Checks + 1;
8847             Ret_Result (Num_Checks) := N;
8848          end if;
8849       end Add_Check;
8850
8851       ------------------
8852       -- Get_E_Length --
8853       ------------------
8854
8855       function Get_E_Length (E : Entity_Id; Indx : Nat) return Node_Id is
8856          SE : constant Entity_Id := Scope (E);
8857          N  : Node_Id;
8858          E1 : Entity_Id := E;
8859
8860       begin
8861          if Ekind (Scope (E)) = E_Record_Type
8862            and then Has_Discriminants (Scope (E))
8863          then
8864             N := Build_Discriminal_Subtype_Of_Component (E);
8865
8866             if Present (N) then
8867                Insert_Action (Ck_Node, N);
8868                E1 := Defining_Identifier (N);
8869             end if;
8870          end if;
8871
8872          if Ekind (E1) = E_String_Literal_Subtype then
8873             return
8874               Make_Integer_Literal (Loc,
8875                 Intval => String_Literal_Length (E1));
8876
8877          elsif SE /= Standard_Standard
8878            and then Ekind (Scope (SE)) = E_Protected_Type
8879            and then Has_Discriminants (Scope (SE))
8880            and then Has_Completion (Scope (SE))
8881            and then not Inside_Init_Proc
8882          then
8883             --  If the type whose length is needed is a private component
8884             --  constrained by a discriminant, we must expand the 'Length
8885             --  attribute into an explicit computation, using the discriminal
8886             --  of the current protected operation. This is because the actual
8887             --  type of the prival is constructed after the protected opera-
8888             --  tion has been fully expanded.
8889
8890             declare
8891                Indx_Type : Node_Id;
8892                Lo        : Node_Id;
8893                Hi        : Node_Id;
8894                Do_Expand : Boolean := False;
8895
8896             begin
8897                Indx_Type := First_Index (E);
8898
8899                for J in 1 .. Indx - 1 loop
8900                   Next_Index (Indx_Type);
8901                end loop;
8902
8903                Get_Index_Bounds (Indx_Type, Lo, Hi);
8904
8905                if Nkind (Lo) = N_Identifier
8906                  and then Ekind (Entity (Lo)) = E_In_Parameter
8907                then
8908                   Lo := Get_Discriminal (E, Lo);
8909                   Do_Expand := True;
8910                end if;
8911
8912                if Nkind (Hi) = N_Identifier
8913                  and then Ekind (Entity (Hi)) = E_In_Parameter
8914                then
8915                   Hi := Get_Discriminal (E, Hi);
8916                   Do_Expand := True;
8917                end if;
8918
8919                if Do_Expand then
8920                   if not Is_Entity_Name (Lo) then
8921                      Lo := Duplicate_Subexpr_No_Checks (Lo);
8922                   end if;
8923
8924                   if not Is_Entity_Name (Hi) then
8925                      Lo := Duplicate_Subexpr_No_Checks (Hi);
8926                   end if;
8927
8928                   N :=
8929                     Make_Op_Add (Loc,
8930                       Left_Opnd =>
8931                         Make_Op_Subtract (Loc,
8932                           Left_Opnd  => Hi,
8933                           Right_Opnd => Lo),
8934
8935                       Right_Opnd => Make_Integer_Literal (Loc, 1));
8936                   return N;
8937
8938                else
8939                   N :=
8940                     Make_Attribute_Reference (Loc,
8941                       Attribute_Name => Name_Length,
8942                       Prefix =>
8943                         New_Occurrence_Of (E1, Loc));
8944
8945                   if Indx > 1 then
8946                      Set_Expressions (N, New_List (
8947                        Make_Integer_Literal (Loc, Indx)));
8948                   end if;
8949
8950                   return N;
8951                end if;
8952             end;
8953
8954          else
8955             N :=
8956               Make_Attribute_Reference (Loc,
8957                 Attribute_Name => Name_Length,
8958                 Prefix =>
8959                   New_Occurrence_Of (E1, Loc));
8960
8961             if Indx > 1 then
8962                Set_Expressions (N, New_List (
8963                  Make_Integer_Literal (Loc, Indx)));
8964             end if;
8965
8966             return N;
8967          end if;
8968       end Get_E_Length;
8969
8970       ------------------
8971       -- Get_N_Length --
8972       ------------------
8973
8974       function Get_N_Length (N : Node_Id; Indx : Nat) return Node_Id is
8975       begin
8976          return
8977            Make_Attribute_Reference (Loc,
8978              Attribute_Name => Name_Length,
8979              Prefix =>
8980                Duplicate_Subexpr_No_Checks (N, Name_Req => True),
8981              Expressions => New_List (
8982                Make_Integer_Literal (Loc, Indx)));
8983       end Get_N_Length;
8984
8985       -------------------
8986       -- Length_E_Cond --
8987       -------------------
8988
8989       function Length_E_Cond
8990         (Exptyp : Entity_Id;
8991          Typ    : Entity_Id;
8992          Indx   : Nat) return Node_Id
8993       is
8994       begin
8995          return
8996            Make_Op_Ne (Loc,
8997              Left_Opnd  => Get_E_Length (Typ, Indx),
8998              Right_Opnd => Get_E_Length (Exptyp, Indx));
8999       end Length_E_Cond;
9000
9001       -------------------
9002       -- Length_N_Cond --
9003       -------------------
9004
9005       function Length_N_Cond
9006         (Expr : Node_Id;
9007          Typ  : Entity_Id;
9008          Indx : Nat) return Node_Id
9009       is
9010       begin
9011          return
9012            Make_Op_Ne (Loc,
9013              Left_Opnd  => Get_E_Length (Typ, Indx),
9014              Right_Opnd => Get_N_Length (Expr, Indx));
9015       end Length_N_Cond;
9016
9017       -----------------
9018       -- Same_Bounds --
9019       -----------------
9020
9021       function Same_Bounds (L : Node_Id; R : Node_Id) return Boolean is
9022       begin
9023          return
9024            (Nkind (L) = N_Integer_Literal
9025              and then Nkind (R) = N_Integer_Literal
9026              and then Intval (L) = Intval (R))
9027
9028           or else
9029             (Is_Entity_Name (L)
9030               and then Ekind (Entity (L)) = E_Constant
9031               and then ((Is_Entity_Name (R)
9032                          and then Entity (L) = Entity (R))
9033                         or else
9034                        (Nkind (R) = N_Type_Conversion
9035                          and then Is_Entity_Name (Expression (R))
9036                          and then Entity (L) = Entity (Expression (R)))))
9037
9038           or else
9039             (Is_Entity_Name (R)
9040               and then Ekind (Entity (R)) = E_Constant
9041               and then Nkind (L) = N_Type_Conversion
9042               and then Is_Entity_Name (Expression (L))
9043               and then Entity (R) = Entity (Expression (L)))
9044
9045          or else
9046             (Is_Entity_Name (L)
9047               and then Is_Entity_Name (R)
9048               and then Entity (L) = Entity (R)
9049               and then Ekind (Entity (L)) = E_In_Parameter
9050               and then Inside_Init_Proc);
9051       end Same_Bounds;
9052
9053    --  Start of processing for Selected_Length_Checks
9054
9055    begin
9056       if not Expander_Active then
9057          return Ret_Result;
9058       end if;
9059
9060       if Target_Typ = Any_Type
9061         or else Target_Typ = Any_Composite
9062         or else Raises_Constraint_Error (Ck_Node)
9063       then
9064          return Ret_Result;
9065       end if;
9066
9067       if No (Wnode) then
9068          Wnode := Ck_Node;
9069       end if;
9070
9071       T_Typ := Target_Typ;
9072
9073       if No (Source_Typ) then
9074          S_Typ := Etype (Ck_Node);
9075       else
9076          S_Typ := Source_Typ;
9077       end if;
9078
9079       if S_Typ = Any_Type or else S_Typ = Any_Composite then
9080          return Ret_Result;
9081       end if;
9082
9083       if Is_Access_Type (T_Typ) and then Is_Access_Type (S_Typ) then
9084          S_Typ := Designated_Type (S_Typ);
9085          T_Typ := Designated_Type (T_Typ);
9086          Do_Access := True;
9087
9088          --  A simple optimization for the null case
9089
9090          if Known_Null (Ck_Node) then
9091             return Ret_Result;
9092          end if;
9093       end if;
9094
9095       if Is_Array_Type (T_Typ) and then Is_Array_Type (S_Typ) then
9096          if Is_Constrained (T_Typ) then
9097
9098             --  The checking code to be generated will freeze the corresponding
9099             --  array type. However, we must freeze the type now, so that the
9100             --  freeze node does not appear within the generated if expression,
9101             --  but ahead of it.
9102
9103             Freeze_Before (Ck_Node, T_Typ);
9104
9105             Expr_Actual := Get_Referenced_Object (Ck_Node);
9106             Exptyp      := Get_Actual_Subtype (Ck_Node);
9107
9108             if Is_Access_Type (Exptyp) then
9109                Exptyp := Designated_Type (Exptyp);
9110             end if;
9111
9112             --  String_Literal case. This needs to be handled specially be-
9113             --  cause no index types are available for string literals. The
9114             --  condition is simply:
9115
9116             --    T_Typ'Length = string-literal-length
9117
9118             if Nkind (Expr_Actual) = N_String_Literal
9119               and then Ekind (Etype (Expr_Actual)) = E_String_Literal_Subtype
9120             then
9121                Cond :=
9122                  Make_Op_Ne (Loc,
9123                    Left_Opnd  => Get_E_Length (T_Typ, 1),
9124                    Right_Opnd =>
9125                      Make_Integer_Literal (Loc,
9126                        Intval =>
9127                          String_Literal_Length (Etype (Expr_Actual))));
9128
9129             --  General array case. Here we have a usable actual subtype for
9130             --  the expression, and the condition is built from the two types
9131             --  (Do_Length):
9132
9133             --     T_Typ'Length     /= Exptyp'Length     or else
9134             --     T_Typ'Length (2) /= Exptyp'Length (2) or else
9135             --     T_Typ'Length (3) /= Exptyp'Length (3) or else
9136             --     ...
9137
9138             elsif Is_Constrained (Exptyp) then
9139                declare
9140                   Ndims : constant Nat := Number_Dimensions (T_Typ);
9141
9142                   L_Index  : Node_Id;
9143                   R_Index  : Node_Id;
9144                   L_Low    : Node_Id;
9145                   L_High   : Node_Id;
9146                   R_Low    : Node_Id;
9147                   R_High   : Node_Id;
9148                   L_Length : Uint;
9149                   R_Length : Uint;
9150                   Ref_Node : Node_Id;
9151
9152                begin
9153                   --  At the library level, we need to ensure that the type of
9154                   --  the object is elaborated before the check itself is
9155                   --  emitted. This is only done if the object is in the
9156                   --  current compilation unit, otherwise the type is frozen
9157                   --  and elaborated in its unit.
9158
9159                   if Is_Itype (Exptyp)
9160                     and then
9161                       Ekind (Cunit_Entity (Current_Sem_Unit)) = E_Package
9162                     and then
9163                       not In_Package_Body (Cunit_Entity (Current_Sem_Unit))
9164                     and then In_Open_Scopes (Scope (Exptyp))
9165                   then
9166                      Ref_Node := Make_Itype_Reference (Sloc (Ck_Node));
9167                      Set_Itype (Ref_Node, Exptyp);
9168                      Insert_Action (Ck_Node, Ref_Node);
9169                   end if;
9170
9171                   L_Index := First_Index (T_Typ);
9172                   R_Index := First_Index (Exptyp);
9173
9174                   for Indx in 1 .. Ndims loop
9175                      if not (Nkind (L_Index) = N_Raise_Constraint_Error
9176                                or else
9177                              Nkind (R_Index) = N_Raise_Constraint_Error)
9178                      then
9179                         Get_Index_Bounds (L_Index, L_Low, L_High);
9180                         Get_Index_Bounds (R_Index, R_Low, R_High);
9181
9182                         --  Deal with compile time length check. Note that we
9183                         --  skip this in the access case, because the access
9184                         --  value may be null, so we cannot know statically.
9185
9186                         if not Do_Access
9187                           and then Compile_Time_Known_Value (L_Low)
9188                           and then Compile_Time_Known_Value (L_High)
9189                           and then Compile_Time_Known_Value (R_Low)
9190                           and then Compile_Time_Known_Value (R_High)
9191                         then
9192                            if Expr_Value (L_High) >= Expr_Value (L_Low) then
9193                               L_Length := Expr_Value (L_High) -
9194                                           Expr_Value (L_Low) + 1;
9195                            else
9196                               L_Length := UI_From_Int (0);
9197                            end if;
9198
9199                            if Expr_Value (R_High) >= Expr_Value (R_Low) then
9200                               R_Length := Expr_Value (R_High) -
9201                                           Expr_Value (R_Low) + 1;
9202                            else
9203                               R_Length := UI_From_Int (0);
9204                            end if;
9205
9206                            if L_Length > R_Length then
9207                               Add_Check
9208                                 (Compile_Time_Constraint_Error
9209                                   (Wnode, "too few elements for}??", T_Typ));
9210
9211                            elsif L_Length < R_Length then
9212                               Add_Check
9213                                 (Compile_Time_Constraint_Error
9214                                   (Wnode, "too many elements for}??", T_Typ));
9215                            end if;
9216
9217                         --  The comparison for an individual index subtype
9218                         --  is omitted if the corresponding index subtypes
9219                         --  statically match, since the result is known to
9220                         --  be true. Note that this test is worth while even
9221                         --  though we do static evaluation, because non-static
9222                         --  subtypes can statically match.
9223
9224                         elsif not
9225                           Subtypes_Statically_Match
9226                             (Etype (L_Index), Etype (R_Index))
9227
9228                           and then not
9229                             (Same_Bounds (L_Low, R_Low)
9230                               and then Same_Bounds (L_High, R_High))
9231                         then
9232                            Evolve_Or_Else
9233                              (Cond, Length_E_Cond (Exptyp, T_Typ, Indx));
9234                         end if;
9235
9236                         Next (L_Index);
9237                         Next (R_Index);
9238                      end if;
9239                   end loop;
9240                end;
9241
9242             --  Handle cases where we do not get a usable actual subtype that
9243             --  is constrained. This happens for example in the function call
9244             --  and explicit dereference cases. In these cases, we have to get
9245             --  the length or range from the expression itself, making sure we
9246             --  do not evaluate it more than once.
9247
9248             --  Here Ck_Node is the original expression, or more properly the
9249             --  result of applying Duplicate_Expr to the original tree, forcing
9250             --  the result to be a name.
9251
9252             else
9253                declare
9254                   Ndims : constant Nat := Number_Dimensions (T_Typ);
9255
9256                begin
9257                   --  Build the condition for the explicit dereference case
9258
9259                   for Indx in 1 .. Ndims loop
9260                      Evolve_Or_Else
9261                        (Cond, Length_N_Cond (Ck_Node, T_Typ, Indx));
9262                   end loop;
9263                end;
9264             end if;
9265          end if;
9266       end if;
9267
9268       --  Construct the test and insert into the tree
9269
9270       if Present (Cond) then
9271          if Do_Access then
9272             Cond := Guard_Access (Cond, Loc, Ck_Node);
9273          end if;
9274
9275          Add_Check
9276            (Make_Raise_Constraint_Error (Loc,
9277               Condition => Cond,
9278               Reason => CE_Length_Check_Failed));
9279       end if;
9280
9281       return Ret_Result;
9282    end Selected_Length_Checks;
9283
9284    ---------------------------
9285    -- Selected_Range_Checks --
9286    ---------------------------
9287
9288    function Selected_Range_Checks
9289      (Ck_Node    : Node_Id;
9290       Target_Typ : Entity_Id;
9291       Source_Typ : Entity_Id;
9292       Warn_Node  : Node_Id) return Check_Result
9293    is
9294       Loc         : constant Source_Ptr := Sloc (Ck_Node);
9295       S_Typ       : Entity_Id;
9296       T_Typ       : Entity_Id;
9297       Expr_Actual : Node_Id;
9298       Exptyp      : Entity_Id;
9299       Cond        : Node_Id := Empty;
9300       Do_Access   : Boolean := False;
9301       Wnode       : Node_Id  := Warn_Node;
9302       Ret_Result  : Check_Result := (Empty, Empty);
9303       Num_Checks  : Integer := 0;
9304
9305       procedure Add_Check (N : Node_Id);
9306       --  Adds the action given to Ret_Result if N is non-Empty
9307
9308       function Discrete_Range_Cond
9309         (Expr : Node_Id;
9310          Typ  : Entity_Id) return Node_Id;
9311       --  Returns expression to compute:
9312       --    Low_Bound (Expr) < Typ'First
9313       --      or else
9314       --    High_Bound (Expr) > Typ'Last
9315
9316       function Discrete_Expr_Cond
9317         (Expr : Node_Id;
9318          Typ  : Entity_Id) return Node_Id;
9319       --  Returns expression to compute:
9320       --    Expr < Typ'First
9321       --      or else
9322       --    Expr > Typ'Last
9323
9324       function Get_E_First_Or_Last
9325         (Loc  : Source_Ptr;
9326          E    : Entity_Id;
9327          Indx : Nat;
9328          Nam  : Name_Id) return Node_Id;
9329       --  Returns an attribute reference
9330       --    E'First or E'Last
9331       --  with a source location of Loc.
9332       --
9333       --  Nam is Name_First or Name_Last, according to which attribute is
9334       --  desired. If Indx is non-zero, it is passed as a literal in the
9335       --  Expressions of the attribute reference (identifying the desired
9336       --  array dimension).
9337
9338       function Get_N_First (N : Node_Id; Indx : Nat) return Node_Id;
9339       function Get_N_Last  (N : Node_Id; Indx : Nat) return Node_Id;
9340       --  Returns expression to compute:
9341       --    N'First or N'Last using Duplicate_Subexpr_No_Checks
9342
9343       function Range_E_Cond
9344         (Exptyp : Entity_Id;
9345          Typ    : Entity_Id;
9346          Indx   : Nat)
9347          return   Node_Id;
9348       --  Returns expression to compute:
9349       --    Exptyp'First < Typ'First or else Exptyp'Last > Typ'Last
9350
9351       function Range_Equal_E_Cond
9352         (Exptyp : Entity_Id;
9353          Typ    : Entity_Id;
9354          Indx   : Nat) return Node_Id;
9355       --  Returns expression to compute:
9356       --    Exptyp'First /= Typ'First or else Exptyp'Last /= Typ'Last
9357
9358       function Range_N_Cond
9359         (Expr : Node_Id;
9360          Typ  : Entity_Id;
9361          Indx : Nat) return Node_Id;
9362       --  Return expression to compute:
9363       --    Expr'First < Typ'First or else Expr'Last > Typ'Last
9364
9365       ---------------
9366       -- Add_Check --
9367       ---------------
9368
9369       procedure Add_Check (N : Node_Id) is
9370       begin
9371          if Present (N) then
9372
9373             --  For now, ignore attempt to place more than 2 checks ???
9374
9375             if Num_Checks = 2 then
9376                return;
9377             end if;
9378
9379             pragma Assert (Num_Checks <= 1);
9380             Num_Checks := Num_Checks + 1;
9381             Ret_Result (Num_Checks) := N;
9382          end if;
9383       end Add_Check;
9384
9385       -------------------------
9386       -- Discrete_Expr_Cond --
9387       -------------------------
9388
9389       function Discrete_Expr_Cond
9390         (Expr : Node_Id;
9391          Typ  : Entity_Id) return Node_Id
9392       is
9393       begin
9394          return
9395            Make_Or_Else (Loc,
9396              Left_Opnd =>
9397                Make_Op_Lt (Loc,
9398                  Left_Opnd =>
9399                    Convert_To (Base_Type (Typ),
9400                      Duplicate_Subexpr_No_Checks (Expr)),
9401                  Right_Opnd =>
9402                    Convert_To (Base_Type (Typ),
9403                                Get_E_First_Or_Last (Loc, Typ, 0, Name_First))),
9404
9405              Right_Opnd =>
9406                Make_Op_Gt (Loc,
9407                  Left_Opnd =>
9408                    Convert_To (Base_Type (Typ),
9409                      Duplicate_Subexpr_No_Checks (Expr)),
9410                  Right_Opnd =>
9411                    Convert_To
9412                      (Base_Type (Typ),
9413                       Get_E_First_Or_Last (Loc, Typ, 0, Name_Last))));
9414       end Discrete_Expr_Cond;
9415
9416       -------------------------
9417       -- Discrete_Range_Cond --
9418       -------------------------
9419
9420       function Discrete_Range_Cond
9421         (Expr : Node_Id;
9422          Typ  : Entity_Id) return Node_Id
9423       is
9424          LB : Node_Id := Low_Bound (Expr);
9425          HB : Node_Id := High_Bound (Expr);
9426
9427          Left_Opnd  : Node_Id;
9428          Right_Opnd : Node_Id;
9429
9430       begin
9431          if Nkind (LB) = N_Identifier
9432            and then Ekind (Entity (LB)) = E_Discriminant
9433          then
9434             LB := New_Occurrence_Of (Discriminal (Entity (LB)), Loc);
9435          end if;
9436
9437          Left_Opnd :=
9438            Make_Op_Lt (Loc,
9439              Left_Opnd  =>
9440                Convert_To
9441                  (Base_Type (Typ), Duplicate_Subexpr_No_Checks (LB)),
9442
9443              Right_Opnd =>
9444                Convert_To
9445                  (Base_Type (Typ),
9446                   Get_E_First_Or_Last (Loc, Typ, 0, Name_First)));
9447
9448          if Nkind (HB) = N_Identifier
9449            and then Ekind (Entity (HB)) = E_Discriminant
9450          then
9451             HB := New_Occurrence_Of (Discriminal (Entity (HB)), Loc);
9452          end if;
9453
9454          Right_Opnd :=
9455            Make_Op_Gt (Loc,
9456              Left_Opnd  =>
9457                Convert_To
9458                  (Base_Type (Typ), Duplicate_Subexpr_No_Checks (HB)),
9459
9460              Right_Opnd =>
9461                Convert_To
9462                  (Base_Type (Typ),
9463                   Get_E_First_Or_Last (Loc, Typ, 0, Name_Last)));
9464
9465          return Make_Or_Else (Loc, Left_Opnd, Right_Opnd);
9466       end Discrete_Range_Cond;
9467
9468       -------------------------
9469       -- Get_E_First_Or_Last --
9470       -------------------------
9471
9472       function Get_E_First_Or_Last
9473         (Loc  : Source_Ptr;
9474          E    : Entity_Id;
9475          Indx : Nat;
9476          Nam  : Name_Id) return Node_Id
9477       is
9478          Exprs : List_Id;
9479       begin
9480          if Indx > 0 then
9481             Exprs := New_List (Make_Integer_Literal (Loc, UI_From_Int (Indx)));
9482          else
9483             Exprs := No_List;
9484          end if;
9485
9486          return Make_Attribute_Reference (Loc,
9487                   Prefix         => New_Occurrence_Of (E, Loc),
9488                   Attribute_Name => Nam,
9489                   Expressions    => Exprs);
9490       end Get_E_First_Or_Last;
9491
9492       -----------------
9493       -- Get_N_First --
9494       -----------------
9495
9496       function Get_N_First (N : Node_Id; Indx : Nat) return Node_Id is
9497       begin
9498          return
9499            Make_Attribute_Reference (Loc,
9500              Attribute_Name => Name_First,
9501              Prefix =>
9502                Duplicate_Subexpr_No_Checks (N, Name_Req => True),
9503              Expressions => New_List (
9504                Make_Integer_Literal (Loc, Indx)));
9505       end Get_N_First;
9506
9507       ----------------
9508       -- Get_N_Last --
9509       ----------------
9510
9511       function Get_N_Last (N : Node_Id; Indx : Nat) return Node_Id is
9512       begin
9513          return
9514            Make_Attribute_Reference (Loc,
9515              Attribute_Name => Name_Last,
9516              Prefix =>
9517                Duplicate_Subexpr_No_Checks (N, Name_Req => True),
9518              Expressions => New_List (
9519               Make_Integer_Literal (Loc, Indx)));
9520       end Get_N_Last;
9521
9522       ------------------
9523       -- Range_E_Cond --
9524       ------------------
9525
9526       function Range_E_Cond
9527         (Exptyp : Entity_Id;
9528          Typ    : Entity_Id;
9529          Indx   : Nat) return Node_Id
9530       is
9531       begin
9532          return
9533            Make_Or_Else (Loc,
9534              Left_Opnd =>
9535                Make_Op_Lt (Loc,
9536                  Left_Opnd   =>
9537                    Get_E_First_Or_Last (Loc, Exptyp, Indx, Name_First),
9538                  Right_Opnd  =>
9539                    Get_E_First_Or_Last (Loc, Typ, Indx, Name_First)),
9540
9541              Right_Opnd =>
9542                Make_Op_Gt (Loc,
9543                  Left_Opnd   =>
9544                    Get_E_First_Or_Last (Loc, Exptyp, Indx, Name_Last),
9545                  Right_Opnd  =>
9546                    Get_E_First_Or_Last (Loc, Typ, Indx, Name_Last)));
9547       end Range_E_Cond;
9548
9549       ------------------------
9550       -- Range_Equal_E_Cond --
9551       ------------------------
9552
9553       function Range_Equal_E_Cond
9554         (Exptyp : Entity_Id;
9555          Typ    : Entity_Id;
9556          Indx   : Nat) return Node_Id
9557       is
9558       begin
9559          return
9560            Make_Or_Else (Loc,
9561              Left_Opnd =>
9562                Make_Op_Ne (Loc,
9563                  Left_Opnd   =>
9564                    Get_E_First_Or_Last (Loc, Exptyp, Indx, Name_First),
9565                  Right_Opnd  =>
9566                    Get_E_First_Or_Last (Loc, Typ, Indx, Name_First)),
9567
9568              Right_Opnd =>
9569                Make_Op_Ne (Loc,
9570                  Left_Opnd   =>
9571                    Get_E_First_Or_Last (Loc, Exptyp, Indx, Name_Last),
9572                  Right_Opnd  =>
9573                    Get_E_First_Or_Last (Loc, Typ, Indx, Name_Last)));
9574       end Range_Equal_E_Cond;
9575
9576       ------------------
9577       -- Range_N_Cond --
9578       ------------------
9579
9580       function Range_N_Cond
9581         (Expr : Node_Id;
9582          Typ  : Entity_Id;
9583          Indx : Nat) return Node_Id
9584       is
9585       begin
9586          return
9587            Make_Or_Else (Loc,
9588              Left_Opnd =>
9589                Make_Op_Lt (Loc,
9590                  Left_Opnd  =>
9591                    Get_N_First (Expr, Indx),
9592                  Right_Opnd =>
9593                    Get_E_First_Or_Last (Loc, Typ, Indx, Name_First)),
9594
9595              Right_Opnd =>
9596                Make_Op_Gt (Loc,
9597                  Left_Opnd  =>
9598                    Get_N_Last (Expr, Indx),
9599                  Right_Opnd =>
9600                    Get_E_First_Or_Last (Loc, Typ, Indx, Name_Last)));
9601       end Range_N_Cond;
9602
9603    --  Start of processing for Selected_Range_Checks
9604
9605    begin
9606       if not Expander_Active then
9607          return Ret_Result;
9608       end if;
9609
9610       if Target_Typ = Any_Type
9611         or else Target_Typ = Any_Composite
9612         or else Raises_Constraint_Error (Ck_Node)
9613       then
9614          return Ret_Result;
9615       end if;
9616
9617       if No (Wnode) then
9618          Wnode := Ck_Node;
9619       end if;
9620
9621       T_Typ := Target_Typ;
9622
9623       if No (Source_Typ) then
9624          S_Typ := Etype (Ck_Node);
9625       else
9626          S_Typ := Source_Typ;
9627       end if;
9628
9629       if S_Typ = Any_Type or else S_Typ = Any_Composite then
9630          return Ret_Result;
9631       end if;
9632
9633       --  The order of evaluating T_Typ before S_Typ seems to be critical
9634       --  because S_Typ can be derived from Etype (Ck_Node), if it's not passed
9635       --  in, and since Node can be an N_Range node, it might be invalid.
9636       --  Should there be an assert check somewhere for taking the Etype of
9637       --  an N_Range node ???
9638
9639       if Is_Access_Type (T_Typ) and then Is_Access_Type (S_Typ) then
9640          S_Typ := Designated_Type (S_Typ);
9641          T_Typ := Designated_Type (T_Typ);
9642          Do_Access := True;
9643
9644          --  A simple optimization for the null case
9645
9646          if Known_Null (Ck_Node) then
9647             return Ret_Result;
9648          end if;
9649       end if;
9650
9651       --  For an N_Range Node, check for a null range and then if not
9652       --  null generate a range check action.
9653
9654       if Nkind (Ck_Node) = N_Range then
9655
9656          --  There's no point in checking a range against itself
9657
9658          if Ck_Node = Scalar_Range (T_Typ) then
9659             return Ret_Result;
9660          end if;
9661
9662          declare
9663             T_LB       : constant Node_Id := Type_Low_Bound  (T_Typ);
9664             T_HB       : constant Node_Id := Type_High_Bound (T_Typ);
9665             Known_T_LB : constant Boolean := Compile_Time_Known_Value (T_LB);
9666             Known_T_HB : constant Boolean := Compile_Time_Known_Value (T_HB);
9667
9668             LB         : Node_Id := Low_Bound (Ck_Node);
9669             HB         : Node_Id := High_Bound (Ck_Node);
9670             Known_LB   : Boolean := False;
9671             Known_HB   : Boolean := False;
9672
9673             Null_Range     : Boolean;
9674             Out_Of_Range_L : Boolean;
9675             Out_Of_Range_H : Boolean;
9676
9677          begin
9678             --  Compute what is known at compile time
9679
9680             if Known_T_LB and Known_T_HB then
9681                if Compile_Time_Known_Value (LB) then
9682                   Known_LB := True;
9683
9684                --  There's no point in checking that a bound is within its
9685                --  own range so pretend that it is known in this case. First
9686                --  deal with low bound.
9687
9688                elsif Ekind (Etype (LB)) = E_Signed_Integer_Subtype
9689                  and then Scalar_Range (Etype (LB)) = Scalar_Range (T_Typ)
9690                then
9691                   LB := T_LB;
9692                   Known_LB := True;
9693                end if;
9694
9695                --  Likewise for the high bound
9696
9697                if Compile_Time_Known_Value (HB) then
9698                   Known_HB := True;
9699
9700                elsif Ekind (Etype (HB)) = E_Signed_Integer_Subtype
9701                  and then Scalar_Range (Etype (HB)) = Scalar_Range (T_Typ)
9702                then
9703                   HB := T_HB;
9704                   Known_HB := True;
9705                end if;
9706             end if;
9707
9708             --  Check for case where everything is static and we can do the
9709             --  check at compile time. This is skipped if we have an access
9710             --  type, since the access value may be null.
9711
9712             --  ??? This code can be improved since you only need to know that
9713             --  the two respective bounds (LB & T_LB or HB & T_HB) are known at
9714             --  compile time to emit pertinent messages.
9715
9716             if Known_T_LB and Known_T_HB and Known_LB and Known_HB
9717               and not Do_Access
9718             then
9719                --  Floating-point case
9720
9721                if Is_Floating_Point_Type (S_Typ) then
9722                   Null_Range := Expr_Value_R (HB) < Expr_Value_R (LB);
9723                   Out_Of_Range_L :=
9724                     (Expr_Value_R (LB) < Expr_Value_R (T_LB))
9725                       or else
9726                     (Expr_Value_R (LB) > Expr_Value_R (T_HB));
9727
9728                   Out_Of_Range_H :=
9729                     (Expr_Value_R (HB) > Expr_Value_R (T_HB))
9730                       or else
9731                     (Expr_Value_R (HB) < Expr_Value_R (T_LB));
9732
9733                --  Fixed or discrete type case
9734
9735                else
9736                   Null_Range := Expr_Value (HB) < Expr_Value (LB);
9737                   Out_Of_Range_L :=
9738                     (Expr_Value (LB) < Expr_Value (T_LB))
9739                       or else
9740                     (Expr_Value (LB) > Expr_Value (T_HB));
9741
9742                   Out_Of_Range_H :=
9743                     (Expr_Value (HB) > Expr_Value (T_HB))
9744                       or else
9745                     (Expr_Value (HB) < Expr_Value (T_LB));
9746                end if;
9747
9748                if not Null_Range then
9749                   if Out_Of_Range_L then
9750                      if No (Warn_Node) then
9751                         Add_Check
9752                           (Compile_Time_Constraint_Error
9753                              (Low_Bound (Ck_Node),
9754                               "static value out of range of}??", T_Typ));
9755
9756                      else
9757                         Add_Check
9758                           (Compile_Time_Constraint_Error
9759                             (Wnode,
9760                              "static range out of bounds of}??", T_Typ));
9761                      end if;
9762                   end if;
9763
9764                   if Out_Of_Range_H then
9765                      if No (Warn_Node) then
9766                         Add_Check
9767                           (Compile_Time_Constraint_Error
9768                              (High_Bound (Ck_Node),
9769                               "static value out of range of}??", T_Typ));
9770
9771                      else
9772                         Add_Check
9773                           (Compile_Time_Constraint_Error
9774                              (Wnode,
9775                               "static range out of bounds of}??", T_Typ));
9776                      end if;
9777                   end if;
9778                end if;
9779
9780             else
9781                declare
9782                   LB : Node_Id := Low_Bound (Ck_Node);
9783                   HB : Node_Id := High_Bound (Ck_Node);
9784
9785                begin
9786                   --  If either bound is a discriminant and we are within the
9787                   --  record declaration, it is a use of the discriminant in a
9788                   --  constraint of a component, and nothing can be checked
9789                   --  here. The check will be emitted within the init proc.
9790                   --  Before then, the discriminal has no real meaning.
9791                   --  Similarly, if the entity is a discriminal, there is no
9792                   --  check to perform yet.
9793
9794                   --  The same holds within a discriminated synchronized type,
9795                   --  where the discriminant may constrain a component or an
9796                   --  entry family.
9797
9798                   if Nkind (LB) = N_Identifier
9799                     and then Denotes_Discriminant (LB, True)
9800                   then
9801                      if Current_Scope = Scope (Entity (LB))
9802                        or else Is_Concurrent_Type (Current_Scope)
9803                        or else Ekind (Entity (LB)) /= E_Discriminant
9804                      then
9805                         return Ret_Result;
9806                      else
9807                         LB :=
9808                           New_Occurrence_Of (Discriminal (Entity (LB)), Loc);
9809                      end if;
9810                   end if;
9811
9812                   if Nkind (HB) = N_Identifier
9813                     and then Denotes_Discriminant (HB, True)
9814                   then
9815                      if Current_Scope = Scope (Entity (HB))
9816                        or else Is_Concurrent_Type (Current_Scope)
9817                        or else Ekind (Entity (HB)) /= E_Discriminant
9818                      then
9819                         return Ret_Result;
9820                      else
9821                         HB :=
9822                           New_Occurrence_Of (Discriminal (Entity (HB)), Loc);
9823                      end if;
9824                   end if;
9825
9826                   Cond := Discrete_Range_Cond (Ck_Node, T_Typ);
9827                   Set_Paren_Count (Cond, 1);
9828
9829                   Cond :=
9830                     Make_And_Then (Loc,
9831                       Left_Opnd =>
9832                         Make_Op_Ge (Loc,
9833                           Left_Opnd  =>
9834                             Convert_To (Base_Type (Etype (HB)),
9835                               Duplicate_Subexpr_No_Checks (HB)),
9836                           Right_Opnd =>
9837                             Convert_To (Base_Type (Etype (LB)),
9838                               Duplicate_Subexpr_No_Checks (LB))),
9839                       Right_Opnd => Cond);
9840                end;
9841             end if;
9842          end;
9843
9844       elsif Is_Scalar_Type (S_Typ) then
9845
9846          --  This somewhat duplicates what Apply_Scalar_Range_Check does,
9847          --  except the above simply sets a flag in the node and lets
9848          --  gigi generate the check base on the Etype of the expression.
9849          --  Sometimes, however we want to do a dynamic check against an
9850          --  arbitrary target type, so we do that here.
9851
9852          if Ekind (Base_Type (S_Typ)) /= Ekind (Base_Type (T_Typ)) then
9853             Cond := Discrete_Expr_Cond (Ck_Node, T_Typ);
9854
9855          --  For literals, we can tell if the constraint error will be
9856          --  raised at compile time, so we never need a dynamic check, but
9857          --  if the exception will be raised, then post the usual warning,
9858          --  and replace the literal with a raise constraint error
9859          --  expression. As usual, skip this for access types
9860
9861          elsif Compile_Time_Known_Value (Ck_Node) and then not Do_Access then
9862             declare
9863                LB : constant Node_Id := Type_Low_Bound (T_Typ);
9864                UB : constant Node_Id := Type_High_Bound (T_Typ);
9865
9866                Out_Of_Range  : Boolean;
9867                Static_Bounds : constant Boolean :=
9868                  Compile_Time_Known_Value (LB)
9869                  and Compile_Time_Known_Value (UB);
9870
9871             begin
9872                --  Following range tests should use Sem_Eval routine ???
9873
9874                if Static_Bounds then
9875                   if Is_Floating_Point_Type (S_Typ) then
9876                      Out_Of_Range :=
9877                        (Expr_Value_R (Ck_Node) < Expr_Value_R (LB))
9878                          or else
9879                        (Expr_Value_R (Ck_Node) > Expr_Value_R (UB));
9880
9881                   --  Fixed or discrete type
9882
9883                   else
9884                      Out_Of_Range :=
9885                        Expr_Value (Ck_Node) < Expr_Value (LB)
9886                          or else
9887                        Expr_Value (Ck_Node) > Expr_Value (UB);
9888                   end if;
9889
9890                   --  Bounds of the type are static and the literal is out of
9891                   --  range so output a warning message.
9892
9893                   if Out_Of_Range then
9894                      if No (Warn_Node) then
9895                         Add_Check
9896                           (Compile_Time_Constraint_Error
9897                              (Ck_Node,
9898                               "static value out of range of}??", T_Typ));
9899
9900                      else
9901                         Add_Check
9902                           (Compile_Time_Constraint_Error
9903                              (Wnode,
9904                               "static value out of range of}??", T_Typ));
9905                      end if;
9906                   end if;
9907
9908                else
9909                   Cond := Discrete_Expr_Cond (Ck_Node, T_Typ);
9910                end if;
9911             end;
9912
9913          --  Here for the case of a non-static expression, we need a runtime
9914          --  check unless the source type range is guaranteed to be in the
9915          --  range of the target type.
9916
9917          else
9918             if not In_Subrange_Of (S_Typ, T_Typ) then
9919                Cond := Discrete_Expr_Cond (Ck_Node, T_Typ);
9920             end if;
9921          end if;
9922       end if;
9923
9924       if Is_Array_Type (T_Typ) and then Is_Array_Type (S_Typ) then
9925          if Is_Constrained (T_Typ) then
9926
9927             Expr_Actual := Get_Referenced_Object (Ck_Node);
9928             Exptyp      := Get_Actual_Subtype (Expr_Actual);
9929
9930             if Is_Access_Type (Exptyp) then
9931                Exptyp := Designated_Type (Exptyp);
9932             end if;
9933
9934             --  String_Literal case. This needs to be handled specially be-
9935             --  cause no index types are available for string literals. The
9936             --  condition is simply:
9937
9938             --    T_Typ'Length = string-literal-length
9939
9940             if Nkind (Expr_Actual) = N_String_Literal then
9941                null;
9942
9943             --  General array case. Here we have a usable actual subtype for
9944             --  the expression, and the condition is built from the two types
9945
9946             --     T_Typ'First     < Exptyp'First     or else
9947             --     T_Typ'Last      > Exptyp'Last      or else
9948             --     T_Typ'First(1)  < Exptyp'First(1)  or else
9949             --     T_Typ'Last(1)   > Exptyp'Last(1)   or else
9950             --     ...
9951
9952             elsif Is_Constrained (Exptyp) then
9953                declare
9954                   Ndims : constant Nat := Number_Dimensions (T_Typ);
9955
9956                   L_Index : Node_Id;
9957                   R_Index : Node_Id;
9958
9959                begin
9960                   L_Index := First_Index (T_Typ);
9961                   R_Index := First_Index (Exptyp);
9962
9963                   for Indx in 1 .. Ndims loop
9964                      if not (Nkind (L_Index) = N_Raise_Constraint_Error
9965                                or else
9966                              Nkind (R_Index) = N_Raise_Constraint_Error)
9967                      then
9968                         --  Deal with compile time length check. Note that we
9969                         --  skip this in the access case, because the access
9970                         --  value may be null, so we cannot know statically.
9971
9972                         if not
9973                           Subtypes_Statically_Match
9974                             (Etype (L_Index), Etype (R_Index))
9975                         then
9976                            --  If the target type is constrained then we
9977                            --  have to check for exact equality of bounds
9978                            --  (required for qualified expressions).
9979
9980                            if Is_Constrained (T_Typ) then
9981                               Evolve_Or_Else
9982                                 (Cond,
9983                                  Range_Equal_E_Cond (Exptyp, T_Typ, Indx));
9984                            else
9985                               Evolve_Or_Else
9986                                 (Cond, Range_E_Cond (Exptyp, T_Typ, Indx));
9987                            end if;
9988                         end if;
9989
9990                         Next (L_Index);
9991                         Next (R_Index);
9992                      end if;
9993                   end loop;
9994                end;
9995
9996             --  Handle cases where we do not get a usable actual subtype that
9997             --  is constrained. This happens for example in the function call
9998             --  and explicit dereference cases. In these cases, we have to get
9999             --  the length or range from the expression itself, making sure we
10000             --  do not evaluate it more than once.
10001
10002             --  Here Ck_Node is the original expression, or more properly the
10003             --  result of applying Duplicate_Expr to the original tree,
10004             --  forcing the result to be a name.
10005
10006             else
10007                declare
10008                   Ndims : constant Nat := Number_Dimensions (T_Typ);
10009
10010                begin
10011                   --  Build the condition for the explicit dereference case
10012
10013                   for Indx in 1 .. Ndims loop
10014                      Evolve_Or_Else
10015                        (Cond, Range_N_Cond (Ck_Node, T_Typ, Indx));
10016                   end loop;
10017                end;
10018             end if;
10019
10020          else
10021             --  For a conversion to an unconstrained array type, generate an
10022             --  Action to check that the bounds of the source value are within
10023             --  the constraints imposed by the target type (RM 4.6(38)). No
10024             --  check is needed for a conversion to an access to unconstrained
10025             --  array type, as 4.6(24.15/2) requires the designated subtypes
10026             --  of the two access types to statically match.
10027
10028             if Nkind (Parent (Ck_Node)) = N_Type_Conversion
10029               and then not Do_Access
10030             then
10031                declare
10032                   Opnd_Index : Node_Id;
10033                   Targ_Index : Node_Id;
10034                   Opnd_Range : Node_Id;
10035
10036                begin
10037                   Opnd_Index := First_Index (Get_Actual_Subtype (Ck_Node));
10038                   Targ_Index := First_Index (T_Typ);
10039                   while Present (Opnd_Index) loop
10040
10041                      --  If the index is a range, use its bounds. If it is an
10042                      --  entity (as will be the case if it is a named subtype
10043                      --  or an itype created for a slice) retrieve its range.
10044
10045                      if Is_Entity_Name (Opnd_Index)
10046                        and then Is_Type (Entity (Opnd_Index))
10047                      then
10048                         Opnd_Range := Scalar_Range (Entity (Opnd_Index));
10049                      else
10050                         Opnd_Range := Opnd_Index;
10051                      end if;
10052
10053                      if Nkind (Opnd_Range) = N_Range then
10054                         if  Is_In_Range
10055                              (Low_Bound (Opnd_Range), Etype (Targ_Index),
10056                               Assume_Valid => True)
10057                           and then
10058                             Is_In_Range
10059                              (High_Bound (Opnd_Range), Etype (Targ_Index),
10060                               Assume_Valid => True)
10061                         then
10062                            null;
10063
10064                         --  If null range, no check needed
10065
10066                         elsif
10067                           Compile_Time_Known_Value (High_Bound (Opnd_Range))
10068                             and then
10069                           Compile_Time_Known_Value (Low_Bound (Opnd_Range))
10070                             and then
10071                               Expr_Value (High_Bound (Opnd_Range)) <
10072                                   Expr_Value (Low_Bound (Opnd_Range))
10073                         then
10074                            null;
10075
10076                         elsif Is_Out_Of_Range
10077                                 (Low_Bound (Opnd_Range), Etype (Targ_Index),
10078                                  Assume_Valid => True)
10079                           or else
10080                               Is_Out_Of_Range
10081                                 (High_Bound (Opnd_Range), Etype (Targ_Index),
10082                                  Assume_Valid => True)
10083                         then
10084                            Add_Check
10085                              (Compile_Time_Constraint_Error
10086                                (Wnode, "value out of range of}??", T_Typ));
10087
10088                         else
10089                            Evolve_Or_Else
10090                              (Cond,
10091                               Discrete_Range_Cond
10092                                 (Opnd_Range, Etype (Targ_Index)));
10093                         end if;
10094                      end if;
10095
10096                      Next_Index (Opnd_Index);
10097                      Next_Index (Targ_Index);
10098                   end loop;
10099                end;
10100             end if;
10101          end if;
10102       end if;
10103
10104       --  Construct the test and insert into the tree
10105
10106       if Present (Cond) then
10107          if Do_Access then
10108             Cond := Guard_Access (Cond, Loc, Ck_Node);
10109          end if;
10110
10111          Add_Check
10112            (Make_Raise_Constraint_Error (Loc,
10113              Condition => Cond,
10114              Reason    => CE_Range_Check_Failed));
10115       end if;
10116
10117       return Ret_Result;
10118    end Selected_Range_Checks;
10119
10120    -------------------------------
10121    -- Storage_Checks_Suppressed --
10122    -------------------------------
10123
10124    function Storage_Checks_Suppressed (E : Entity_Id) return Boolean is
10125    begin
10126       if Present (E) and then Checks_May_Be_Suppressed (E) then
10127          return Is_Check_Suppressed (E, Storage_Check);
10128       else
10129          return Scope_Suppress.Suppress (Storage_Check);
10130       end if;
10131    end Storage_Checks_Suppressed;
10132
10133    ---------------------------
10134    -- Tag_Checks_Suppressed --
10135    ---------------------------
10136
10137    function Tag_Checks_Suppressed (E : Entity_Id) return Boolean is
10138    begin
10139       if Present (E)
10140         and then Checks_May_Be_Suppressed (E)
10141       then
10142          return Is_Check_Suppressed (E, Tag_Check);
10143       else
10144          return Scope_Suppress.Suppress (Tag_Check);
10145       end if;
10146    end Tag_Checks_Suppressed;
10147
10148    ---------------------------------------
10149    -- Validate_Alignment_Check_Warnings --
10150    ---------------------------------------
10151
10152    procedure Validate_Alignment_Check_Warnings is
10153    begin
10154       for J in Alignment_Warnings.First .. Alignment_Warnings.Last loop
10155          declare
10156             AWR : Alignment_Warnings_Record
10157                     renames Alignment_Warnings.Table (J);
10158          begin
10159             if Known_Alignment (AWR.E)
10160               and then AWR.A mod Alignment (AWR.E) = 0
10161             then
10162                Delete_Warning_And_Continuations (AWR.W);
10163             end if;
10164          end;
10165       end loop;
10166    end Validate_Alignment_Check_Warnings;
10167
10168    --------------------------
10169    -- Validity_Check_Range --
10170    --------------------------
10171
10172    procedure Validity_Check_Range
10173      (N          : Node_Id;
10174       Related_Id : Entity_Id := Empty)
10175    is
10176    begin
10177       if Validity_Checks_On and Validity_Check_Operands then
10178          if Nkind (N) = N_Range then
10179             Ensure_Valid
10180               (Expr          => Low_Bound (N),
10181                Related_Id    => Related_Id,
10182                Is_Low_Bound  => True);
10183
10184             Ensure_Valid
10185               (Expr          => High_Bound (N),
10186                Related_Id    => Related_Id,
10187                Is_High_Bound => True);
10188          end if;
10189       end if;
10190    end Validity_Check_Range;
10191
10192    --------------------------------
10193    -- Validity_Checks_Suppressed --
10194    --------------------------------
10195
10196    function Validity_Checks_Suppressed (E : Entity_Id) return Boolean is
10197    begin
10198       if Present (E) and then Checks_May_Be_Suppressed (E) then
10199          return Is_Check_Suppressed (E, Validity_Check);
10200       else
10201          return Scope_Suppress.Suppress (Validity_Check);
10202       end if;
10203    end Validity_Checks_Suppressed;
10204
10205 end Checks;