OSDN Git Service

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