OSDN Git Service

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