]> gcc.gnu.org Git - gcc.git/blame - gcc/ada/sem_eval.adb
Makefile.in, [...]: Update dependencies.
[gcc.git] / gcc / ada / sem_eval.adb
CommitLineData
fbf5a39b 1------------------------------------------------------------------------------
996ae0b0
RK
2-- --
3-- GNAT COMPILER COMPONENTS --
4-- --
5-- S E M _ E V A L --
6-- --
7-- B o d y --
8-- --
22cb89b5 9-- Copyright (C) 1992-2010, Free Software Foundation, Inc. --
996ae0b0
RK
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- --
b5c84c3c 13-- ware Foundation; either version 3, or (at your option) any later ver- --
996ae0b0
RK
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 --
b5c84c3c
RD
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. --
996ae0b0
RK
20-- --
21-- GNAT was originally developed by the GNAT team at New York University. --
71ff80dc 22-- Extensive contributions were provided by Ada Core Technologies Inc. --
996ae0b0
RK
23-- --
24------------------------------------------------------------------------------
25
26with Atree; use Atree;
27with Checks; use Checks;
28with Debug; use Debug;
29with Einfo; use Einfo;
30with Elists; use Elists;
31with Errout; use Errout;
32with Eval_Fat; use Eval_Fat;
8cbb664e 33with Exp_Util; use Exp_Util;
0356699b 34with Lib; use Lib;
13f34a3f 35with Namet; use Namet;
996ae0b0
RK
36with Nmake; use Nmake;
37with Nlists; use Nlists;
38with Opt; use Opt;
39with Sem; use Sem;
a4100e55 40with Sem_Aux; use Sem_Aux;
996ae0b0 41with Sem_Cat; use Sem_Cat;
b5bd964f 42with Sem_Ch6; use Sem_Ch6;
996ae0b0
RK
43with Sem_Ch8; use Sem_Ch8;
44with Sem_Res; use Sem_Res;
45with Sem_Util; use Sem_Util;
46with Sem_Type; use Sem_Type;
47with Sem_Warn; use Sem_Warn;
48with Sinfo; use Sinfo;
49with Snames; use Snames;
50with Stand; use Stand;
51with Stringt; use Stringt;
07fc65c4 52with Tbuild; use Tbuild;
996ae0b0
RK
53
54package body Sem_Eval is
55
56 -----------------------------------------
57 -- Handling of Compile Time Evaluation --
58 -----------------------------------------
59
60 -- The compile time evaluation of expressions is distributed over several
f3d57416 61 -- Eval_xxx procedures. These procedures are called immediately after
996ae0b0
RK
62 -- a subexpression is resolved and is therefore accomplished in a bottom
63 -- up fashion. The flags are synthesized using the following approach.
64
65 -- Is_Static_Expression is determined by following the detailed rules
66 -- in RM 4.9(4-14). This involves testing the Is_Static_Expression
67 -- flag of the operands in many cases.
68
69 -- Raises_Constraint_Error is set if any of the operands have the flag
70 -- set or if an attempt to compute the value of the current expression
71 -- results in detection of a runtime constraint error.
72
73 -- As described in the spec, the requirement is that Is_Static_Expression
74 -- be accurately set, and in addition for nodes for which this flag is set,
75 -- Raises_Constraint_Error must also be set. Furthermore a node which has
76 -- Is_Static_Expression set, and Raises_Constraint_Error clear, then the
77 -- requirement is that the expression value must be precomputed, and the
78 -- node is either a literal, or the name of a constant entity whose value
79 -- is a static expression.
80
81 -- The general approach is as follows. First compute Is_Static_Expression.
82 -- If the node is not static, then the flag is left off in the node and
83 -- we are all done. Otherwise for a static node, we test if any of the
84 -- operands will raise constraint error, and if so, propagate the flag
85 -- Raises_Constraint_Error to the result node and we are done (since the
86 -- error was already posted at a lower level).
87
88 -- For the case of a static node whose operands do not raise constraint
89 -- error, we attempt to evaluate the node. If this evaluation succeeds,
90 -- then the node is replaced by the result of this computation. If the
91 -- evaluation raises constraint error, then we rewrite the node with
92 -- Apply_Compile_Time_Constraint_Error to raise the exception and also
93 -- to post appropriate error messages.
94
95 ----------------
96 -- Local Data --
97 ----------------
98
99 type Bits is array (Nat range <>) of Boolean;
100 -- Used to convert unsigned (modular) values for folding logical ops
101
07fc65c4
GB
102 -- The following definitions are used to maintain a cache of nodes that
103 -- have compile time known values. The cache is maintained only for
104 -- discrete types (the most common case), and is populated by calls to
105 -- Compile_Time_Known_Value and Expr_Value, but only used by Expr_Value
106 -- since it is possible for the status to change (in particular it is
107 -- possible for a node to get replaced by a constraint error node).
108
109 CV_Bits : constant := 5;
110 -- Number of low order bits of Node_Id value used to reference entries
111 -- in the cache table.
112
113 CV_Cache_Size : constant Nat := 2 ** CV_Bits;
114 -- Size of cache for compile time values
115
116 subtype CV_Range is Nat range 0 .. CV_Cache_Size;
117
118 type CV_Entry is record
119 N : Node_Id;
120 V : Uint;
121 end record;
122
123 type CV_Cache_Array is array (CV_Range) of CV_Entry;
124
125 CV_Cache : CV_Cache_Array := (others => (Node_High_Bound, Uint_0));
126 -- This is the actual cache, with entries consisting of node/value pairs,
127 -- and the impossible value Node_High_Bound used for unset entries.
128
305caf42
AC
129 type Range_Membership is (In_Range, Out_Of_Range, Unknown);
130 -- Range membership may either be statically known to be in range or out
131 -- of range, or not statically known. Used for Test_In_Range below.
132
996ae0b0
RK
133 -----------------------
134 -- Local Subprograms --
135 -----------------------
136
996ae0b0
RK
137 function From_Bits (B : Bits; T : Entity_Id) return Uint;
138 -- Converts a bit string of length B'Length to a Uint value to be used
139 -- for a target of type T, which is a modular type. This procedure
140 -- includes the necessary reduction by the modulus in the case of a
141 -- non-binary modulus (for a binary modulus, the bit string is the
142 -- right length any way so all is well).
143
144 function Get_String_Val (N : Node_Id) return Node_Id;
145 -- Given a tree node for a folded string or character value, returns
146 -- the corresponding string literal or character literal (one of the
147 -- two must be available, or the operand would not have been marked
148 -- as foldable in the earlier analysis of the operation).
149
07fc65c4
GB
150 function OK_Bits (N : Node_Id; Bits : Uint) return Boolean;
151 -- Bits represents the number of bits in an integer value to be computed
152 -- (but the value has not been computed yet). If this value in Bits is
153 -- reasonable, a result of True is returned, with the implication that
154 -- the caller should go ahead and complete the calculation. If the value
155 -- in Bits is unreasonably large, then an error is posted on node N, and
156 -- False is returned (and the caller skips the proposed calculation).
157
996ae0b0
RK
158 procedure Out_Of_Range (N : Node_Id);
159 -- This procedure is called if it is determined that node N, which
160 -- appears in a non-static context, is a compile time known value
161 -- which is outside its range, i.e. the range of Etype. This is used
162 -- in contexts where this is an illegality if N is static, and should
163 -- generate a warning otherwise.
164
165 procedure Rewrite_In_Raise_CE (N : Node_Id; Exp : Node_Id);
166 -- N and Exp are nodes representing an expression, Exp is known
167 -- to raise CE. N is rewritten in term of Exp in the optimal way.
168
169 function String_Type_Len (Stype : Entity_Id) return Uint;
170 -- Given a string type, determines the length of the index type, or,
171 -- if this index type is non-static, the length of the base type of
172 -- this index type. Note that if the string type is itself static,
173 -- then the index type is static, so the second case applies only
174 -- if the string type passed is non-static.
175
176 function Test (Cond : Boolean) return Uint;
177 pragma Inline (Test);
178 -- This function simply returns the appropriate Boolean'Pos value
179 -- corresponding to the value of Cond as a universal integer. It is
180 -- used for producing the result of the static evaluation of the
181 -- logical operators
182
183 procedure Test_Expression_Is_Foldable
184 (N : Node_Id;
185 Op1 : Node_Id;
186 Stat : out Boolean;
187 Fold : out Boolean);
188 -- Tests to see if expression N whose single operand is Op1 is foldable,
189 -- i.e. the operand value is known at compile time. If the operation is
190 -- foldable, then Fold is True on return, and Stat indicates whether
191 -- the result is static (i.e. both operands were static). Note that it
192 -- is quite possible for Fold to be True, and Stat to be False, since
193 -- there are cases in which we know the value of an operand even though
194 -- it is not technically static (e.g. the static lower bound of a range
195 -- whose upper bound is non-static).
196 --
3d5952be 197 -- If Stat is set False on return, then Test_Expression_Is_Foldable makes a
996ae0b0
RK
198 -- call to Check_Non_Static_Context on the operand. If Fold is False on
199 -- return, then all processing is complete, and the caller should
200 -- return, since there is nothing else to do.
93c3fca7
AC
201 --
202 -- If Stat is set True on return, then Is_Static_Expression is also set
203 -- true in node N. There are some cases where this is over-enthusiastic,
204 -- e.g. in the two operand case below, for string comaprison, the result
205 -- is not static even though the two operands are static. In such cases,
206 -- the caller must reset the Is_Static_Expression flag in N.
996ae0b0
RK
207
208 procedure Test_Expression_Is_Foldable
209 (N : Node_Id;
210 Op1 : Node_Id;
211 Op2 : Node_Id;
212 Stat : out Boolean;
213 Fold : out Boolean);
214 -- Same processing, except applies to an expression N with two operands
215 -- Op1 and Op2.
216
305caf42
AC
217 function Test_In_Range
218 (N : Node_Id;
219 Typ : Entity_Id;
220 Assume_Valid : Boolean;
221 Fixed_Int : Boolean;
222 Int_Real : Boolean) return Range_Membership;
223 -- Common processing for Is_In_Range and Is_Out_Of_Range:
224 -- Returns In_Range or Out_Of_Range if it can be guaranteed at compile time
225 -- that expression N is known to be in or out of range of the subtype Typ.
226 -- If not compile time known, Unknown is returned.
227 -- See documentation of Is_In_Range for complete description of parameters.
228
996ae0b0
RK
229 procedure To_Bits (U : Uint; B : out Bits);
230 -- Converts a Uint value to a bit string of length B'Length
231
232 ------------------------------
233 -- Check_Non_Static_Context --
234 ------------------------------
235
236 procedure Check_Non_Static_Context (N : Node_Id) is
fbf5a39b
AC
237 T : constant Entity_Id := Etype (N);
238 Checks_On : constant Boolean :=
996ae0b0
RK
239 not Index_Checks_Suppressed (T)
240 and not Range_Checks_Suppressed (T);
241
242 begin
fbf5a39b 243 -- Ignore cases of non-scalar types or error types
996ae0b0 244
fbf5a39b 245 if T = Any_Type or else not Is_Scalar_Type (T) then
996ae0b0 246 return;
fbf5a39b 247 end if;
996ae0b0 248
fbf5a39b
AC
249 -- At this stage we have a scalar type. If we have an expression
250 -- that raises CE, then we already issued a warning or error msg
251 -- so there is nothing more to be done in this routine.
252
253 if Raises_Constraint_Error (N) then
254 return;
255 end if;
256
257 -- Now we have a scalar type which is not marked as raising a
258 -- constraint error exception. The main purpose of this routine
259 -- is to deal with static expressions appearing in a non-static
260 -- context. That means that if we do not have a static expression
261 -- then there is not much to do. The one case that we deal with
262 -- here is that if we have a floating-point value that is out of
263 -- range, then we post a warning that an infinity will result.
264
265 if not Is_Static_Expression (N) then
266 if Is_Floating_Point_Type (T)
c800f862 267 and then Is_Out_Of_Range (N, Base_Type (T), Assume_Valid => True)
fbf5a39b
AC
268 then
269 Error_Msg_N
270 ("?float value out of range, infinity will be generated", N);
271 end if;
996ae0b0 272
996ae0b0
RK
273 return;
274 end if;
275
276 -- Here we have the case of outer level static expression of
277 -- scalar type, where the processing of this procedure is needed.
278
279 -- For real types, this is where we convert the value to a machine
280 -- number (see RM 4.9(38)). Also see ACVC test C490001. We should
281 -- only need to do this if the parent is a constant declaration,
282 -- since in other cases, gigi should do the necessary conversion
283 -- correctly, but experimentation shows that this is not the case
284 -- on all machines, in particular if we do not convert all literals
285 -- to machine values in non-static contexts, then ACVC test C490001
286 -- fails on Sparc/Solaris and SGI/Irix.
287
288 if Nkind (N) = N_Real_Literal
289 and then not Is_Machine_Number (N)
290 and then not Is_Generic_Type (Etype (N))
291 and then Etype (N) /= Universal_Real
996ae0b0
RK
292 then
293 -- Check that value is in bounds before converting to machine
294 -- number, so as not to lose case where value overflows in the
295 -- least significant bit or less. See B490001.
296
c800f862 297 if Is_Out_Of_Range (N, Base_Type (T), Assume_Valid => True) then
996ae0b0
RK
298 Out_Of_Range (N);
299 return;
300 end if;
301
302 -- Note: we have to copy the node, to avoid problems with conformance
303 -- of very similar numbers (see ACVC tests B4A010C and B63103A).
304
305 Rewrite (N, New_Copy (N));
306
307 if not Is_Floating_Point_Type (T) then
308 Set_Realval
309 (N, Corresponding_Integer_Value (N) * Small_Value (T));
310
311 elsif not UR_Is_Zero (Realval (N)) then
996ae0b0 312
fbf5a39b
AC
313 -- Note: even though RM 4.9(38) specifies biased rounding,
314 -- this has been modified by AI-100 in order to prevent
315 -- confusing differences in rounding between static and
316 -- non-static expressions. AI-100 specifies that the effect
317 -- of such rounding is implementation dependent, and in GNAT
318 -- we round to nearest even to match the run-time behavior.
996ae0b0 319
fbf5a39b
AC
320 Set_Realval
321 (N, Machine (Base_Type (T), Realval (N), Round_Even, N));
996ae0b0
RK
322 end if;
323
324 Set_Is_Machine_Number (N);
325 end if;
326
327 -- Check for out of range universal integer. This is a non-static
328 -- context, so the integer value must be in range of the runtime
329 -- representation of universal integers.
330
331 -- We do this only within an expression, because that is the only
332 -- case in which non-static universal integer values can occur, and
333 -- furthermore, Check_Non_Static_Context is currently (incorrectly???)
334 -- called in contexts like the expression of a number declaration where
335 -- we certainly want to allow out of range values.
336
337 if Etype (N) = Universal_Integer
338 and then Nkind (N) = N_Integer_Literal
339 and then Nkind (Parent (N)) in N_Subexpr
340 and then
341 (Intval (N) < Expr_Value (Type_Low_Bound (Universal_Integer))
342 or else
343 Intval (N) > Expr_Value (Type_High_Bound (Universal_Integer)))
344 then
345 Apply_Compile_Time_Constraint_Error
07fc65c4
GB
346 (N, "non-static universal integer value out of range?",
347 CE_Range_Check_Failed);
996ae0b0
RK
348
349 -- Check out of range of base type
350
c800f862 351 elsif Is_Out_Of_Range (N, Base_Type (T), Assume_Valid => True) then
996ae0b0
RK
352 Out_Of_Range (N);
353
c800f862
RD
354 -- Give warning if outside subtype (where one or both of the bounds of
355 -- the subtype is static). This warning is omitted if the expression
356 -- appears in a range that could be null (warnings are handled elsewhere
357 -- for this case).
996ae0b0
RK
358
359 elsif T /= Base_Type (T)
360 and then Nkind (Parent (N)) /= N_Range
361 then
c800f862 362 if Is_In_Range (N, T, Assume_Valid => True) then
996ae0b0
RK
363 null;
364
c800f862 365 elsif Is_Out_Of_Range (N, T, Assume_Valid => True) then
996ae0b0 366 Apply_Compile_Time_Constraint_Error
07fc65c4 367 (N, "value not in range of}?", CE_Range_Check_Failed);
996ae0b0
RK
368
369 elsif Checks_On then
370 Enable_Range_Check (N);
371
372 else
373 Set_Do_Range_Check (N, False);
374 end if;
375 end if;
376 end Check_Non_Static_Context;
377
378 ---------------------------------
379 -- Check_String_Literal_Length --
380 ---------------------------------
381
382 procedure Check_String_Literal_Length (N : Node_Id; Ttype : Entity_Id) is
383 begin
384 if not Raises_Constraint_Error (N)
385 and then Is_Constrained (Ttype)
386 then
387 if
388 UI_From_Int (String_Length (Strval (N))) /= String_Type_Len (Ttype)
389 then
390 Apply_Compile_Time_Constraint_Error
391 (N, "string length wrong for}?",
07fc65c4 392 CE_Length_Check_Failed,
996ae0b0
RK
393 Ent => Ttype,
394 Typ => Ttype);
395 end if;
396 end if;
397 end Check_String_Literal_Length;
398
399 --------------------------
400 -- Compile_Time_Compare --
401 --------------------------
402
fbf5a39b 403 function Compile_Time_Compare
1c7717c3 404 (L, R : Node_Id;
af02a866
RD
405 Assume_Valid : Boolean) return Compare_Result
406 is
407 Discard : aliased Uint;
408 begin
409 return Compile_Time_Compare (L, R, Discard'Access, Assume_Valid);
410 end Compile_Time_Compare;
411
412 function Compile_Time_Compare
413 (L, R : Node_Id;
414 Diff : access Uint;
1c7717c3
AC
415 Assume_Valid : Boolean;
416 Rec : Boolean := False) return Compare_Result
fbf5a39b 417 is
93c3fca7
AC
418 Ltyp : Entity_Id := Underlying_Type (Etype (L));
419 Rtyp : Entity_Id := Underlying_Type (Etype (R));
1c7717c3
AC
420 -- These get reset to the base type for the case of entities where
421 -- Is_Known_Valid is not set. This takes care of handling possible
422 -- invalid representations using the value of the base type, in
423 -- accordance with RM 13.9.1(10).
996ae0b0 424
af02a866
RD
425 Discard : aliased Uint;
426
996ae0b0
RK
427 procedure Compare_Decompose
428 (N : Node_Id;
429 R : out Node_Id;
430 V : out Uint);
b49365b2
RD
431 -- This procedure decomposes the node N into an expression node and a
432 -- signed offset, so that the value of N is equal to the value of R plus
433 -- the value V (which may be negative). If no such decomposition is
434 -- possible, then on return R is a copy of N, and V is set to zero.
996ae0b0
RK
435
436 function Compare_Fixup (N : Node_Id) return Node_Id;
b49365b2
RD
437 -- This function deals with replacing 'Last and 'First references with
438 -- their corresponding type bounds, which we then can compare. The
439 -- argument is the original node, the result is the identity, unless we
440 -- have a 'Last/'First reference in which case the value returned is the
441 -- appropriate type bound.
996ae0b0 442
57036dcc
ES
443 function Is_Known_Valid_Operand (Opnd : Node_Id) return Boolean;
444 -- Even if the context does not assume that values are valid, some
445 -- simple cases can be recognized.
446
996ae0b0
RK
447 function Is_Same_Value (L, R : Node_Id) return Boolean;
448 -- Returns True iff L and R represent expressions that definitely
449 -- have identical (but not necessarily compile time known) values
450 -- Indeed the caller is expected to have already dealt with the
451 -- cases of compile time known values, so these are not tested here.
452
453 -----------------------
454 -- Compare_Decompose --
455 -----------------------
456
457 procedure Compare_Decompose
458 (N : Node_Id;
459 R : out Node_Id;
460 V : out Uint)
461 is
462 begin
463 if Nkind (N) = N_Op_Add
464 and then Nkind (Right_Opnd (N)) = N_Integer_Literal
465 then
466 R := Left_Opnd (N);
467 V := Intval (Right_Opnd (N));
468 return;
469
470 elsif Nkind (N) = N_Op_Subtract
471 and then Nkind (Right_Opnd (N)) = N_Integer_Literal
472 then
473 R := Left_Opnd (N);
474 V := UI_Negate (Intval (Right_Opnd (N)));
475 return;
476
477 elsif Nkind (N) = N_Attribute_Reference then
996ae0b0
RK
478 if Attribute_Name (N) = Name_Succ then
479 R := First (Expressions (N));
480 V := Uint_1;
481 return;
482
483 elsif Attribute_Name (N) = Name_Pred then
484 R := First (Expressions (N));
485 V := Uint_Minus_1;
486 return;
487 end if;
488 end if;
489
490 R := N;
491 V := Uint_0;
492 end Compare_Decompose;
493
494 -------------------
495 -- Compare_Fixup --
496 -------------------
497
498 function Compare_Fixup (N : Node_Id) return Node_Id is
499 Indx : Node_Id;
500 Xtyp : Entity_Id;
501 Subs : Nat;
502
503 begin
504 if Nkind (N) = N_Attribute_Reference
505 and then (Attribute_Name (N) = Name_First
506 or else
507 Attribute_Name (N) = Name_Last)
508 then
509 Xtyp := Etype (Prefix (N));
510
511 -- If we have no type, then just abandon the attempt to do
512 -- a fixup, this is probably the result of some other error.
513
514 if No (Xtyp) then
515 return N;
516 end if;
517
518 -- Dereference an access type
519
520 if Is_Access_Type (Xtyp) then
521 Xtyp := Designated_Type (Xtyp);
522 end if;
523
524 -- If we don't have an array type at this stage, something
525 -- is peculiar, e.g. another error, and we abandon the attempt
526 -- at a fixup.
527
528 if not Is_Array_Type (Xtyp) then
529 return N;
530 end if;
531
532 -- Ignore unconstrained array, since bounds are not meaningful
533
534 if not Is_Constrained (Xtyp) then
535 return N;
536 end if;
537
c3de5c4c
ES
538 if Ekind (Xtyp) = E_String_Literal_Subtype then
539 if Attribute_Name (N) = Name_First then
540 return String_Literal_Low_Bound (Xtyp);
541
542 else -- Attribute_Name (N) = Name_Last
543 return Make_Integer_Literal (Sloc (N),
544 Intval => Intval (String_Literal_Low_Bound (Xtyp))
57036dcc 545 + String_Literal_Length (Xtyp));
c3de5c4c
ES
546 end if;
547 end if;
548
996ae0b0
RK
549 -- Find correct index type
550
551 Indx := First_Index (Xtyp);
552
553 if Present (Expressions (N)) then
554 Subs := UI_To_Int (Expr_Value (First (Expressions (N))));
555
556 for J in 2 .. Subs loop
557 Indx := Next_Index (Indx);
558 end loop;
559 end if;
560
561 Xtyp := Etype (Indx);
562
563 if Attribute_Name (N) = Name_First then
564 return Type_Low_Bound (Xtyp);
565
566 else -- Attribute_Name (N) = Name_Last
567 return Type_High_Bound (Xtyp);
568 end if;
569 end if;
570
571 return N;
572 end Compare_Fixup;
573
57036dcc
ES
574 ----------------------------
575 -- Is_Known_Valid_Operand --
576 ----------------------------
577
578 function Is_Known_Valid_Operand (Opnd : Node_Id) return Boolean is
579 begin
580 return (Is_Entity_Name (Opnd)
581 and then
582 (Is_Known_Valid (Entity (Opnd))
583 or else Ekind (Entity (Opnd)) = E_In_Parameter
584 or else
585 (Ekind (Entity (Opnd)) in Object_Kind
586 and then Present (Current_Value (Entity (Opnd))))))
587 or else Is_OK_Static_Expression (Opnd);
588 end Is_Known_Valid_Operand;
589
996ae0b0
RK
590 -------------------
591 -- Is_Same_Value --
592 -------------------
593
594 function Is_Same_Value (L, R : Node_Id) return Boolean is
595 Lf : constant Node_Id := Compare_Fixup (L);
596 Rf : constant Node_Id := Compare_Fixup (R);
597
fbf5a39b 598 function Is_Same_Subscript (L, R : List_Id) return Boolean;
57036dcc
ES
599 -- L, R are the Expressions values from two attribute nodes for First
600 -- or Last attributes. Either may be set to No_List if no expressions
601 -- are present (indicating subscript 1). The result is True if both
602 -- expressions represent the same subscript (note one case is where
603 -- one subscript is missing and the other is explicitly set to 1).
fbf5a39b
AC
604
605 -----------------------
606 -- Is_Same_Subscript --
607 -----------------------
608
609 function Is_Same_Subscript (L, R : List_Id) return Boolean is
610 begin
611 if L = No_List then
612 if R = No_List then
613 return True;
614 else
615 return Expr_Value (First (R)) = Uint_1;
616 end if;
617
618 else
619 if R = No_List then
620 return Expr_Value (First (L)) = Uint_1;
621 else
622 return Expr_Value (First (L)) = Expr_Value (First (R));
623 end if;
624 end if;
625 end Is_Same_Subscript;
626
627 -- Start of processing for Is_Same_Value
628
996ae0b0 629 begin
b49365b2 630 -- Values are the same if they refer to the same entity and the
c800f862
RD
631 -- entity is non-volatile. This does not however apply to Float
632 -- types, since we may have two NaN values and they should never
633 -- compare equal.
996ae0b0 634
b49365b2
RD
635 if Nkind_In (Lf, N_Identifier, N_Expanded_Name)
636 and then Nkind_In (Rf, N_Identifier, N_Expanded_Name)
996ae0b0 637 and then Entity (Lf) = Entity (Rf)
b49365b2 638 and then Present (Entity (Lf))
fbf5a39b 639 and then not Is_Floating_Point_Type (Etype (L))
c800f862
RD
640 and then not Is_Volatile_Reference (L)
641 and then not Is_Volatile_Reference (R)
996ae0b0
RK
642 then
643 return True;
644
645 -- Or if they are compile time known and identical
646
647 elsif Compile_Time_Known_Value (Lf)
648 and then
649 Compile_Time_Known_Value (Rf)
650 and then Expr_Value (Lf) = Expr_Value (Rf)
651 then
652 return True;
653
b49365b2
RD
654 -- False if Nkind of the two nodes is different for remaining cases
655
656 elsif Nkind (Lf) /= Nkind (Rf) then
657 return False;
658
659 -- True if both 'First or 'Last values applying to the same entity
660 -- (first and last don't change even if value does). Note that we
661 -- need this even with the calls to Compare_Fixup, to handle the
662 -- case of unconstrained array attributes where Compare_Fixup
663 -- cannot find useful bounds.
996ae0b0
RK
664
665 elsif Nkind (Lf) = N_Attribute_Reference
996ae0b0
RK
666 and then Attribute_Name (Lf) = Attribute_Name (Rf)
667 and then (Attribute_Name (Lf) = Name_First
668 or else
669 Attribute_Name (Lf) = Name_Last)
b49365b2
RD
670 and then Nkind_In (Prefix (Lf), N_Identifier, N_Expanded_Name)
671 and then Nkind_In (Prefix (Rf), N_Identifier, N_Expanded_Name)
996ae0b0 672 and then Entity (Prefix (Lf)) = Entity (Prefix (Rf))
fbf5a39b 673 and then Is_Same_Subscript (Expressions (Lf), Expressions (Rf))
996ae0b0
RK
674 then
675 return True;
676
b49365b2
RD
677 -- True if the same selected component from the same record
678
679 elsif Nkind (Lf) = N_Selected_Component
680 and then Selector_Name (Lf) = Selector_Name (Rf)
681 and then Is_Same_Value (Prefix (Lf), Prefix (Rf))
682 then
683 return True;
684
685 -- True if the same unary operator applied to the same operand
686
687 elsif Nkind (Lf) in N_Unary_Op
688 and then Is_Same_Value (Right_Opnd (Lf), Right_Opnd (Rf))
689 then
690 return True;
691
8682d22c 692 -- True if the same binary operator applied to the same operands
b49365b2
RD
693
694 elsif Nkind (Lf) in N_Binary_Op
695 and then Is_Same_Value (Left_Opnd (Lf), Left_Opnd (Rf))
696 and then Is_Same_Value (Right_Opnd (Lf), Right_Opnd (Rf))
697 then
698 return True;
699
8682d22c 700 -- All other cases, we can't tell, so return False
996ae0b0
RK
701
702 else
703 return False;
704 end if;
705 end Is_Same_Value;
706
707 -- Start of processing for Compile_Time_Compare
708
709 begin
af02a866
RD
710 Diff.all := No_Uint;
711
07fc65c4
GB
712 -- If either operand could raise constraint error, then we cannot
713 -- know the result at compile time (since CE may be raised!)
714
715 if not (Cannot_Raise_Constraint_Error (L)
716 and then
717 Cannot_Raise_Constraint_Error (R))
718 then
719 return Unknown;
720 end if;
721
722 -- Identical operands are most certainly equal
723
996ae0b0
RK
724 if L = R then
725 return EQ;
726
93c3fca7
AC
727 -- If expressions have no types, then do not attempt to determine if
728 -- they are the same, since something funny is going on. One case in
729 -- which this happens is during generic template analysis, when bounds
730 -- are not fully analyzed.
996ae0b0
RK
731
732 elsif No (Ltyp) or else No (Rtyp) then
733 return Unknown;
734
93c3fca7
AC
735 -- We do not attempt comparisons for packed arrays arrays represented as
736 -- modular types, where the semantics of comparison is quite different.
996ae0b0 737
93c3fca7
AC
738 elsif Is_Packed_Array_Type (Ltyp)
739 and then Is_Modular_Integer_Type (Ltyp)
996ae0b0
RK
740 then
741 return Unknown;
742
93c3fca7 743 -- For access types, the only time we know the result at compile time
f61580d4 744 -- (apart from identical operands, which we handled already) is if we
93c3fca7
AC
745 -- know one operand is null and the other is not, or both operands are
746 -- known null.
747
748 elsif Is_Access_Type (Ltyp) then
749 if Known_Null (L) then
750 if Known_Null (R) then
751 return EQ;
752 elsif Known_Non_Null (R) then
753 return NE;
754 else
755 return Unknown;
756 end if;
757
f61580d4 758 elsif Known_Non_Null (L) and then Known_Null (R) then
93c3fca7
AC
759 return NE;
760
761 else
762 return Unknown;
763 end if;
764
996ae0b0
RK
765 -- Case where comparison involves two compile time known values
766
767 elsif Compile_Time_Known_Value (L)
768 and then Compile_Time_Known_Value (R)
769 then
770 -- For the floating-point case, we have to be a little careful, since
771 -- at compile time we are dealing with universal exact values, but at
772 -- runtime, these will be in non-exact target form. That's why the
773 -- returned results are LE and GE below instead of LT and GT.
774
775 if Is_Floating_Point_Type (Ltyp)
776 or else
777 Is_Floating_Point_Type (Rtyp)
778 then
779 declare
780 Lo : constant Ureal := Expr_Value_R (L);
781 Hi : constant Ureal := Expr_Value_R (R);
782
783 begin
784 if Lo < Hi then
785 return LE;
786 elsif Lo = Hi then
787 return EQ;
788 else
789 return GE;
790 end if;
791 end;
792
93c3fca7
AC
793 -- For string types, we have two string literals and we proceed to
794 -- compare them using the Ada style dictionary string comparison.
795
796 elsif not Is_Scalar_Type (Ltyp) then
797 declare
798 Lstring : constant String_Id := Strval (Expr_Value_S (L));
799 Rstring : constant String_Id := Strval (Expr_Value_S (R));
800 Llen : constant Nat := String_Length (Lstring);
801 Rlen : constant Nat := String_Length (Rstring);
802
803 begin
804 for J in 1 .. Nat'Min (Llen, Rlen) loop
805 declare
806 LC : constant Char_Code := Get_String_Char (Lstring, J);
807 RC : constant Char_Code := Get_String_Char (Rstring, J);
808 begin
809 if LC < RC then
810 return LT;
811 elsif LC > RC then
812 return GT;
813 end if;
814 end;
815 end loop;
816
817 if Llen < Rlen then
818 return LT;
819 elsif Llen > Rlen then
820 return GT;
821 else
822 return EQ;
823 end if;
824 end;
825
826 -- For remaining scalar cases we know exactly (note that this does
827 -- include the fixed-point case, where we know the run time integer
f61580d4 828 -- values now).
996ae0b0
RK
829
830 else
831 declare
832 Lo : constant Uint := Expr_Value (L);
833 Hi : constant Uint := Expr_Value (R);
834
835 begin
836 if Lo < Hi then
af02a866 837 Diff.all := Hi - Lo;
996ae0b0 838 return LT;
af02a866 839
996ae0b0
RK
840 elsif Lo = Hi then
841 return EQ;
af02a866 842
996ae0b0 843 else
af02a866 844 Diff.all := Lo - Hi;
996ae0b0
RK
845 return GT;
846 end if;
847 end;
848 end if;
849
850 -- Cases where at least one operand is not known at compile time
851
852 else
93c3fca7 853 -- Remaining checks apply only for discrete types
29797f34
RD
854
855 if not Is_Discrete_Type (Ltyp)
856 or else not Is_Discrete_Type (Rtyp)
93c3fca7
AC
857 then
858 return Unknown;
859 end if;
860
861 -- Defend against generic types, or actually any expressions that
862 -- contain a reference to a generic type from within a generic
863 -- template. We don't want to do any range analysis of such
864 -- expressions for two reasons. First, the bounds of a generic type
865 -- itself are junk and cannot be used for any kind of analysis.
866 -- Second, we may have a case where the range at run time is indeed
867 -- known, but we don't want to do compile time analysis in the
868 -- template based on that range since in an instance the value may be
869 -- static, and able to be elaborated without reference to the bounds
870 -- of types involved. As an example, consider:
871
872 -- (F'Pos (F'Last) + 1) > Integer'Last
873
874 -- The expression on the left side of > is Universal_Integer and thus
875 -- acquires the type Integer for evaluation at run time, and at run
876 -- time it is true that this condition is always False, but within
877 -- an instance F may be a type with a static range greater than the
878 -- range of Integer, and the expression statically evaluates to True.
879
880 if References_Generic_Formal_Type (L)
881 or else
882 References_Generic_Formal_Type (R)
29797f34
RD
883 then
884 return Unknown;
885 end if;
886
1c7717c3
AC
887 -- Replace types by base types for the case of entities which are
888 -- not known to have valid representations. This takes care of
889 -- properly dealing with invalid representations.
890
c800f862 891 if not Assume_Valid and then not Assume_No_Invalid_Values then
1c7717c3 892 if Is_Entity_Name (L) and then not Is_Known_Valid (Entity (L)) then
93c3fca7 893 Ltyp := Underlying_Type (Base_Type (Ltyp));
1c7717c3
AC
894 end if;
895
896 if Is_Entity_Name (R) and then not Is_Known_Valid (Entity (R)) then
93c3fca7 897 Rtyp := Underlying_Type (Base_Type (Rtyp));
1c7717c3
AC
898 end if;
899 end if;
900
c800f862
RD
901 -- Try range analysis on variables and see if ranges are disjoint
902
903 declare
904 LOK, ROK : Boolean;
905 LLo, LHi : Uint;
906 RLo, RHi : Uint;
907
908 begin
909 Determine_Range (L, LOK, LLo, LHi, Assume_Valid);
910 Determine_Range (R, ROK, RLo, RHi, Assume_Valid);
911
912 if LOK and ROK then
913 if LHi < RLo then
914 return LT;
915
916 elsif RHi < LLo then
917 return GT;
918
919 elsif LLo = LHi
920 and then RLo = RHi
921 and then LLo = RLo
922 then
e27b834b 923
75ba322d
AC
924 -- If the range includes a single literal and we can assume
925 -- validity then the result is known even if an operand is
926 -- not static.
e27b834b
AC
927
928 if Assume_Valid then
929 return EQ;
e27b834b
AC
930 else
931 return Unknown;
932 end if;
c800f862
RD
933
934 elsif LHi = RLo then
935 return LE;
936
937 elsif RHi = LLo then
938 return GE;
57036dcc
ES
939
940 elsif not Is_Known_Valid_Operand (L)
941 and then not Assume_Valid
942 then
943 if Is_Same_Value (L, R) then
944 return EQ;
945 else
946 return Unknown;
947 end if;
c800f862
RD
948 end if;
949 end if;
950 end;
951
996ae0b0
RK
952 -- Here is where we check for comparisons against maximum bounds of
953 -- types, where we know that no value can be outside the bounds of
954 -- the subtype. Note that this routine is allowed to assume that all
955 -- expressions are within their subtype bounds. Callers wishing to
956 -- deal with possibly invalid values must in any case take special
957 -- steps (e.g. conversions to larger types) to avoid this kind of
958 -- optimization, which is always considered to be valid. We do not
959 -- attempt this optimization with generic types, since the type
960 -- bounds may not be meaningful in this case.
961
93c3fca7 962 -- We are in danger of an infinite recursion here. It does not seem
fbf5a39b
AC
963 -- useful to go more than one level deep, so the parameter Rec is
964 -- used to protect ourselves against this infinite recursion.
965
29797f34
RD
966 if not Rec then
967
fbf5a39b
AC
968 -- See if we can get a decisive check against one operand and
969 -- a bound of the other operand (four possible tests here).
93c3fca7
AC
970 -- Note that we avoid testing junk bounds of a generic type.
971
972 if not Is_Generic_Type (Rtyp) then
973 case Compile_Time_Compare (L, Type_Low_Bound (Rtyp),
974 Discard'Access,
975 Assume_Valid, Rec => True)
976 is
977 when LT => return LT;
978 when LE => return LE;
979 when EQ => return LE;
980 when others => null;
981 end case;
fbf5a39b 982
93c3fca7
AC
983 case Compile_Time_Compare (L, Type_High_Bound (Rtyp),
984 Discard'Access,
985 Assume_Valid, Rec => True)
986 is
987 when GT => return GT;
988 when GE => return GE;
989 when EQ => return GE;
990 when others => null;
991 end case;
992 end if;
996ae0b0 993
93c3fca7
AC
994 if not Is_Generic_Type (Ltyp) then
995 case Compile_Time_Compare (Type_Low_Bound (Ltyp), R,
996 Discard'Access,
997 Assume_Valid, Rec => True)
998 is
999 when GT => return GT;
1000 when GE => return GE;
1001 when EQ => return GE;
1002 when others => null;
1003 end case;
996ae0b0 1004
93c3fca7
AC
1005 case Compile_Time_Compare (Type_High_Bound (Ltyp), R,
1006 Discard'Access,
1007 Assume_Valid, Rec => True)
1008 is
1009 when LT => return LT;
1010 when LE => return LE;
1011 when EQ => return LE;
1012 when others => null;
1013 end case;
1014 end if;
996ae0b0
RK
1015 end if;
1016
1017 -- Next attempt is to decompose the expressions to extract
1018 -- a constant offset resulting from the use of any of the forms:
1019
1020 -- expr + literal
1021 -- expr - literal
1022 -- typ'Succ (expr)
1023 -- typ'Pred (expr)
1024
1025 -- Then we see if the two expressions are the same value, and if so
1026 -- the result is obtained by comparing the offsets.
1027
1028 declare
1029 Lnode : Node_Id;
1030 Loffs : Uint;
1031 Rnode : Node_Id;
1032 Roffs : Uint;
1033
1034 begin
1035 Compare_Decompose (L, Lnode, Loffs);
1036 Compare_Decompose (R, Rnode, Roffs);
1037
1038 if Is_Same_Value (Lnode, Rnode) then
1039 if Loffs = Roffs then
1040 return EQ;
1041
1042 elsif Loffs < Roffs then
af02a866 1043 Diff.all := Roffs - Loffs;
996ae0b0
RK
1044 return LT;
1045
1046 else
af02a866 1047 Diff.all := Loffs - Roffs;
996ae0b0
RK
1048 return GT;
1049 end if;
29797f34
RD
1050 end if;
1051 end;
1052
1053 -- Next attempt is to see if we have an entity compared with a
1054 -- compile time known value, where there is a current value
1055 -- conditional for the entity which can tell us the result.
1056
1057 declare
1058 Var : Node_Id;
1059 -- Entity variable (left operand)
1060
1061 Val : Uint;
1062 -- Value (right operand)
1063
1064 Inv : Boolean;
1065 -- If False, we have reversed the operands
1066
1067 Op : Node_Kind;
1068 -- Comparison operator kind from Get_Current_Value_Condition call
996ae0b0 1069
29797f34
RD
1070 Opn : Node_Id;
1071 -- Value from Get_Current_Value_Condition call
1072
1073 Opv : Uint;
1074 -- Value of Opn
1075
1076 Result : Compare_Result;
1077 -- Known result before inversion
1078
1079 begin
1080 if Is_Entity_Name (L)
1081 and then Compile_Time_Known_Value (R)
1082 then
1083 Var := L;
1084 Val := Expr_Value (R);
1085 Inv := False;
1086
1087 elsif Is_Entity_Name (R)
1088 and then Compile_Time_Known_Value (L)
1089 then
1090 Var := R;
1091 Val := Expr_Value (L);
1092 Inv := True;
1093
1094 -- That was the last chance at finding a compile time result
996ae0b0
RK
1095
1096 else
1097 return Unknown;
1098 end if;
29797f34
RD
1099
1100 Get_Current_Value_Condition (Var, Op, Opn);
1101
1102 -- That was the last chance, so if we got nothing return
1103
1104 if No (Opn) then
1105 return Unknown;
1106 end if;
1107
1108 Opv := Expr_Value (Opn);
1109
1110 -- We got a comparison, so we might have something interesting
1111
1112 -- Convert LE to LT and GE to GT, just so we have fewer cases
1113
1114 if Op = N_Op_Le then
1115 Op := N_Op_Lt;
1116 Opv := Opv + 1;
af02a866 1117
29797f34
RD
1118 elsif Op = N_Op_Ge then
1119 Op := N_Op_Gt;
1120 Opv := Opv - 1;
1121 end if;
1122
1123 -- Deal with equality case
1124
1125 if Op = N_Op_Eq then
1126 if Val = Opv then
1127 Result := EQ;
1128 elsif Opv < Val then
1129 Result := LT;
1130 else
1131 Result := GT;
1132 end if;
1133
1134 -- Deal with inequality case
1135
1136 elsif Op = N_Op_Ne then
1137 if Val = Opv then
1138 Result := NE;
1139 else
1140 return Unknown;
1141 end if;
1142
1143 -- Deal with greater than case
1144
1145 elsif Op = N_Op_Gt then
1146 if Opv >= Val then
1147 Result := GT;
1148 elsif Opv = Val - 1 then
1149 Result := GE;
1150 else
1151 return Unknown;
1152 end if;
1153
1154 -- Deal with less than case
1155
1156 else pragma Assert (Op = N_Op_Lt);
1157 if Opv <= Val then
1158 Result := LT;
1159 elsif Opv = Val + 1 then
1160 Result := LE;
1161 else
1162 return Unknown;
1163 end if;
1164 end if;
1165
1166 -- Deal with inverting result
1167
1168 if Inv then
1169 case Result is
1170 when GT => return LT;
1171 when GE => return LE;
1172 when LT => return GT;
1173 when LE => return GE;
1174 when others => return Result;
1175 end case;
1176 end if;
1177
1178 return Result;
996ae0b0
RK
1179 end;
1180 end if;
1181 end Compile_Time_Compare;
1182
f44fe430
RD
1183 -------------------------------
1184 -- Compile_Time_Known_Bounds --
1185 -------------------------------
1186
1187 function Compile_Time_Known_Bounds (T : Entity_Id) return Boolean is
1188 Indx : Node_Id;
1189 Typ : Entity_Id;
1190
1191 begin
1192 if not Is_Array_Type (T) then
1193 return False;
1194 end if;
1195
1196 Indx := First_Index (T);
1197 while Present (Indx) loop
1198 Typ := Underlying_Type (Etype (Indx));
93c3fca7
AC
1199
1200 -- Never look at junk bounds of a generic type
1201
1202 if Is_Generic_Type (Typ) then
1203 return False;
1204 end if;
1205
1206 -- Otherwise check bounds for compile time known
1207
f44fe430
RD
1208 if not Compile_Time_Known_Value (Type_Low_Bound (Typ)) then
1209 return False;
1210 elsif not Compile_Time_Known_Value (Type_High_Bound (Typ)) then
1211 return False;
1212 else
1213 Next_Index (Indx);
1214 end if;
1215 end loop;
1216
1217 return True;
1218 end Compile_Time_Known_Bounds;
1219
996ae0b0
RK
1220 ------------------------------
1221 -- Compile_Time_Known_Value --
1222 ------------------------------
1223
1224 function Compile_Time_Known_Value (Op : Node_Id) return Boolean is
07fc65c4
GB
1225 K : constant Node_Kind := Nkind (Op);
1226 CV_Ent : CV_Entry renames CV_Cache (Nat (Op) mod CV_Cache_Size);
996ae0b0
RK
1227
1228 begin
1229 -- Never known at compile time if bad type or raises constraint error
1230 -- or empty (latter case occurs only as a result of a previous error)
1231
1232 if No (Op)
1233 or else Op = Error
1234 or else Etype (Op) = Any_Type
1235 or else Raises_Constraint_Error (Op)
1236 then
1237 return False;
1238 end if;
1239
597d7158
GD
1240 -- If this is not a static expression or a null literal, and we are in
1241 -- configurable run-time mode, then we consider it not known at compile
1242 -- time. This avoids anomalies where whether something is allowed with a
1243 -- given configurable run-time library depends on how good the compiler
1244 -- is at optimizing and knowing that things are constant when they are
1245 -- nonstatic.
1246
1247 if Configurable_Run_Time_Mode
1248 and then K /= N_Null
1249 and then not Is_Static_Expression (Op)
1250 then
fbf5a39b
AC
1251 return False;
1252 end if;
1253
996ae0b0
RK
1254 -- If we have an entity name, then see if it is the name of a constant
1255 -- and if so, test the corresponding constant value, or the name of
1256 -- an enumeration literal, which is always a constant.
1257
1258 if Present (Etype (Op)) and then Is_Entity_Name (Op) then
1259 declare
1260 E : constant Entity_Id := Entity (Op);
1261 V : Node_Id;
1262
1263 begin
1264 -- Never known at compile time if it is a packed array value.
1265 -- We might want to try to evaluate these at compile time one
1266 -- day, but we do not make that attempt now.
1267
1268 if Is_Packed_Array_Type (Etype (Op)) then
1269 return False;
1270 end if;
1271
1272 if Ekind (E) = E_Enumeration_Literal then
1273 return True;
1274
07fc65c4 1275 elsif Ekind (E) = E_Constant then
996ae0b0
RK
1276 V := Constant_Value (E);
1277 return Present (V) and then Compile_Time_Known_Value (V);
1278 end if;
1279 end;
1280
1281 -- We have a value, see if it is compile time known
1282
1283 else
07fc65c4 1284 -- Integer literals are worth storing in the cache
996ae0b0 1285
07fc65c4
GB
1286 if K = N_Integer_Literal then
1287 CV_Ent.N := Op;
1288 CV_Ent.V := Intval (Op);
1289 return True;
1290
1291 -- Other literals and NULL are known at compile time
1292
1293 elsif
996ae0b0
RK
1294 K = N_Character_Literal
1295 or else
1296 K = N_Real_Literal
1297 or else
1298 K = N_String_Literal
1299 or else
1300 K = N_Null
1301 then
1302 return True;
1303
1304 -- Any reference to Null_Parameter is known at compile time. No
1305 -- other attribute references (that have not already been folded)
1306 -- are known at compile time.
1307
1308 elsif K = N_Attribute_Reference then
1309 return Attribute_Name (Op) = Name_Null_Parameter;
07fc65c4 1310 end if;
996ae0b0 1311 end if;
07fc65c4
GB
1312
1313 -- If we fall through, not known at compile time
1314
1315 return False;
1316
1317 -- If we get an exception while trying to do this test, then some error
1318 -- has occurred, and we simply say that the value is not known after all
1319
1320 exception
1321 when others =>
1322 return False;
996ae0b0
RK
1323 end Compile_Time_Known_Value;
1324
1325 --------------------------------------
1326 -- Compile_Time_Known_Value_Or_Aggr --
1327 --------------------------------------
1328
1329 function Compile_Time_Known_Value_Or_Aggr (Op : Node_Id) return Boolean is
1330 begin
1331 -- If we have an entity name, then see if it is the name of a constant
1332 -- and if so, test the corresponding constant value, or the name of
1333 -- an enumeration literal, which is always a constant.
1334
1335 if Is_Entity_Name (Op) then
1336 declare
1337 E : constant Entity_Id := Entity (Op);
1338 V : Node_Id;
1339
1340 begin
1341 if Ekind (E) = E_Enumeration_Literal then
1342 return True;
1343
1344 elsif Ekind (E) /= E_Constant then
1345 return False;
1346
1347 else
1348 V := Constant_Value (E);
1349 return Present (V)
1350 and then Compile_Time_Known_Value_Or_Aggr (V);
1351 end if;
1352 end;
1353
1354 -- We have a value, see if it is compile time known
1355
1356 else
1357 if Compile_Time_Known_Value (Op) then
1358 return True;
1359
1360 elsif Nkind (Op) = N_Aggregate then
1361
1362 if Present (Expressions (Op)) then
1363 declare
1364 Expr : Node_Id;
1365
1366 begin
1367 Expr := First (Expressions (Op));
1368 while Present (Expr) loop
1369 if not Compile_Time_Known_Value_Or_Aggr (Expr) then
1370 return False;
1371 end if;
1372
1373 Next (Expr);
1374 end loop;
1375 end;
1376 end if;
1377
1378 if Present (Component_Associations (Op)) then
1379 declare
1380 Cass : Node_Id;
1381
1382 begin
1383 Cass := First (Component_Associations (Op));
1384 while Present (Cass) loop
1385 if not
1386 Compile_Time_Known_Value_Or_Aggr (Expression (Cass))
1387 then
1388 return False;
1389 end if;
1390
1391 Next (Cass);
1392 end loop;
1393 end;
1394 end if;
1395
1396 return True;
1397
1398 -- All other types of values are not known at compile time
1399
1400 else
1401 return False;
1402 end if;
1403
1404 end if;
1405 end Compile_Time_Known_Value_Or_Aggr;
1406
1407 -----------------
1408 -- Eval_Actual --
1409 -----------------
1410
1411 -- This is only called for actuals of functions that are not predefined
1412 -- operators (which have already been rewritten as operators at this
1413 -- stage), so the call can never be folded, and all that needs doing for
1414 -- the actual is to do the check for a non-static context.
1415
1416 procedure Eval_Actual (N : Node_Id) is
1417 begin
1418 Check_Non_Static_Context (N);
1419 end Eval_Actual;
1420
1421 --------------------
1422 -- Eval_Allocator --
1423 --------------------
1424
1425 -- Allocators are never static, so all we have to do is to do the
1426 -- check for a non-static context if an expression is present.
1427
1428 procedure Eval_Allocator (N : Node_Id) is
1429 Expr : constant Node_Id := Expression (N);
1430
1431 begin
1432 if Nkind (Expr) = N_Qualified_Expression then
1433 Check_Non_Static_Context (Expression (Expr));
1434 end if;
1435 end Eval_Allocator;
1436
1437 ------------------------
1438 -- Eval_Arithmetic_Op --
1439 ------------------------
1440
1441 -- Arithmetic operations are static functions, so the result is static
1442 -- if both operands are static (RM 4.9(7), 4.9(20)).
1443
1444 procedure Eval_Arithmetic_Op (N : Node_Id) is
1445 Left : constant Node_Id := Left_Opnd (N);
1446 Right : constant Node_Id := Right_Opnd (N);
1447 Ltype : constant Entity_Id := Etype (Left);
1448 Rtype : constant Entity_Id := Etype (Right);
1449 Stat : Boolean;
1450 Fold : Boolean;
1451
1452 begin
1453 -- If not foldable we are done
1454
1455 Test_Expression_Is_Foldable (N, Left, Right, Stat, Fold);
1456
1457 if not Fold then
1458 return;
1459 end if;
1460
1461 -- Fold for cases where both operands are of integer type
1462
1463 if Is_Integer_Type (Ltype) and then Is_Integer_Type (Rtype) then
1464 declare
1465 Left_Int : constant Uint := Expr_Value (Left);
1466 Right_Int : constant Uint := Expr_Value (Right);
1467 Result : Uint;
1468
1469 begin
1470 case Nkind (N) is
1471
1472 when N_Op_Add =>
1473 Result := Left_Int + Right_Int;
1474
1475 when N_Op_Subtract =>
1476 Result := Left_Int - Right_Int;
1477
1478 when N_Op_Multiply =>
1479 if OK_Bits
1480 (N, UI_From_Int
1481 (Num_Bits (Left_Int) + Num_Bits (Right_Int)))
1482 then
1483 Result := Left_Int * Right_Int;
1484 else
1485 Result := Left_Int;
1486 end if;
1487
1488 when N_Op_Divide =>
1489
1490 -- The exception Constraint_Error is raised by integer
1491 -- division, rem and mod if the right operand is zero.
1492
1493 if Right_Int = 0 then
1494 Apply_Compile_Time_Constraint_Error
fbf5a39b
AC
1495 (N, "division by zero",
1496 CE_Divide_By_Zero,
1497 Warn => not Stat);
996ae0b0 1498 return;
fbf5a39b 1499
996ae0b0
RK
1500 else
1501 Result := Left_Int / Right_Int;
1502 end if;
1503
1504 when N_Op_Mod =>
1505
1506 -- The exception Constraint_Error is raised by integer
1507 -- division, rem and mod if the right operand is zero.
1508
1509 if Right_Int = 0 then
1510 Apply_Compile_Time_Constraint_Error
fbf5a39b
AC
1511 (N, "mod with zero divisor",
1512 CE_Divide_By_Zero,
1513 Warn => not Stat);
996ae0b0
RK
1514 return;
1515 else
1516 Result := Left_Int mod Right_Int;
1517 end if;
1518
1519 when N_Op_Rem =>
1520
1521 -- The exception Constraint_Error is raised by integer
1522 -- division, rem and mod if the right operand is zero.
1523
1524 if Right_Int = 0 then
1525 Apply_Compile_Time_Constraint_Error
fbf5a39b
AC
1526 (N, "rem with zero divisor",
1527 CE_Divide_By_Zero,
1528 Warn => not Stat);
996ae0b0 1529 return;
fbf5a39b 1530
996ae0b0
RK
1531 else
1532 Result := Left_Int rem Right_Int;
1533 end if;
1534
1535 when others =>
1536 raise Program_Error;
1537 end case;
1538
1539 -- Adjust the result by the modulus if the type is a modular type
1540
1541 if Is_Modular_Integer_Type (Ltype) then
1542 Result := Result mod Modulus (Ltype);
82c80734
RD
1543
1544 -- For a signed integer type, check non-static overflow
1545
1546 elsif (not Stat) and then Is_Signed_Integer_Type (Ltype) then
1547 declare
1548 BT : constant Entity_Id := Base_Type (Ltype);
1549 Lo : constant Uint := Expr_Value (Type_Low_Bound (BT));
1550 Hi : constant Uint := Expr_Value (Type_High_Bound (BT));
1551 begin
1552 if Result < Lo or else Result > Hi then
1553 Apply_Compile_Time_Constraint_Error
1554 (N, "value not in range of }?",
1555 CE_Overflow_Check_Failed,
1556 Ent => BT);
1557 return;
1558 end if;
1559 end;
996ae0b0
RK
1560 end if;
1561
82c80734
RD
1562 -- If we get here we can fold the result
1563
fbf5a39b 1564 Fold_Uint (N, Result, Stat);
996ae0b0
RK
1565 end;
1566
1567 -- Cases where at least one operand is a real. We handle the cases
1568 -- of both reals, or mixed/real integer cases (the latter happen
1569 -- only for divide and multiply, and the result is always real).
1570
1571 elsif Is_Real_Type (Ltype) or else Is_Real_Type (Rtype) then
1572 declare
1573 Left_Real : Ureal;
1574 Right_Real : Ureal;
1575 Result : Ureal;
1576
1577 begin
1578 if Is_Real_Type (Ltype) then
1579 Left_Real := Expr_Value_R (Left);
1580 else
1581 Left_Real := UR_From_Uint (Expr_Value (Left));
1582 end if;
1583
1584 if Is_Real_Type (Rtype) then
1585 Right_Real := Expr_Value_R (Right);
1586 else
1587 Right_Real := UR_From_Uint (Expr_Value (Right));
1588 end if;
1589
1590 if Nkind (N) = N_Op_Add then
1591 Result := Left_Real + Right_Real;
1592
1593 elsif Nkind (N) = N_Op_Subtract then
1594 Result := Left_Real - Right_Real;
1595
1596 elsif Nkind (N) = N_Op_Multiply then
1597 Result := Left_Real * Right_Real;
1598
1599 else pragma Assert (Nkind (N) = N_Op_Divide);
1600 if UR_Is_Zero (Right_Real) then
1601 Apply_Compile_Time_Constraint_Error
07fc65c4 1602 (N, "division by zero", CE_Divide_By_Zero);
996ae0b0
RK
1603 return;
1604 end if;
1605
1606 Result := Left_Real / Right_Real;
1607 end if;
1608
fbf5a39b 1609 Fold_Ureal (N, Result, Stat);
996ae0b0
RK
1610 end;
1611 end if;
996ae0b0
RK
1612 end Eval_Arithmetic_Op;
1613
1614 ----------------------------
1615 -- Eval_Character_Literal --
1616 ----------------------------
1617
1618 -- Nothing to be done!
1619
1620 procedure Eval_Character_Literal (N : Node_Id) is
07fc65c4 1621 pragma Warnings (Off, N);
996ae0b0
RK
1622 begin
1623 null;
1624 end Eval_Character_Literal;
1625
c01a9391
AC
1626 ---------------
1627 -- Eval_Call --
1628 ---------------
1629
1630 -- Static function calls are either calls to predefined operators
1631 -- with static arguments, or calls to functions that rename a literal.
1632 -- Only the latter case is handled here, predefined operators are
1633 -- constant-folded elsewhere.
29797f34 1634
c01a9391
AC
1635 -- If the function is itself inherited (see 7423-001) the literal of
1636 -- the parent type must be explicitly converted to the return type
1637 -- of the function.
1638
1639 procedure Eval_Call (N : Node_Id) is
1640 Loc : constant Source_Ptr := Sloc (N);
1641 Typ : constant Entity_Id := Etype (N);
1642 Lit : Entity_Id;
1643
1644 begin
1645 if Nkind (N) = N_Function_Call
1646 and then No (Parameter_Associations (N))
1647 and then Is_Entity_Name (Name (N))
1648 and then Present (Alias (Entity (Name (N))))
1649 and then Is_Enumeration_Type (Base_Type (Typ))
1650 then
1651 Lit := Alias (Entity (Name (N)));
c01a9391
AC
1652 while Present (Alias (Lit)) loop
1653 Lit := Alias (Lit);
1654 end loop;
1655
1656 if Ekind (Lit) = E_Enumeration_Literal then
1657 if Base_Type (Etype (Lit)) /= Base_Type (Typ) then
1658 Rewrite
1659 (N, Convert_To (Typ, New_Occurrence_Of (Lit, Loc)));
1660 else
1661 Rewrite (N, New_Occurrence_Of (Lit, Loc));
1662 end if;
1663
1664 Resolve (N, Typ);
1665 end if;
1666 end if;
1667 end Eval_Call;
1668
19d846a0
RD
1669 --------------------------
1670 -- Eval_Case_Expression --
1671 --------------------------
1672
1673 -- Right now we do not attempt folding of any case expressions, and the
1674 -- language does not require it, so the only required processing is to
1675 -- do the check for all expressions appearing in the case expression.
1676
1677 procedure Eval_Case_Expression (N : Node_Id) is
1678 Alt : Node_Id;
1679
1680 begin
1681 Check_Non_Static_Context (Expression (N));
1682
1683 Alt := First (Alternatives (N));
1684 while Present (Alt) loop
1685 Check_Non_Static_Context (Expression (Alt));
1686 Next (Alt);
1687 end loop;
1688 end Eval_Case_Expression;
1689
996ae0b0
RK
1690 ------------------------
1691 -- Eval_Concatenation --
1692 ------------------------
1693
3996951a
TQ
1694 -- Concatenation is a static function, so the result is static if both
1695 -- operands are static (RM 4.9(7), 4.9(21)).
996ae0b0
RK
1696
1697 procedure Eval_Concatenation (N : Node_Id) is
f91b40db
GB
1698 Left : constant Node_Id := Left_Opnd (N);
1699 Right : constant Node_Id := Right_Opnd (N);
1700 C_Typ : constant Entity_Id := Root_Type (Component_Type (Etype (N)));
996ae0b0
RK
1701 Stat : Boolean;
1702 Fold : Boolean;
996ae0b0
RK
1703
1704 begin
3996951a
TQ
1705 -- Concatenation is never static in Ada 83, so if Ada 83 check operand
1706 -- non-static context.
996ae0b0 1707
0ab80019 1708 if Ada_Version = Ada_83
996ae0b0
RK
1709 and then Comes_From_Source (N)
1710 then
1711 Check_Non_Static_Context (Left);
1712 Check_Non_Static_Context (Right);
1713 return;
1714 end if;
1715
1716 -- If not foldable we are done. In principle concatenation that yields
1717 -- any string type is static (i.e. an array type of character types).
1718 -- However, character types can include enumeration literals, and
1719 -- concatenation in that case cannot be described by a literal, so we
1720 -- only consider the operation static if the result is an array of
1721 -- (a descendant of) a predefined character type.
1722
1723 Test_Expression_Is_Foldable (N, Left, Right, Stat, Fold);
1724
3996951a 1725 if not (Is_Standard_Character_Type (C_Typ) and then Fold) then
996ae0b0
RK
1726 Set_Is_Static_Expression (N, False);
1727 return;
1728 end if;
1729
82c80734 1730 -- Compile time string concatenation
996ae0b0 1731
3996951a
TQ
1732 -- ??? Note that operands that are aggregates can be marked as static,
1733 -- so we should attempt at a later stage to fold concatenations with
1734 -- such aggregates.
996ae0b0
RK
1735
1736 declare
b54ddf5a
BD
1737 Left_Str : constant Node_Id := Get_String_Val (Left);
1738 Left_Len : Nat;
1739 Right_Str : constant Node_Id := Get_String_Val (Right);
1740 Folded_Val : String_Id;
996ae0b0
RK
1741
1742 begin
1743 -- Establish new string literal, and store left operand. We make
1744 -- sure to use the special Start_String that takes an operand if
1745 -- the left operand is a string literal. Since this is optimized
1746 -- in the case where that is the most recently created string
1747 -- literal, we ensure efficient time/space behavior for the
1748 -- case of a concatenation of a series of string literals.
1749
1750 if Nkind (Left_Str) = N_String_Literal then
f91b40db 1751 Left_Len := String_Length (Strval (Left_Str));
b54ddf5a
BD
1752
1753 -- If the left operand is the empty string, and the right operand
1754 -- is a string literal (the case of "" & "..."), the result is the
1755 -- value of the right operand. This optimization is important when
1756 -- Is_Folded_In_Parser, to avoid copying an enormous right
1757 -- operand.
1758
1759 if Left_Len = 0 and then Nkind (Right_Str) = N_String_Literal then
1760 Folded_Val := Strval (Right_Str);
1761 else
1762 Start_String (Strval (Left_Str));
1763 end if;
1764
996ae0b0
RK
1765 else
1766 Start_String;
82c80734 1767 Store_String_Char (UI_To_CC (Char_Literal_Value (Left_Str)));
f91b40db 1768 Left_Len := 1;
996ae0b0
RK
1769 end if;
1770
b54ddf5a
BD
1771 -- Now append the characters of the right operand, unless we
1772 -- optimized the "" & "..." case above.
996ae0b0
RK
1773
1774 if Nkind (Right_Str) = N_String_Literal then
b54ddf5a
BD
1775 if Left_Len /= 0 then
1776 Store_String_Chars (Strval (Right_Str));
1777 Folded_Val := End_String;
1778 end if;
996ae0b0 1779 else
82c80734 1780 Store_String_Char (UI_To_CC (Char_Literal_Value (Right_Str)));
b54ddf5a 1781 Folded_Val := End_String;
996ae0b0
RK
1782 end if;
1783
1784 Set_Is_Static_Expression (N, Stat);
1785
1786 if Stat then
f91b40db
GB
1787
1788 -- If left operand is the empty string, the result is the
1789 -- right operand, including its bounds if anomalous.
1790
1791 if Left_Len = 0
1792 and then Is_Array_Type (Etype (Right))
1793 and then Etype (Right) /= Any_String
1794 then
1795 Set_Etype (N, Etype (Right));
1796 end if;
1797
b54ddf5a 1798 Fold_Str (N, Folded_Val, Static => True);
996ae0b0
RK
1799 end if;
1800 end;
1801 end Eval_Concatenation;
1802
1803 ---------------------------------
1804 -- Eval_Conditional_Expression --
1805 ---------------------------------
1806
19d846a0
RD
1807 -- We never attempt folding of conditional expressions (and the language)
1808 -- does not require it, so the only required processing is to do the check
1809 -- for non-static context for the then and else expressions.
996ae0b0
RK
1810
1811 procedure Eval_Conditional_Expression (N : Node_Id) is
1812 Condition : constant Node_Id := First (Expressions (N));
1813 Then_Expr : constant Node_Id := Next (Condition);
1814 Else_Expr : constant Node_Id := Next (Then_Expr);
996ae0b0
RK
1815 begin
1816 Check_Non_Static_Context (Then_Expr);
1817 Check_Non_Static_Context (Else_Expr);
1818 end Eval_Conditional_Expression;
1819
1820 ----------------------
1821 -- Eval_Entity_Name --
1822 ----------------------
1823
1824 -- This procedure is used for identifiers and expanded names other than
1825 -- named numbers (see Eval_Named_Integer, Eval_Named_Real. These are
1826 -- static if they denote a static constant (RM 4.9(6)) or if the name
1827 -- denotes an enumeration literal (RM 4.9(22)).
1828
1829 procedure Eval_Entity_Name (N : Node_Id) is
1830 Def_Id : constant Entity_Id := Entity (N);
1831 Val : Node_Id;
1832
1833 begin
1834 -- Enumeration literals are always considered to be constants
1835 -- and cannot raise constraint error (RM 4.9(22)).
1836
1837 if Ekind (Def_Id) = E_Enumeration_Literal then
1838 Set_Is_Static_Expression (N);
1839 return;
1840
1841 -- A name is static if it denotes a static constant (RM 4.9(5)), and
1842 -- we also copy Raise_Constraint_Error. Notice that even if non-static,
1843 -- it does not violate 10.2.1(8) here, since this is not a variable.
1844
1845 elsif Ekind (Def_Id) = E_Constant then
1846
1847 -- Deferred constants must always be treated as nonstatic
1848 -- outside the scope of their full view.
1849
1850 if Present (Full_View (Def_Id))
1851 and then not In_Open_Scopes (Scope (Def_Id))
1852 then
1853 Val := Empty;
1854 else
1855 Val := Constant_Value (Def_Id);
1856 end if;
1857
1858 if Present (Val) then
1859 Set_Is_Static_Expression
1860 (N, Is_Static_Expression (Val)
1861 and then Is_Static_Subtype (Etype (Def_Id)));
1862 Set_Raises_Constraint_Error (N, Raises_Constraint_Error (Val));
1863
1864 if not Is_Static_Expression (N)
1865 and then not Is_Generic_Type (Etype (N))
1866 then
1867 Validate_Static_Object_Name (N);
1868 end if;
1869
1870 return;
1871 end if;
1872 end if;
1873
82c80734 1874 -- Fall through if the name is not static
996ae0b0
RK
1875
1876 Validate_Static_Object_Name (N);
1877 end Eval_Entity_Name;
1878
1879 ----------------------------
1880 -- Eval_Indexed_Component --
1881 ----------------------------
1882
8cbb664e
MG
1883 -- Indexed components are never static, so we need to perform the check
1884 -- for non-static context on the index values. Then, we check if the
1885 -- value can be obtained at compile time, even though it is non-static.
996ae0b0
RK
1886
1887 procedure Eval_Indexed_Component (N : Node_Id) is
1888 Expr : Node_Id;
1889
1890 begin
fbf5a39b
AC
1891 -- Check for non-static context on index values
1892
996ae0b0
RK
1893 Expr := First (Expressions (N));
1894 while Present (Expr) loop
1895 Check_Non_Static_Context (Expr);
1896 Next (Expr);
1897 end loop;
1898
fbf5a39b
AC
1899 -- If the indexed component appears in an object renaming declaration
1900 -- then we do not want to try to evaluate it, since in this case we
1901 -- need the identity of the array element.
1902
1903 if Nkind (Parent (N)) = N_Object_Renaming_Declaration then
1904 return;
1905
1906 -- Similarly if the indexed component appears as the prefix of an
1907 -- attribute we don't want to evaluate it, because at least for
1908 -- some cases of attributes we need the identify (e.g. Access, Size)
1909
1910 elsif Nkind (Parent (N)) = N_Attribute_Reference then
1911 return;
1912 end if;
1913
1914 -- Note: there are other cases, such as the left side of an assignment,
1915 -- or an OUT parameter for a call, where the replacement results in the
1916 -- illegal use of a constant, But these cases are illegal in the first
1917 -- place, so the replacement, though silly, is harmless.
1918
1919 -- Now see if this is a constant array reference
8cbb664e
MG
1920
1921 if List_Length (Expressions (N)) = 1
1922 and then Is_Entity_Name (Prefix (N))
1923 and then Ekind (Entity (Prefix (N))) = E_Constant
1924 and then Present (Constant_Value (Entity (Prefix (N))))
1925 then
1926 declare
1927 Loc : constant Source_Ptr := Sloc (N);
1928 Arr : constant Node_Id := Constant_Value (Entity (Prefix (N)));
1929 Sub : constant Node_Id := First (Expressions (N));
1930
1931 Atyp : Entity_Id;
1932 -- Type of array
1933
1934 Lin : Nat;
1935 -- Linear one's origin subscript value for array reference
1936
1937 Lbd : Node_Id;
1938 -- Lower bound of the first array index
1939
1940 Elm : Node_Id;
1941 -- Value from constant array
1942
1943 begin
1944 Atyp := Etype (Arr);
1945
1946 if Is_Access_Type (Atyp) then
1947 Atyp := Designated_Type (Atyp);
1948 end if;
1949
9dbf1c3e
RD
1950 -- If we have an array type (we should have but perhaps there are
1951 -- error cases where this is not the case), then see if we can do
1952 -- a constant evaluation of the array reference.
8cbb664e 1953
ebd34478 1954 if Is_Array_Type (Atyp) and then Atyp /= Any_Composite then
8cbb664e
MG
1955 if Ekind (Atyp) = E_String_Literal_Subtype then
1956 Lbd := String_Literal_Low_Bound (Atyp);
1957 else
1958 Lbd := Type_Low_Bound (Etype (First_Index (Atyp)));
1959 end if;
1960
1961 if Compile_Time_Known_Value (Sub)
1962 and then Nkind (Arr) = N_Aggregate
1963 and then Compile_Time_Known_Value (Lbd)
1964 and then Is_Discrete_Type (Component_Type (Atyp))
1965 then
1966 Lin := UI_To_Int (Expr_Value (Sub) - Expr_Value (Lbd)) + 1;
1967
1968 if List_Length (Expressions (Arr)) >= Lin then
1969 Elm := Pick (Expressions (Arr), Lin);
1970
1971 -- If the resulting expression is compile time known,
1972 -- then we can rewrite the indexed component with this
1973 -- value, being sure to mark the result as non-static.
1974 -- We also reset the Sloc, in case this generates an
1975 -- error later on (e.g. 136'Access).
1976
1977 if Compile_Time_Known_Value (Elm) then
1978 Rewrite (N, Duplicate_Subexpr_No_Checks (Elm));
1979 Set_Is_Static_Expression (N, False);
1980 Set_Sloc (N, Loc);
1981 end if;
1982 end if;
9fbb3ae6
AC
1983
1984 -- We can also constant-fold if the prefix is a string literal.
1985 -- This will be useful in an instantiation or an inlining.
1986
1987 elsif Compile_Time_Known_Value (Sub)
1988 and then Nkind (Arr) = N_String_Literal
1989 and then Compile_Time_Known_Value (Lbd)
1990 and then Expr_Value (Lbd) = 1
1991 and then Expr_Value (Sub) <=
1992 String_Literal_Length (Etype (Arr))
1993 then
1994 declare
1995 C : constant Char_Code :=
1996 Get_String_Char (Strval (Arr),
1997 UI_To_Int (Expr_Value (Sub)));
1998 begin
1999 Set_Character_Literal_Name (C);
2000
2001 Elm :=
2002 Make_Character_Literal (Loc,
2003 Chars => Name_Find,
2004 Char_Literal_Value => UI_From_CC (C));
2005 Set_Etype (Elm, Component_Type (Atyp));
2006 Rewrite (N, Duplicate_Subexpr_No_Checks (Elm));
2007 Set_Is_Static_Expression (N, False);
2008 end;
8cbb664e
MG
2009 end if;
2010 end if;
2011 end;
2012 end if;
996ae0b0
RK
2013 end Eval_Indexed_Component;
2014
2015 --------------------------
2016 -- Eval_Integer_Literal --
2017 --------------------------
2018
2019 -- Numeric literals are static (RM 4.9(1)), and have already been marked
2020 -- as static by the analyzer. The reason we did it that early is to allow
2021 -- the possibility of turning off the Is_Static_Expression flag after
9dbf1c3e
RD
2022 -- analysis, but before resolution, when integer literals are generated in
2023 -- the expander that do not correspond to static expressions.
996ae0b0
RK
2024
2025 procedure Eval_Integer_Literal (N : Node_Id) is
2026 T : constant Entity_Id := Etype (N);
2027
5d09245e 2028 function In_Any_Integer_Context return Boolean;
1d1bd8ad
AC
2029 -- If the literal is resolved with a specific type in a context where
2030 -- the expected type is Any_Integer, there are no range checks on the
2031 -- literal. By the time the literal is evaluated, it carries the type
2032 -- imposed by the enclosing expression, and we must recover the context
2033 -- to determine that Any_Integer is meant.
5d09245e
AC
2034
2035 ----------------------------
09494c32 2036 -- In_Any_Integer_Context --
5d09245e
AC
2037 ----------------------------
2038
2039 function In_Any_Integer_Context return Boolean is
2040 Par : constant Node_Id := Parent (N);
2041 K : constant Node_Kind := Nkind (Par);
2042
2043 begin
2044 -- Any_Integer also appears in digits specifications for real types,
1d1bd8ad
AC
2045 -- but those have bounds smaller that those of any integer base type,
2046 -- so we can safely ignore these cases.
5d09245e
AC
2047
2048 return K = N_Number_Declaration
2049 or else K = N_Attribute_Reference
2050 or else K = N_Attribute_Definition_Clause
2051 or else K = N_Modular_Type_Definition
2052 or else K = N_Signed_Integer_Type_Definition;
2053 end In_Any_Integer_Context;
2054
2055 -- Start of processing for Eval_Integer_Literal
2056
996ae0b0 2057 begin
5d09245e 2058
996ae0b0 2059 -- If the literal appears in a non-expression context, then it is
1d1bd8ad
AC
2060 -- certainly appearing in a non-static context, so check it. This is
2061 -- actually a redundant check, since Check_Non_Static_Context would
2062 -- check it, but it seems worth while avoiding the call.
996ae0b0 2063
5d09245e
AC
2064 if Nkind (Parent (N)) not in N_Subexpr
2065 and then not In_Any_Integer_Context
2066 then
996ae0b0
RK
2067 Check_Non_Static_Context (N);
2068 end if;
2069
2070 -- Modular integer literals must be in their base range
2071
2072 if Is_Modular_Integer_Type (T)
c800f862 2073 and then Is_Out_Of_Range (N, Base_Type (T), Assume_Valid => True)
996ae0b0
RK
2074 then
2075 Out_Of_Range (N);
2076 end if;
2077 end Eval_Integer_Literal;
2078
2079 ---------------------
2080 -- Eval_Logical_Op --
2081 ---------------------
2082
2083 -- Logical operations are static functions, so the result is potentially
2084 -- static if both operands are potentially static (RM 4.9(7), 4.9(20)).
2085
2086 procedure Eval_Logical_Op (N : Node_Id) is
2087 Left : constant Node_Id := Left_Opnd (N);
2088 Right : constant Node_Id := Right_Opnd (N);
2089 Stat : Boolean;
2090 Fold : Boolean;
2091
2092 begin
2093 -- If not foldable we are done
2094
2095 Test_Expression_Is_Foldable (N, Left, Right, Stat, Fold);
2096
2097 if not Fold then
2098 return;
2099 end if;
2100
2101 -- Compile time evaluation of logical operation
2102
2103 declare
2104 Left_Int : constant Uint := Expr_Value (Left);
2105 Right_Int : constant Uint := Expr_Value (Right);
2106
2107 begin
22cb89b5 2108 -- VMS includes bitwise operations on signed types
001c7783
AC
2109
2110 if Is_Modular_Integer_Type (Etype (N))
2111 or else Is_VMS_Operator (Entity (N))
2112 then
996ae0b0
RK
2113 declare
2114 Left_Bits : Bits (0 .. UI_To_Int (Esize (Etype (N))) - 1);
2115 Right_Bits : Bits (0 .. UI_To_Int (Esize (Etype (N))) - 1);
2116
2117 begin
2118 To_Bits (Left_Int, Left_Bits);
2119 To_Bits (Right_Int, Right_Bits);
2120
2121 -- Note: should really be able to use array ops instead of
2122 -- these loops, but they weren't working at the time ???
2123
2124 if Nkind (N) = N_Op_And then
2125 for J in Left_Bits'Range loop
2126 Left_Bits (J) := Left_Bits (J) and Right_Bits (J);
2127 end loop;
2128
2129 elsif Nkind (N) = N_Op_Or then
2130 for J in Left_Bits'Range loop
2131 Left_Bits (J) := Left_Bits (J) or Right_Bits (J);
2132 end loop;
2133
2134 else
2135 pragma Assert (Nkind (N) = N_Op_Xor);
2136
2137 for J in Left_Bits'Range loop
2138 Left_Bits (J) := Left_Bits (J) xor Right_Bits (J);
2139 end loop;
2140 end if;
2141
fbf5a39b 2142 Fold_Uint (N, From_Bits (Left_Bits, Etype (N)), Stat);
996ae0b0
RK
2143 end;
2144
2145 else
2146 pragma Assert (Is_Boolean_Type (Etype (N)));
2147
2148 if Nkind (N) = N_Op_And then
2149 Fold_Uint (N,
fbf5a39b 2150 Test (Is_True (Left_Int) and then Is_True (Right_Int)), Stat);
996ae0b0
RK
2151
2152 elsif Nkind (N) = N_Op_Or then
2153 Fold_Uint (N,
fbf5a39b 2154 Test (Is_True (Left_Int) or else Is_True (Right_Int)), Stat);
996ae0b0
RK
2155
2156 else
2157 pragma Assert (Nkind (N) = N_Op_Xor);
2158 Fold_Uint (N,
fbf5a39b 2159 Test (Is_True (Left_Int) xor Is_True (Right_Int)), Stat);
996ae0b0
RK
2160 end if;
2161 end if;
996ae0b0
RK
2162 end;
2163 end Eval_Logical_Op;
2164
2165 ------------------------
2166 -- Eval_Membership_Op --
2167 ------------------------
2168
1d1bd8ad
AC
2169 -- A membership test is potentially static if the expression is static, and
2170 -- the range is a potentially static range, or is a subtype mark denoting a
2171 -- static subtype (RM 4.9(12)).
996ae0b0
RK
2172
2173 procedure Eval_Membership_Op (N : Node_Id) is
2174 Left : constant Node_Id := Left_Opnd (N);
2175 Right : constant Node_Id := Right_Opnd (N);
2176 Def_Id : Entity_Id;
2177 Lo : Node_Id;
2178 Hi : Node_Id;
2179 Result : Boolean;
2180 Stat : Boolean;
2181 Fold : Boolean;
2182
2183 begin
1d1bd8ad
AC
2184 -- Ignore if error in either operand, except to make sure that Any_Type
2185 -- is properly propagated to avoid junk cascaded errors.
996ae0b0 2186
22cb89b5 2187 if Etype (Left) = Any_Type or else Etype (Right) = Any_Type then
996ae0b0
RK
2188 Set_Etype (N, Any_Type);
2189 return;
2190 end if;
2191
2192 -- Case of right operand is a subtype name
2193
2194 if Is_Entity_Name (Right) then
2195 Def_Id := Entity (Right);
2196
2197 if (Is_Scalar_Type (Def_Id) or else Is_String_Type (Def_Id))
2198 and then Is_OK_Static_Subtype (Def_Id)
2199 then
2200 Test_Expression_Is_Foldable (N, Left, Stat, Fold);
2201
2202 if not Fold or else not Stat then
2203 return;
2204 end if;
2205 else
2206 Check_Non_Static_Context (Left);
2207 return;
2208 end if;
2209
1d1bd8ad 2210 -- For string membership tests we will check the length further on
996ae0b0
RK
2211
2212 if not Is_String_Type (Def_Id) then
2213 Lo := Type_Low_Bound (Def_Id);
2214 Hi := Type_High_Bound (Def_Id);
2215
2216 else
2217 Lo := Empty;
2218 Hi := Empty;
2219 end if;
2220
2221 -- Case of right operand is a range
2222
2223 else
2224 if Is_Static_Range (Right) then
2225 Test_Expression_Is_Foldable (N, Left, Stat, Fold);
2226
2227 if not Fold or else not Stat then
2228 return;
2229
2230 -- If one bound of range raises CE, then don't try to fold
2231
2232 elsif not Is_OK_Static_Range (Right) then
2233 Check_Non_Static_Context (Left);
2234 return;
2235 end if;
2236
2237 else
2238 Check_Non_Static_Context (Left);
2239 return;
2240 end if;
2241
2242 -- Here we know range is an OK static range
2243
2244 Lo := Low_Bound (Right);
2245 Hi := High_Bound (Right);
2246 end if;
2247
2248 -- For strings we check that the length of the string expression is
2249 -- compatible with the string subtype if the subtype is constrained,
2250 -- or if unconstrained then the test is always true.
2251
2252 if Is_String_Type (Etype (Right)) then
2253 if not Is_Constrained (Etype (Right)) then
2254 Result := True;
2255
2256 else
2257 declare
2258 Typlen : constant Uint := String_Type_Len (Etype (Right));
2259 Strlen : constant Uint :=
22cb89b5
AC
2260 UI_From_Int
2261 (String_Length (Strval (Get_String_Val (Left))));
996ae0b0
RK
2262 begin
2263 Result := (Typlen = Strlen);
2264 end;
2265 end if;
2266
1d1bd8ad
AC
2267 -- Fold the membership test. We know we have a static range and Lo and
2268 -- Hi are set to the expressions for the end points of this range.
996ae0b0
RK
2269
2270 elsif Is_Real_Type (Etype (Right)) then
2271 declare
2272 Leftval : constant Ureal := Expr_Value_R (Left);
2273
2274 begin
2275 Result := Expr_Value_R (Lo) <= Leftval
2276 and then Leftval <= Expr_Value_R (Hi);
2277 end;
2278
2279 else
2280 declare
2281 Leftval : constant Uint := Expr_Value (Left);
2282
2283 begin
2284 Result := Expr_Value (Lo) <= Leftval
2285 and then Leftval <= Expr_Value (Hi);
2286 end;
2287 end if;
2288
2289 if Nkind (N) = N_Not_In then
2290 Result := not Result;
2291 end if;
2292
fbf5a39b 2293 Fold_Uint (N, Test (Result), True);
996ae0b0 2294 Warn_On_Known_Condition (N);
996ae0b0
RK
2295 end Eval_Membership_Op;
2296
2297 ------------------------
2298 -- Eval_Named_Integer --
2299 ------------------------
2300
2301 procedure Eval_Named_Integer (N : Node_Id) is
2302 begin
2303 Fold_Uint (N,
fbf5a39b 2304 Expr_Value (Expression (Declaration_Node (Entity (N)))), True);
996ae0b0
RK
2305 end Eval_Named_Integer;
2306
2307 ---------------------
2308 -- Eval_Named_Real --
2309 ---------------------
2310
2311 procedure Eval_Named_Real (N : Node_Id) is
2312 begin
2313 Fold_Ureal (N,
fbf5a39b 2314 Expr_Value_R (Expression (Declaration_Node (Entity (N)))), True);
996ae0b0
RK
2315 end Eval_Named_Real;
2316
2317 -------------------
2318 -- Eval_Op_Expon --
2319 -------------------
2320
2321 -- Exponentiation is a static functions, so the result is potentially
2322 -- static if both operands are potentially static (RM 4.9(7), 4.9(20)).
2323
2324 procedure Eval_Op_Expon (N : Node_Id) is
2325 Left : constant Node_Id := Left_Opnd (N);
2326 Right : constant Node_Id := Right_Opnd (N);
2327 Stat : Boolean;
2328 Fold : Boolean;
2329
2330 begin
2331 -- If not foldable we are done
2332
2333 Test_Expression_Is_Foldable (N, Left, Right, Stat, Fold);
2334
2335 if not Fold then
2336 return;
2337 end if;
2338
2339 -- Fold exponentiation operation
2340
2341 declare
2342 Right_Int : constant Uint := Expr_Value (Right);
2343
2344 begin
2345 -- Integer case
2346
2347 if Is_Integer_Type (Etype (Left)) then
2348 declare
2349 Left_Int : constant Uint := Expr_Value (Left);
2350 Result : Uint;
2351
2352 begin
22cb89b5
AC
2353 -- Exponentiation of an integer raises Constraint_Error for a
2354 -- negative exponent (RM 4.5.6).
996ae0b0
RK
2355
2356 if Right_Int < 0 then
2357 Apply_Compile_Time_Constraint_Error
fbf5a39b
AC
2358 (N, "integer exponent negative",
2359 CE_Range_Check_Failed,
2360 Warn => not Stat);
996ae0b0
RK
2361 return;
2362
2363 else
2364 if OK_Bits (N, Num_Bits (Left_Int) * Right_Int) then
2365 Result := Left_Int ** Right_Int;
2366 else
2367 Result := Left_Int;
2368 end if;
2369
2370 if Is_Modular_Integer_Type (Etype (N)) then
2371 Result := Result mod Modulus (Etype (N));
2372 end if;
2373
fbf5a39b 2374 Fold_Uint (N, Result, Stat);
996ae0b0
RK
2375 end if;
2376 end;
2377
2378 -- Real case
2379
2380 else
2381 declare
2382 Left_Real : constant Ureal := Expr_Value_R (Left);
2383
2384 begin
2385 -- Cannot have a zero base with a negative exponent
2386
2387 if UR_Is_Zero (Left_Real) then
2388
2389 if Right_Int < 0 then
2390 Apply_Compile_Time_Constraint_Error
fbf5a39b
AC
2391 (N, "zero ** negative integer",
2392 CE_Range_Check_Failed,
2393 Warn => not Stat);
996ae0b0
RK
2394 return;
2395 else
fbf5a39b 2396 Fold_Ureal (N, Ureal_0, Stat);
996ae0b0
RK
2397 end if;
2398
2399 else
fbf5a39b 2400 Fold_Ureal (N, Left_Real ** Right_Int, Stat);
996ae0b0
RK
2401 end if;
2402 end;
2403 end if;
996ae0b0
RK
2404 end;
2405 end Eval_Op_Expon;
2406
2407 -----------------
2408 -- Eval_Op_Not --
2409 -----------------
2410
2411 -- The not operation is a static functions, so the result is potentially
2412 -- static if the operand is potentially static (RM 4.9(7), 4.9(20)).
2413
2414 procedure Eval_Op_Not (N : Node_Id) is
2415 Right : constant Node_Id := Right_Opnd (N);
2416 Stat : Boolean;
2417 Fold : Boolean;
2418
2419 begin
2420 -- If not foldable we are done
2421
2422 Test_Expression_Is_Foldable (N, Right, Stat, Fold);
2423
2424 if not Fold then
2425 return;
2426 end if;
2427
2428 -- Fold not operation
2429
2430 declare
2431 Rint : constant Uint := Expr_Value (Right);
2432 Typ : constant Entity_Id := Etype (N);
2433
2434 begin
1d1bd8ad
AC
2435 -- Negation is equivalent to subtracting from the modulus minus one.
2436 -- For a binary modulus this is equivalent to the ones-complement of
2437 -- the original value. For non-binary modulus this is an arbitrary
2438 -- but consistent definition.
996ae0b0
RK
2439
2440 if Is_Modular_Integer_Type (Typ) then
fbf5a39b 2441 Fold_Uint (N, Modulus (Typ) - 1 - Rint, Stat);
996ae0b0
RK
2442
2443 else
2444 pragma Assert (Is_Boolean_Type (Typ));
fbf5a39b 2445 Fold_Uint (N, Test (not Is_True (Rint)), Stat);
996ae0b0
RK
2446 end if;
2447
2448 Set_Is_Static_Expression (N, Stat);
2449 end;
2450 end Eval_Op_Not;
2451
2452 -------------------------------
2453 -- Eval_Qualified_Expression --
2454 -------------------------------
2455
2456 -- A qualified expression is potentially static if its subtype mark denotes
2457 -- a static subtype and its expression is potentially static (RM 4.9 (11)).
2458
2459 procedure Eval_Qualified_Expression (N : Node_Id) is
2460 Operand : constant Node_Id := Expression (N);
2461 Target_Type : constant Entity_Id := Entity (Subtype_Mark (N));
2462
07fc65c4
GB
2463 Stat : Boolean;
2464 Fold : Boolean;
2465 Hex : Boolean;
996ae0b0
RK
2466
2467 begin
1d1bd8ad 2468 -- Can only fold if target is string or scalar and subtype is static.
22cb89b5
AC
2469 -- Also, do not fold if our parent is an allocator (this is because the
2470 -- qualified expression is really part of the syntactic structure of an
2471 -- allocator, and we do not want to end up with something that
996ae0b0
RK
2472 -- corresponds to "new 1" where the 1 is the result of folding a
2473 -- qualified expression).
2474
2475 if not Is_Static_Subtype (Target_Type)
2476 or else Nkind (Parent (N)) = N_Allocator
2477 then
2478 Check_Non_Static_Context (Operand);
af152989 2479
1d1bd8ad
AC
2480 -- If operand is known to raise constraint_error, set the flag on the
2481 -- expression so it does not get optimized away.
af152989
AC
2482
2483 if Nkind (Operand) = N_Raise_Constraint_Error then
2484 Set_Raises_Constraint_Error (N);
2485 end if;
7324bf49 2486
996ae0b0
RK
2487 return;
2488 end if;
2489
2490 -- If not foldable we are done
2491
2492 Test_Expression_Is_Foldable (N, Operand, Stat, Fold);
2493
2494 if not Fold then
2495 return;
2496
2497 -- Don't try fold if target type has constraint error bounds
2498
2499 elsif not Is_OK_Static_Subtype (Target_Type) then
2500 Set_Raises_Constraint_Error (N);
2501 return;
2502 end if;
2503
07fc65c4
GB
2504 -- Here we will fold, save Print_In_Hex indication
2505
2506 Hex := Nkind (Operand) = N_Integer_Literal
2507 and then Print_In_Hex (Operand);
2508
996ae0b0
RK
2509 -- Fold the result of qualification
2510
2511 if Is_Discrete_Type (Target_Type) then
fbf5a39b 2512 Fold_Uint (N, Expr_Value (Operand), Stat);
996ae0b0 2513
07fc65c4
GB
2514 -- Preserve Print_In_Hex indication
2515
2516 if Hex and then Nkind (N) = N_Integer_Literal then
2517 Set_Print_In_Hex (N);
2518 end if;
2519
996ae0b0 2520 elsif Is_Real_Type (Target_Type) then
fbf5a39b 2521 Fold_Ureal (N, Expr_Value_R (Operand), Stat);
996ae0b0
RK
2522
2523 else
fbf5a39b 2524 Fold_Str (N, Strval (Get_String_Val (Operand)), Stat);
996ae0b0
RK
2525
2526 if not Stat then
2527 Set_Is_Static_Expression (N, False);
2528 else
2529 Check_String_Literal_Length (N, Target_Type);
2530 end if;
2531
2532 return;
2533 end if;
2534
fbf5a39b
AC
2535 -- The expression may be foldable but not static
2536
2537 Set_Is_Static_Expression (N, Stat);
2538
c800f862 2539 if Is_Out_Of_Range (N, Etype (N), Assume_Valid => True) then
996ae0b0
RK
2540 Out_Of_Range (N);
2541 end if;
996ae0b0
RK
2542 end Eval_Qualified_Expression;
2543
2544 -----------------------
2545 -- Eval_Real_Literal --
2546 -----------------------
2547
2548 -- Numeric literals are static (RM 4.9(1)), and have already been marked
2549 -- as static by the analyzer. The reason we did it that early is to allow
2550 -- the possibility of turning off the Is_Static_Expression flag after
2551 -- analysis, but before resolution, when integer literals are generated
2552 -- in the expander that do not correspond to static expressions.
2553
2554 procedure Eval_Real_Literal (N : Node_Id) is
a1980be8
GB
2555 PK : constant Node_Kind := Nkind (Parent (N));
2556
996ae0b0 2557 begin
1d1bd8ad
AC
2558 -- If the literal appears in a non-expression context and not as part of
2559 -- a number declaration, then it is appearing in a non-static context,
2560 -- so check it.
996ae0b0 2561
a1980be8 2562 if PK not in N_Subexpr and then PK /= N_Number_Declaration then
996ae0b0
RK
2563 Check_Non_Static_Context (N);
2564 end if;
996ae0b0
RK
2565 end Eval_Real_Literal;
2566
2567 ------------------------
2568 -- Eval_Relational_Op --
2569 ------------------------
2570
8a95f4e8
RD
2571 -- Relational operations are static functions, so the result is static if
2572 -- both operands are static (RM 4.9(7), 4.9(20)), except that for strings,
2573 -- the result is never static, even if the operands are.
996ae0b0
RK
2574
2575 procedure Eval_Relational_Op (N : Node_Id) is
2576 Left : constant Node_Id := Left_Opnd (N);
2577 Right : constant Node_Id := Right_Opnd (N);
2578 Typ : constant Entity_Id := Etype (Left);
2579 Result : Boolean;
2580 Stat : Boolean;
2581 Fold : Boolean;
2582
2583 begin
45fc7ddb
HK
2584 -- One special case to deal with first. If we can tell that the result
2585 -- will be false because the lengths of one or more index subtypes are
2586 -- compile time known and different, then we can replace the entire
2587 -- result by False. We only do this for one dimensional arrays, because
2588 -- the case of multi-dimensional arrays is rare and too much trouble! If
2589 -- one of the operands is an illegal aggregate, its type might still be
2590 -- an arbitrary composite type, so nothing to do.
996ae0b0
RK
2591
2592 if Is_Array_Type (Typ)
13f34a3f 2593 and then Typ /= Any_Composite
996ae0b0 2594 and then Number_Dimensions (Typ) = 1
13f34a3f 2595 and then (Nkind (N) = N_Op_Eq or else Nkind (N) = N_Op_Ne)
996ae0b0
RK
2596 then
2597 if Raises_Constraint_Error (Left)
2598 or else Raises_Constraint_Error (Right)
2599 then
2600 return;
2601 end if;
2602
45fc7ddb
HK
2603 -- OK, we have the case where we may be able to do this fold
2604
2605 Length_Mismatch : declare
996ae0b0 2606 procedure Get_Static_Length (Op : Node_Id; Len : out Uint);
1d1bd8ad
AC
2607 -- If Op is an expression for a constrained array with a known at
2608 -- compile time length, then Len is set to this (non-negative
13f34a3f 2609 -- length). Otherwise Len is set to minus 1.
996ae0b0 2610
fbf5a39b
AC
2611 -----------------------
2612 -- Get_Static_Length --
2613 -----------------------
2614
996ae0b0
RK
2615 procedure Get_Static_Length (Op : Node_Id; Len : out Uint) is
2616 T : Entity_Id;
2617
2618 begin
45fc7ddb
HK
2619 -- First easy case string literal
2620
996ae0b0
RK
2621 if Nkind (Op) = N_String_Literal then
2622 Len := UI_From_Int (String_Length (Strval (Op)));
45fc7ddb
HK
2623 return;
2624 end if;
2625
2626 -- Second easy case, not constrained subtype, so no length
996ae0b0 2627
45fc7ddb 2628 if not Is_Constrained (Etype (Op)) then
996ae0b0 2629 Len := Uint_Minus_1;
45fc7ddb
HK
2630 return;
2631 end if;
996ae0b0 2632
45fc7ddb
HK
2633 -- General case
2634
2635 T := Etype (First_Index (Etype (Op)));
2636
2637 -- The simple case, both bounds are known at compile time
2638
2639 if Is_Discrete_Type (T)
2640 and then
2641 Compile_Time_Known_Value (Type_Low_Bound (T))
2642 and then
2643 Compile_Time_Known_Value (Type_High_Bound (T))
2644 then
2645 Len := UI_Max (Uint_0,
2646 Expr_Value (Type_High_Bound (T)) -
2647 Expr_Value (Type_Low_Bound (T)) + 1);
2648 return;
2649 end if;
2650
2651 -- A more complex case, where the bounds are of the form
2652 -- X [+/- K1] .. X [+/- K2]), where X is an expression that is
2653 -- either A'First or A'Last (with A an entity name), or X is an
2654 -- entity name, and the two X's are the same and K1 and K2 are
2655 -- known at compile time, in this case, the length can also be
2656 -- computed at compile time, even though the bounds are not
22cb89b5 2657 -- known. A common case of this is e.g. (X'First .. X'First+5).
45fc7ddb
HK
2658
2659 Extract_Length : declare
2660 procedure Decompose_Expr
2661 (Expr : Node_Id;
2662 Ent : out Entity_Id;
2663 Kind : out Character;
2664 Cons : out Uint);
2665 -- Given an expression, see if is of the form above,
2666 -- X [+/- K]. If so Ent is set to the entity in X,
2667 -- Kind is 'F','L','E' for 'First/'Last/simple entity,
2668 -- and Cons is the value of K. If the expression is
2669 -- not of the required form, Ent is set to Empty.
2670
2671 --------------------
2672 -- Decompose_Expr --
2673 --------------------
2674
2675 procedure Decompose_Expr
2676 (Expr : Node_Id;
2677 Ent : out Entity_Id;
2678 Kind : out Character;
2679 Cons : out Uint)
2680 is
2681 Exp : Node_Id;
2682
2683 begin
2684 if Nkind (Expr) = N_Op_Add
2685 and then Compile_Time_Known_Value (Right_Opnd (Expr))
2686 then
8a95f4e8 2687 Exp := Left_Opnd (Expr);
45fc7ddb
HK
2688 Cons := Expr_Value (Right_Opnd (Expr));
2689
2690 elsif Nkind (Expr) = N_Op_Subtract
2691 and then Compile_Time_Known_Value (Right_Opnd (Expr))
2692 then
8a95f4e8 2693 Exp := Left_Opnd (Expr);
45fc7ddb 2694 Cons := -Expr_Value (Right_Opnd (Expr));
996ae0b0 2695
8a95f4e8
RD
2696 -- If the bound is a constant created to remove side
2697 -- effects, recover original expression to see if it has
2698 -- one of the recognizable forms.
2699
2700 elsif Nkind (Expr) = N_Identifier
2701 and then not Comes_From_Source (Entity (Expr))
2702 and then Ekind (Entity (Expr)) = E_Constant
2703 and then
2704 Nkind (Parent (Entity (Expr))) = N_Object_Declaration
2705 then
2706 Exp := Expression (Parent (Entity (Expr)));
2707 Decompose_Expr (Exp, Ent, Kind, Cons);
2708
2709 -- If original expression includes an entity, create a
2710 -- reference to it for use below.
2711
2712 if Present (Ent) then
2713 Exp := New_Occurrence_Of (Ent, Sloc (Ent));
2714 end if;
2715
45fc7ddb 2716 else
8a95f4e8 2717 Exp := Expr;
45fc7ddb
HK
2718 Cons := Uint_0;
2719 end if;
2720
2721 -- At this stage Exp is set to the potential X
2722
2723 if Nkind (Exp) = N_Attribute_Reference then
2724 if Attribute_Name (Exp) = Name_First then
2725 Kind := 'F';
8a95f4e8 2726
45fc7ddb
HK
2727 elsif Attribute_Name (Exp) = Name_Last then
2728 Kind := 'L';
8a95f4e8 2729
45fc7ddb
HK
2730 else
2731 Ent := Empty;
2732 return;
2733 end if;
2734
2735 Exp := Prefix (Exp);
2736
2737 else
2738 Kind := 'E';
2739 end if;
2740
2741 if Is_Entity_Name (Exp)
2742 and then Present (Entity (Exp))
2743 then
2744 Ent := Entity (Exp);
2745 else
2746 Ent := Empty;
2747 end if;
2748 end Decompose_Expr;
2749
2750 -- Local Variables
2751
2752 Ent1, Ent2 : Entity_Id;
2753 Kind1, Kind2 : Character;
2754 Cons1, Cons2 : Uint;
2755
2756 -- Start of processing for Extract_Length
2757
2758 begin
bafc9e1d
AC
2759 Decompose_Expr
2760 (Original_Node (Type_Low_Bound (T)), Ent1, Kind1, Cons1);
2761 Decompose_Expr
2762 (Original_Node (Type_High_Bound (T)), Ent2, Kind2, Cons2);
45fc7ddb
HK
2763
2764 if Present (Ent1)
2765 and then Kind1 = Kind2
2766 and then Ent1 = Ent2
996ae0b0 2767 then
45fc7ddb 2768 Len := Cons2 - Cons1 + 1;
996ae0b0
RK
2769 else
2770 Len := Uint_Minus_1;
2771 end if;
45fc7ddb 2772 end Extract_Length;
996ae0b0
RK
2773 end Get_Static_Length;
2774
45fc7ddb
HK
2775 -- Local Variables
2776
996ae0b0
RK
2777 Len_L : Uint;
2778 Len_R : Uint;
2779
45fc7ddb
HK
2780 -- Start of processing for Length_Mismatch
2781
996ae0b0
RK
2782 begin
2783 Get_Static_Length (Left, Len_L);
2784 Get_Static_Length (Right, Len_R);
2785
2786 if Len_L /= Uint_Minus_1
2787 and then Len_R /= Uint_Minus_1
2788 and then Len_L /= Len_R
2789 then
fbf5a39b 2790 Fold_Uint (N, Test (Nkind (N) = N_Op_Ne), False);
996ae0b0
RK
2791 Warn_On_Known_Condition (N);
2792 return;
2793 end if;
45fc7ddb
HK
2794 end Length_Mismatch;
2795 end if;
6eaf4095 2796
93c3fca7 2797 -- Test for expression being foldable
7a3f77d2 2798
93c3fca7 2799 Test_Expression_Is_Foldable (N, Left, Right, Stat, Fold);
996ae0b0 2800
93c3fca7
AC
2801 -- Only comparisons of scalars can give static results. In particular,
2802 -- comparisons of strings never yield a static result, even if both
2803 -- operands are static strings.
996ae0b0
RK
2804
2805 if not Is_Scalar_Type (Typ) then
93c3fca7
AC
2806 Stat := False;
2807 Set_Is_Static_Expression (N, False);
996ae0b0
RK
2808 end if;
2809
93c3fca7
AC
2810 -- For static real type expressions, we cannot use Compile_Time_Compare
2811 -- since it worries about run-time results which are not exact.
996ae0b0 2812
93c3fca7 2813 if Stat and then Is_Real_Type (Typ) then
996ae0b0 2814 declare
93c3fca7
AC
2815 Left_Real : constant Ureal := Expr_Value_R (Left);
2816 Right_Real : constant Ureal := Expr_Value_R (Right);
996ae0b0
RK
2817
2818 begin
2819 case Nkind (N) is
93c3fca7
AC
2820 when N_Op_Eq => Result := (Left_Real = Right_Real);
2821 when N_Op_Ne => Result := (Left_Real /= Right_Real);
2822 when N_Op_Lt => Result := (Left_Real < Right_Real);
2823 when N_Op_Le => Result := (Left_Real <= Right_Real);
2824 when N_Op_Gt => Result := (Left_Real > Right_Real);
2825 when N_Op_Ge => Result := (Left_Real >= Right_Real);
996ae0b0
RK
2826
2827 when others =>
2828 raise Program_Error;
2829 end case;
2830
93c3fca7 2831 Fold_Uint (N, Test (Result), True);
996ae0b0
RK
2832 end;
2833
93c3fca7 2834 -- For all other cases, we use Compile_Time_Compare to do the compare
996ae0b0
RK
2835
2836 else
996ae0b0 2837 declare
93c3fca7
AC
2838 CR : constant Compare_Result :=
2839 Compile_Time_Compare (Left, Right, Assume_Valid => False);
996ae0b0
RK
2840
2841 begin
93c3fca7
AC
2842 if CR = Unknown then
2843 return;
2844 end if;
2845
996ae0b0 2846 case Nkind (N) is
93c3fca7
AC
2847 when N_Op_Eq =>
2848 if CR = EQ then
2849 Result := True;
2850 elsif CR = NE or else CR = GT or else CR = LT then
2851 Result := False;
2852 else
2853 return;
2854 end if;
2855
2856 when N_Op_Ne =>
2857 if CR = NE or else CR = GT or else CR = LT then
2858 Result := True;
2859 elsif CR = EQ then
2860 Result := False;
2861 else
2862 return;
2863 end if;
2864
2865 when N_Op_Lt =>
2866 if CR = LT then
2867 Result := True;
2868 elsif CR = EQ or else CR = GT or else CR = GE then
2869 Result := False;
2870 else
2871 return;
2872 end if;
2873
2874 when N_Op_Le =>
2875 if CR = LT or else CR = EQ or else CR = LE then
2876 Result := True;
2877 elsif CR = GT then
2878 Result := False;
2879 else
2880 return;
2881 end if;
2882
2883 when N_Op_Gt =>
2884 if CR = GT then
2885 Result := True;
2886 elsif CR = EQ or else CR = LT or else CR = LE then
2887 Result := False;
2888 else
2889 return;
2890 end if;
2891
2892 when N_Op_Ge =>
2893 if CR = GT or else CR = EQ or else CR = GE then
2894 Result := True;
2895 elsif CR = LT then
2896 Result := False;
2897 else
2898 return;
2899 end if;
996ae0b0
RK
2900
2901 when others =>
2902 raise Program_Error;
2903 end case;
996ae0b0 2904 end;
93c3fca7
AC
2905
2906 Fold_Uint (N, Test (Result), Stat);
996ae0b0
RK
2907 end if;
2908
996ae0b0
RK
2909 Warn_On_Known_Condition (N);
2910 end Eval_Relational_Op;
2911
2912 ----------------
2913 -- Eval_Shift --
2914 ----------------
2915
22cb89b5
AC
2916 -- Shift operations are intrinsic operations that can never be static, so
2917 -- the only processing required is to perform the required check for a non
2918 -- static context for the two operands.
996ae0b0
RK
2919
2920 -- Actually we could do some compile time evaluation here some time ???
2921
2922 procedure Eval_Shift (N : Node_Id) is
2923 begin
2924 Check_Non_Static_Context (Left_Opnd (N));
2925 Check_Non_Static_Context (Right_Opnd (N));
2926 end Eval_Shift;
2927
2928 ------------------------
2929 -- Eval_Short_Circuit --
2930 ------------------------
2931
22cb89b5
AC
2932 -- A short circuit operation is potentially static if both operands are
2933 -- potentially static (RM 4.9 (13)).
996ae0b0
RK
2934
2935 procedure Eval_Short_Circuit (N : Node_Id) is
2936 Kind : constant Node_Kind := Nkind (N);
2937 Left : constant Node_Id := Left_Opnd (N);
2938 Right : constant Node_Id := Right_Opnd (N);
2939 Left_Int : Uint;
2940 Rstat : constant Boolean :=
2941 Is_Static_Expression (Left)
2942 and then Is_Static_Expression (Right);
2943
2944 begin
2945 -- Short circuit operations are never static in Ada 83
2946
22cb89b5 2947 if Ada_Version = Ada_83 and then Comes_From_Source (N) then
996ae0b0
RK
2948 Check_Non_Static_Context (Left);
2949 Check_Non_Static_Context (Right);
2950 return;
2951 end if;
2952
2953 -- Now look at the operands, we can't quite use the normal call to
2954 -- Test_Expression_Is_Foldable here because short circuit operations
2955 -- are a special case, they can still be foldable, even if the right
2956 -- operand raises constraint error.
2957
22cb89b5
AC
2958 -- If either operand is Any_Type, just propagate to result and do not
2959 -- try to fold, this prevents cascaded errors.
996ae0b0
RK
2960
2961 if Etype (Left) = Any_Type or else Etype (Right) = Any_Type then
2962 Set_Etype (N, Any_Type);
2963 return;
2964
2965 -- If left operand raises constraint error, then replace node N with
2966 -- the raise constraint error node, and we are obviously not foldable.
2967 -- Is_Static_Expression is set from the two operands in the normal way,
2968 -- and we check the right operand if it is in a non-static context.
2969
2970 elsif Raises_Constraint_Error (Left) then
2971 if not Rstat then
2972 Check_Non_Static_Context (Right);
2973 end if;
2974
2975 Rewrite_In_Raise_CE (N, Left);
2976 Set_Is_Static_Expression (N, Rstat);
2977 return;
2978
2979 -- If the result is not static, then we won't in any case fold
2980
2981 elsif not Rstat then
2982 Check_Non_Static_Context (Left);
2983 Check_Non_Static_Context (Right);
2984 return;
2985 end if;
2986
2987 -- Here the result is static, note that, unlike the normal processing
2988 -- in Test_Expression_Is_Foldable, we did *not* check above to see if
2989 -- the right operand raises constraint error, that's because it is not
2990 -- significant if the left operand is decisive.
2991
2992 Set_Is_Static_Expression (N);
2993
2994 -- It does not matter if the right operand raises constraint error if
2995 -- it will not be evaluated. So deal specially with the cases where
2996 -- the right operand is not evaluated. Note that we will fold these
2997 -- cases even if the right operand is non-static, which is fine, but
2998 -- of course in these cases the result is not potentially static.
2999
3000 Left_Int := Expr_Value (Left);
3001
3002 if (Kind = N_And_Then and then Is_False (Left_Int))
514d0fc5
AC
3003 or else
3004 (Kind = N_Or_Else and then Is_True (Left_Int))
996ae0b0 3005 then
fbf5a39b 3006 Fold_Uint (N, Left_Int, Rstat);
996ae0b0
RK
3007 return;
3008 end if;
3009
3010 -- If first operand not decisive, then it does matter if the right
3011 -- operand raises constraint error, since it will be evaluated, so
3012 -- we simply replace the node with the right operand. Note that this
3013 -- properly propagates Is_Static_Expression and Raises_Constraint_Error
3014 -- (both are set to True in Right).
3015
3016 if Raises_Constraint_Error (Right) then
3017 Rewrite_In_Raise_CE (N, Right);
3018 Check_Non_Static_Context (Left);
3019 return;
3020 end if;
3021
3022 -- Otherwise the result depends on the right operand
3023
fbf5a39b 3024 Fold_Uint (N, Expr_Value (Right), Rstat);
996ae0b0 3025 return;
996ae0b0
RK
3026 end Eval_Short_Circuit;
3027
3028 ----------------
3029 -- Eval_Slice --
3030 ----------------
3031
22cb89b5
AC
3032 -- Slices can never be static, so the only processing required is to check
3033 -- for non-static context if an explicit range is given.
996ae0b0
RK
3034
3035 procedure Eval_Slice (N : Node_Id) is
3036 Drange : constant Node_Id := Discrete_Range (N);
996ae0b0
RK
3037 begin
3038 if Nkind (Drange) = N_Range then
3039 Check_Non_Static_Context (Low_Bound (Drange));
3040 Check_Non_Static_Context (High_Bound (Drange));
3041 end if;
cd2fb920 3042
22cb89b5 3043 -- A slice of the form A (subtype), when the subtype is the index of
cd2fb920
ES
3044 -- the type of A, is redundant, the slice can be replaced with A, and
3045 -- this is worth a warning.
3046
3047 if Is_Entity_Name (Prefix (N)) then
3048 declare
3049 E : constant Entity_Id := Entity (Prefix (N));
3050 T : constant Entity_Id := Etype (E);
3051 begin
3052 if Ekind (E) = E_Constant
3053 and then Is_Array_Type (T)
3054 and then Is_Entity_Name (Drange)
3055 then
3056 if Is_Entity_Name (Original_Node (First_Index (T)))
3057 and then Entity (Original_Node (First_Index (T)))
3058 = Entity (Drange)
3059 then
3060 if Warn_On_Redundant_Constructs then
ed2233dc 3061 Error_Msg_N ("redundant slice denotes whole array?", N);
cd2fb920
ES
3062 end if;
3063
22cb89b5 3064 -- The following might be a useful optimization????
cd2fb920
ES
3065
3066 -- Rewrite (N, New_Occurrence_Of (E, Sloc (N)));
3067 end if;
3068 end if;
3069 end;
3070 end if;
996ae0b0
RK
3071 end Eval_Slice;
3072
3073 -------------------------
3074 -- Eval_String_Literal --
3075 -------------------------
3076
3077 procedure Eval_String_Literal (N : Node_Id) is
91b1417d
AC
3078 Typ : constant Entity_Id := Etype (N);
3079 Bas : constant Entity_Id := Base_Type (Typ);
3080 Xtp : Entity_Id;
3081 Len : Nat;
3082 Lo : Node_Id;
996ae0b0
RK
3083
3084 begin
3085 -- Nothing to do if error type (handles cases like default expressions
22cb89b5 3086 -- or generics where we have not yet fully resolved the type).
996ae0b0 3087
91b1417d 3088 if Bas = Any_Type or else Bas = Any_String then
996ae0b0 3089 return;
91b1417d 3090 end if;
996ae0b0
RK
3091
3092 -- String literals are static if the subtype is static (RM 4.9(2)), so
3093 -- reset the static expression flag (it was set unconditionally in
3094 -- Analyze_String_Literal) if the subtype is non-static. We tell if
3095 -- the subtype is static by looking at the lower bound.
3096
91b1417d
AC
3097 if Ekind (Typ) = E_String_Literal_Subtype then
3098 if not Is_OK_Static_Expression (String_Literal_Low_Bound (Typ)) then
3099 Set_Is_Static_Expression (N, False);
3100 return;
3101 end if;
3102
3103 -- Here if Etype of string literal is normal Etype (not yet possible,
22cb89b5 3104 -- but may be possible in future).
91b1417d
AC
3105
3106 elsif not Is_OK_Static_Expression
3107 (Type_Low_Bound (Etype (First_Index (Typ))))
3108 then
996ae0b0 3109 Set_Is_Static_Expression (N, False);
91b1417d
AC
3110 return;
3111 end if;
996ae0b0 3112
91b1417d
AC
3113 -- If original node was a type conversion, then result if non-static
3114
3115 if Nkind (Original_Node (N)) = N_Type_Conversion then
996ae0b0 3116 Set_Is_Static_Expression (N, False);
91b1417d
AC
3117 return;
3118 end if;
996ae0b0 3119
22cb89b5
AC
3120 -- Test for illegal Ada 95 cases. A string literal is illegal in Ada 95
3121 -- if its bounds are outside the index base type and this index type is
3122 -- static. This can happen in only two ways. Either the string literal
3123 -- is too long, or it is null, and the lower bound is type'First. In
3124 -- either case it is the upper bound that is out of range of the index
3125 -- type.
996ae0b0 3126
0ab80019 3127 if Ada_Version >= Ada_95 then
91b1417d
AC
3128 if Root_Type (Bas) = Standard_String
3129 or else
3130 Root_Type (Bas) = Standard_Wide_String
996ae0b0 3131 then
91b1417d 3132 Xtp := Standard_Positive;
996ae0b0 3133 else
91b1417d 3134 Xtp := Etype (First_Index (Bas));
996ae0b0
RK
3135 end if;
3136
91b1417d
AC
3137 if Ekind (Typ) = E_String_Literal_Subtype then
3138 Lo := String_Literal_Low_Bound (Typ);
3139 else
3140 Lo := Type_Low_Bound (Etype (First_Index (Typ)));
3141 end if;
3142
3143 Len := String_Length (Strval (N));
3144
3145 if UI_From_Int (Len) > String_Type_Len (Bas) then
996ae0b0 3146 Apply_Compile_Time_Constraint_Error
07fc65c4 3147 (N, "string literal too long for}", CE_Length_Check_Failed,
91b1417d
AC
3148 Ent => Bas,
3149 Typ => First_Subtype (Bas));
996ae0b0 3150
91b1417d
AC
3151 elsif Len = 0
3152 and then not Is_Generic_Type (Xtp)
3153 and then
3154 Expr_Value (Lo) = Expr_Value (Type_Low_Bound (Base_Type (Xtp)))
996ae0b0
RK
3155 then
3156 Apply_Compile_Time_Constraint_Error
3157 (N, "null string literal not allowed for}",
07fc65c4 3158 CE_Length_Check_Failed,
91b1417d
AC
3159 Ent => Bas,
3160 Typ => First_Subtype (Bas));
996ae0b0
RK
3161 end if;
3162 end if;
996ae0b0
RK
3163 end Eval_String_Literal;
3164
3165 --------------------------
3166 -- Eval_Type_Conversion --
3167 --------------------------
3168
3169 -- A type conversion is potentially static if its subtype mark is for a
3170 -- static scalar subtype, and its operand expression is potentially static
22cb89b5 3171 -- (RM 4.9(10)).
996ae0b0
RK
3172
3173 procedure Eval_Type_Conversion (N : Node_Id) is
3174 Operand : constant Node_Id := Expression (N);
3175 Source_Type : constant Entity_Id := Etype (Operand);
3176 Target_Type : constant Entity_Id := Etype (N);
3177
3178 Stat : Boolean;
3179 Fold : Boolean;
3180
3181 function To_Be_Treated_As_Integer (T : Entity_Id) return Boolean;
22cb89b5
AC
3182 -- Returns true if type T is an integer type, or if it is a fixed-point
3183 -- type to be treated as an integer (i.e. the flag Conversion_OK is set
3184 -- on the conversion node).
996ae0b0
RK
3185
3186 function To_Be_Treated_As_Real (T : Entity_Id) return Boolean;
3187 -- Returns true if type T is a floating-point type, or if it is a
3188 -- fixed-point type that is not to be treated as an integer (i.e. the
3189 -- flag Conversion_OK is not set on the conversion node).
3190
fbf5a39b
AC
3191 ------------------------------
3192 -- To_Be_Treated_As_Integer --
3193 ------------------------------
3194
996ae0b0
RK
3195 function To_Be_Treated_As_Integer (T : Entity_Id) return Boolean is
3196 begin
3197 return
3198 Is_Integer_Type (T)
3199 or else (Is_Fixed_Point_Type (T) and then Conversion_OK (N));
3200 end To_Be_Treated_As_Integer;
3201
fbf5a39b
AC
3202 ---------------------------
3203 -- To_Be_Treated_As_Real --
3204 ---------------------------
3205
996ae0b0
RK
3206 function To_Be_Treated_As_Real (T : Entity_Id) return Boolean is
3207 begin
3208 return
3209 Is_Floating_Point_Type (T)
3210 or else (Is_Fixed_Point_Type (T) and then not Conversion_OK (N));
3211 end To_Be_Treated_As_Real;
3212
3213 -- Start of processing for Eval_Type_Conversion
3214
3215 begin
82c80734 3216 -- Cannot fold if target type is non-static or if semantic error
996ae0b0
RK
3217
3218 if not Is_Static_Subtype (Target_Type) then
3219 Check_Non_Static_Context (Operand);
3220 return;
3221
3222 elsif Error_Posted (N) then
3223 return;
3224 end if;
3225
3226 -- If not foldable we are done
3227
3228 Test_Expression_Is_Foldable (N, Operand, Stat, Fold);
3229
3230 if not Fold then
3231 return;
3232
3233 -- Don't try fold if target type has constraint error bounds
3234
3235 elsif not Is_OK_Static_Subtype (Target_Type) then
3236 Set_Raises_Constraint_Error (N);
3237 return;
3238 end if;
3239
3240 -- Remaining processing depends on operand types. Note that in the
3241 -- following type test, fixed-point counts as real unless the flag
3242 -- Conversion_OK is set, in which case it counts as integer.
3243
82c80734 3244 -- Fold conversion, case of string type. The result is not static
996ae0b0
RK
3245
3246 if Is_String_Type (Target_Type) then
b11e8d6f 3247 Fold_Str (N, Strval (Get_String_Val (Operand)), Static => False);
996ae0b0
RK
3248
3249 return;
3250
3251 -- Fold conversion, case of integer target type
3252
3253 elsif To_Be_Treated_As_Integer (Target_Type) then
3254 declare
3255 Result : Uint;
3256
3257 begin
3258 -- Integer to integer conversion
3259
3260 if To_Be_Treated_As_Integer (Source_Type) then
3261 Result := Expr_Value (Operand);
3262
3263 -- Real to integer conversion
3264
3265 else
3266 Result := UR_To_Uint (Expr_Value_R (Operand));
3267 end if;
3268
3269 -- If fixed-point type (Conversion_OK must be set), then the
3270 -- result is logically an integer, but we must replace the
3271 -- conversion with the corresponding real literal, since the
3272 -- type from a semantic point of view is still fixed-point.
3273
3274 if Is_Fixed_Point_Type (Target_Type) then
3275 Fold_Ureal
fbf5a39b 3276 (N, UR_From_Uint (Result) * Small_Value (Target_Type), Stat);
996ae0b0
RK
3277
3278 -- Otherwise result is integer literal
3279
3280 else
fbf5a39b 3281 Fold_Uint (N, Result, Stat);
996ae0b0
RK
3282 end if;
3283 end;
3284
3285 -- Fold conversion, case of real target type
3286
3287 elsif To_Be_Treated_As_Real (Target_Type) then
3288 declare
3289 Result : Ureal;
3290
3291 begin
3292 if To_Be_Treated_As_Real (Source_Type) then
3293 Result := Expr_Value_R (Operand);
3294 else
3295 Result := UR_From_Uint (Expr_Value (Operand));
3296 end if;
3297
fbf5a39b 3298 Fold_Ureal (N, Result, Stat);
996ae0b0
RK
3299 end;
3300
3301 -- Enumeration types
3302
3303 else
fbf5a39b 3304 Fold_Uint (N, Expr_Value (Operand), Stat);
996ae0b0
RK
3305 end if;
3306
c800f862 3307 if Is_Out_Of_Range (N, Etype (N), Assume_Valid => True) then
996ae0b0
RK
3308 Out_Of_Range (N);
3309 end if;
3310
3311 end Eval_Type_Conversion;
3312
3313 -------------------
3314 -- Eval_Unary_Op --
3315 -------------------
3316
3317 -- Predefined unary operators are static functions (RM 4.9(20)) and thus
22cb89b5 3318 -- are potentially static if the operand is potentially static (RM 4.9(7)).
996ae0b0
RK
3319
3320 procedure Eval_Unary_Op (N : Node_Id) is
3321 Right : constant Node_Id := Right_Opnd (N);
3322 Stat : Boolean;
3323 Fold : Boolean;
3324
3325 begin
3326 -- If not foldable we are done
3327
3328 Test_Expression_Is_Foldable (N, Right, Stat, Fold);
3329
3330 if not Fold then
3331 return;
3332 end if;
3333
3334 -- Fold for integer case
3335
3336 if Is_Integer_Type (Etype (N)) then
3337 declare
3338 Rint : constant Uint := Expr_Value (Right);
3339 Result : Uint;
3340
3341 begin
3342 -- In the case of modular unary plus and abs there is no need
3343 -- to adjust the result of the operation since if the original
3344 -- operand was in bounds the result will be in the bounds of the
3345 -- modular type. However, in the case of modular unary minus the
3346 -- result may go out of the bounds of the modular type and needs
3347 -- adjustment.
3348
3349 if Nkind (N) = N_Op_Plus then
3350 Result := Rint;
3351
3352 elsif Nkind (N) = N_Op_Minus then
3353 if Is_Modular_Integer_Type (Etype (N)) then
3354 Result := (-Rint) mod Modulus (Etype (N));
3355 else
3356 Result := (-Rint);
3357 end if;
3358
3359 else
3360 pragma Assert (Nkind (N) = N_Op_Abs);
3361 Result := abs Rint;
3362 end if;
3363
fbf5a39b 3364 Fold_Uint (N, Result, Stat);
996ae0b0
RK
3365 end;
3366
3367 -- Fold for real case
3368
3369 elsif Is_Real_Type (Etype (N)) then
3370 declare
3371 Rreal : constant Ureal := Expr_Value_R (Right);
3372 Result : Ureal;
3373
3374 begin
3375 if Nkind (N) = N_Op_Plus then
3376 Result := Rreal;
3377
3378 elsif Nkind (N) = N_Op_Minus then
3379 Result := UR_Negate (Rreal);
3380
3381 else
3382 pragma Assert (Nkind (N) = N_Op_Abs);
3383 Result := abs Rreal;
3384 end if;
3385
fbf5a39b 3386 Fold_Ureal (N, Result, Stat);
996ae0b0
RK
3387 end;
3388 end if;
996ae0b0
RK
3389 end Eval_Unary_Op;
3390
3391 -------------------------------
3392 -- Eval_Unchecked_Conversion --
3393 -------------------------------
3394
3395 -- Unchecked conversions can never be static, so the only required
3396 -- processing is to check for a non-static context for the operand.
3397
3398 procedure Eval_Unchecked_Conversion (N : Node_Id) is
3399 begin
3400 Check_Non_Static_Context (Expression (N));
3401 end Eval_Unchecked_Conversion;
3402
3403 --------------------
3404 -- Expr_Rep_Value --
3405 --------------------
3406
3407 function Expr_Rep_Value (N : Node_Id) return Uint is
07fc65c4
GB
3408 Kind : constant Node_Kind := Nkind (N);
3409 Ent : Entity_Id;
996ae0b0
RK
3410
3411 begin
3412 if Is_Entity_Name (N) then
3413 Ent := Entity (N);
3414
22cb89b5
AC
3415 -- An enumeration literal that was either in the source or created
3416 -- as a result of static evaluation.
996ae0b0
RK
3417
3418 if Ekind (Ent) = E_Enumeration_Literal then
3419 return Enumeration_Rep (Ent);
3420
3421 -- A user defined static constant
3422
3423 else
3424 pragma Assert (Ekind (Ent) = E_Constant);
3425 return Expr_Rep_Value (Constant_Value (Ent));
3426 end if;
3427
22cb89b5
AC
3428 -- An integer literal that was either in the source or created as a
3429 -- result of static evaluation.
996ae0b0
RK
3430
3431 elsif Kind = N_Integer_Literal then
3432 return Intval (N);
3433
3434 -- A real literal for a fixed-point type. This must be the fixed-point
3435 -- case, either the literal is of a fixed-point type, or it is a bound
3436 -- of a fixed-point type, with type universal real. In either case we
3437 -- obtain the desired value from Corresponding_Integer_Value.
3438
3439 elsif Kind = N_Real_Literal then
996ae0b0
RK
3440 pragma Assert (Is_Fixed_Point_Type (Underlying_Type (Etype (N))));
3441 return Corresponding_Integer_Value (N);
3442
07fc65c4
GB
3443 -- Peculiar VMS case, if we have xxx'Null_Parameter, return zero
3444
3445 elsif Kind = N_Attribute_Reference
3446 and then Attribute_Name (N) = Name_Null_Parameter
3447 then
3448 return Uint_0;
3449
07fc65c4 3450 -- Otherwise must be character literal
8cbb664e 3451
996ae0b0
RK
3452 else
3453 pragma Assert (Kind = N_Character_Literal);
3454 Ent := Entity (N);
3455
22cb89b5
AC
3456 -- Since Character literals of type Standard.Character don't have any
3457 -- defining character literals built for them, they do not have their
3458 -- Entity set, so just use their Char code. Otherwise for user-
3459 -- defined character literals use their Pos value as usual which is
3460 -- the same as the Rep value.
996ae0b0
RK
3461
3462 if No (Ent) then
82c80734 3463 return Char_Literal_Value (N);
996ae0b0
RK
3464 else
3465 return Enumeration_Rep (Ent);
3466 end if;
3467 end if;
3468 end Expr_Rep_Value;
3469
3470 ----------------
3471 -- Expr_Value --
3472 ----------------
3473
3474 function Expr_Value (N : Node_Id) return Uint is
07fc65c4
GB
3475 Kind : constant Node_Kind := Nkind (N);
3476 CV_Ent : CV_Entry renames CV_Cache (Nat (N) mod CV_Cache_Size);
3477 Ent : Entity_Id;
3478 Val : Uint;
996ae0b0
RK
3479
3480 begin
13f34a3f
RD
3481 -- If already in cache, then we know it's compile time known and we can
3482 -- return the value that was previously stored in the cache since
3483 -- compile time known values cannot change.
07fc65c4
GB
3484
3485 if CV_Ent.N = N then
3486 return CV_Ent.V;
3487 end if;
3488
3489 -- Otherwise proceed to test value
3490
996ae0b0
RK
3491 if Is_Entity_Name (N) then
3492 Ent := Entity (N);
3493
22cb89b5
AC
3494 -- An enumeration literal that was either in the source or created as
3495 -- a result of static evaluation.
996ae0b0
RK
3496
3497 if Ekind (Ent) = E_Enumeration_Literal then
07fc65c4 3498 Val := Enumeration_Pos (Ent);
996ae0b0
RK
3499
3500 -- A user defined static constant
3501
3502 else
3503 pragma Assert (Ekind (Ent) = E_Constant);
07fc65c4 3504 Val := Expr_Value (Constant_Value (Ent));
996ae0b0
RK
3505 end if;
3506
22cb89b5
AC
3507 -- An integer literal that was either in the source or created as a
3508 -- result of static evaluation.
996ae0b0
RK
3509
3510 elsif Kind = N_Integer_Literal then
07fc65c4 3511 Val := Intval (N);
996ae0b0
RK
3512
3513 -- A real literal for a fixed-point type. This must be the fixed-point
3514 -- case, either the literal is of a fixed-point type, or it is a bound
3515 -- of a fixed-point type, with type universal real. In either case we
3516 -- obtain the desired value from Corresponding_Integer_Value.
3517
3518 elsif Kind = N_Real_Literal then
3519
996ae0b0 3520 pragma Assert (Is_Fixed_Point_Type (Underlying_Type (Etype (N))));
07fc65c4 3521 Val := Corresponding_Integer_Value (N);
996ae0b0
RK
3522
3523 -- Peculiar VMS case, if we have xxx'Null_Parameter, return zero
3524
3525 elsif Kind = N_Attribute_Reference
3526 and then Attribute_Name (N) = Name_Null_Parameter
3527 then
07fc65c4
GB
3528 Val := Uint_0;
3529
996ae0b0
RK
3530 -- Otherwise must be character literal
3531
3532 else
3533 pragma Assert (Kind = N_Character_Literal);
3534 Ent := Entity (N);
3535
3536 -- Since Character literals of type Standard.Character don't
3537 -- have any defining character literals built for them, they
3538 -- do not have their Entity set, so just use their Char
3539 -- code. Otherwise for user-defined character literals use
3540 -- their Pos value as usual.
3541
3542 if No (Ent) then
82c80734 3543 Val := Char_Literal_Value (N);
996ae0b0 3544 else
07fc65c4 3545 Val := Enumeration_Pos (Ent);
996ae0b0
RK
3546 end if;
3547 end if;
3548
07fc65c4
GB
3549 -- Come here with Val set to value to be returned, set cache
3550
3551 CV_Ent.N := N;
3552 CV_Ent.V := Val;
3553 return Val;
996ae0b0
RK
3554 end Expr_Value;
3555
3556 ------------------
3557 -- Expr_Value_E --
3558 ------------------
3559
3560 function Expr_Value_E (N : Node_Id) return Entity_Id is
3561 Ent : constant Entity_Id := Entity (N);
3562
3563 begin
3564 if Ekind (Ent) = E_Enumeration_Literal then
3565 return Ent;
3566 else
3567 pragma Assert (Ekind (Ent) = E_Constant);
3568 return Expr_Value_E (Constant_Value (Ent));
3569 end if;
3570 end Expr_Value_E;
3571
3572 ------------------
3573 -- Expr_Value_R --
3574 ------------------
3575
3576 function Expr_Value_R (N : Node_Id) return Ureal is
3577 Kind : constant Node_Kind := Nkind (N);
3578 Ent : Entity_Id;
3579 Expr : Node_Id;
3580
3581 begin
3582 if Kind = N_Real_Literal then
3583 return Realval (N);
3584
3585 elsif Kind = N_Identifier or else Kind = N_Expanded_Name then
3586 Ent := Entity (N);
3587 pragma Assert (Ekind (Ent) = E_Constant);
3588 return Expr_Value_R (Constant_Value (Ent));
3589
3590 elsif Kind = N_Integer_Literal then
3591 return UR_From_Uint (Expr_Value (N));
3592
3593 -- Strange case of VAX literals, which are at this stage transformed
3594 -- into Vax_Type!x_To_y(IEEE_Literal). See Expand_N_Real_Literal in
3595 -- Exp_Vfpt for further details.
3596
3597 elsif Vax_Float (Etype (N))
3598 and then Nkind (N) = N_Unchecked_Type_Conversion
3599 then
3600 Expr := Expression (N);
3601
3602 if Nkind (Expr) = N_Function_Call
3603 and then Present (Parameter_Associations (Expr))
3604 then
3605 Expr := First (Parameter_Associations (Expr));
3606
3607 if Nkind (Expr) = N_Real_Literal then
3608 return Realval (Expr);
3609 end if;
3610 end if;
3611
3612 -- Peculiar VMS case, if we have xxx'Null_Parameter, return 0.0
3613
3614 elsif Kind = N_Attribute_Reference
3615 and then Attribute_Name (N) = Name_Null_Parameter
3616 then
3617 return Ureal_0;
3618 end if;
3619
22cb89b5
AC
3620 -- If we fall through, we have a node that cannot be interpreted as a
3621 -- compile time constant. That is definitely an error.
996ae0b0
RK
3622
3623 raise Program_Error;
3624 end Expr_Value_R;
3625
3626 ------------------
3627 -- Expr_Value_S --
3628 ------------------
3629
3630 function Expr_Value_S (N : Node_Id) return Node_Id is
3631 begin
3632 if Nkind (N) = N_String_Literal then
3633 return N;
3634 else
3635 pragma Assert (Ekind (Entity (N)) = E_Constant);
3636 return Expr_Value_S (Constant_Value (Entity (N)));
3637 end if;
3638 end Expr_Value_S;
3639
fbf5a39b
AC
3640 --------------------------
3641 -- Flag_Non_Static_Expr --
3642 --------------------------
3643
3644 procedure Flag_Non_Static_Expr (Msg : String; Expr : Node_Id) is
3645 begin
3646 if Error_Posted (Expr) and then not All_Errors_Mode then
3647 return;
3648 else
3649 Error_Msg_F (Msg, Expr);
3650 Why_Not_Static (Expr);
3651 end if;
3652 end Flag_Non_Static_Expr;
3653
996ae0b0
RK
3654 --------------
3655 -- Fold_Str --
3656 --------------
3657
fbf5a39b 3658 procedure Fold_Str (N : Node_Id; Val : String_Id; Static : Boolean) is
996ae0b0
RK
3659 Loc : constant Source_Ptr := Sloc (N);
3660 Typ : constant Entity_Id := Etype (N);
3661
3662 begin
3663 Rewrite (N, Make_String_Literal (Loc, Strval => Val));
fbf5a39b
AC
3664
3665 -- We now have the literal with the right value, both the actual type
3666 -- and the expected type of this literal are taken from the expression
3667 -- that was evaluated.
3668
3669 Analyze (N);
3670 Set_Is_Static_Expression (N, Static);
3671 Set_Etype (N, Typ);
3672 Resolve (N);
996ae0b0
RK
3673 end Fold_Str;
3674
3675 ---------------
3676 -- Fold_Uint --
3677 ---------------
3678
fbf5a39b 3679 procedure Fold_Uint (N : Node_Id; Val : Uint; Static : Boolean) is
996ae0b0 3680 Loc : constant Source_Ptr := Sloc (N);
fbf5a39b
AC
3681 Typ : Entity_Id := Etype (N);
3682 Ent : Entity_Id;
996ae0b0
RK
3683
3684 begin
22cb89b5
AC
3685 -- If we are folding a named number, retain the entity in the literal,
3686 -- for ASIS use.
fbf5a39b
AC
3687
3688 if Is_Entity_Name (N)
3689 and then Ekind (Entity (N)) = E_Named_Integer
3690 then
3691 Ent := Entity (N);
3692 else
3693 Ent := Empty;
3694 end if;
3695
3696 if Is_Private_Type (Typ) then
3697 Typ := Full_View (Typ);
3698 end if;
3699
f3d57416 3700 -- For a result of type integer, substitute an N_Integer_Literal node
996ae0b0 3701 -- for the result of the compile time evaluation of the expression.
cd2fb920
ES
3702 -- For ASIS use, set a link to the original named number when not in
3703 -- a generic context.
996ae0b0 3704
fbf5a39b 3705 if Is_Integer_Type (Typ) then
996ae0b0 3706 Rewrite (N, Make_Integer_Literal (Loc, Val));
cd2fb920 3707
fbf5a39b 3708 Set_Original_Entity (N, Ent);
996ae0b0
RK
3709
3710 -- Otherwise we have an enumeration type, and we substitute either
3711 -- an N_Identifier or N_Character_Literal to represent the enumeration
3712 -- literal corresponding to the given value, which must always be in
3713 -- range, because appropriate tests have already been made for this.
3714
fbf5a39b 3715 else pragma Assert (Is_Enumeration_Type (Typ));
996ae0b0
RK
3716 Rewrite (N, Get_Enum_Lit_From_Pos (Etype (N), Val, Loc));
3717 end if;
3718
3719 -- We now have the literal with the right value, both the actual type
3720 -- and the expected type of this literal are taken from the expression
3721 -- that was evaluated.
3722
3723 Analyze (N);
fbf5a39b 3724 Set_Is_Static_Expression (N, Static);
996ae0b0 3725 Set_Etype (N, Typ);
fbf5a39b 3726 Resolve (N);
996ae0b0
RK
3727 end Fold_Uint;
3728
3729 ----------------
3730 -- Fold_Ureal --
3731 ----------------
3732
fbf5a39b 3733 procedure Fold_Ureal (N : Node_Id; Val : Ureal; Static : Boolean) is
996ae0b0
RK
3734 Loc : constant Source_Ptr := Sloc (N);
3735 Typ : constant Entity_Id := Etype (N);
fbf5a39b 3736 Ent : Entity_Id;
996ae0b0
RK
3737
3738 begin
22cb89b5
AC
3739 -- If we are folding a named number, retain the entity in the literal,
3740 -- for ASIS use.
fbf5a39b
AC
3741
3742 if Is_Entity_Name (N)
3743 and then Ekind (Entity (N)) = E_Named_Real
3744 then
3745 Ent := Entity (N);
3746 else
3747 Ent := Empty;
3748 end if;
3749
996ae0b0 3750 Rewrite (N, Make_Real_Literal (Loc, Realval => Val));
cd2fb920 3751
5a30024a 3752 -- Set link to original named number, for ASIS use
cd2fb920 3753
fbf5a39b 3754 Set_Original_Entity (N, Ent);
996ae0b0
RK
3755
3756 -- Both the actual and expected type comes from the original expression
3757
fbf5a39b
AC
3758 Analyze (N);
3759 Set_Is_Static_Expression (N, Static);
996ae0b0 3760 Set_Etype (N, Typ);
fbf5a39b 3761 Resolve (N);
996ae0b0
RK
3762 end Fold_Ureal;
3763
3764 ---------------
3765 -- From_Bits --
3766 ---------------
3767
3768 function From_Bits (B : Bits; T : Entity_Id) return Uint is
3769 V : Uint := Uint_0;
3770
3771 begin
3772 for J in 0 .. B'Last loop
3773 if B (J) then
3774 V := V + 2 ** J;
3775 end if;
3776 end loop;
3777
3778 if Non_Binary_Modulus (T) then
3779 V := V mod Modulus (T);
3780 end if;
3781
3782 return V;
3783 end From_Bits;
3784
3785 --------------------
3786 -- Get_String_Val --
3787 --------------------
3788
3789 function Get_String_Val (N : Node_Id) return Node_Id is
3790 begin
3791 if Nkind (N) = N_String_Literal then
3792 return N;
3793
3794 elsif Nkind (N) = N_Character_Literal then
3795 return N;
3796
3797 else
3798 pragma Assert (Is_Entity_Name (N));
3799 return Get_String_Val (Constant_Value (Entity (N)));
3800 end if;
3801 end Get_String_Val;
3802
fbf5a39b
AC
3803 ----------------
3804 -- Initialize --
3805 ----------------
3806
3807 procedure Initialize is
3808 begin
3809 CV_Cache := (others => (Node_High_Bound, Uint_0));
3810 end Initialize;
3811
996ae0b0
RK
3812 --------------------
3813 -- In_Subrange_Of --
3814 --------------------
3815
3816 function In_Subrange_Of
c27f2f15
RD
3817 (T1 : Entity_Id;
3818 T2 : Entity_Id;
3819 Fixed_Int : Boolean := False) return Boolean
996ae0b0
RK
3820 is
3821 L1 : Node_Id;
3822 H1 : Node_Id;
3823
3824 L2 : Node_Id;
3825 H2 : Node_Id;
3826
3827 begin
3828 if T1 = T2 or else Is_Subtype_Of (T1, T2) then
3829 return True;
3830
3831 -- Never in range if both types are not scalar. Don't know if this can
3832 -- actually happen, but just in case.
3833
3834 elsif not Is_Scalar_Type (T1) or else not Is_Scalar_Type (T1) then
3835 return False;
3836
d79e621a
GD
3837 -- If T1 has infinities but T2 doesn't have infinities, then T1 is
3838 -- definitely not compatible with T2.
3839
3840 elsif Is_Floating_Point_Type (T1)
3841 and then Has_Infinities (T1)
3842 and then Is_Floating_Point_Type (T2)
3843 and then not Has_Infinities (T2)
3844 then
3845 return False;
3846
996ae0b0
RK
3847 else
3848 L1 := Type_Low_Bound (T1);
3849 H1 := Type_High_Bound (T1);
3850
3851 L2 := Type_Low_Bound (T2);
3852 H2 := Type_High_Bound (T2);
3853
3854 -- Check bounds to see if comparison possible at compile time
3855
c27f2f15 3856 if Compile_Time_Compare (L1, L2, Assume_Valid => True) in Compare_GE
996ae0b0 3857 and then
c27f2f15 3858 Compile_Time_Compare (H1, H2, Assume_Valid => True) in Compare_LE
996ae0b0
RK
3859 then
3860 return True;
3861 end if;
3862
3863 -- If bounds not comparable at compile time, then the bounds of T2
3864 -- must be compile time known or we cannot answer the query.
3865
3866 if not Compile_Time_Known_Value (L2)
3867 or else not Compile_Time_Known_Value (H2)
3868 then
3869 return False;
3870 end if;
3871
3872 -- If the bounds of T1 are know at compile time then use these
3873 -- ones, otherwise use the bounds of the base type (which are of
3874 -- course always static).
3875
3876 if not Compile_Time_Known_Value (L1) then
3877 L1 := Type_Low_Bound (Base_Type (T1));
3878 end if;
3879
3880 if not Compile_Time_Known_Value (H1) then
3881 H1 := Type_High_Bound (Base_Type (T1));
3882 end if;
3883
3884 -- Fixed point types should be considered as such only if
3885 -- flag Fixed_Int is set to False.
3886
3887 if Is_Floating_Point_Type (T1) or else Is_Floating_Point_Type (T2)
3888 or else (Is_Fixed_Point_Type (T1) and then not Fixed_Int)
3889 or else (Is_Fixed_Point_Type (T2) and then not Fixed_Int)
3890 then
3891 return
3892 Expr_Value_R (L2) <= Expr_Value_R (L1)
3893 and then
3894 Expr_Value_R (H2) >= Expr_Value_R (H1);
3895
3896 else
3897 return
3898 Expr_Value (L2) <= Expr_Value (L1)
3899 and then
3900 Expr_Value (H2) >= Expr_Value (H1);
3901
3902 end if;
3903 end if;
3904
3905 -- If any exception occurs, it means that we have some bug in the compiler
f3d57416 3906 -- possibly triggered by a previous error, or by some unforeseen peculiar
996ae0b0
RK
3907 -- occurrence. However, this is only an optimization attempt, so there is
3908 -- really no point in crashing the compiler. Instead we just decide, too
3909 -- bad, we can't figure out the answer in this case after all.
3910
3911 exception
3912 when others =>
3913
3914 -- Debug flag K disables this behavior (useful for debugging)
3915
3916 if Debug_Flag_K then
3917 raise;
3918 else
3919 return False;
3920 end if;
3921 end In_Subrange_Of;
3922
3923 -----------------
3924 -- Is_In_Range --
3925 -----------------
3926
3927 function Is_In_Range
c800f862
RD
3928 (N : Node_Id;
3929 Typ : Entity_Id;
3930 Assume_Valid : Boolean := False;
3931 Fixed_Int : Boolean := False;
3932 Int_Real : Boolean := False) return Boolean
996ae0b0 3933 is
996ae0b0 3934 begin
305caf42
AC
3935 return Test_In_Range (N, Typ, Assume_Valid, Fixed_Int, Int_Real)
3936 = In_Range;
996ae0b0
RK
3937 end Is_In_Range;
3938
3939 -------------------
3940 -- Is_Null_Range --
3941 -------------------
3942
3943 function Is_Null_Range (Lo : Node_Id; Hi : Node_Id) return Boolean is
3944 Typ : constant Entity_Id := Etype (Lo);
3945
3946 begin
3947 if not Compile_Time_Known_Value (Lo)
3948 or else not Compile_Time_Known_Value (Hi)
3949 then
3950 return False;
3951 end if;
3952
3953 if Is_Discrete_Type (Typ) then
3954 return Expr_Value (Lo) > Expr_Value (Hi);
3955
3956 else
3957 pragma Assert (Is_Real_Type (Typ));
3958 return Expr_Value_R (Lo) > Expr_Value_R (Hi);
3959 end if;
3960 end Is_Null_Range;
3961
3962 -----------------------------
3963 -- Is_OK_Static_Expression --
3964 -----------------------------
3965
3966 function Is_OK_Static_Expression (N : Node_Id) return Boolean is
3967 begin
3968 return Is_Static_Expression (N)
3969 and then not Raises_Constraint_Error (N);
3970 end Is_OK_Static_Expression;
3971
3972 ------------------------
3973 -- Is_OK_Static_Range --
3974 ------------------------
3975
3976 -- A static range is a range whose bounds are static expressions, or a
3977 -- Range_Attribute_Reference equivalent to such a range (RM 4.9(26)).
3978 -- We have already converted range attribute references, so we get the
3979 -- "or" part of this rule without needing a special test.
3980
3981 function Is_OK_Static_Range (N : Node_Id) return Boolean is
3982 begin
3983 return Is_OK_Static_Expression (Low_Bound (N))
3984 and then Is_OK_Static_Expression (High_Bound (N));
3985 end Is_OK_Static_Range;
3986
3987 --------------------------
3988 -- Is_OK_Static_Subtype --
3989 --------------------------
3990
22cb89b5
AC
3991 -- Determines if Typ is a static subtype as defined in (RM 4.9(26)) where
3992 -- neither bound raises constraint error when evaluated.
996ae0b0
RK
3993
3994 function Is_OK_Static_Subtype (Typ : Entity_Id) return Boolean is
3995 Base_T : constant Entity_Id := Base_Type (Typ);
3996 Anc_Subt : Entity_Id;
3997
3998 begin
3999 -- First a quick check on the non static subtype flag. As described
4000 -- in further detail in Einfo, this flag is not decisive in all cases,
4001 -- but if it is set, then the subtype is definitely non-static.
4002
4003 if Is_Non_Static_Subtype (Typ) then
4004 return False;
4005 end if;
4006
4007 Anc_Subt := Ancestor_Subtype (Typ);
4008
4009 if Anc_Subt = Empty then
4010 Anc_Subt := Base_T;
4011 end if;
4012
4013 if Is_Generic_Type (Root_Type (Base_T))
4014 or else Is_Generic_Actual_Type (Base_T)
4015 then
4016 return False;
4017
4018 -- String types
4019
4020 elsif Is_String_Type (Typ) then
4021 return
4022 Ekind (Typ) = E_String_Literal_Subtype
4023 or else
4024 (Is_OK_Static_Subtype (Component_Type (Typ))
4025 and then Is_OK_Static_Subtype (Etype (First_Index (Typ))));
4026
4027 -- Scalar types
4028
4029 elsif Is_Scalar_Type (Typ) then
4030 if Base_T = Typ then
4031 return True;
4032
4033 else
22cb89b5
AC
4034 -- Scalar_Range (Typ) might be an N_Subtype_Indication, so use
4035 -- Get_Type_{Low,High}_Bound.
996ae0b0
RK
4036
4037 return Is_OK_Static_Subtype (Anc_Subt)
4038 and then Is_OK_Static_Expression (Type_Low_Bound (Typ))
4039 and then Is_OK_Static_Expression (Type_High_Bound (Typ));
4040 end if;
4041
4042 -- Types other than string and scalar types are never static
4043
4044 else
4045 return False;
4046 end if;
4047 end Is_OK_Static_Subtype;
4048
4049 ---------------------
4050 -- Is_Out_Of_Range --
4051 ---------------------
4052
4053 function Is_Out_Of_Range
1c7717c3
AC
4054 (N : Node_Id;
4055 Typ : Entity_Id;
c800f862 4056 Assume_Valid : Boolean := False;
1c7717c3
AC
4057 Fixed_Int : Boolean := False;
4058 Int_Real : Boolean := False) return Boolean
996ae0b0 4059 is
996ae0b0 4060 begin
305caf42
AC
4061 return Test_In_Range (N, Typ, Assume_Valid, Fixed_Int, Int_Real)
4062 = Out_Of_Range;
996ae0b0
RK
4063 end Is_Out_Of_Range;
4064
4065 ---------------------
4066 -- Is_Static_Range --
4067 ---------------------
4068
4069 -- A static range is a range whose bounds are static expressions, or a
4070 -- Range_Attribute_Reference equivalent to such a range (RM 4.9(26)).
4071 -- We have already converted range attribute references, so we get the
4072 -- "or" part of this rule without needing a special test.
4073
4074 function Is_Static_Range (N : Node_Id) return Boolean is
4075 begin
4076 return Is_Static_Expression (Low_Bound (N))
4077 and then Is_Static_Expression (High_Bound (N));
4078 end Is_Static_Range;
4079
4080 -----------------------
4081 -- Is_Static_Subtype --
4082 -----------------------
4083
82c80734 4084 -- Determines if Typ is a static subtype as defined in (RM 4.9(26))
996ae0b0
RK
4085
4086 function Is_Static_Subtype (Typ : Entity_Id) return Boolean is
4087 Base_T : constant Entity_Id := Base_Type (Typ);
4088 Anc_Subt : Entity_Id;
4089
4090 begin
4091 -- First a quick check on the non static subtype flag. As described
4092 -- in further detail in Einfo, this flag is not decisive in all cases,
4093 -- but if it is set, then the subtype is definitely non-static.
4094
4095 if Is_Non_Static_Subtype (Typ) then
4096 return False;
4097 end if;
4098
4099 Anc_Subt := Ancestor_Subtype (Typ);
4100
4101 if Anc_Subt = Empty then
4102 Anc_Subt := Base_T;
4103 end if;
4104
4105 if Is_Generic_Type (Root_Type (Base_T))
4106 or else Is_Generic_Actual_Type (Base_T)
4107 then
4108 return False;
4109
4110 -- String types
4111
4112 elsif Is_String_Type (Typ) then
4113 return
4114 Ekind (Typ) = E_String_Literal_Subtype
4115 or else
4116 (Is_Static_Subtype (Component_Type (Typ))
4117 and then Is_Static_Subtype (Etype (First_Index (Typ))));
4118
4119 -- Scalar types
4120
4121 elsif Is_Scalar_Type (Typ) then
4122 if Base_T = Typ then
4123 return True;
4124
4125 else
4126 return Is_Static_Subtype (Anc_Subt)
4127 and then Is_Static_Expression (Type_Low_Bound (Typ))
4128 and then Is_Static_Expression (Type_High_Bound (Typ));
4129 end if;
4130
4131 -- Types other than string and scalar types are never static
4132
4133 else
4134 return False;
4135 end if;
4136 end Is_Static_Subtype;
4137
4138 --------------------
4139 -- Not_Null_Range --
4140 --------------------
4141
4142 function Not_Null_Range (Lo : Node_Id; Hi : Node_Id) return Boolean is
4143 Typ : constant Entity_Id := Etype (Lo);
4144
4145 begin
4146 if not Compile_Time_Known_Value (Lo)
4147 or else not Compile_Time_Known_Value (Hi)
4148 then
4149 return False;
4150 end if;
4151
4152 if Is_Discrete_Type (Typ) then
4153 return Expr_Value (Lo) <= Expr_Value (Hi);
4154
4155 else
4156 pragma Assert (Is_Real_Type (Typ));
4157
4158 return Expr_Value_R (Lo) <= Expr_Value_R (Hi);
4159 end if;
4160 end Not_Null_Range;
4161
4162 -------------
4163 -- OK_Bits --
4164 -------------
4165
4166 function OK_Bits (N : Node_Id; Bits : Uint) return Boolean is
4167 begin
4168 -- We allow a maximum of 500,000 bits which seems a reasonable limit
4169
4170 if Bits < 500_000 then
4171 return True;
4172
4173 else
4174 Error_Msg_N ("static value too large, capacity exceeded", N);
4175 return False;
4176 end if;
4177 end OK_Bits;
4178
4179 ------------------
4180 -- Out_Of_Range --
4181 ------------------
4182
4183 procedure Out_Of_Range (N : Node_Id) is
4184 begin
4185 -- If we have the static expression case, then this is an illegality
4186 -- in Ada 95 mode, except that in an instance, we never generate an
22cb89b5
AC
4187 -- error (if the error is legitimate, it was already diagnosed in the
4188 -- template). The expression to compute the length of a packed array is
4189 -- attached to the array type itself, and deserves a separate message.
996ae0b0
RK
4190
4191 if Is_Static_Expression (N)
4192 and then not In_Instance
fbf5a39b 4193 and then not In_Inlined_Body
0ab80019 4194 and then Ada_Version >= Ada_95
996ae0b0 4195 then
996ae0b0
RK
4196 if Nkind (Parent (N)) = N_Defining_Identifier
4197 and then Is_Array_Type (Parent (N))
4198 and then Present (Packed_Array_Type (Parent (N)))
4199 and then Present (First_Rep_Item (Parent (N)))
4200 then
4201 Error_Msg_N
4202 ("length of packed array must not exceed Integer''Last",
4203 First_Rep_Item (Parent (N)));
4204 Rewrite (N, Make_Integer_Literal (Sloc (N), Uint_1));
4205
4206 else
4207 Apply_Compile_Time_Constraint_Error
07fc65c4 4208 (N, "value not in range of}", CE_Range_Check_Failed);
996ae0b0
RK
4209 end if;
4210
22cb89b5
AC
4211 -- Here we generate a warning for the Ada 83 case, or when we are in an
4212 -- instance, or when we have a non-static expression case.
996ae0b0
RK
4213
4214 else
996ae0b0 4215 Apply_Compile_Time_Constraint_Error
07fc65c4 4216 (N, "value not in range of}?", CE_Range_Check_Failed);
996ae0b0
RK
4217 end if;
4218 end Out_Of_Range;
4219
4220 -------------------------
4221 -- Rewrite_In_Raise_CE --
4222 -------------------------
4223
4224 procedure Rewrite_In_Raise_CE (N : Node_Id; Exp : Node_Id) is
4225 Typ : constant Entity_Id := Etype (N);
4226
4227 begin
22cb89b5
AC
4228 -- If we want to raise CE in the condition of a N_Raise_CE node
4229 -- we may as well get rid of the condition.
996ae0b0
RK
4230
4231 if Present (Parent (N))
4232 and then Nkind (Parent (N)) = N_Raise_Constraint_Error
4233 then
4234 Set_Condition (Parent (N), Empty);
4235
22cb89b5
AC
4236 -- If the expression raising CE is a N_Raise_CE node, we can use that
4237 -- one. We just preserve the type of the context.
996ae0b0
RK
4238
4239 elsif Nkind (Exp) = N_Raise_Constraint_Error then
4240 Rewrite (N, Exp);
4241 Set_Etype (N, Typ);
4242
22cb89b5 4243 -- Else build an explcit N_Raise_CE
996ae0b0
RK
4244
4245 else
07fc65c4
GB
4246 Rewrite (N,
4247 Make_Raise_Constraint_Error (Sloc (Exp),
4248 Reason => CE_Range_Check_Failed));
996ae0b0
RK
4249 Set_Raises_Constraint_Error (N);
4250 Set_Etype (N, Typ);
4251 end if;
4252 end Rewrite_In_Raise_CE;
4253
4254 ---------------------
4255 -- String_Type_Len --
4256 ---------------------
4257
4258 function String_Type_Len (Stype : Entity_Id) return Uint is
4259 NT : constant Entity_Id := Etype (First_Index (Stype));
4260 T : Entity_Id;
4261
4262 begin
4263 if Is_OK_Static_Subtype (NT) then
4264 T := NT;
4265 else
4266 T := Base_Type (NT);
4267 end if;
4268
4269 return Expr_Value (Type_High_Bound (T)) -
4270 Expr_Value (Type_Low_Bound (T)) + 1;
4271 end String_Type_Len;
4272
4273 ------------------------------------
4274 -- Subtypes_Statically_Compatible --
4275 ------------------------------------
4276
4277 function Subtypes_Statically_Compatible
f44fe430
RD
4278 (T1 : Entity_Id;
4279 T2 : Entity_Id) return Boolean
996ae0b0
RK
4280 is
4281 begin
4282 if Is_Scalar_Type (T1) then
4283
4284 -- Definitely compatible if we match
4285
4286 if Subtypes_Statically_Match (T1, T2) then
4287 return True;
4288
4289 -- If either subtype is nonstatic then they're not compatible
4290
4291 elsif not Is_Static_Subtype (T1)
4292 or else not Is_Static_Subtype (T2)
4293 then
4294 return False;
4295
4296 -- If either type has constraint error bounds, then consider that
4297 -- they match to avoid junk cascaded errors here.
4298
4299 elsif not Is_OK_Static_Subtype (T1)
4300 or else not Is_OK_Static_Subtype (T2)
4301 then
4302 return True;
4303
4304 -- Base types must match, but we don't check that (should
4305 -- we???) but we do at least check that both types are
4306 -- real, or both types are not real.
4307
fbf5a39b 4308 elsif Is_Real_Type (T1) /= Is_Real_Type (T2) then
996ae0b0
RK
4309 return False;
4310
4311 -- Here we check the bounds
4312
4313 else
4314 declare
4315 LB1 : constant Node_Id := Type_Low_Bound (T1);
4316 HB1 : constant Node_Id := Type_High_Bound (T1);
4317 LB2 : constant Node_Id := Type_Low_Bound (T2);
4318 HB2 : constant Node_Id := Type_High_Bound (T2);
4319
4320 begin
4321 if Is_Real_Type (T1) then
4322 return
4323 (Expr_Value_R (LB1) > Expr_Value_R (HB1))
4324 or else
4325 (Expr_Value_R (LB2) <= Expr_Value_R (LB1)
4326 and then
4327 Expr_Value_R (HB1) <= Expr_Value_R (HB2));
4328
4329 else
4330 return
4331 (Expr_Value (LB1) > Expr_Value (HB1))
4332 or else
4333 (Expr_Value (LB2) <= Expr_Value (LB1)
4334 and then
4335 Expr_Value (HB1) <= Expr_Value (HB2));
4336 end if;
4337 end;
4338 end if;
4339
4340 elsif Is_Access_Type (T1) then
4341 return not Is_Constrained (T2)
4342 or else Subtypes_Statically_Match
4343 (Designated_Type (T1), Designated_Type (T2));
4344
4345 else
4346 return (Is_Composite_Type (T1) and then not Is_Constrained (T2))
4347 or else Subtypes_Statically_Match (T1, T2);
4348 end if;
4349 end Subtypes_Statically_Compatible;
4350
4351 -------------------------------
4352 -- Subtypes_Statically_Match --
4353 -------------------------------
4354
4355 -- Subtypes statically match if they have statically matching constraints
4356 -- (RM 4.9.1(2)). Constraints statically match if there are none, or if
4357 -- they are the same identical constraint, or if they are static and the
4358 -- values match (RM 4.9.1(1)).
4359
4360 function Subtypes_Statically_Match (T1, T2 : Entity_Id) return Boolean is
4361 begin
4362 -- A type always statically matches itself
4363
4364 if T1 = T2 then
4365 return True;
4366
4367 -- Scalar types
4368
4369 elsif Is_Scalar_Type (T1) then
4370
4371 -- Base types must be the same
4372
4373 if Base_Type (T1) /= Base_Type (T2) then
4374 return False;
4375 end if;
4376
4377 -- A constrained numeric subtype never matches an unconstrained
4378 -- subtype, i.e. both types must be constrained or unconstrained.
4379
305caf42
AC
4380 -- To understand the requirement for this test, see RM 4.9.1(1).
4381 -- As is made clear in RM 3.5.4(11), type Integer, for example is
4382 -- a constrained subtype with constraint bounds matching the bounds
4383 -- of its corresponding unconstrained base type. In this situation,
4384 -- Integer and Integer'Base do not statically match, even though
4385 -- they have the same bounds.
996ae0b0 4386
22cb89b5
AC
4387 -- We only apply this test to types in Standard and types that appear
4388 -- in user programs. That way, we do not have to be too careful about
4389 -- setting Is_Constrained right for Itypes.
996ae0b0
RK
4390
4391 if Is_Numeric_Type (T1)
4392 and then (Is_Constrained (T1) /= Is_Constrained (T2))
4393 and then (Scope (T1) = Standard_Standard
4394 or else Comes_From_Source (T1))
4395 and then (Scope (T2) = Standard_Standard
4396 or else Comes_From_Source (T2))
4397 then
4398 return False;
82c80734 4399
22cb89b5
AC
4400 -- A generic scalar type does not statically match its base type
4401 -- (AI-311). In this case we make sure that the formals, which are
4402 -- first subtypes of their bases, are constrained.
82c80734
RD
4403
4404 elsif Is_Generic_Type (T1)
4405 and then Is_Generic_Type (T2)
4406 and then (Is_Constrained (T1) /= Is_Constrained (T2))
4407 then
4408 return False;
996ae0b0
RK
4409 end if;
4410
22cb89b5
AC
4411 -- If there was an error in either range, then just assume the types
4412 -- statically match to avoid further junk errors.
996ae0b0
RK
4413
4414 if Error_Posted (Scalar_Range (T1))
4415 or else
4416 Error_Posted (Scalar_Range (T2))
4417 then
4418 return True;
4419 end if;
4420
4421 -- Otherwise both types have bound that can be compared
4422
4423 declare
4424 LB1 : constant Node_Id := Type_Low_Bound (T1);
4425 HB1 : constant Node_Id := Type_High_Bound (T1);
4426 LB2 : constant Node_Id := Type_Low_Bound (T2);
4427 HB2 : constant Node_Id := Type_High_Bound (T2);
4428
4429 begin
4430 -- If the bounds are the same tree node, then match
4431
4432 if LB1 = LB2 and then HB1 = HB2 then
4433 return True;
4434
4435 -- Otherwise bounds must be static and identical value
4436
4437 else
4438 if not Is_Static_Subtype (T1)
4439 or else not Is_Static_Subtype (T2)
4440 then
4441 return False;
4442
22cb89b5
AC
4443 -- If either type has constraint error bounds, then say that
4444 -- they match to avoid junk cascaded errors here.
996ae0b0
RK
4445
4446 elsif not Is_OK_Static_Subtype (T1)
4447 or else not Is_OK_Static_Subtype (T2)
4448 then
4449 return True;
4450
4451 elsif Is_Real_Type (T1) then
4452 return
4453 (Expr_Value_R (LB1) = Expr_Value_R (LB2))
4454 and then
4455 (Expr_Value_R (HB1) = Expr_Value_R (HB2));
4456
4457 else
4458 return
4459 Expr_Value (LB1) = Expr_Value (LB2)
4460 and then
4461 Expr_Value (HB1) = Expr_Value (HB2);
4462 end if;
4463 end if;
4464 end;
4465
4466 -- Type with discriminants
4467
4468 elsif Has_Discriminants (T1) or else Has_Discriminants (T2) then
6eaf4095 4469
c2bf339e
GD
4470 -- Because of view exchanges in multiple instantiations, conformance
4471 -- checking might try to match a partial view of a type with no
4472 -- discriminants with a full view that has defaulted discriminants.
4473 -- In such a case, use the discriminant constraint of the full view,
4474 -- which must exist because we know that the two subtypes have the
4475 -- same base type.
6eaf4095 4476
996ae0b0 4477 if Has_Discriminants (T1) /= Has_Discriminants (T2) then
c2bf339e
GD
4478 if In_Instance then
4479 if Is_Private_Type (T2)
4480 and then Present (Full_View (T2))
4481 and then Has_Discriminants (Full_View (T2))
4482 then
4483 return Subtypes_Statically_Match (T1, Full_View (T2));
4484
4485 elsif Is_Private_Type (T1)
4486 and then Present (Full_View (T1))
4487 and then Has_Discriminants (Full_View (T1))
4488 then
4489 return Subtypes_Statically_Match (Full_View (T1), T2);
4490
4491 else
4492 return False;
4493 end if;
6eaf4095
ES
4494 else
4495 return False;
4496 end if;
996ae0b0
RK
4497 end if;
4498
4499 declare
4500 DL1 : constant Elist_Id := Discriminant_Constraint (T1);
4501 DL2 : constant Elist_Id := Discriminant_Constraint (T2);
4502
13f34a3f
RD
4503 DA1 : Elmt_Id;
4504 DA2 : Elmt_Id;
996ae0b0
RK
4505
4506 begin
4507 if DL1 = DL2 then
4508 return True;
996ae0b0
RK
4509 elsif Is_Constrained (T1) /= Is_Constrained (T2) then
4510 return False;
4511 end if;
4512
13f34a3f 4513 -- Now loop through the discriminant constraints
996ae0b0 4514
13f34a3f
RD
4515 -- Note: the guard here seems necessary, since it is possible at
4516 -- least for DL1 to be No_Elist. Not clear this is reasonable ???
996ae0b0 4517
13f34a3f
RD
4518 if Present (DL1) and then Present (DL2) then
4519 DA1 := First_Elmt (DL1);
4520 DA2 := First_Elmt (DL2);
4521 while Present (DA1) loop
4522 declare
4523 Expr1 : constant Node_Id := Node (DA1);
4524 Expr2 : constant Node_Id := Node (DA2);
996ae0b0 4525
13f34a3f
RD
4526 begin
4527 if not Is_Static_Expression (Expr1)
4528 or else not Is_Static_Expression (Expr2)
4529 then
4530 return False;
996ae0b0 4531
13f34a3f
RD
4532 -- If either expression raised a constraint error,
4533 -- consider the expressions as matching, since this
4534 -- helps to prevent cascading errors.
4535
4536 elsif Raises_Constraint_Error (Expr1)
4537 or else Raises_Constraint_Error (Expr2)
4538 then
4539 null;
4540
4541 elsif Expr_Value (Expr1) /= Expr_Value (Expr2) then
4542 return False;
4543 end if;
4544 end;
996ae0b0 4545
13f34a3f
RD
4546 Next_Elmt (DA1);
4547 Next_Elmt (DA2);
4548 end loop;
4549 end if;
996ae0b0
RK
4550 end;
4551
4552 return True;
4553
22cb89b5 4554 -- A definite type does not match an indefinite or classwide type.
0356699b
RD
4555 -- However, a generic type with unknown discriminants may be
4556 -- instantiated with a type with no discriminants, and conformance
22cb89b5
AC
4557 -- checking on an inherited operation may compare the actual with the
4558 -- subtype that renames it in the instance.
996ae0b0
RK
4559
4560 elsif
4561 Has_Unknown_Discriminants (T1) /= Has_Unknown_Discriminants (T2)
4562 then
7a3f77d2
AC
4563 return
4564 Is_Generic_Actual_Type (T1) or else Is_Generic_Actual_Type (T2);
996ae0b0
RK
4565
4566 -- Array type
4567
4568 elsif Is_Array_Type (T1) then
4569
22cb89b5
AC
4570 -- If either subtype is unconstrained then both must be, and if both
4571 -- are unconstrained then no further checking is neede.
996ae0b0
RK
4572
4573 if not Is_Constrained (T1) or else not Is_Constrained (T2) then
4574 return not (Is_Constrained (T1) or else Is_Constrained (T2));
4575 end if;
4576
22cb89b5
AC
4577 -- Both subtypes are constrained, so check that the index subtypes
4578 -- statically match.
996ae0b0
RK
4579
4580 declare
4581 Index1 : Node_Id := First_Index (T1);
4582 Index2 : Node_Id := First_Index (T2);
4583
4584 begin
4585 while Present (Index1) loop
4586 if not
4587 Subtypes_Statically_Match (Etype (Index1), Etype (Index2))
4588 then
4589 return False;
4590 end if;
4591
4592 Next_Index (Index1);
4593 Next_Index (Index2);
4594 end loop;
4595
4596 return True;
4597 end;
4598
4599 elsif Is_Access_Type (T1) then
b5bd964f
ES
4600 if Can_Never_Be_Null (T1) /= Can_Never_Be_Null (T2) then
4601 return False;
4602
e1b871e9
AC
4603 elsif Ekind_In (T1, E_Access_Subprogram_Type,
4604 E_Anonymous_Access_Subprogram_Type)
7a3f77d2 4605 then
b5bd964f
ES
4606 return
4607 Subtype_Conformant
4608 (Designated_Type (T1),
bb98fe75 4609 Designated_Type (T2));
b5bd964f
ES
4610 else
4611 return
4612 Subtypes_Statically_Match
4613 (Designated_Type (T1),
4614 Designated_Type (T2))
4615 and then Is_Access_Constant (T1) = Is_Access_Constant (T2);
4616 end if;
996ae0b0
RK
4617
4618 -- All other types definitely match
4619
4620 else
4621 return True;
4622 end if;
4623 end Subtypes_Statically_Match;
4624
4625 ----------
4626 -- Test --
4627 ----------
4628
4629 function Test (Cond : Boolean) return Uint is
4630 begin
4631 if Cond then
4632 return Uint_1;
4633 else
4634 return Uint_0;
4635 end if;
4636 end Test;
4637
4638 ---------------------------------
4639 -- Test_Expression_Is_Foldable --
4640 ---------------------------------
4641
4642 -- One operand case
4643
4644 procedure Test_Expression_Is_Foldable
4645 (N : Node_Id;
4646 Op1 : Node_Id;
4647 Stat : out Boolean;
4648 Fold : out Boolean)
4649 is
4650 begin
4651 Stat := False;
0356699b
RD
4652 Fold := False;
4653
4654 if Debug_Flag_Dot_F and then In_Extended_Main_Source_Unit (N) then
4655 return;
4656 end if;
996ae0b0
RK
4657
4658 -- If operand is Any_Type, just propagate to result and do not
4659 -- try to fold, this prevents cascaded errors.
4660
4661 if Etype (Op1) = Any_Type then
4662 Set_Etype (N, Any_Type);
996ae0b0
RK
4663 return;
4664
4665 -- If operand raises constraint error, then replace node N with the
4666 -- raise constraint error node, and we are obviously not foldable.
4667 -- Note that this replacement inherits the Is_Static_Expression flag
4668 -- from the operand.
4669
4670 elsif Raises_Constraint_Error (Op1) then
4671 Rewrite_In_Raise_CE (N, Op1);
996ae0b0
RK
4672 return;
4673
4674 -- If the operand is not static, then the result is not static, and
4675 -- all we have to do is to check the operand since it is now known
4676 -- to appear in a non-static context.
4677
4678 elsif not Is_Static_Expression (Op1) then
4679 Check_Non_Static_Context (Op1);
4680 Fold := Compile_Time_Known_Value (Op1);
4681 return;
4682
4683 -- An expression of a formal modular type is not foldable because
4684 -- the modulus is unknown.
4685
4686 elsif Is_Modular_Integer_Type (Etype (Op1))
4687 and then Is_Generic_Type (Etype (Op1))
4688 then
4689 Check_Non_Static_Context (Op1);
996ae0b0
RK
4690 return;
4691
4692 -- Here we have the case of an operand whose type is OK, which is
4693 -- static, and which does not raise constraint error, we can fold.
4694
4695 else
4696 Set_Is_Static_Expression (N);
4697 Fold := True;
4698 Stat := True;
4699 end if;
4700 end Test_Expression_Is_Foldable;
4701
4702 -- Two operand case
4703
4704 procedure Test_Expression_Is_Foldable
4705 (N : Node_Id;
4706 Op1 : Node_Id;
4707 Op2 : Node_Id;
4708 Stat : out Boolean;
4709 Fold : out Boolean)
4710 is
4711 Rstat : constant Boolean := Is_Static_Expression (Op1)
4712 and then Is_Static_Expression (Op2);
4713
4714 begin
4715 Stat := False;
0356699b
RD
4716 Fold := False;
4717
4718 if Debug_Flag_Dot_F and then In_Extended_Main_Source_Unit (N) then
4719 return;
4720 end if;
996ae0b0
RK
4721
4722 -- If either operand is Any_Type, just propagate to result and
4723 -- do not try to fold, this prevents cascaded errors.
4724
4725 if Etype (Op1) = Any_Type or else Etype (Op2) = Any_Type then
4726 Set_Etype (N, Any_Type);
996ae0b0
RK
4727 return;
4728
22cb89b5
AC
4729 -- If left operand raises constraint error, then replace node N with the
4730 -- Raise_Constraint_Error node, and we are obviously not foldable.
996ae0b0
RK
4731 -- Is_Static_Expression is set from the two operands in the normal way,
4732 -- and we check the right operand if it is in a non-static context.
4733
4734 elsif Raises_Constraint_Error (Op1) then
4735 if not Rstat then
4736 Check_Non_Static_Context (Op2);
4737 end if;
4738
4739 Rewrite_In_Raise_CE (N, Op1);
4740 Set_Is_Static_Expression (N, Rstat);
996ae0b0
RK
4741 return;
4742
22cb89b5
AC
4743 -- Similar processing for the case of the right operand. Note that we
4744 -- don't use this routine for the short-circuit case, so we do not have
4745 -- to worry about that special case here.
996ae0b0
RK
4746
4747 elsif Raises_Constraint_Error (Op2) then
4748 if not Rstat then
4749 Check_Non_Static_Context (Op1);
4750 end if;
4751
4752 Rewrite_In_Raise_CE (N, Op2);
4753 Set_Is_Static_Expression (N, Rstat);
996ae0b0
RK
4754 return;
4755
82c80734 4756 -- Exclude expressions of a generic modular type, as above
996ae0b0
RK
4757
4758 elsif Is_Modular_Integer_Type (Etype (Op1))
4759 and then Is_Generic_Type (Etype (Op1))
4760 then
4761 Check_Non_Static_Context (Op1);
996ae0b0
RK
4762 return;
4763
4764 -- If result is not static, then check non-static contexts on operands
22cb89b5 4765 -- since one of them may be static and the other one may not be static.
996ae0b0
RK
4766
4767 elsif not Rstat then
4768 Check_Non_Static_Context (Op1);
4769 Check_Non_Static_Context (Op2);
4770 Fold := Compile_Time_Known_Value (Op1)
4771 and then Compile_Time_Known_Value (Op2);
4772 return;
4773
22cb89b5
AC
4774 -- Else result is static and foldable. Both operands are static, and
4775 -- neither raises constraint error, so we can definitely fold.
996ae0b0
RK
4776
4777 else
4778 Set_Is_Static_Expression (N);
4779 Fold := True;
4780 Stat := True;
4781 return;
4782 end if;
4783 end Test_Expression_Is_Foldable;
4784
305caf42
AC
4785 -------------------
4786 -- Test_In_Range --
4787 -------------------
4788
4789 function Test_In_Range
4790 (N : Node_Id;
4791 Typ : Entity_Id;
4792 Assume_Valid : Boolean;
4793 Fixed_Int : Boolean;
4794 Int_Real : Boolean) return Range_Membership
4795 is
4796 Val : Uint;
4797 Valr : Ureal;
4798
4799 pragma Warnings (Off, Assume_Valid);
4800 -- For now Assume_Valid is unreferenced since the current implementation
4801 -- always returns Unknown if N is not a compile time known value, but we
4802 -- keep the parameter to allow for future enhancements in which we try
4803 -- to get the information in the variable case as well.
4804
4805 begin
4806 -- Universal types have no range limits, so always in range
4807
4808 if Typ = Universal_Integer or else Typ = Universal_Real then
4809 return In_Range;
4810
4811 -- Never known if not scalar type. Don't know if this can actually
4812 -- happen, but our spec allows it, so we must check!
4813
4814 elsif not Is_Scalar_Type (Typ) then
4815 return Unknown;
4816
4817 -- Never known if this is a generic type, since the bounds of generic
4818 -- types are junk. Note that if we only checked for static expressions
4819 -- (instead of compile time known values) below, we would not need this
4820 -- check, because values of a generic type can never be static, but they
4821 -- can be known at compile time.
4822
4823 elsif Is_Generic_Type (Typ) then
4824 return Unknown;
4825
4826 -- Never known unless we have a compile time known value
4827
4828 elsif not Compile_Time_Known_Value (N) then
4829 return Unknown;
4830
4831 -- General processing with a known compile time value
4832
4833 else
4834 declare
4835 Lo : Node_Id;
4836 Hi : Node_Id;
4837
4838 LB_Known : Boolean;
4839 HB_Known : Boolean;
4840
4841 begin
4842 Lo := Type_Low_Bound (Typ);
4843 Hi := Type_High_Bound (Typ);
4844
4845 LB_Known := Compile_Time_Known_Value (Lo);
4846 HB_Known := Compile_Time_Known_Value (Hi);
4847
4848 -- Fixed point types should be considered as such only if flag
4849 -- Fixed_Int is set to False.
4850
4851 if Is_Floating_Point_Type (Typ)
4852 or else (Is_Fixed_Point_Type (Typ) and then not Fixed_Int)
4853 or else Int_Real
4854 then
4855 Valr := Expr_Value_R (N);
4856
4857 if LB_Known and HB_Known then
4858 if Valr >= Expr_Value_R (Lo)
4859 and then
4860 Valr <= Expr_Value_R (Hi)
4861 then
4862 return In_Range;
4863 else
4864 return Out_Of_Range;
4865 end if;
4866
4867 elsif (LB_Known and then Valr < Expr_Value_R (Lo))
4868 or else
4869 (HB_Known and then Valr > Expr_Value_R (Hi))
4870 then
4871 return Out_Of_Range;
4872
4873 else
4874 return Unknown;
4875 end if;
4876
4877 else
4878 Val := Expr_Value (N);
4879
4880 if LB_Known and HB_Known then
4881 if Val >= Expr_Value (Lo)
4882 and then
4883 Val <= Expr_Value (Hi)
4884 then
4885 return In_Range;
4886 else
4887 return Out_Of_Range;
4888 end if;
4889
4890 elsif (LB_Known and then Val < Expr_Value (Lo))
4891 or else
4892 (HB_Known and then Val > Expr_Value (Hi))
4893 then
4894 return Out_Of_Range;
4895
4896 else
4897 return Unknown;
4898 end if;
4899 end if;
4900 end;
4901 end if;
4902 end Test_In_Range;
4903
996ae0b0
RK
4904 --------------
4905 -- To_Bits --
4906 --------------
4907
4908 procedure To_Bits (U : Uint; B : out Bits) is
4909 begin
4910 for J in 0 .. B'Last loop
4911 B (J) := (U / (2 ** J)) mod 2 /= 0;
4912 end loop;
4913 end To_Bits;
4914
fbf5a39b
AC
4915 --------------------
4916 -- Why_Not_Static --
4917 --------------------
4918
4919 procedure Why_Not_Static (Expr : Node_Id) is
4920 N : constant Node_Id := Original_Node (Expr);
4921 Typ : Entity_Id;
4922 E : Entity_Id;
4923
4924 procedure Why_Not_Static_List (L : List_Id);
22cb89b5
AC
4925 -- A version that can be called on a list of expressions. Finds all
4926 -- non-static violations in any element of the list.
fbf5a39b
AC
4927
4928 -------------------------
4929 -- Why_Not_Static_List --
4930 -------------------------
4931
4932 procedure Why_Not_Static_List (L : List_Id) is
4933 N : Node_Id;
4934
4935 begin
4936 if Is_Non_Empty_List (L) then
4937 N := First (L);
4938 while Present (N) loop
4939 Why_Not_Static (N);
4940 Next (N);
4941 end loop;
4942 end if;
4943 end Why_Not_Static_List;
4944
4945 -- Start of processing for Why_Not_Static
4946
4947 begin
22cb89b5
AC
4948 -- If in ACATS mode (debug flag 2), then suppress all these messages,
4949 -- this avoids massive updates to the ACATS base line.
fbf5a39b
AC
4950
4951 if Debug_Flag_2 then
4952 return;
4953 end if;
4954
4955 -- Ignore call on error or empty node
4956
4957 if No (Expr) or else Nkind (Expr) = N_Error then
4958 return;
4959 end if;
4960
4961 -- Preprocessing for sub expressions
4962
4963 if Nkind (Expr) in N_Subexpr then
4964
4965 -- Nothing to do if expression is static
4966
4967 if Is_OK_Static_Expression (Expr) then
4968 return;
4969 end if;
4970
4971 -- Test for constraint error raised
4972
4973 if Raises_Constraint_Error (Expr) then
4974 Error_Msg_N
4975 ("expression raises exception, cannot be static " &
b11e8d6f 4976 "(RM 4.9(34))!", N);
fbf5a39b
AC
4977 return;
4978 end if;
4979
4980 -- If no type, then something is pretty wrong, so ignore
4981
4982 Typ := Etype (Expr);
4983
4984 if No (Typ) then
4985 return;
4986 end if;
4987
4988 -- Type must be scalar or string type
4989
4990 if not Is_Scalar_Type (Typ)
4991 and then not Is_String_Type (Typ)
4992 then
4993 Error_Msg_N
4994 ("static expression must have scalar or string type " &
b11e8d6f 4995 "(RM 4.9(2))!", N);
fbf5a39b
AC
4996 return;
4997 end if;
4998 end if;
4999
5000 -- If we got through those checks, test particular node kind
5001
5002 case Nkind (N) is
5003 when N_Expanded_Name | N_Identifier | N_Operator_Symbol =>
5004 E := Entity (N);
5005
5006 if Is_Named_Number (E) then
5007 null;
5008
5009 elsif Ekind (E) = E_Constant then
5010 if not Is_Static_Expression (Constant_Value (E)) then
5011 Error_Msg_NE
b11e8d6f 5012 ("& is not a static constant (RM 4.9(5))!", N, E);
fbf5a39b
AC
5013 end if;
5014
5015 else
5016 Error_Msg_NE
5017 ("& is not static constant or named number " &
b11e8d6f 5018 "(RM 4.9(5))!", N, E);
fbf5a39b
AC
5019 end if;
5020
514d0fc5 5021 when N_Binary_Op | N_Short_Circuit | N_Membership_Test =>
fbf5a39b
AC
5022 if Nkind (N) in N_Op_Shift then
5023 Error_Msg_N
b11e8d6f 5024 ("shift functions are never static (RM 4.9(6,18))!", N);
fbf5a39b
AC
5025
5026 else
5027 Why_Not_Static (Left_Opnd (N));
5028 Why_Not_Static (Right_Opnd (N));
5029 end if;
5030
5031 when N_Unary_Op =>
5032 Why_Not_Static (Right_Opnd (N));
5033
5034 when N_Attribute_Reference =>
5035 Why_Not_Static_List (Expressions (N));
5036
5037 E := Etype (Prefix (N));
5038
5039 if E = Standard_Void_Type then
5040 return;
5041 end if;
5042
5043 -- Special case non-scalar'Size since this is a common error
5044
5045 if Attribute_Name (N) = Name_Size then
5046 Error_Msg_N
fdfea49e 5047 ("size attribute is only static for static scalar type " &
b11e8d6f 5048 "(RM 4.9(7,8))", N);
fbf5a39b
AC
5049
5050 -- Flag array cases
5051
5052 elsif Is_Array_Type (E) then
5053 if Attribute_Name (N) /= Name_First
5054 and then
5055 Attribute_Name (N) /= Name_Last
5056 and then
5057 Attribute_Name (N) /= Name_Length
5058 then
5059 Error_Msg_N
5060 ("static array attribute must be Length, First, or Last " &
b11e8d6f 5061 "(RM 4.9(8))!", N);
fbf5a39b
AC
5062
5063 -- Since we know the expression is not-static (we already
5064 -- tested for this, must mean array is not static).
5065
5066 else
5067 Error_Msg_N
b11e8d6f 5068 ("prefix is non-static array (RM 4.9(8))!", Prefix (N));
fbf5a39b
AC
5069 end if;
5070
5071 return;
5072
22cb89b5
AC
5073 -- Special case generic types, since again this is a common source
5074 -- of confusion.
fbf5a39b
AC
5075
5076 elsif Is_Generic_Actual_Type (E)
5077 or else
5078 Is_Generic_Type (E)
5079 then
5080 Error_Msg_N
5081 ("attribute of generic type is never static " &
b11e8d6f 5082 "(RM 4.9(7,8))!", N);
fbf5a39b
AC
5083
5084 elsif Is_Static_Subtype (E) then
5085 null;
5086
5087 elsif Is_Scalar_Type (E) then
5088 Error_Msg_N
5089 ("prefix type for attribute is not static scalar subtype " &
b11e8d6f 5090 "(RM 4.9(7))!", N);
fbf5a39b
AC
5091
5092 else
5093 Error_Msg_N
5094 ("static attribute must apply to array/scalar type " &
b11e8d6f 5095 "(RM 4.9(7,8))!", N);
fbf5a39b
AC
5096 end if;
5097
5098 when N_String_Literal =>
5099 Error_Msg_N
b11e8d6f 5100 ("subtype of string literal is non-static (RM 4.9(4))!", N);
fbf5a39b
AC
5101
5102 when N_Explicit_Dereference =>
5103 Error_Msg_N
b11e8d6f 5104 ("explicit dereference is never static (RM 4.9)!", N);
fbf5a39b
AC
5105
5106 when N_Function_Call =>
5107 Why_Not_Static_List (Parameter_Associations (N));
b11e8d6f 5108 Error_Msg_N ("non-static function call (RM 4.9(6,18))!", N);
fbf5a39b
AC
5109
5110 when N_Parameter_Association =>
5111 Why_Not_Static (Explicit_Actual_Parameter (N));
5112
5113 when N_Indexed_Component =>
5114 Error_Msg_N
b11e8d6f 5115 ("indexed component is never static (RM 4.9)!", N);
fbf5a39b
AC
5116
5117 when N_Procedure_Call_Statement =>
5118 Error_Msg_N
b11e8d6f 5119 ("procedure call is never static (RM 4.9)!", N);
fbf5a39b
AC
5120
5121 when N_Qualified_Expression =>
5122 Why_Not_Static (Expression (N));
5123
5124 when N_Aggregate | N_Extension_Aggregate =>
5125 Error_Msg_N
b11e8d6f 5126 ("an aggregate is never static (RM 4.9)!", N);
fbf5a39b
AC
5127
5128 when N_Range =>
5129 Why_Not_Static (Low_Bound (N));
5130 Why_Not_Static (High_Bound (N));
5131
5132 when N_Range_Constraint =>
5133 Why_Not_Static (Range_Expression (N));
5134
5135 when N_Subtype_Indication =>
5136 Why_Not_Static (Constraint (N));
5137
5138 when N_Selected_Component =>
5139 Error_Msg_N
b11e8d6f 5140 ("selected component is never static (RM 4.9)!", N);
fbf5a39b
AC
5141
5142 when N_Slice =>
5143 Error_Msg_N
b11e8d6f 5144 ("slice is never static (RM 4.9)!", N);
fbf5a39b
AC
5145
5146 when N_Type_Conversion =>
5147 Why_Not_Static (Expression (N));
5148
5149 if not Is_Scalar_Type (Etype (Prefix (N)))
5150 or else not Is_Static_Subtype (Etype (Prefix (N)))
5151 then
5152 Error_Msg_N
5153 ("static conversion requires static scalar subtype result " &
b11e8d6f 5154 "(RM 4.9(9))!", N);
fbf5a39b
AC
5155 end if;
5156
5157 when N_Unchecked_Type_Conversion =>
5158 Error_Msg_N
b11e8d6f 5159 ("unchecked type conversion is never static (RM 4.9)!", N);
fbf5a39b
AC
5160
5161 when others =>
5162 null;
5163
5164 end case;
5165 end Why_Not_Static;
5166
996ae0b0 5167end Sem_Eval;
This page took 2.997342 seconds and 5 git commands to generate.