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