]> git.ipfire.org Git - thirdparty/gcc.git/blame - gcc/ada/sem_eval.adb
expr.c (expand_expr): Use unsave lang hook.
[thirdparty/gcc.git] / gcc / ada / sem_eval.adb
CommitLineData
996ae0b0
RK
1------------------------------------------------------------------------------
2-- --
3-- GNAT COMPILER COMPONENTS --
4-- --
5-- S E M _ E V A L --
6-- --
7-- B o d y --
8-- --
c3de5c4c 9-- $Revision$
996ae0b0
RK
10-- --
11-- Copyright (C) 1992-2001 Free Software Foundation, Inc. --
12-- --
13-- GNAT is free software; you can redistribute it and/or modify it under --
14-- terms of the GNU General Public License as published by the Free Soft- --
15-- ware Foundation; either version 2, or (at your option) any later ver- --
16-- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
17-- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
18-- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
19-- for more details. You should have received a copy of the GNU General --
20-- Public License distributed with GNAT; see file COPYING. If not, write --
21-- to the Free Software Foundation, 59 Temple Place - Suite 330, Boston, --
22-- MA 02111-1307, USA. --
23-- --
24-- GNAT was originally developed by the GNAT team at New York University. --
25-- It is now maintained by Ada Core Technologies Inc (http://www.gnat.com). --
26-- --
27------------------------------------------------------------------------------
28
29with Atree; use Atree;
30with Checks; use Checks;
31with Debug; use Debug;
32with Einfo; use Einfo;
33with Elists; use Elists;
34with Errout; use Errout;
35with Eval_Fat; use Eval_Fat;
36with Nmake; use Nmake;
37with Nlists; use Nlists;
38with Opt; use Opt;
39with Sem; use Sem;
40with Sem_Cat; use Sem_Cat;
41with Sem_Ch8; use Sem_Ch8;
42with Sem_Res; use Sem_Res;
43with Sem_Util; use Sem_Util;
44with Sem_Type; use Sem_Type;
45with Sem_Warn; use Sem_Warn;
46with Sinfo; use Sinfo;
47with Snames; use Snames;
48with Stand; use Stand;
49with Stringt; use Stringt;
50
51package body Sem_Eval is
52
53 -----------------------------------------
54 -- Handling of Compile Time Evaluation --
55 -----------------------------------------
56
57 -- The compile time evaluation of expressions is distributed over several
58 -- Eval_xxx procedures. These procedures are called immediatedly after
59 -- a subexpression is resolved and is therefore accomplished in a bottom
60 -- up fashion. The flags are synthesized using the following approach.
61
62 -- Is_Static_Expression is determined by following the detailed rules
63 -- in RM 4.9(4-14). This involves testing the Is_Static_Expression
64 -- flag of the operands in many cases.
65
66 -- Raises_Constraint_Error is set if any of the operands have the flag
67 -- set or if an attempt to compute the value of the current expression
68 -- results in detection of a runtime constraint error.
69
70 -- As described in the spec, the requirement is that Is_Static_Expression
71 -- be accurately set, and in addition for nodes for which this flag is set,
72 -- Raises_Constraint_Error must also be set. Furthermore a node which has
73 -- Is_Static_Expression set, and Raises_Constraint_Error clear, then the
74 -- requirement is that the expression value must be precomputed, and the
75 -- node is either a literal, or the name of a constant entity whose value
76 -- is a static expression.
77
78 -- The general approach is as follows. First compute Is_Static_Expression.
79 -- If the node is not static, then the flag is left off in the node and
80 -- we are all done. Otherwise for a static node, we test if any of the
81 -- operands will raise constraint error, and if so, propagate the flag
82 -- Raises_Constraint_Error to the result node and we are done (since the
83 -- error was already posted at a lower level).
84
85 -- For the case of a static node whose operands do not raise constraint
86 -- error, we attempt to evaluate the node. If this evaluation succeeds,
87 -- then the node is replaced by the result of this computation. If the
88 -- evaluation raises constraint error, then we rewrite the node with
89 -- Apply_Compile_Time_Constraint_Error to raise the exception and also
90 -- to post appropriate error messages.
91
92 ----------------
93 -- Local Data --
94 ----------------
95
96 type Bits is array (Nat range <>) of Boolean;
97 -- Used to convert unsigned (modular) values for folding logical ops
98
99 -----------------------
100 -- Local Subprograms --
101 -----------------------
102
103 function OK_Bits (N : Node_Id; Bits : Uint) return Boolean;
104 -- Bits represents the number of bits in an integer value to be computed
105 -- (but the value has not been computed yet). If this value in Bits is
106 -- reasonable, a result of True is returned, with the implication that
107 -- the caller should go ahead and complete the calculation. If the value
108 -- in Bits is unreasonably large, then an error is posted on node N, and
109 -- False is returned (and the caller skips the proposed calculation).
110
111 function From_Bits (B : Bits; T : Entity_Id) return Uint;
112 -- Converts a bit string of length B'Length to a Uint value to be used
113 -- for a target of type T, which is a modular type. This procedure
114 -- includes the necessary reduction by the modulus in the case of a
115 -- non-binary modulus (for a binary modulus, the bit string is the
116 -- right length any way so all is well).
117
118 function Get_String_Val (N : Node_Id) return Node_Id;
119 -- Given a tree node for a folded string or character value, returns
120 -- the corresponding string literal or character literal (one of the
121 -- two must be available, or the operand would not have been marked
122 -- as foldable in the earlier analysis of the operation).
123
124 procedure Out_Of_Range (N : Node_Id);
125 -- This procedure is called if it is determined that node N, which
126 -- appears in a non-static context, is a compile time known value
127 -- which is outside its range, i.e. the range of Etype. This is used
128 -- in contexts where this is an illegality if N is static, and should
129 -- generate a warning otherwise.
130
131 procedure Rewrite_In_Raise_CE (N : Node_Id; Exp : Node_Id);
132 -- N and Exp are nodes representing an expression, Exp is known
133 -- to raise CE. N is rewritten in term of Exp in the optimal way.
134
135 function String_Type_Len (Stype : Entity_Id) return Uint;
136 -- Given a string type, determines the length of the index type, or,
137 -- if this index type is non-static, the length of the base type of
138 -- this index type. Note that if the string type is itself static,
139 -- then the index type is static, so the second case applies only
140 -- if the string type passed is non-static.
141
142 function Test (Cond : Boolean) return Uint;
143 pragma Inline (Test);
144 -- This function simply returns the appropriate Boolean'Pos value
145 -- corresponding to the value of Cond as a universal integer. It is
146 -- used for producing the result of the static evaluation of the
147 -- logical operators
148
149 procedure Test_Expression_Is_Foldable
150 (N : Node_Id;
151 Op1 : Node_Id;
152 Stat : out Boolean;
153 Fold : out Boolean);
154 -- Tests to see if expression N whose single operand is Op1 is foldable,
155 -- i.e. the operand value is known at compile time. If the operation is
156 -- foldable, then Fold is True on return, and Stat indicates whether
157 -- the result is static (i.e. both operands were static). Note that it
158 -- is quite possible for Fold to be True, and Stat to be False, since
159 -- there are cases in which we know the value of an operand even though
160 -- it is not technically static (e.g. the static lower bound of a range
161 -- whose upper bound is non-static).
162 --
163 -- If Stat is set False on return, then Expression_Is_Foldable makes a
164 -- call to Check_Non_Static_Context on the operand. If Fold is False on
165 -- return, then all processing is complete, and the caller should
166 -- return, since there is nothing else to do.
167
168 procedure Test_Expression_Is_Foldable
169 (N : Node_Id;
170 Op1 : Node_Id;
171 Op2 : Node_Id;
172 Stat : out Boolean;
173 Fold : out Boolean);
174 -- Same processing, except applies to an expression N with two operands
175 -- Op1 and Op2.
176
177 procedure To_Bits (U : Uint; B : out Bits);
178 -- Converts a Uint value to a bit string of length B'Length
179
180 ------------------------------
181 -- Check_Non_Static_Context --
182 ------------------------------
183
184 procedure Check_Non_Static_Context (N : Node_Id) is
185 T : Entity_Id := Etype (N);
186 Checks_On : constant Boolean :=
187 not Index_Checks_Suppressed (T)
188 and not Range_Checks_Suppressed (T);
189
190 begin
191 -- We need the check only for static expressions not raising CE
192 -- We can also ignore cases in which the type is Any_Type
193
194 if not Is_OK_Static_Expression (N)
195 or else Etype (N) = Any_Type
196 then
197 return;
198
199 -- Skip this check for non-scalar expressions
200
201 elsif not Is_Scalar_Type (T) then
202 return;
203 end if;
204
205 -- Here we have the case of outer level static expression of
206 -- scalar type, where the processing of this procedure is needed.
207
208 -- For real types, this is where we convert the value to a machine
209 -- number (see RM 4.9(38)). Also see ACVC test C490001. We should
210 -- only need to do this if the parent is a constant declaration,
211 -- since in other cases, gigi should do the necessary conversion
212 -- correctly, but experimentation shows that this is not the case
213 -- on all machines, in particular if we do not convert all literals
214 -- to machine values in non-static contexts, then ACVC test C490001
215 -- fails on Sparc/Solaris and SGI/Irix.
216
217 if Nkind (N) = N_Real_Literal
218 and then not Is_Machine_Number (N)
219 and then not Is_Generic_Type (Etype (N))
220 and then Etype (N) /= Universal_Real
221 and then not Debug_Flag_S
222 and then (not Debug_Flag_T
223 or else
224 (Nkind (Parent (N)) = N_Object_Declaration
225 and then Constant_Present (Parent (N))))
226 then
227 -- Check that value is in bounds before converting to machine
228 -- number, so as not to lose case where value overflows in the
229 -- least significant bit or less. See B490001.
230
231 if Is_Out_Of_Range (N, Base_Type (T)) then
232 Out_Of_Range (N);
233 return;
234 end if;
235
236 -- Note: we have to copy the node, to avoid problems with conformance
237 -- of very similar numbers (see ACVC tests B4A010C and B63103A).
238
239 Rewrite (N, New_Copy (N));
240
241 if not Is_Floating_Point_Type (T) then
242 Set_Realval
243 (N, Corresponding_Integer_Value (N) * Small_Value (T));
244
245 elsif not UR_Is_Zero (Realval (N)) then
246 declare
247 RT : constant Entity_Id := Base_Type (T);
248 X : constant Ureal := Machine (RT, Realval (N), Round);
249
250 begin
251 -- Warn if result of static rounding actually differs from
252 -- runtime evaluation, which uses round to even.
253
254 if Warn_On_Biased_Rounding and Rounding_Was_Biased then
255 Error_Msg_N ("static expression does not round to even"
256 & " ('R'M 4.9(38))?", N);
257 end if;
258
259 Set_Realval (N, X);
260 end;
261 end if;
262
263 Set_Is_Machine_Number (N);
264 end if;
265
266 -- Check for out of range universal integer. This is a non-static
267 -- context, so the integer value must be in range of the runtime
268 -- representation of universal integers.
269
270 -- We do this only within an expression, because that is the only
271 -- case in which non-static universal integer values can occur, and
272 -- furthermore, Check_Non_Static_Context is currently (incorrectly???)
273 -- called in contexts like the expression of a number declaration where
274 -- we certainly want to allow out of range values.
275
276 if Etype (N) = Universal_Integer
277 and then Nkind (N) = N_Integer_Literal
278 and then Nkind (Parent (N)) in N_Subexpr
279 and then
280 (Intval (N) < Expr_Value (Type_Low_Bound (Universal_Integer))
281 or else
282 Intval (N) > Expr_Value (Type_High_Bound (Universal_Integer)))
283 then
284 Apply_Compile_Time_Constraint_Error
285 (N, "non-static universal integer value out of range?");
286
287 -- Check out of range of base type
288
289 elsif Is_Out_Of_Range (N, Base_Type (T)) then
290 Out_Of_Range (N);
291
292 -- Give warning if outside subtype (where one or both of the
293 -- bounds of the subtype is static). This warning is omitted
294 -- if the expression appears in a range that could be null
295 -- (warnings are handled elsewhere for this case).
296
297 elsif T /= Base_Type (T)
298 and then Nkind (Parent (N)) /= N_Range
299 then
300 if Is_In_Range (N, T) then
301 null;
302
303 elsif Is_Out_Of_Range (N, T) then
304 Apply_Compile_Time_Constraint_Error
305 (N, "value not in range of}?");
306
307 elsif Checks_On then
308 Enable_Range_Check (N);
309
310 else
311 Set_Do_Range_Check (N, False);
312 end if;
313 end if;
314 end Check_Non_Static_Context;
315
316 ---------------------------------
317 -- Check_String_Literal_Length --
318 ---------------------------------
319
320 procedure Check_String_Literal_Length (N : Node_Id; Ttype : Entity_Id) is
321 begin
322 if not Raises_Constraint_Error (N)
323 and then Is_Constrained (Ttype)
324 then
325 if
326 UI_From_Int (String_Length (Strval (N))) /= String_Type_Len (Ttype)
327 then
328 Apply_Compile_Time_Constraint_Error
329 (N, "string length wrong for}?",
330 Ent => Ttype,
331 Typ => Ttype);
332 end if;
333 end if;
334 end Check_String_Literal_Length;
335
336 --------------------------
337 -- Compile_Time_Compare --
338 --------------------------
339
340 function Compile_Time_Compare (L, R : Node_Id) return Compare_Result is
341 Ltyp : constant Entity_Id := Etype (L);
342 Rtyp : constant Entity_Id := Etype (R);
343
344 procedure Compare_Decompose
345 (N : Node_Id;
346 R : out Node_Id;
347 V : out Uint);
348 -- This procedure decomposes the node N into an expression node
349 -- and a signed offset, so that the value of N is equal to the
350 -- value of R plus the value V (which may be negative). If no
351 -- such decomposition is possible, then on return R is a copy
352 -- of N, and V is set to zero.
353
354 function Compare_Fixup (N : Node_Id) return Node_Id;
355 -- This function deals with replacing 'Last and 'First references
356 -- with their corresponding type bounds, which we then can compare.
357 -- The argument is the original node, the result is the identity,
358 -- unless we have a 'Last/'First reference in which case the value
359 -- returned is the appropriate type bound.
360
361 function Is_Same_Value (L, R : Node_Id) return Boolean;
362 -- Returns True iff L and R represent expressions that definitely
363 -- have identical (but not necessarily compile time known) values
364 -- Indeed the caller is expected to have already dealt with the
365 -- cases of compile time known values, so these are not tested here.
366
367 -----------------------
368 -- Compare_Decompose --
369 -----------------------
370
371 procedure Compare_Decompose
372 (N : Node_Id;
373 R : out Node_Id;
374 V : out Uint)
375 is
376 begin
377 if Nkind (N) = N_Op_Add
378 and then Nkind (Right_Opnd (N)) = N_Integer_Literal
379 then
380 R := Left_Opnd (N);
381 V := Intval (Right_Opnd (N));
382 return;
383
384 elsif Nkind (N) = N_Op_Subtract
385 and then Nkind (Right_Opnd (N)) = N_Integer_Literal
386 then
387 R := Left_Opnd (N);
388 V := UI_Negate (Intval (Right_Opnd (N)));
389 return;
390
391 elsif Nkind (N) = N_Attribute_Reference then
392
393 if Attribute_Name (N) = Name_Succ then
394 R := First (Expressions (N));
395 V := Uint_1;
396 return;
397
398 elsif Attribute_Name (N) = Name_Pred then
399 R := First (Expressions (N));
400 V := Uint_Minus_1;
401 return;
402 end if;
403 end if;
404
405 R := N;
406 V := Uint_0;
407 end Compare_Decompose;
408
409 -------------------
410 -- Compare_Fixup --
411 -------------------
412
413 function Compare_Fixup (N : Node_Id) return Node_Id is
414 Indx : Node_Id;
415 Xtyp : Entity_Id;
416 Subs : Nat;
417
418 begin
419 if Nkind (N) = N_Attribute_Reference
420 and then (Attribute_Name (N) = Name_First
421 or else
422 Attribute_Name (N) = Name_Last)
423 then
424 Xtyp := Etype (Prefix (N));
425
426 -- If we have no type, then just abandon the attempt to do
427 -- a fixup, this is probably the result of some other error.
428
429 if No (Xtyp) then
430 return N;
431 end if;
432
433 -- Dereference an access type
434
435 if Is_Access_Type (Xtyp) then
436 Xtyp := Designated_Type (Xtyp);
437 end if;
438
439 -- If we don't have an array type at this stage, something
440 -- is peculiar, e.g. another error, and we abandon the attempt
441 -- at a fixup.
442
443 if not Is_Array_Type (Xtyp) then
444 return N;
445 end if;
446
447 -- Ignore unconstrained array, since bounds are not meaningful
448
449 if not Is_Constrained (Xtyp) then
450 return N;
451 end if;
452
c3de5c4c
ES
453 if Ekind (Xtyp) = E_String_Literal_Subtype then
454 if Attribute_Name (N) = Name_First then
455 return String_Literal_Low_Bound (Xtyp);
456
457 else -- Attribute_Name (N) = Name_Last
458 return Make_Integer_Literal (Sloc (N),
459 Intval => Intval (String_Literal_Low_Bound (Xtyp))
460 + String_Literal_Length (Xtyp));
461 end if;
462 end if;
463
996ae0b0
RK
464 -- Find correct index type
465
466 Indx := First_Index (Xtyp);
467
468 if Present (Expressions (N)) then
469 Subs := UI_To_Int (Expr_Value (First (Expressions (N))));
470
471 for J in 2 .. Subs loop
472 Indx := Next_Index (Indx);
473 end loop;
474 end if;
475
476 Xtyp := Etype (Indx);
477
478 if Attribute_Name (N) = Name_First then
479 return Type_Low_Bound (Xtyp);
480
481 else -- Attribute_Name (N) = Name_Last
482 return Type_High_Bound (Xtyp);
483 end if;
484 end if;
485
486 return N;
487 end Compare_Fixup;
488
489 -------------------
490 -- Is_Same_Value --
491 -------------------
492
493 function Is_Same_Value (L, R : Node_Id) return Boolean is
494 Lf : constant Node_Id := Compare_Fixup (L);
495 Rf : constant Node_Id := Compare_Fixup (R);
496
497 begin
498 -- Values are the same if they are the same identifier and the
499 -- identifier refers to a constant object (E_Constant)
500
501 if Nkind (Lf) = N_Identifier and then Nkind (Rf) = N_Identifier
502 and then Entity (Lf) = Entity (Rf)
503 and then (Ekind (Entity (Lf)) = E_Constant or else
504 Ekind (Entity (Lf)) = E_In_Parameter or else
505 Ekind (Entity (Lf)) = E_Loop_Parameter)
506 then
507 return True;
508
509 -- Or if they are compile time known and identical
510
511 elsif Compile_Time_Known_Value (Lf)
512 and then
513 Compile_Time_Known_Value (Rf)
514 and then Expr_Value (Lf) = Expr_Value (Rf)
515 then
516 return True;
517
518 -- Or if they are both 'First or 'Last values applying to the
519 -- same entity (first and last don't change even if value does)
520
521 elsif Nkind (Lf) = N_Attribute_Reference
522 and then
523 Nkind (Rf) = N_Attribute_Reference
524 and then Attribute_Name (Lf) = Attribute_Name (Rf)
525 and then (Attribute_Name (Lf) = Name_First
526 or else
527 Attribute_Name (Lf) = Name_Last)
528 and then Is_Entity_Name (Prefix (Lf))
529 and then Is_Entity_Name (Prefix (Rf))
530 and then Entity (Prefix (Lf)) = Entity (Prefix (Rf))
531 then
532 return True;
533
534 -- All other cases, we can't tell
535
536 else
537 return False;
538 end if;
539 end Is_Same_Value;
540
541 -- Start of processing for Compile_Time_Compare
542
543 begin
544 if L = R then
545 return EQ;
546
547 -- If expressions have no types, then do not attempt to determine
548 -- if they are the same, since something funny is going on. One
549 -- case in which this happens is during generic template analysis,
550 -- when bounds are not fully analyzed.
551
552 elsif No (Ltyp) or else No (Rtyp) then
553 return Unknown;
554
555 -- We only attempt compile time analysis for scalar values
556
557 elsif not Is_Scalar_Type (Ltyp)
558 or else Is_Packed_Array_Type (Ltyp)
559 then
560 return Unknown;
561
562 -- Case where comparison involves two compile time known values
563
564 elsif Compile_Time_Known_Value (L)
565 and then Compile_Time_Known_Value (R)
566 then
567 -- For the floating-point case, we have to be a little careful, since
568 -- at compile time we are dealing with universal exact values, but at
569 -- runtime, these will be in non-exact target form. That's why the
570 -- returned results are LE and GE below instead of LT and GT.
571
572 if Is_Floating_Point_Type (Ltyp)
573 or else
574 Is_Floating_Point_Type (Rtyp)
575 then
576 declare
577 Lo : constant Ureal := Expr_Value_R (L);
578 Hi : constant Ureal := Expr_Value_R (R);
579
580 begin
581 if Lo < Hi then
582 return LE;
583 elsif Lo = Hi then
584 return EQ;
585 else
586 return GE;
587 end if;
588 end;
589
590 -- For the integer case we know exactly (note that this includes the
591 -- fixed-point case, where we know the run time integer values now)
592
593 else
594 declare
595 Lo : constant Uint := Expr_Value (L);
596 Hi : constant Uint := Expr_Value (R);
597
598 begin
599 if Lo < Hi then
600 return LT;
601 elsif Lo = Hi then
602 return EQ;
603 else
604 return GT;
605 end if;
606 end;
607 end if;
608
609 -- Cases where at least one operand is not known at compile time
610
611 else
612 -- Here is where we check for comparisons against maximum bounds of
613 -- types, where we know that no value can be outside the bounds of
614 -- the subtype. Note that this routine is allowed to assume that all
615 -- expressions are within their subtype bounds. Callers wishing to
616 -- deal with possibly invalid values must in any case take special
617 -- steps (e.g. conversions to larger types) to avoid this kind of
618 -- optimization, which is always considered to be valid. We do not
619 -- attempt this optimization with generic types, since the type
620 -- bounds may not be meaningful in this case.
621
622 if Is_Discrete_Type (Ltyp)
623 and then not Is_Generic_Type (Ltyp)
624 and then not Is_Generic_Type (Rtyp)
625 then
626 if Is_Same_Value (R, Type_High_Bound (Ltyp)) then
627 return LE;
628
629 elsif Is_Same_Value (R, Type_Low_Bound (Ltyp)) then
630 return GE;
631
632 elsif Is_Same_Value (L, Type_High_Bound (Rtyp)) then
633 return GE;
634
635 elsif Is_Same_Value (L, Type_Low_Bound (Ltyp)) then
636 return LE;
637 end if;
638 end if;
639
640 -- Next attempt is to decompose the expressions to extract
641 -- a constant offset resulting from the use of any of the forms:
642
643 -- expr + literal
644 -- expr - literal
645 -- typ'Succ (expr)
646 -- typ'Pred (expr)
647
648 -- Then we see if the two expressions are the same value, and if so
649 -- the result is obtained by comparing the offsets.
650
651 declare
652 Lnode : Node_Id;
653 Loffs : Uint;
654 Rnode : Node_Id;
655 Roffs : Uint;
656
657 begin
658 Compare_Decompose (L, Lnode, Loffs);
659 Compare_Decompose (R, Rnode, Roffs);
660
661 if Is_Same_Value (Lnode, Rnode) then
662 if Loffs = Roffs then
663 return EQ;
664
665 elsif Loffs < Roffs then
666 return LT;
667
668 else
669 return GT;
670 end if;
671
672 -- If the expressions are different, we cannot say at compile
673 -- time how they compare, so we return the Unknown indication.
674
675 else
676 return Unknown;
677 end if;
678 end;
679 end if;
680 end Compile_Time_Compare;
681
682 ------------------------------
683 -- Compile_Time_Known_Value --
684 ------------------------------
685
686 function Compile_Time_Known_Value (Op : Node_Id) return Boolean is
687 K : constant Node_Kind := Nkind (Op);
688
689 begin
690 -- Never known at compile time if bad type or raises constraint error
691 -- or empty (latter case occurs only as a result of a previous error)
692
693 if No (Op)
694 or else Op = Error
695 or else Etype (Op) = Any_Type
696 or else Raises_Constraint_Error (Op)
697 then
698 return False;
699 end if;
700
701 -- If we have an entity name, then see if it is the name of a constant
702 -- and if so, test the corresponding constant value, or the name of
703 -- an enumeration literal, which is always a constant.
704
705 if Present (Etype (Op)) and then Is_Entity_Name (Op) then
706 declare
707 E : constant Entity_Id := Entity (Op);
708 V : Node_Id;
709
710 begin
711 -- Never known at compile time if it is a packed array value.
712 -- We might want to try to evaluate these at compile time one
713 -- day, but we do not make that attempt now.
714
715 if Is_Packed_Array_Type (Etype (Op)) then
716 return False;
717 end if;
718
719 if Ekind (E) = E_Enumeration_Literal then
720 return True;
721
722 elsif Ekind (E) /= E_Constant then
723 return False;
724
725 else
726 V := Constant_Value (E);
727 return Present (V) and then Compile_Time_Known_Value (V);
728 end if;
729 end;
730
731 -- We have a value, see if it is compile time known
732
733 else
734 -- Literals and NULL are known at compile time
735
736 if K = N_Integer_Literal
737 or else
738 K = N_Character_Literal
739 or else
740 K = N_Real_Literal
741 or else
742 K = N_String_Literal
743 or else
744 K = N_Null
745 then
746 return True;
747
748 -- Any reference to Null_Parameter is known at compile time. No
749 -- other attribute references (that have not already been folded)
750 -- are known at compile time.
751
752 elsif K = N_Attribute_Reference then
753 return Attribute_Name (Op) = Name_Null_Parameter;
754
755 -- All other types of values are not known at compile time
756
757 else
758 return False;
759 end if;
760
761 end if;
762 end Compile_Time_Known_Value;
763
764 --------------------------------------
765 -- Compile_Time_Known_Value_Or_Aggr --
766 --------------------------------------
767
768 function Compile_Time_Known_Value_Or_Aggr (Op : Node_Id) return Boolean is
769 begin
770 -- If we have an entity name, then see if it is the name of a constant
771 -- and if so, test the corresponding constant value, or the name of
772 -- an enumeration literal, which is always a constant.
773
774 if Is_Entity_Name (Op) then
775 declare
776 E : constant Entity_Id := Entity (Op);
777 V : Node_Id;
778
779 begin
780 if Ekind (E) = E_Enumeration_Literal then
781 return True;
782
783 elsif Ekind (E) /= E_Constant then
784 return False;
785
786 else
787 V := Constant_Value (E);
788 return Present (V)
789 and then Compile_Time_Known_Value_Or_Aggr (V);
790 end if;
791 end;
792
793 -- We have a value, see if it is compile time known
794
795 else
796 if Compile_Time_Known_Value (Op) then
797 return True;
798
799 elsif Nkind (Op) = N_Aggregate then
800
801 if Present (Expressions (Op)) then
802 declare
803 Expr : Node_Id;
804
805 begin
806 Expr := First (Expressions (Op));
807 while Present (Expr) loop
808 if not Compile_Time_Known_Value_Or_Aggr (Expr) then
809 return False;
810 end if;
811
812 Next (Expr);
813 end loop;
814 end;
815 end if;
816
817 if Present (Component_Associations (Op)) then
818 declare
819 Cass : Node_Id;
820
821 begin
822 Cass := First (Component_Associations (Op));
823 while Present (Cass) loop
824 if not
825 Compile_Time_Known_Value_Or_Aggr (Expression (Cass))
826 then
827 return False;
828 end if;
829
830 Next (Cass);
831 end loop;
832 end;
833 end if;
834
835 return True;
836
837 -- All other types of values are not known at compile time
838
839 else
840 return False;
841 end if;
842
843 end if;
844 end Compile_Time_Known_Value_Or_Aggr;
845
846 -----------------
847 -- Eval_Actual --
848 -----------------
849
850 -- This is only called for actuals of functions that are not predefined
851 -- operators (which have already been rewritten as operators at this
852 -- stage), so the call can never be folded, and all that needs doing for
853 -- the actual is to do the check for a non-static context.
854
855 procedure Eval_Actual (N : Node_Id) is
856 begin
857 Check_Non_Static_Context (N);
858 end Eval_Actual;
859
860 --------------------
861 -- Eval_Allocator --
862 --------------------
863
864 -- Allocators are never static, so all we have to do is to do the
865 -- check for a non-static context if an expression is present.
866
867 procedure Eval_Allocator (N : Node_Id) is
868 Expr : constant Node_Id := Expression (N);
869
870 begin
871 if Nkind (Expr) = N_Qualified_Expression then
872 Check_Non_Static_Context (Expression (Expr));
873 end if;
874 end Eval_Allocator;
875
876 ------------------------
877 -- Eval_Arithmetic_Op --
878 ------------------------
879
880 -- Arithmetic operations are static functions, so the result is static
881 -- if both operands are static (RM 4.9(7), 4.9(20)).
882
883 procedure Eval_Arithmetic_Op (N : Node_Id) is
884 Left : constant Node_Id := Left_Opnd (N);
885 Right : constant Node_Id := Right_Opnd (N);
886 Ltype : constant Entity_Id := Etype (Left);
887 Rtype : constant Entity_Id := Etype (Right);
888 Stat : Boolean;
889 Fold : Boolean;
890
891 begin
892 -- If not foldable we are done
893
894 Test_Expression_Is_Foldable (N, Left, Right, Stat, Fold);
895
896 if not Fold then
897 return;
898 end if;
899
900 -- Fold for cases where both operands are of integer type
901
902 if Is_Integer_Type (Ltype) and then Is_Integer_Type (Rtype) then
903 declare
904 Left_Int : constant Uint := Expr_Value (Left);
905 Right_Int : constant Uint := Expr_Value (Right);
906 Result : Uint;
907
908 begin
909 case Nkind (N) is
910
911 when N_Op_Add =>
912 Result := Left_Int + Right_Int;
913
914 when N_Op_Subtract =>
915 Result := Left_Int - Right_Int;
916
917 when N_Op_Multiply =>
918 if OK_Bits
919 (N, UI_From_Int
920 (Num_Bits (Left_Int) + Num_Bits (Right_Int)))
921 then
922 Result := Left_Int * Right_Int;
923 else
924 Result := Left_Int;
925 end if;
926
927 when N_Op_Divide =>
928
929 -- The exception Constraint_Error is raised by integer
930 -- division, rem and mod if the right operand is zero.
931
932 if Right_Int = 0 then
933 Apply_Compile_Time_Constraint_Error
934 (N, "division by zero");
935 return;
936 else
937 Result := Left_Int / Right_Int;
938 end if;
939
940 when N_Op_Mod =>
941
942 -- The exception Constraint_Error is raised by integer
943 -- division, rem and mod if the right operand is zero.
944
945 if Right_Int = 0 then
946 Apply_Compile_Time_Constraint_Error
947 (N, "mod with zero divisor");
948 return;
949 else
950 Result := Left_Int mod Right_Int;
951 end if;
952
953 when N_Op_Rem =>
954
955 -- The exception Constraint_Error is raised by integer
956 -- division, rem and mod if the right operand is zero.
957
958 if Right_Int = 0 then
959 Apply_Compile_Time_Constraint_Error
960 (N, "rem with zero divisor");
961 return;
962 else
963 Result := Left_Int rem Right_Int;
964 end if;
965
966 when others =>
967 raise Program_Error;
968 end case;
969
970 -- Adjust the result by the modulus if the type is a modular type
971
972 if Is_Modular_Integer_Type (Ltype) then
973 Result := Result mod Modulus (Ltype);
974 end if;
975
976 Fold_Uint (N, Result);
977 end;
978
979 -- Cases where at least one operand is a real. We handle the cases
980 -- of both reals, or mixed/real integer cases (the latter happen
981 -- only for divide and multiply, and the result is always real).
982
983 elsif Is_Real_Type (Ltype) or else Is_Real_Type (Rtype) then
984 declare
985 Left_Real : Ureal;
986 Right_Real : Ureal;
987 Result : Ureal;
988
989 begin
990 if Is_Real_Type (Ltype) then
991 Left_Real := Expr_Value_R (Left);
992 else
993 Left_Real := UR_From_Uint (Expr_Value (Left));
994 end if;
995
996 if Is_Real_Type (Rtype) then
997 Right_Real := Expr_Value_R (Right);
998 else
999 Right_Real := UR_From_Uint (Expr_Value (Right));
1000 end if;
1001
1002 if Nkind (N) = N_Op_Add then
1003 Result := Left_Real + Right_Real;
1004
1005 elsif Nkind (N) = N_Op_Subtract then
1006 Result := Left_Real - Right_Real;
1007
1008 elsif Nkind (N) = N_Op_Multiply then
1009 Result := Left_Real * Right_Real;
1010
1011 else pragma Assert (Nkind (N) = N_Op_Divide);
1012 if UR_Is_Zero (Right_Real) then
1013 Apply_Compile_Time_Constraint_Error
1014 (N, "division by zero");
1015 return;
1016 end if;
1017
1018 Result := Left_Real / Right_Real;
1019 end if;
1020
1021 Fold_Ureal (N, Result);
1022 end;
1023 end if;
1024
1025 Set_Is_Static_Expression (N, Stat);
1026
1027 end Eval_Arithmetic_Op;
1028
1029 ----------------------------
1030 -- Eval_Character_Literal --
1031 ----------------------------
1032
1033 -- Nothing to be done!
1034
1035 procedure Eval_Character_Literal (N : Node_Id) is
1036 begin
1037 null;
1038 end Eval_Character_Literal;
1039
1040 ------------------------
1041 -- Eval_Concatenation --
1042 ------------------------
1043
1044 -- Concatenation is a static function, so the result is static if
1045 -- both operands are static (RM 4.9(7), 4.9(21)).
1046
1047 procedure Eval_Concatenation (N : Node_Id) is
f91b40db
GB
1048 Left : constant Node_Id := Left_Opnd (N);
1049 Right : constant Node_Id := Right_Opnd (N);
1050 C_Typ : constant Entity_Id := Root_Type (Component_Type (Etype (N)));
996ae0b0
RK
1051 Stat : Boolean;
1052 Fold : Boolean;
996ae0b0
RK
1053
1054 begin
1055 -- Concatenation is never static in Ada 83, so if Ada 83
1056 -- check operand non-static context
1057
1058 if Ada_83
1059 and then Comes_From_Source (N)
1060 then
1061 Check_Non_Static_Context (Left);
1062 Check_Non_Static_Context (Right);
1063 return;
1064 end if;
1065
1066 -- If not foldable we are done. In principle concatenation that yields
1067 -- any string type is static (i.e. an array type of character types).
1068 -- However, character types can include enumeration literals, and
1069 -- concatenation in that case cannot be described by a literal, so we
1070 -- only consider the operation static if the result is an array of
1071 -- (a descendant of) a predefined character type.
1072
1073 Test_Expression_Is_Foldable (N, Left, Right, Stat, Fold);
1074
1075 if (C_Typ = Standard_Character
1076 or else C_Typ = Standard_Wide_Character)
1077 and then Fold
1078 then
1079 null;
1080 else
1081 Set_Is_Static_Expression (N, False);
1082 return;
1083 end if;
1084
1085 -- Compile time string concatenation.
1086
1087 -- ??? Note that operands that are aggregates can be marked as
1088 -- static, so we should attempt at a later stage to fold
1089 -- concatenations with such aggregates.
1090
1091 declare
1092 Left_Str : constant Node_Id := Get_String_Val (Left);
f91b40db 1093 Left_Len : Nat;
996ae0b0
RK
1094 Right_Str : constant Node_Id := Get_String_Val (Right);
1095
1096 begin
1097 -- Establish new string literal, and store left operand. We make
1098 -- sure to use the special Start_String that takes an operand if
1099 -- the left operand is a string literal. Since this is optimized
1100 -- in the case where that is the most recently created string
1101 -- literal, we ensure efficient time/space behavior for the
1102 -- case of a concatenation of a series of string literals.
1103
1104 if Nkind (Left_Str) = N_String_Literal then
f91b40db 1105 Left_Len := String_Length (Strval (Left_Str));
996ae0b0
RK
1106 Start_String (Strval (Left_Str));
1107 else
1108 Start_String;
1109 Store_String_Char (Char_Literal_Value (Left_Str));
f91b40db 1110 Left_Len := 1;
996ae0b0
RK
1111 end if;
1112
1113 -- Now append the characters of the right operand
1114
1115 if Nkind (Right_Str) = N_String_Literal then
1116 declare
1117 S : constant String_Id := Strval (Right_Str);
1118
1119 begin
1120 for J in 1 .. String_Length (S) loop
1121 Store_String_Char (Get_String_Char (S, J));
1122 end loop;
1123 end;
1124 else
1125 Store_String_Char (Char_Literal_Value (Right_Str));
1126 end if;
1127
1128 Set_Is_Static_Expression (N, Stat);
1129
1130 if Stat then
f91b40db
GB
1131
1132 -- If left operand is the empty string, the result is the
1133 -- right operand, including its bounds if anomalous.
1134
1135 if Left_Len = 0
1136 and then Is_Array_Type (Etype (Right))
1137 and then Etype (Right) /= Any_String
1138 then
1139 Set_Etype (N, Etype (Right));
1140 end if;
1141
996ae0b0
RK
1142 Fold_Str (N, End_String);
1143 end if;
1144 end;
1145 end Eval_Concatenation;
1146
1147 ---------------------------------
1148 -- Eval_Conditional_Expression --
1149 ---------------------------------
1150
1151 -- This GNAT internal construct can never be statically folded, so the
1152 -- only required processing is to do the check for non-static context
1153 -- for the two expression operands.
1154
1155 procedure Eval_Conditional_Expression (N : Node_Id) is
1156 Condition : constant Node_Id := First (Expressions (N));
1157 Then_Expr : constant Node_Id := Next (Condition);
1158 Else_Expr : constant Node_Id := Next (Then_Expr);
1159
1160 begin
1161 Check_Non_Static_Context (Then_Expr);
1162 Check_Non_Static_Context (Else_Expr);
1163 end Eval_Conditional_Expression;
1164
1165 ----------------------
1166 -- Eval_Entity_Name --
1167 ----------------------
1168
1169 -- This procedure is used for identifiers and expanded names other than
1170 -- named numbers (see Eval_Named_Integer, Eval_Named_Real. These are
1171 -- static if they denote a static constant (RM 4.9(6)) or if the name
1172 -- denotes an enumeration literal (RM 4.9(22)).
1173
1174 procedure Eval_Entity_Name (N : Node_Id) is
1175 Def_Id : constant Entity_Id := Entity (N);
1176 Val : Node_Id;
1177
1178 begin
1179 -- Enumeration literals are always considered to be constants
1180 -- and cannot raise constraint error (RM 4.9(22)).
1181
1182 if Ekind (Def_Id) = E_Enumeration_Literal then
1183 Set_Is_Static_Expression (N);
1184 return;
1185
1186 -- A name is static if it denotes a static constant (RM 4.9(5)), and
1187 -- we also copy Raise_Constraint_Error. Notice that even if non-static,
1188 -- it does not violate 10.2.1(8) here, since this is not a variable.
1189
1190 elsif Ekind (Def_Id) = E_Constant then
1191
1192 -- Deferred constants must always be treated as nonstatic
1193 -- outside the scope of their full view.
1194
1195 if Present (Full_View (Def_Id))
1196 and then not In_Open_Scopes (Scope (Def_Id))
1197 then
1198 Val := Empty;
1199 else
1200 Val := Constant_Value (Def_Id);
1201 end if;
1202
1203 if Present (Val) then
1204 Set_Is_Static_Expression
1205 (N, Is_Static_Expression (Val)
1206 and then Is_Static_Subtype (Etype (Def_Id)));
1207 Set_Raises_Constraint_Error (N, Raises_Constraint_Error (Val));
1208
1209 if not Is_Static_Expression (N)
1210 and then not Is_Generic_Type (Etype (N))
1211 then
1212 Validate_Static_Object_Name (N);
1213 end if;
1214
1215 return;
1216 end if;
1217 end if;
1218
1219 -- Fall through if the name is not static.
1220
1221 Validate_Static_Object_Name (N);
1222 end Eval_Entity_Name;
1223
1224 ----------------------------
1225 -- Eval_Indexed_Component --
1226 ----------------------------
1227
1228 -- Indexed components are never static, so the only required processing
1229 -- is to perform the check for non-static context on the index values.
1230
1231 procedure Eval_Indexed_Component (N : Node_Id) is
1232 Expr : Node_Id;
1233
1234 begin
1235 Expr := First (Expressions (N));
1236 while Present (Expr) loop
1237 Check_Non_Static_Context (Expr);
1238 Next (Expr);
1239 end loop;
1240
1241 end Eval_Indexed_Component;
1242
1243 --------------------------
1244 -- Eval_Integer_Literal --
1245 --------------------------
1246
1247 -- Numeric literals are static (RM 4.9(1)), and have already been marked
1248 -- as static by the analyzer. The reason we did it that early is to allow
1249 -- the possibility of turning off the Is_Static_Expression flag after
1250 -- analysis, but before resolution, when integer literals are generated
1251 -- in the expander that do not correspond to static expressions.
1252
1253 procedure Eval_Integer_Literal (N : Node_Id) is
1254 T : constant Entity_Id := Etype (N);
1255
1256 begin
1257 -- If the literal appears in a non-expression context, then it is
1258 -- certainly appearing in a non-static context, so check it. This
1259 -- is actually a redundant check, since Check_Non_Static_Context
1260 -- would check it, but it seems worth while avoiding the call.
1261
1262 if Nkind (Parent (N)) not in N_Subexpr then
1263 Check_Non_Static_Context (N);
1264 end if;
1265
1266 -- Modular integer literals must be in their base range
1267
1268 if Is_Modular_Integer_Type (T)
1269 and then Is_Out_Of_Range (N, Base_Type (T))
1270 then
1271 Out_Of_Range (N);
1272 end if;
1273 end Eval_Integer_Literal;
1274
1275 ---------------------
1276 -- Eval_Logical_Op --
1277 ---------------------
1278
1279 -- Logical operations are static functions, so the result is potentially
1280 -- static if both operands are potentially static (RM 4.9(7), 4.9(20)).
1281
1282 procedure Eval_Logical_Op (N : Node_Id) is
1283 Left : constant Node_Id := Left_Opnd (N);
1284 Right : constant Node_Id := Right_Opnd (N);
1285 Stat : Boolean;
1286 Fold : Boolean;
1287
1288 begin
1289 -- If not foldable we are done
1290
1291 Test_Expression_Is_Foldable (N, Left, Right, Stat, Fold);
1292
1293 if not Fold then
1294 return;
1295 end if;
1296
1297 -- Compile time evaluation of logical operation
1298
1299 declare
1300 Left_Int : constant Uint := Expr_Value (Left);
1301 Right_Int : constant Uint := Expr_Value (Right);
1302
1303 begin
1304 if Is_Modular_Integer_Type (Etype (N)) then
1305 declare
1306 Left_Bits : Bits (0 .. UI_To_Int (Esize (Etype (N))) - 1);
1307 Right_Bits : Bits (0 .. UI_To_Int (Esize (Etype (N))) - 1);
1308
1309 begin
1310 To_Bits (Left_Int, Left_Bits);
1311 To_Bits (Right_Int, Right_Bits);
1312
1313 -- Note: should really be able to use array ops instead of
1314 -- these loops, but they weren't working at the time ???
1315
1316 if Nkind (N) = N_Op_And then
1317 for J in Left_Bits'Range loop
1318 Left_Bits (J) := Left_Bits (J) and Right_Bits (J);
1319 end loop;
1320
1321 elsif Nkind (N) = N_Op_Or then
1322 for J in Left_Bits'Range loop
1323 Left_Bits (J) := Left_Bits (J) or Right_Bits (J);
1324 end loop;
1325
1326 else
1327 pragma Assert (Nkind (N) = N_Op_Xor);
1328
1329 for J in Left_Bits'Range loop
1330 Left_Bits (J) := Left_Bits (J) xor Right_Bits (J);
1331 end loop;
1332 end if;
1333
1334 Fold_Uint (N, From_Bits (Left_Bits, Etype (N)));
1335 end;
1336
1337 else
1338 pragma Assert (Is_Boolean_Type (Etype (N)));
1339
1340 if Nkind (N) = N_Op_And then
1341 Fold_Uint (N,
1342 Test (Is_True (Left_Int) and then Is_True (Right_Int)));
1343
1344 elsif Nkind (N) = N_Op_Or then
1345 Fold_Uint (N,
1346 Test (Is_True (Left_Int) or else Is_True (Right_Int)));
1347
1348 else
1349 pragma Assert (Nkind (N) = N_Op_Xor);
1350 Fold_Uint (N,
1351 Test (Is_True (Left_Int) xor Is_True (Right_Int)));
1352 end if;
1353 end if;
1354
1355 Set_Is_Static_Expression (N, Stat);
1356 end;
1357 end Eval_Logical_Op;
1358
1359 ------------------------
1360 -- Eval_Membership_Op --
1361 ------------------------
1362
1363 -- A membership test is potentially static if the expression is static,
1364 -- and the range is a potentially static range, or is a subtype mark
1365 -- denoting a static subtype (RM 4.9(12)).
1366
1367 procedure Eval_Membership_Op (N : Node_Id) is
1368 Left : constant Node_Id := Left_Opnd (N);
1369 Right : constant Node_Id := Right_Opnd (N);
1370 Def_Id : Entity_Id;
1371 Lo : Node_Id;
1372 Hi : Node_Id;
1373 Result : Boolean;
1374 Stat : Boolean;
1375 Fold : Boolean;
1376
1377 begin
1378 -- Ignore if error in either operand, except to make sure that
1379 -- Any_Type is properly propagated to avoid junk cascaded errors.
1380
1381 if Etype (Left) = Any_Type
1382 or else Etype (Right) = Any_Type
1383 then
1384 Set_Etype (N, Any_Type);
1385 return;
1386 end if;
1387
1388 -- Case of right operand is a subtype name
1389
1390 if Is_Entity_Name (Right) then
1391 Def_Id := Entity (Right);
1392
1393 if (Is_Scalar_Type (Def_Id) or else Is_String_Type (Def_Id))
1394 and then Is_OK_Static_Subtype (Def_Id)
1395 then
1396 Test_Expression_Is_Foldable (N, Left, Stat, Fold);
1397
1398 if not Fold or else not Stat then
1399 return;
1400 end if;
1401 else
1402 Check_Non_Static_Context (Left);
1403 return;
1404 end if;
1405
1406 -- For string membership tests we will check the length
1407 -- further below.
1408
1409 if not Is_String_Type (Def_Id) then
1410 Lo := Type_Low_Bound (Def_Id);
1411 Hi := Type_High_Bound (Def_Id);
1412
1413 else
1414 Lo := Empty;
1415 Hi := Empty;
1416 end if;
1417
1418 -- Case of right operand is a range
1419
1420 else
1421 if Is_Static_Range (Right) then
1422 Test_Expression_Is_Foldable (N, Left, Stat, Fold);
1423
1424 if not Fold or else not Stat then
1425 return;
1426
1427 -- If one bound of range raises CE, then don't try to fold
1428
1429 elsif not Is_OK_Static_Range (Right) then
1430 Check_Non_Static_Context (Left);
1431 return;
1432 end if;
1433
1434 else
1435 Check_Non_Static_Context (Left);
1436 return;
1437 end if;
1438
1439 -- Here we know range is an OK static range
1440
1441 Lo := Low_Bound (Right);
1442 Hi := High_Bound (Right);
1443 end if;
1444
1445 -- For strings we check that the length of the string expression is
1446 -- compatible with the string subtype if the subtype is constrained,
1447 -- or if unconstrained then the test is always true.
1448
1449 if Is_String_Type (Etype (Right)) then
1450 if not Is_Constrained (Etype (Right)) then
1451 Result := True;
1452
1453 else
1454 declare
1455 Typlen : constant Uint := String_Type_Len (Etype (Right));
1456 Strlen : constant Uint :=
1457 UI_From_Int (String_Length (Strval (Get_String_Val (Left))));
1458 begin
1459 Result := (Typlen = Strlen);
1460 end;
1461 end if;
1462
1463 -- Fold the membership test. We know we have a static range and Lo
1464 -- and Hi are set to the expressions for the end points of this range.
1465
1466 elsif Is_Real_Type (Etype (Right)) then
1467 declare
1468 Leftval : constant Ureal := Expr_Value_R (Left);
1469
1470 begin
1471 Result := Expr_Value_R (Lo) <= Leftval
1472 and then Leftval <= Expr_Value_R (Hi);
1473 end;
1474
1475 else
1476 declare
1477 Leftval : constant Uint := Expr_Value (Left);
1478
1479 begin
1480 Result := Expr_Value (Lo) <= Leftval
1481 and then Leftval <= Expr_Value (Hi);
1482 end;
1483 end if;
1484
1485 if Nkind (N) = N_Not_In then
1486 Result := not Result;
1487 end if;
1488
1489 Fold_Uint (N, Test (Result));
1490 Warn_On_Known_Condition (N);
1491
1492 end Eval_Membership_Op;
1493
1494 ------------------------
1495 -- Eval_Named_Integer --
1496 ------------------------
1497
1498 procedure Eval_Named_Integer (N : Node_Id) is
1499 begin
1500 Fold_Uint (N,
1501 Expr_Value (Expression (Declaration_Node (Entity (N)))));
1502 end Eval_Named_Integer;
1503
1504 ---------------------
1505 -- Eval_Named_Real --
1506 ---------------------
1507
1508 procedure Eval_Named_Real (N : Node_Id) is
1509 begin
1510 Fold_Ureal (N,
1511 Expr_Value_R (Expression (Declaration_Node (Entity (N)))));
1512 end Eval_Named_Real;
1513
1514 -------------------
1515 -- Eval_Op_Expon --
1516 -------------------
1517
1518 -- Exponentiation is a static functions, so the result is potentially
1519 -- static if both operands are potentially static (RM 4.9(7), 4.9(20)).
1520
1521 procedure Eval_Op_Expon (N : Node_Id) is
1522 Left : constant Node_Id := Left_Opnd (N);
1523 Right : constant Node_Id := Right_Opnd (N);
1524 Stat : Boolean;
1525 Fold : Boolean;
1526
1527 begin
1528 -- If not foldable we are done
1529
1530 Test_Expression_Is_Foldable (N, Left, Right, Stat, Fold);
1531
1532 if not Fold then
1533 return;
1534 end if;
1535
1536 -- Fold exponentiation operation
1537
1538 declare
1539 Right_Int : constant Uint := Expr_Value (Right);
1540
1541 begin
1542 -- Integer case
1543
1544 if Is_Integer_Type (Etype (Left)) then
1545 declare
1546 Left_Int : constant Uint := Expr_Value (Left);
1547 Result : Uint;
1548
1549 begin
1550 -- Exponentiation of an integer raises the exception
1551 -- Constraint_Error for a negative exponent (RM 4.5.6)
1552
1553 if Right_Int < 0 then
1554 Apply_Compile_Time_Constraint_Error
1555 (N, "integer exponent negative");
1556 return;
1557
1558 else
1559 if OK_Bits (N, Num_Bits (Left_Int) * Right_Int) then
1560 Result := Left_Int ** Right_Int;
1561 else
1562 Result := Left_Int;
1563 end if;
1564
1565 if Is_Modular_Integer_Type (Etype (N)) then
1566 Result := Result mod Modulus (Etype (N));
1567 end if;
1568
1569 Fold_Uint (N, Result);
1570 end if;
1571 end;
1572
1573 -- Real case
1574
1575 else
1576 declare
1577 Left_Real : constant Ureal := Expr_Value_R (Left);
1578
1579 begin
1580 -- Cannot have a zero base with a negative exponent
1581
1582 if UR_Is_Zero (Left_Real) then
1583
1584 if Right_Int < 0 then
1585 Apply_Compile_Time_Constraint_Error
1586 (N, "zero ** negative integer");
1587 return;
1588 else
1589 Fold_Ureal (N, Ureal_0);
1590 end if;
1591
1592 else
1593 Fold_Ureal (N, Left_Real ** Right_Int);
1594 end if;
1595 end;
1596 end if;
1597
1598 Set_Is_Static_Expression (N, Stat);
1599 end;
1600 end Eval_Op_Expon;
1601
1602 -----------------
1603 -- Eval_Op_Not --
1604 -----------------
1605
1606 -- The not operation is a static functions, so the result is potentially
1607 -- static if the operand is potentially static (RM 4.9(7), 4.9(20)).
1608
1609 procedure Eval_Op_Not (N : Node_Id) is
1610 Right : constant Node_Id := Right_Opnd (N);
1611 Stat : Boolean;
1612 Fold : Boolean;
1613
1614 begin
1615 -- If not foldable we are done
1616
1617 Test_Expression_Is_Foldable (N, Right, Stat, Fold);
1618
1619 if not Fold then
1620 return;
1621 end if;
1622
1623 -- Fold not operation
1624
1625 declare
1626 Rint : constant Uint := Expr_Value (Right);
1627 Typ : constant Entity_Id := Etype (N);
1628
1629 begin
1630 -- Negation is equivalent to subtracting from the modulus minus
1631 -- one. For a binary modulus this is equivalent to the ones-
1632 -- component of the original value. For non-binary modulus this
1633 -- is an arbitrary but consistent definition.
1634
1635 if Is_Modular_Integer_Type (Typ) then
1636 Fold_Uint (N, Modulus (Typ) - 1 - Rint);
1637
1638 else
1639 pragma Assert (Is_Boolean_Type (Typ));
1640 Fold_Uint (N, Test (not Is_True (Rint)));
1641 end if;
1642
1643 Set_Is_Static_Expression (N, Stat);
1644 end;
1645 end Eval_Op_Not;
1646
1647 -------------------------------
1648 -- Eval_Qualified_Expression --
1649 -------------------------------
1650
1651 -- A qualified expression is potentially static if its subtype mark denotes
1652 -- a static subtype and its expression is potentially static (RM 4.9 (11)).
1653
1654 procedure Eval_Qualified_Expression (N : Node_Id) is
1655 Operand : constant Node_Id := Expression (N);
1656 Target_Type : constant Entity_Id := Entity (Subtype_Mark (N));
1657
1658 Stat : Boolean;
1659 Fold : Boolean;
1660
1661 begin
1662 -- Can only fold if target is string or scalar and subtype is static
1663 -- Also, do not fold if our parent is an allocator (this is because
1664 -- the qualified expression is really part of the syntactic structure
1665 -- of an allocator, and we do not want to end up with something that
1666 -- corresponds to "new 1" where the 1 is the result of folding a
1667 -- qualified expression).
1668
1669 if not Is_Static_Subtype (Target_Type)
1670 or else Nkind (Parent (N)) = N_Allocator
1671 then
1672 Check_Non_Static_Context (Operand);
1673 return;
1674 end if;
1675
1676 -- If not foldable we are done
1677
1678 Test_Expression_Is_Foldable (N, Operand, Stat, Fold);
1679
1680 if not Fold then
1681 return;
1682
1683 -- Don't try fold if target type has constraint error bounds
1684
1685 elsif not Is_OK_Static_Subtype (Target_Type) then
1686 Set_Raises_Constraint_Error (N);
1687 return;
1688 end if;
1689
1690 -- Fold the result of qualification
1691
1692 if Is_Discrete_Type (Target_Type) then
1693 Fold_Uint (N, Expr_Value (Operand));
1694 Set_Is_Static_Expression (N, Stat);
1695
1696 elsif Is_Real_Type (Target_Type) then
1697 Fold_Ureal (N, Expr_Value_R (Operand));
1698 Set_Is_Static_Expression (N, Stat);
1699
1700 else
1701 Fold_Str (N, Strval (Get_String_Val (Operand)));
1702
1703 if not Stat then
1704 Set_Is_Static_Expression (N, False);
1705 else
1706 Check_String_Literal_Length (N, Target_Type);
1707 end if;
1708
1709 return;
1710 end if;
1711
1712 if Is_Out_Of_Range (N, Etype (N)) then
1713 Out_Of_Range (N);
1714 end if;
1715
1716 end Eval_Qualified_Expression;
1717
1718 -----------------------
1719 -- Eval_Real_Literal --
1720 -----------------------
1721
1722 -- Numeric literals are static (RM 4.9(1)), and have already been marked
1723 -- as static by the analyzer. The reason we did it that early is to allow
1724 -- the possibility of turning off the Is_Static_Expression flag after
1725 -- analysis, but before resolution, when integer literals are generated
1726 -- in the expander that do not correspond to static expressions.
1727
1728 procedure Eval_Real_Literal (N : Node_Id) is
1729 begin
1730 -- If the literal appears in a non-expression context, then it is
1731 -- certainly appearing in a non-static context, so check it.
1732
1733 if Nkind (Parent (N)) not in N_Subexpr then
1734 Check_Non_Static_Context (N);
1735 end if;
1736
1737 end Eval_Real_Literal;
1738
1739 ------------------------
1740 -- Eval_Relational_Op --
1741 ------------------------
1742
1743 -- Relational operations are static functions, so the result is static
1744 -- if both operands are static (RM 4.9(7), 4.9(20)).
1745
1746 procedure Eval_Relational_Op (N : Node_Id) is
1747 Left : constant Node_Id := Left_Opnd (N);
1748 Right : constant Node_Id := Right_Opnd (N);
1749 Typ : constant Entity_Id := Etype (Left);
1750 Result : Boolean;
1751 Stat : Boolean;
1752 Fold : Boolean;
1753
1754 begin
1755 -- One special case to deal with first. If we can tell that
1756 -- the result will be false because the lengths of one or
1757 -- more index subtypes are compile time known and different,
1758 -- then we can replace the entire result by False. We only
1759 -- do this for one dimensional arrays, because the case of
1760 -- multi-dimensional arrays is rare and too much trouble!
1761
1762 if Is_Array_Type (Typ)
1763 and then Number_Dimensions (Typ) = 1
1764 and then (Nkind (N) = N_Op_Eq
1765 or else Nkind (N) = N_Op_Ne)
1766 then
1767 if Raises_Constraint_Error (Left)
1768 or else Raises_Constraint_Error (Right)
1769 then
1770 return;
1771 end if;
1772
1773 declare
1774 procedure Get_Static_Length (Op : Node_Id; Len : out Uint);
1775 -- If Op is an expression for a constrained array with a
1776 -- known at compile time length, then Len is set to this
1777 -- (non-negative length). Otherwise Len is set to minus 1.
1778
1779 procedure Get_Static_Length (Op : Node_Id; Len : out Uint) is
1780 T : Entity_Id;
1781
1782 begin
1783 if Nkind (Op) = N_String_Literal then
1784 Len := UI_From_Int (String_Length (Strval (Op)));
1785
1786 elsif not Is_Constrained (Etype (Op)) then
1787 Len := Uint_Minus_1;
1788
1789 else
1790 T := Etype (First_Index (Etype (Op)));
1791
1792 if Is_Discrete_Type (T)
1793 and then
1794 Compile_Time_Known_Value (Type_Low_Bound (T))
1795 and then
1796 Compile_Time_Known_Value (Type_High_Bound (T))
1797 then
1798 Len := UI_Max (Uint_0,
1799 Expr_Value (Type_High_Bound (T)) -
1800 Expr_Value (Type_Low_Bound (T)) + 1);
1801 else
1802 Len := Uint_Minus_1;
1803 end if;
1804 end if;
1805 end Get_Static_Length;
1806
1807 Len_L : Uint;
1808 Len_R : Uint;
1809
1810 begin
1811 Get_Static_Length (Left, Len_L);
1812 Get_Static_Length (Right, Len_R);
1813
1814 if Len_L /= Uint_Minus_1
1815 and then Len_R /= Uint_Minus_1
1816 and then Len_L /= Len_R
1817 then
1818 Fold_Uint (N, Test (Nkind (N) = N_Op_Ne));
1819 Set_Is_Static_Expression (N, False);
1820 Warn_On_Known_Condition (N);
1821 return;
1822 end if;
1823 end;
1824 end if;
1825
1826 -- Can only fold if type is scalar (don't fold string ops)
1827
1828 if not Is_Scalar_Type (Typ) then
1829 Check_Non_Static_Context (Left);
1830 Check_Non_Static_Context (Right);
1831 return;
1832 end if;
1833
1834 -- If not foldable we are done
1835
1836 Test_Expression_Is_Foldable (N, Left, Right, Stat, Fold);
1837
1838 if not Fold then
1839 return;
1840 end if;
1841
1842 -- Integer and Enumeration (discrete) type cases
1843
1844 if Is_Discrete_Type (Typ) then
1845 declare
1846 Left_Int : constant Uint := Expr_Value (Left);
1847 Right_Int : constant Uint := Expr_Value (Right);
1848
1849 begin
1850 case Nkind (N) is
1851 when N_Op_Eq => Result := Left_Int = Right_Int;
1852 when N_Op_Ne => Result := Left_Int /= Right_Int;
1853 when N_Op_Lt => Result := Left_Int < Right_Int;
1854 when N_Op_Le => Result := Left_Int <= Right_Int;
1855 when N_Op_Gt => Result := Left_Int > Right_Int;
1856 when N_Op_Ge => Result := Left_Int >= Right_Int;
1857
1858 when others =>
1859 raise Program_Error;
1860 end case;
1861
1862 Fold_Uint (N, Test (Result));
1863 end;
1864
1865 -- Real type case
1866
1867 else
1868 pragma Assert (Is_Real_Type (Typ));
1869
1870 declare
1871 Left_Real : constant Ureal := Expr_Value_R (Left);
1872 Right_Real : constant Ureal := Expr_Value_R (Right);
1873
1874 begin
1875 case Nkind (N) is
1876 when N_Op_Eq => Result := (Left_Real = Right_Real);
1877 when N_Op_Ne => Result := (Left_Real /= Right_Real);
1878 when N_Op_Lt => Result := (Left_Real < Right_Real);
1879 when N_Op_Le => Result := (Left_Real <= Right_Real);
1880 when N_Op_Gt => Result := (Left_Real > Right_Real);
1881 when N_Op_Ge => Result := (Left_Real >= Right_Real);
1882
1883 when others =>
1884 raise Program_Error;
1885 end case;
1886
1887 Fold_Uint (N, Test (Result));
1888 end;
1889 end if;
1890
1891 Set_Is_Static_Expression (N, Stat);
1892 Warn_On_Known_Condition (N);
1893 end Eval_Relational_Op;
1894
1895 ----------------
1896 -- Eval_Shift --
1897 ----------------
1898
1899 -- Shift operations are intrinsic operations that can never be static,
1900 -- so the only processing required is to perform the required check for
1901 -- a non static context for the two operands.
1902
1903 -- Actually we could do some compile time evaluation here some time ???
1904
1905 procedure Eval_Shift (N : Node_Id) is
1906 begin
1907 Check_Non_Static_Context (Left_Opnd (N));
1908 Check_Non_Static_Context (Right_Opnd (N));
1909 end Eval_Shift;
1910
1911 ------------------------
1912 -- Eval_Short_Circuit --
1913 ------------------------
1914
1915 -- A short circuit operation is potentially static if both operands
1916 -- are potentially static (RM 4.9 (13))
1917
1918 procedure Eval_Short_Circuit (N : Node_Id) is
1919 Kind : constant Node_Kind := Nkind (N);
1920 Left : constant Node_Id := Left_Opnd (N);
1921 Right : constant Node_Id := Right_Opnd (N);
1922 Left_Int : Uint;
1923 Rstat : constant Boolean :=
1924 Is_Static_Expression (Left)
1925 and then Is_Static_Expression (Right);
1926
1927 begin
1928 -- Short circuit operations are never static in Ada 83
1929
1930 if Ada_83
1931 and then Comes_From_Source (N)
1932 then
1933 Check_Non_Static_Context (Left);
1934 Check_Non_Static_Context (Right);
1935 return;
1936 end if;
1937
1938 -- Now look at the operands, we can't quite use the normal call to
1939 -- Test_Expression_Is_Foldable here because short circuit operations
1940 -- are a special case, they can still be foldable, even if the right
1941 -- operand raises constraint error.
1942
1943 -- If either operand is Any_Type, just propagate to result and
1944 -- do not try to fold, this prevents cascaded errors.
1945
1946 if Etype (Left) = Any_Type or else Etype (Right) = Any_Type then
1947 Set_Etype (N, Any_Type);
1948 return;
1949
1950 -- If left operand raises constraint error, then replace node N with
1951 -- the raise constraint error node, and we are obviously not foldable.
1952 -- Is_Static_Expression is set from the two operands in the normal way,
1953 -- and we check the right operand if it is in a non-static context.
1954
1955 elsif Raises_Constraint_Error (Left) then
1956 if not Rstat then
1957 Check_Non_Static_Context (Right);
1958 end if;
1959
1960 Rewrite_In_Raise_CE (N, Left);
1961 Set_Is_Static_Expression (N, Rstat);
1962 return;
1963
1964 -- If the result is not static, then we won't in any case fold
1965
1966 elsif not Rstat then
1967 Check_Non_Static_Context (Left);
1968 Check_Non_Static_Context (Right);
1969 return;
1970 end if;
1971
1972 -- Here the result is static, note that, unlike the normal processing
1973 -- in Test_Expression_Is_Foldable, we did *not* check above to see if
1974 -- the right operand raises constraint error, that's because it is not
1975 -- significant if the left operand is decisive.
1976
1977 Set_Is_Static_Expression (N);
1978
1979 -- It does not matter if the right operand raises constraint error if
1980 -- it will not be evaluated. So deal specially with the cases where
1981 -- the right operand is not evaluated. Note that we will fold these
1982 -- cases even if the right operand is non-static, which is fine, but
1983 -- of course in these cases the result is not potentially static.
1984
1985 Left_Int := Expr_Value (Left);
1986
1987 if (Kind = N_And_Then and then Is_False (Left_Int))
1988 or else (Kind = N_Or_Else and Is_True (Left_Int))
1989 then
1990 Fold_Uint (N, Left_Int);
1991 return;
1992 end if;
1993
1994 -- If first operand not decisive, then it does matter if the right
1995 -- operand raises constraint error, since it will be evaluated, so
1996 -- we simply replace the node with the right operand. Note that this
1997 -- properly propagates Is_Static_Expression and Raises_Constraint_Error
1998 -- (both are set to True in Right).
1999
2000 if Raises_Constraint_Error (Right) then
2001 Rewrite_In_Raise_CE (N, Right);
2002 Check_Non_Static_Context (Left);
2003 return;
2004 end if;
2005
2006 -- Otherwise the result depends on the right operand
2007
2008 Fold_Uint (N, Expr_Value (Right));
2009 return;
2010
2011 end Eval_Short_Circuit;
2012
2013 ----------------
2014 -- Eval_Slice --
2015 ----------------
2016
2017 -- Slices can never be static, so the only processing required is to
2018 -- check for non-static context if an explicit range is given.
2019
2020 procedure Eval_Slice (N : Node_Id) is
2021 Drange : constant Node_Id := Discrete_Range (N);
2022
2023 begin
2024 if Nkind (Drange) = N_Range then
2025 Check_Non_Static_Context (Low_Bound (Drange));
2026 Check_Non_Static_Context (High_Bound (Drange));
2027 end if;
2028 end Eval_Slice;
2029
2030 -------------------------
2031 -- Eval_String_Literal --
2032 -------------------------
2033
2034 procedure Eval_String_Literal (N : Node_Id) is
2035 T : constant Entity_Id := Etype (N);
2036 B : constant Entity_Id := Base_Type (T);
2037 I : Entity_Id;
2038
2039 begin
2040 -- Nothing to do if error type (handles cases like default expressions
2041 -- or generics where we have not yet fully resolved the type)
2042
2043 if B = Any_Type or else B = Any_String then
2044 return;
2045
2046 -- String literals are static if the subtype is static (RM 4.9(2)), so
2047 -- reset the static expression flag (it was set unconditionally in
2048 -- Analyze_String_Literal) if the subtype is non-static. We tell if
2049 -- the subtype is static by looking at the lower bound.
2050
2051 elsif not Is_OK_Static_Expression (String_Literal_Low_Bound (T)) then
2052 Set_Is_Static_Expression (N, False);
2053
2054 elsif Nkind (Original_Node (N)) = N_Type_Conversion then
2055 Set_Is_Static_Expression (N, False);
2056
2057 -- Test for illegal Ada 95 cases. A string literal is illegal in
2058 -- Ada 95 if its bounds are outside the index base type and this
2059 -- index type is static. This can hapen in only two ways. Either
2060 -- the string literal is too long, or it is null, and the lower
2061 -- bound is type'First. In either case it is the upper bound that
2062 -- is out of range of the index type.
2063
2064 elsif Ada_95 then
2065 if Root_Type (B) = Standard_String
2066 or else Root_Type (B) = Standard_Wide_String
2067 then
2068 I := Standard_Positive;
2069 else
2070 I := Etype (First_Index (B));
2071 end if;
2072
2073 if String_Literal_Length (T) > String_Type_Len (B) then
2074 Apply_Compile_Time_Constraint_Error
2075 (N, "string literal too long for}",
2076 Ent => B,
2077 Typ => First_Subtype (B));
2078
2079 elsif String_Literal_Length (T) = 0
2080 and then not Is_Generic_Type (I)
2081 and then Expr_Value (String_Literal_Low_Bound (T)) =
2082 Expr_Value (Type_Low_Bound (Base_Type (I)))
2083 then
2084 Apply_Compile_Time_Constraint_Error
2085 (N, "null string literal not allowed for}",
2086 Ent => B,
2087 Typ => First_Subtype (B));
2088 end if;
2089 end if;
2090
2091 end Eval_String_Literal;
2092
2093 --------------------------
2094 -- Eval_Type_Conversion --
2095 --------------------------
2096
2097 -- A type conversion is potentially static if its subtype mark is for a
2098 -- static scalar subtype, and its operand expression is potentially static
2099 -- (RM 4.9 (10))
2100
2101 procedure Eval_Type_Conversion (N : Node_Id) is
2102 Operand : constant Node_Id := Expression (N);
2103 Source_Type : constant Entity_Id := Etype (Operand);
2104 Target_Type : constant Entity_Id := Etype (N);
2105
2106 Stat : Boolean;
2107 Fold : Boolean;
2108
2109 function To_Be_Treated_As_Integer (T : Entity_Id) return Boolean;
2110 -- Returns true if type T is an integer type, or if it is a
2111 -- fixed-point type to be treated as an integer (i.e. the flag
2112 -- Conversion_OK is set on the conversion node).
2113
2114 function To_Be_Treated_As_Real (T : Entity_Id) return Boolean;
2115 -- Returns true if type T is a floating-point type, or if it is a
2116 -- fixed-point type that is not to be treated as an integer (i.e. the
2117 -- flag Conversion_OK is not set on the conversion node).
2118
2119 function To_Be_Treated_As_Integer (T : Entity_Id) return Boolean is
2120 begin
2121 return
2122 Is_Integer_Type (T)
2123 or else (Is_Fixed_Point_Type (T) and then Conversion_OK (N));
2124 end To_Be_Treated_As_Integer;
2125
2126 function To_Be_Treated_As_Real (T : Entity_Id) return Boolean is
2127 begin
2128 return
2129 Is_Floating_Point_Type (T)
2130 or else (Is_Fixed_Point_Type (T) and then not Conversion_OK (N));
2131 end To_Be_Treated_As_Real;
2132
2133 -- Start of processing for Eval_Type_Conversion
2134
2135 begin
2136 -- Cannot fold if target type is non-static or if semantic error.
2137
2138 if not Is_Static_Subtype (Target_Type) then
2139 Check_Non_Static_Context (Operand);
2140 return;
2141
2142 elsif Error_Posted (N) then
2143 return;
2144 end if;
2145
2146 -- If not foldable we are done
2147
2148 Test_Expression_Is_Foldable (N, Operand, Stat, Fold);
2149
2150 if not Fold then
2151 return;
2152
2153 -- Don't try fold if target type has constraint error bounds
2154
2155 elsif not Is_OK_Static_Subtype (Target_Type) then
2156 Set_Raises_Constraint_Error (N);
2157 return;
2158 end if;
2159
2160 -- Remaining processing depends on operand types. Note that in the
2161 -- following type test, fixed-point counts as real unless the flag
2162 -- Conversion_OK is set, in which case it counts as integer.
2163
2164 -- Fold conversion, case of string type. The result is not static.
2165
2166 if Is_String_Type (Target_Type) then
2167 Fold_Str (N, Strval (Get_String_Val (Operand)));
2168 Set_Is_Static_Expression (N, False);
2169
2170 return;
2171
2172 -- Fold conversion, case of integer target type
2173
2174 elsif To_Be_Treated_As_Integer (Target_Type) then
2175 declare
2176 Result : Uint;
2177
2178 begin
2179 -- Integer to integer conversion
2180
2181 if To_Be_Treated_As_Integer (Source_Type) then
2182 Result := Expr_Value (Operand);
2183
2184 -- Real to integer conversion
2185
2186 else
2187 Result := UR_To_Uint (Expr_Value_R (Operand));
2188 end if;
2189
2190 -- If fixed-point type (Conversion_OK must be set), then the
2191 -- result is logically an integer, but we must replace the
2192 -- conversion with the corresponding real literal, since the
2193 -- type from a semantic point of view is still fixed-point.
2194
2195 if Is_Fixed_Point_Type (Target_Type) then
2196 Fold_Ureal
2197 (N, UR_From_Uint (Result) * Small_Value (Target_Type));
2198
2199 -- Otherwise result is integer literal
2200
2201 else
2202 Fold_Uint (N, Result);
2203 end if;
2204 end;
2205
2206 -- Fold conversion, case of real target type
2207
2208 elsif To_Be_Treated_As_Real (Target_Type) then
2209 declare
2210 Result : Ureal;
2211
2212 begin
2213 if To_Be_Treated_As_Real (Source_Type) then
2214 Result := Expr_Value_R (Operand);
2215 else
2216 Result := UR_From_Uint (Expr_Value (Operand));
2217 end if;
2218
2219 Fold_Ureal (N, Result);
2220 end;
2221
2222 -- Enumeration types
2223
2224 else
2225 Fold_Uint (N, Expr_Value (Operand));
2226 end if;
2227
2228 Set_Is_Static_Expression (N, Stat);
2229
2230 if Is_Out_Of_Range (N, Etype (N)) then
2231 Out_Of_Range (N);
2232 end if;
2233
2234 end Eval_Type_Conversion;
2235
2236 -------------------
2237 -- Eval_Unary_Op --
2238 -------------------
2239
2240 -- Predefined unary operators are static functions (RM 4.9(20)) and thus
2241 -- are potentially static if the operand is potentially static (RM 4.9(7))
2242
2243 procedure Eval_Unary_Op (N : Node_Id) is
2244 Right : constant Node_Id := Right_Opnd (N);
2245 Stat : Boolean;
2246 Fold : Boolean;
2247
2248 begin
2249 -- If not foldable we are done
2250
2251 Test_Expression_Is_Foldable (N, Right, Stat, Fold);
2252
2253 if not Fold then
2254 return;
2255 end if;
2256
2257 -- Fold for integer case
2258
2259 if Is_Integer_Type (Etype (N)) then
2260 declare
2261 Rint : constant Uint := Expr_Value (Right);
2262 Result : Uint;
2263
2264 begin
2265 -- In the case of modular unary plus and abs there is no need
2266 -- to adjust the result of the operation since if the original
2267 -- operand was in bounds the result will be in the bounds of the
2268 -- modular type. However, in the case of modular unary minus the
2269 -- result may go out of the bounds of the modular type and needs
2270 -- adjustment.
2271
2272 if Nkind (N) = N_Op_Plus then
2273 Result := Rint;
2274
2275 elsif Nkind (N) = N_Op_Minus then
2276 if Is_Modular_Integer_Type (Etype (N)) then
2277 Result := (-Rint) mod Modulus (Etype (N));
2278 else
2279 Result := (-Rint);
2280 end if;
2281
2282 else
2283 pragma Assert (Nkind (N) = N_Op_Abs);
2284 Result := abs Rint;
2285 end if;
2286
2287 Fold_Uint (N, Result);
2288 end;
2289
2290 -- Fold for real case
2291
2292 elsif Is_Real_Type (Etype (N)) then
2293 declare
2294 Rreal : constant Ureal := Expr_Value_R (Right);
2295 Result : Ureal;
2296
2297 begin
2298 if Nkind (N) = N_Op_Plus then
2299 Result := Rreal;
2300
2301 elsif Nkind (N) = N_Op_Minus then
2302 Result := UR_Negate (Rreal);
2303
2304 else
2305 pragma Assert (Nkind (N) = N_Op_Abs);
2306 Result := abs Rreal;
2307 end if;
2308
2309 Fold_Ureal (N, Result);
2310 end;
2311 end if;
2312
2313 Set_Is_Static_Expression (N, Stat);
2314
2315 end Eval_Unary_Op;
2316
2317 -------------------------------
2318 -- Eval_Unchecked_Conversion --
2319 -------------------------------
2320
2321 -- Unchecked conversions can never be static, so the only required
2322 -- processing is to check for a non-static context for the operand.
2323
2324 procedure Eval_Unchecked_Conversion (N : Node_Id) is
2325 begin
2326 Check_Non_Static_Context (Expression (N));
2327 end Eval_Unchecked_Conversion;
2328
2329 --------------------
2330 -- Expr_Rep_Value --
2331 --------------------
2332
2333 function Expr_Rep_Value (N : Node_Id) return Uint is
2334 Kind : constant Node_Kind := Nkind (N);
2335 Ent : Entity_Id;
2336
2337 begin
2338 if Is_Entity_Name (N) then
2339 Ent := Entity (N);
2340
2341 -- An enumeration literal that was either in the source or
2342 -- created as a result of static evaluation.
2343
2344 if Ekind (Ent) = E_Enumeration_Literal then
2345 return Enumeration_Rep (Ent);
2346
2347 -- A user defined static constant
2348
2349 else
2350 pragma Assert (Ekind (Ent) = E_Constant);
2351 return Expr_Rep_Value (Constant_Value (Ent));
2352 end if;
2353
2354 -- An integer literal that was either in the source or created
2355 -- as a result of static evaluation.
2356
2357 elsif Kind = N_Integer_Literal then
2358 return Intval (N);
2359
2360 -- A real literal for a fixed-point type. This must be the fixed-point
2361 -- case, either the literal is of a fixed-point type, or it is a bound
2362 -- of a fixed-point type, with type universal real. In either case we
2363 -- obtain the desired value from Corresponding_Integer_Value.
2364
2365 elsif Kind = N_Real_Literal then
2366
2367 -- Apply the assertion to the Underlying_Type of the literal for
2368 -- the benefit of calls to this function in the JGNAT back end,
2369 -- where literal types can reflect private views.
2370
2371 pragma Assert (Is_Fixed_Point_Type (Underlying_Type (Etype (N))));
2372 return Corresponding_Integer_Value (N);
2373
2374 else
2375 pragma Assert (Kind = N_Character_Literal);
2376 Ent := Entity (N);
2377
2378 -- Since Character literals of type Standard.Character don't
2379 -- have any defining character literals built for them, they
2380 -- do not have their Entity set, so just use their Char
2381 -- code. Otherwise for user-defined character literals use
2382 -- their Pos value as usual which is the same as the Rep value.
2383
2384 if No (Ent) then
2385 return UI_From_Int (Int (Char_Literal_Value (N)));
2386 else
2387 return Enumeration_Rep (Ent);
2388 end if;
2389 end if;
2390 end Expr_Rep_Value;
2391
2392 ----------------
2393 -- Expr_Value --
2394 ----------------
2395
2396 function Expr_Value (N : Node_Id) return Uint is
2397 Kind : constant Node_Kind := Nkind (N);
2398 Ent : Entity_Id;
2399
2400 begin
2401 if Is_Entity_Name (N) then
2402 Ent := Entity (N);
2403
2404 -- An enumeration literal that was either in the source or
2405 -- created as a result of static evaluation.
2406
2407 if Ekind (Ent) = E_Enumeration_Literal then
2408 return Enumeration_Pos (Ent);
2409
2410 -- A user defined static constant
2411
2412 else
2413 pragma Assert (Ekind (Ent) = E_Constant);
2414 return Expr_Value (Constant_Value (Ent));
2415 end if;
2416
2417 -- An integer literal that was either in the source or created
2418 -- as a result of static evaluation.
2419
2420 elsif Kind = N_Integer_Literal then
2421 return Intval (N);
2422
2423 -- A real literal for a fixed-point type. This must be the fixed-point
2424 -- case, either the literal is of a fixed-point type, or it is a bound
2425 -- of a fixed-point type, with type universal real. In either case we
2426 -- obtain the desired value from Corresponding_Integer_Value.
2427
2428 elsif Kind = N_Real_Literal then
2429
2430 -- Apply the assertion to the Underlying_Type of the literal for
2431 -- the benefit of calls to this function in the JGNAT back end,
2432 -- where literal types can reflect private views.
2433
2434 pragma Assert (Is_Fixed_Point_Type (Underlying_Type (Etype (N))));
2435 return Corresponding_Integer_Value (N);
2436
2437 -- Peculiar VMS case, if we have xxx'Null_Parameter, return zero
2438
2439 elsif Kind = N_Attribute_Reference
2440 and then Attribute_Name (N) = Name_Null_Parameter
2441 then
2442 return Uint_0;
2443
2444 -- Otherwise must be character literal
2445
2446 else
2447 pragma Assert (Kind = N_Character_Literal);
2448 Ent := Entity (N);
2449
2450 -- Since Character literals of type Standard.Character don't
2451 -- have any defining character literals built for them, they
2452 -- do not have their Entity set, so just use their Char
2453 -- code. Otherwise for user-defined character literals use
2454 -- their Pos value as usual.
2455
2456 if No (Ent) then
2457 return UI_From_Int (Int (Char_Literal_Value (N)));
2458 else
2459 return Enumeration_Pos (Ent);
2460 end if;
2461 end if;
2462
2463 end Expr_Value;
2464
2465 ------------------
2466 -- Expr_Value_E --
2467 ------------------
2468
2469 function Expr_Value_E (N : Node_Id) return Entity_Id is
2470 Ent : constant Entity_Id := Entity (N);
2471
2472 begin
2473 if Ekind (Ent) = E_Enumeration_Literal then
2474 return Ent;
2475 else
2476 pragma Assert (Ekind (Ent) = E_Constant);
2477 return Expr_Value_E (Constant_Value (Ent));
2478 end if;
2479 end Expr_Value_E;
2480
2481 ------------------
2482 -- Expr_Value_R --
2483 ------------------
2484
2485 function Expr_Value_R (N : Node_Id) return Ureal is
2486 Kind : constant Node_Kind := Nkind (N);
2487 Ent : Entity_Id;
2488 Expr : Node_Id;
2489
2490 begin
2491 if Kind = N_Real_Literal then
2492 return Realval (N);
2493
2494 elsif Kind = N_Identifier or else Kind = N_Expanded_Name then
2495 Ent := Entity (N);
2496 pragma Assert (Ekind (Ent) = E_Constant);
2497 return Expr_Value_R (Constant_Value (Ent));
2498
2499 elsif Kind = N_Integer_Literal then
2500 return UR_From_Uint (Expr_Value (N));
2501
2502 -- Strange case of VAX literals, which are at this stage transformed
2503 -- into Vax_Type!x_To_y(IEEE_Literal). See Expand_N_Real_Literal in
2504 -- Exp_Vfpt for further details.
2505
2506 elsif Vax_Float (Etype (N))
2507 and then Nkind (N) = N_Unchecked_Type_Conversion
2508 then
2509 Expr := Expression (N);
2510
2511 if Nkind (Expr) = N_Function_Call
2512 and then Present (Parameter_Associations (Expr))
2513 then
2514 Expr := First (Parameter_Associations (Expr));
2515
2516 if Nkind (Expr) = N_Real_Literal then
2517 return Realval (Expr);
2518 end if;
2519 end if;
2520
2521 -- Peculiar VMS case, if we have xxx'Null_Parameter, return 0.0
2522
2523 elsif Kind = N_Attribute_Reference
2524 and then Attribute_Name (N) = Name_Null_Parameter
2525 then
2526 return Ureal_0;
2527 end if;
2528
2529 -- If we fall through, we have a node that cannot be interepreted
2530 -- as a compile time constant. That is definitely an error.
2531
2532 raise Program_Error;
2533 end Expr_Value_R;
2534
2535 ------------------
2536 -- Expr_Value_S --
2537 ------------------
2538
2539 function Expr_Value_S (N : Node_Id) return Node_Id is
2540 begin
2541 if Nkind (N) = N_String_Literal then
2542 return N;
2543 else
2544 pragma Assert (Ekind (Entity (N)) = E_Constant);
2545 return Expr_Value_S (Constant_Value (Entity (N)));
2546 end if;
2547 end Expr_Value_S;
2548
2549 --------------
2550 -- Fold_Str --
2551 --------------
2552
2553 procedure Fold_Str (N : Node_Id; Val : String_Id) is
2554 Loc : constant Source_Ptr := Sloc (N);
2555 Typ : constant Entity_Id := Etype (N);
2556
2557 begin
2558 Rewrite (N, Make_String_Literal (Loc, Strval => Val));
2559 Analyze_And_Resolve (N, Typ);
2560 end Fold_Str;
2561
2562 ---------------
2563 -- Fold_Uint --
2564 ---------------
2565
2566 procedure Fold_Uint (N : Node_Id; Val : Uint) is
2567 Loc : constant Source_Ptr := Sloc (N);
2568 Typ : constant Entity_Id := Etype (N);
2569
2570 begin
2571 -- For a result of type integer, subsitute an N_Integer_Literal node
2572 -- for the result of the compile time evaluation of the expression.
2573
2574 if Is_Integer_Type (Etype (N)) then
2575 Rewrite (N, Make_Integer_Literal (Loc, Val));
2576
2577 -- Otherwise we have an enumeration type, and we substitute either
2578 -- an N_Identifier or N_Character_Literal to represent the enumeration
2579 -- literal corresponding to the given value, which must always be in
2580 -- range, because appropriate tests have already been made for this.
2581
2582 else pragma Assert (Is_Enumeration_Type (Etype (N)));
2583 Rewrite (N, Get_Enum_Lit_From_Pos (Etype (N), Val, Loc));
2584 end if;
2585
2586 -- We now have the literal with the right value, both the actual type
2587 -- and the expected type of this literal are taken from the expression
2588 -- that was evaluated.
2589
2590 Analyze (N);
2591 Set_Etype (N, Typ);
2592 Resolve (N, Typ);
2593 end Fold_Uint;
2594
2595 ----------------
2596 -- Fold_Ureal --
2597 ----------------
2598
2599 procedure Fold_Ureal (N : Node_Id; Val : Ureal) is
2600 Loc : constant Source_Ptr := Sloc (N);
2601 Typ : constant Entity_Id := Etype (N);
2602
2603 begin
2604 Rewrite (N, Make_Real_Literal (Loc, Realval => Val));
2605 Analyze (N);
2606
2607 -- Both the actual and expected type comes from the original expression
2608
2609 Set_Etype (N, Typ);
2610 Resolve (N, Typ);
2611 end Fold_Ureal;
2612
2613 ---------------
2614 -- From_Bits --
2615 ---------------
2616
2617 function From_Bits (B : Bits; T : Entity_Id) return Uint is
2618 V : Uint := Uint_0;
2619
2620 begin
2621 for J in 0 .. B'Last loop
2622 if B (J) then
2623 V := V + 2 ** J;
2624 end if;
2625 end loop;
2626
2627 if Non_Binary_Modulus (T) then
2628 V := V mod Modulus (T);
2629 end if;
2630
2631 return V;
2632 end From_Bits;
2633
2634 --------------------
2635 -- Get_String_Val --
2636 --------------------
2637
2638 function Get_String_Val (N : Node_Id) return Node_Id is
2639 begin
2640 if Nkind (N) = N_String_Literal then
2641 return N;
2642
2643 elsif Nkind (N) = N_Character_Literal then
2644 return N;
2645
2646 else
2647 pragma Assert (Is_Entity_Name (N));
2648 return Get_String_Val (Constant_Value (Entity (N)));
2649 end if;
2650 end Get_String_Val;
2651
2652 --------------------
2653 -- In_Subrange_Of --
2654 --------------------
2655
2656 function In_Subrange_Of
2657 (T1 : Entity_Id;
2658 T2 : Entity_Id;
2659 Fixed_Int : Boolean := False)
2660 return Boolean
2661 is
2662 L1 : Node_Id;
2663 H1 : Node_Id;
2664
2665 L2 : Node_Id;
2666 H2 : Node_Id;
2667
2668 begin
2669 if T1 = T2 or else Is_Subtype_Of (T1, T2) then
2670 return True;
2671
2672 -- Never in range if both types are not scalar. Don't know if this can
2673 -- actually happen, but just in case.
2674
2675 elsif not Is_Scalar_Type (T1) or else not Is_Scalar_Type (T1) then
2676 return False;
2677
2678 else
2679 L1 := Type_Low_Bound (T1);
2680 H1 := Type_High_Bound (T1);
2681
2682 L2 := Type_Low_Bound (T2);
2683 H2 := Type_High_Bound (T2);
2684
2685 -- Check bounds to see if comparison possible at compile time
2686
2687 if Compile_Time_Compare (L1, L2) in Compare_GE
2688 and then
2689 Compile_Time_Compare (H1, H2) in Compare_LE
2690 then
2691 return True;
2692 end if;
2693
2694 -- If bounds not comparable at compile time, then the bounds of T2
2695 -- must be compile time known or we cannot answer the query.
2696
2697 if not Compile_Time_Known_Value (L2)
2698 or else not Compile_Time_Known_Value (H2)
2699 then
2700 return False;
2701 end if;
2702
2703 -- If the bounds of T1 are know at compile time then use these
2704 -- ones, otherwise use the bounds of the base type (which are of
2705 -- course always static).
2706
2707 if not Compile_Time_Known_Value (L1) then
2708 L1 := Type_Low_Bound (Base_Type (T1));
2709 end if;
2710
2711 if not Compile_Time_Known_Value (H1) then
2712 H1 := Type_High_Bound (Base_Type (T1));
2713 end if;
2714
2715 -- Fixed point types should be considered as such only if
2716 -- flag Fixed_Int is set to False.
2717
2718 if Is_Floating_Point_Type (T1) or else Is_Floating_Point_Type (T2)
2719 or else (Is_Fixed_Point_Type (T1) and then not Fixed_Int)
2720 or else (Is_Fixed_Point_Type (T2) and then not Fixed_Int)
2721 then
2722 return
2723 Expr_Value_R (L2) <= Expr_Value_R (L1)
2724 and then
2725 Expr_Value_R (H2) >= Expr_Value_R (H1);
2726
2727 else
2728 return
2729 Expr_Value (L2) <= Expr_Value (L1)
2730 and then
2731 Expr_Value (H2) >= Expr_Value (H1);
2732
2733 end if;
2734 end if;
2735
2736 -- If any exception occurs, it means that we have some bug in the compiler
2737 -- possibly triggered by a previous error, or by some unforseen peculiar
2738 -- occurrence. However, this is only an optimization attempt, so there is
2739 -- really no point in crashing the compiler. Instead we just decide, too
2740 -- bad, we can't figure out the answer in this case after all.
2741
2742 exception
2743 when others =>
2744
2745 -- Debug flag K disables this behavior (useful for debugging)
2746
2747 if Debug_Flag_K then
2748 raise;
2749 else
2750 return False;
2751 end if;
2752 end In_Subrange_Of;
2753
2754 -----------------
2755 -- Is_In_Range --
2756 -----------------
2757
2758 function Is_In_Range
2759 (N : Node_Id;
2760 Typ : Entity_Id;
2761 Fixed_Int : Boolean := False;
2762 Int_Real : Boolean := False)
2763 return Boolean
2764 is
2765 Val : Uint;
2766 Valr : Ureal;
2767
2768 begin
2769 -- Universal types have no range limits, so always in range.
2770
2771 if Typ = Universal_Integer or else Typ = Universal_Real then
2772 return True;
2773
2774 -- Never in range if not scalar type. Don't know if this can
2775 -- actually happen, but our spec allows it, so we must check!
2776
2777 elsif not Is_Scalar_Type (Typ) then
2778 return False;
2779
2780 -- Never in range unless we have a compile time known value.
2781
2782 elsif not Compile_Time_Known_Value (N) then
2783 return False;
2784
2785 else
2786 declare
2787 Lo : constant Node_Id := Type_Low_Bound (Typ);
2788 Hi : constant Node_Id := Type_High_Bound (Typ);
2789 LB_Known : constant Boolean := Compile_Time_Known_Value (Lo);
2790 UB_Known : constant Boolean := Compile_Time_Known_Value (Hi);
2791
2792 begin
2793 -- Fixed point types should be considered as such only in
2794 -- flag Fixed_Int is set to False.
2795
2796 if Is_Floating_Point_Type (Typ)
2797 or else (Is_Fixed_Point_Type (Typ) and then not Fixed_Int)
2798 or else Int_Real
2799 then
2800 Valr := Expr_Value_R (N);
2801
2802 if LB_Known and then Valr >= Expr_Value_R (Lo)
2803 and then UB_Known and then Valr <= Expr_Value_R (Hi)
2804 then
2805 return True;
2806 else
2807 return False;
2808 end if;
2809
2810 else
2811 Val := Expr_Value (N);
2812
2813 if LB_Known and then Val >= Expr_Value (Lo)
2814 and then UB_Known and then Val <= Expr_Value (Hi)
2815 then
2816 return True;
2817 else
2818 return False;
2819 end if;
2820 end if;
2821 end;
2822 end if;
2823 end Is_In_Range;
2824
2825 -------------------
2826 -- Is_Null_Range --
2827 -------------------
2828
2829 function Is_Null_Range (Lo : Node_Id; Hi : Node_Id) return Boolean is
2830 Typ : constant Entity_Id := Etype (Lo);
2831
2832 begin
2833 if not Compile_Time_Known_Value (Lo)
2834 or else not Compile_Time_Known_Value (Hi)
2835 then
2836 return False;
2837 end if;
2838
2839 if Is_Discrete_Type (Typ) then
2840 return Expr_Value (Lo) > Expr_Value (Hi);
2841
2842 else
2843 pragma Assert (Is_Real_Type (Typ));
2844 return Expr_Value_R (Lo) > Expr_Value_R (Hi);
2845 end if;
2846 end Is_Null_Range;
2847
2848 -----------------------------
2849 -- Is_OK_Static_Expression --
2850 -----------------------------
2851
2852 function Is_OK_Static_Expression (N : Node_Id) return Boolean is
2853 begin
2854 return Is_Static_Expression (N)
2855 and then not Raises_Constraint_Error (N);
2856 end Is_OK_Static_Expression;
2857
2858 ------------------------
2859 -- Is_OK_Static_Range --
2860 ------------------------
2861
2862 -- A static range is a range whose bounds are static expressions, or a
2863 -- Range_Attribute_Reference equivalent to such a range (RM 4.9(26)).
2864 -- We have already converted range attribute references, so we get the
2865 -- "or" part of this rule without needing a special test.
2866
2867 function Is_OK_Static_Range (N : Node_Id) return Boolean is
2868 begin
2869 return Is_OK_Static_Expression (Low_Bound (N))
2870 and then Is_OK_Static_Expression (High_Bound (N));
2871 end Is_OK_Static_Range;
2872
2873 --------------------------
2874 -- Is_OK_Static_Subtype --
2875 --------------------------
2876
2877 -- Determines if Typ is a static subtype as defined in (RM 4.9(26))
2878 -- where neither bound raises constraint error when evaluated.
2879
2880 function Is_OK_Static_Subtype (Typ : Entity_Id) return Boolean is
2881 Base_T : constant Entity_Id := Base_Type (Typ);
2882 Anc_Subt : Entity_Id;
2883
2884 begin
2885 -- First a quick check on the non static subtype flag. As described
2886 -- in further detail in Einfo, this flag is not decisive in all cases,
2887 -- but if it is set, then the subtype is definitely non-static.
2888
2889 if Is_Non_Static_Subtype (Typ) then
2890 return False;
2891 end if;
2892
2893 Anc_Subt := Ancestor_Subtype (Typ);
2894
2895 if Anc_Subt = Empty then
2896 Anc_Subt := Base_T;
2897 end if;
2898
2899 if Is_Generic_Type (Root_Type (Base_T))
2900 or else Is_Generic_Actual_Type (Base_T)
2901 then
2902 return False;
2903
2904 -- String types
2905
2906 elsif Is_String_Type (Typ) then
2907 return
2908 Ekind (Typ) = E_String_Literal_Subtype
2909 or else
2910 (Is_OK_Static_Subtype (Component_Type (Typ))
2911 and then Is_OK_Static_Subtype (Etype (First_Index (Typ))));
2912
2913 -- Scalar types
2914
2915 elsif Is_Scalar_Type (Typ) then
2916 if Base_T = Typ then
2917 return True;
2918
2919 else
2920 -- Scalar_Range (Typ) might be an N_Subtype_Indication, so
2921 -- use Get_Type_Low,High_Bound.
2922
2923 return Is_OK_Static_Subtype (Anc_Subt)
2924 and then Is_OK_Static_Expression (Type_Low_Bound (Typ))
2925 and then Is_OK_Static_Expression (Type_High_Bound (Typ));
2926 end if;
2927
2928 -- Types other than string and scalar types are never static
2929
2930 else
2931 return False;
2932 end if;
2933 end Is_OK_Static_Subtype;
2934
2935 ---------------------
2936 -- Is_Out_Of_Range --
2937 ---------------------
2938
2939 function Is_Out_Of_Range
2940 (N : Node_Id;
2941 Typ : Entity_Id;
2942 Fixed_Int : Boolean := False;
2943 Int_Real : Boolean := False)
2944 return Boolean
2945 is
2946 Val : Uint;
2947 Valr : Ureal;
2948
2949 begin
2950 -- Universal types have no range limits, so always in range.
2951
2952 if Typ = Universal_Integer or else Typ = Universal_Real then
2953 return False;
2954
2955 -- Never out of range if not scalar type. Don't know if this can
2956 -- actually happen, but our spec allows it, so we must check!
2957
2958 elsif not Is_Scalar_Type (Typ) then
2959 return False;
2960
2961 -- Never out of range if this is a generic type, since the bounds
2962 -- of generic types are junk. Note that if we only checked for
2963 -- static expressions (instead of compile time known values) below,
2964 -- we would not need this check, because values of a generic type
2965 -- can never be static, but they can be known at compile time.
2966
2967 elsif Is_Generic_Type (Typ) then
2968 return False;
2969
2970 -- Never out of range unless we have a compile time known value.
2971
2972 elsif not Compile_Time_Known_Value (N) then
2973 return False;
2974
2975 else
2976 declare
2977 Lo : constant Node_Id := Type_Low_Bound (Typ);
2978 Hi : constant Node_Id := Type_High_Bound (Typ);
2979 LB_Known : constant Boolean := Compile_Time_Known_Value (Lo);
2980 UB_Known : constant Boolean := Compile_Time_Known_Value (Hi);
2981
2982 begin
2983 -- Real types (note that fixed-point types are not treated
2984 -- as being of a real type if the flag Fixed_Int is set,
2985 -- since in that case they are regarded as integer types).
2986
2987 if Is_Floating_Point_Type (Typ)
2988 or else (Is_Fixed_Point_Type (Typ) and then not Fixed_Int)
2989 or else Int_Real
2990 then
2991 Valr := Expr_Value_R (N);
2992
2993 if LB_Known and then Valr < Expr_Value_R (Lo) then
2994 return True;
2995
2996 elsif UB_Known and then Expr_Value_R (Hi) < Valr then
2997 return True;
2998
2999 else
3000 return False;
3001 end if;
3002
3003 else
3004 Val := Expr_Value (N);
3005
3006 if LB_Known and then Val < Expr_Value (Lo) then
3007 return True;
3008
3009 elsif UB_Known and then Expr_Value (Hi) < Val then
3010 return True;
3011
3012 else
3013 return False;
3014 end if;
3015 end if;
3016 end;
3017 end if;
3018 end Is_Out_Of_Range;
3019
3020 ---------------------
3021 -- Is_Static_Range --
3022 ---------------------
3023
3024 -- A static range is a range whose bounds are static expressions, or a
3025 -- Range_Attribute_Reference equivalent to such a range (RM 4.9(26)).
3026 -- We have already converted range attribute references, so we get the
3027 -- "or" part of this rule without needing a special test.
3028
3029 function Is_Static_Range (N : Node_Id) return Boolean is
3030 begin
3031 return Is_Static_Expression (Low_Bound (N))
3032 and then Is_Static_Expression (High_Bound (N));
3033 end Is_Static_Range;
3034
3035 -----------------------
3036 -- Is_Static_Subtype --
3037 -----------------------
3038
3039 -- Determines if Typ is a static subtype as defined in (RM 4.9(26)).
3040
3041 function Is_Static_Subtype (Typ : Entity_Id) return Boolean is
3042 Base_T : constant Entity_Id := Base_Type (Typ);
3043 Anc_Subt : Entity_Id;
3044
3045 begin
3046 -- First a quick check on the non static subtype flag. As described
3047 -- in further detail in Einfo, this flag is not decisive in all cases,
3048 -- but if it is set, then the subtype is definitely non-static.
3049
3050 if Is_Non_Static_Subtype (Typ) then
3051 return False;
3052 end if;
3053
3054 Anc_Subt := Ancestor_Subtype (Typ);
3055
3056 if Anc_Subt = Empty then
3057 Anc_Subt := Base_T;
3058 end if;
3059
3060 if Is_Generic_Type (Root_Type (Base_T))
3061 or else Is_Generic_Actual_Type (Base_T)
3062 then
3063 return False;
3064
3065 -- String types
3066
3067 elsif Is_String_Type (Typ) then
3068 return
3069 Ekind (Typ) = E_String_Literal_Subtype
3070 or else
3071 (Is_Static_Subtype (Component_Type (Typ))
3072 and then Is_Static_Subtype (Etype (First_Index (Typ))));
3073
3074 -- Scalar types
3075
3076 elsif Is_Scalar_Type (Typ) then
3077 if Base_T = Typ then
3078 return True;
3079
3080 else
3081 return Is_Static_Subtype (Anc_Subt)
3082 and then Is_Static_Expression (Type_Low_Bound (Typ))
3083 and then Is_Static_Expression (Type_High_Bound (Typ));
3084 end if;
3085
3086 -- Types other than string and scalar types are never static
3087
3088 else
3089 return False;
3090 end if;
3091 end Is_Static_Subtype;
3092
3093 --------------------
3094 -- Not_Null_Range --
3095 --------------------
3096
3097 function Not_Null_Range (Lo : Node_Id; Hi : Node_Id) return Boolean is
3098 Typ : constant Entity_Id := Etype (Lo);
3099
3100 begin
3101 if not Compile_Time_Known_Value (Lo)
3102 or else not Compile_Time_Known_Value (Hi)
3103 then
3104 return False;
3105 end if;
3106
3107 if Is_Discrete_Type (Typ) then
3108 return Expr_Value (Lo) <= Expr_Value (Hi);
3109
3110 else
3111 pragma Assert (Is_Real_Type (Typ));
3112
3113 return Expr_Value_R (Lo) <= Expr_Value_R (Hi);
3114 end if;
3115 end Not_Null_Range;
3116
3117 -------------
3118 -- OK_Bits --
3119 -------------
3120
3121 function OK_Bits (N : Node_Id; Bits : Uint) return Boolean is
3122 begin
3123 -- We allow a maximum of 500,000 bits which seems a reasonable limit
3124
3125 if Bits < 500_000 then
3126 return True;
3127
3128 else
3129 Error_Msg_N ("static value too large, capacity exceeded", N);
3130 return False;
3131 end if;
3132 end OK_Bits;
3133
3134 ------------------
3135 -- Out_Of_Range --
3136 ------------------
3137
3138 procedure Out_Of_Range (N : Node_Id) is
3139 begin
3140 -- If we have the static expression case, then this is an illegality
3141 -- in Ada 95 mode, except that in an instance, we never generate an
3142 -- error (if the error is legitimate, it was already diagnosed in
3143 -- the template). The expression to compute the length of a packed
3144 -- array is attached to the array type itself, and deserves a separate
3145 -- message.
3146
3147 if Is_Static_Expression (N)
3148 and then not In_Instance
3149 and then Ada_95
3150 then
3151
3152 if Nkind (Parent (N)) = N_Defining_Identifier
3153 and then Is_Array_Type (Parent (N))
3154 and then Present (Packed_Array_Type (Parent (N)))
3155 and then Present (First_Rep_Item (Parent (N)))
3156 then
3157 Error_Msg_N
3158 ("length of packed array must not exceed Integer''Last",
3159 First_Rep_Item (Parent (N)));
3160 Rewrite (N, Make_Integer_Literal (Sloc (N), Uint_1));
3161
3162 else
3163 Apply_Compile_Time_Constraint_Error
3164 (N, "value not in range of}");
3165 end if;
3166
3167 -- Here we generate a warning for the Ada 83 case, or when we are
3168 -- in an instance, or when we have a non-static expression case.
3169
3170 else
3171 Warn_On_Instance := True;
3172 Apply_Compile_Time_Constraint_Error
3173 (N, "value not in range of}?");
3174 Warn_On_Instance := False;
3175 end if;
3176 end Out_Of_Range;
3177
3178 -------------------------
3179 -- Rewrite_In_Raise_CE --
3180 -------------------------
3181
3182 procedure Rewrite_In_Raise_CE (N : Node_Id; Exp : Node_Id) is
3183 Typ : constant Entity_Id := Etype (N);
3184
3185 begin
3186 -- If we want to raise CE in the condition of a raise_CE node
3187 -- we may as well get rid of the condition
3188
3189 if Present (Parent (N))
3190 and then Nkind (Parent (N)) = N_Raise_Constraint_Error
3191 then
3192 Set_Condition (Parent (N), Empty);
3193
3194 -- If the expression raising CE is a N_Raise_CE node, we can use
3195 -- that one. We just preserve the type of the context
3196
3197 elsif Nkind (Exp) = N_Raise_Constraint_Error then
3198 Rewrite (N, Exp);
3199 Set_Etype (N, Typ);
3200
3201 -- We have to build an explicit raise_ce node
3202
3203 else
3204 Rewrite (N, Make_Raise_Constraint_Error (Sloc (Exp)));
3205 Set_Raises_Constraint_Error (N);
3206 Set_Etype (N, Typ);
3207 end if;
3208 end Rewrite_In_Raise_CE;
3209
3210 ---------------------
3211 -- String_Type_Len --
3212 ---------------------
3213
3214 function String_Type_Len (Stype : Entity_Id) return Uint is
3215 NT : constant Entity_Id := Etype (First_Index (Stype));
3216 T : Entity_Id;
3217
3218 begin
3219 if Is_OK_Static_Subtype (NT) then
3220 T := NT;
3221 else
3222 T := Base_Type (NT);
3223 end if;
3224
3225 return Expr_Value (Type_High_Bound (T)) -
3226 Expr_Value (Type_Low_Bound (T)) + 1;
3227 end String_Type_Len;
3228
3229 ------------------------------------
3230 -- Subtypes_Statically_Compatible --
3231 ------------------------------------
3232
3233 function Subtypes_Statically_Compatible
3234 (T1 : Entity_Id;
3235 T2 : Entity_Id)
3236 return Boolean
3237 is
3238 begin
3239 if Is_Scalar_Type (T1) then
3240
3241 -- Definitely compatible if we match
3242
3243 if Subtypes_Statically_Match (T1, T2) then
3244 return True;
3245
3246 -- If either subtype is nonstatic then they're not compatible
3247
3248 elsif not Is_Static_Subtype (T1)
3249 or else not Is_Static_Subtype (T2)
3250 then
3251 return False;
3252
3253 -- If either type has constraint error bounds, then consider that
3254 -- they match to avoid junk cascaded errors here.
3255
3256 elsif not Is_OK_Static_Subtype (T1)
3257 or else not Is_OK_Static_Subtype (T2)
3258 then
3259 return True;
3260
3261 -- Base types must match, but we don't check that (should
3262 -- we???) but we do at least check that both types are
3263 -- real, or both types are not real.
3264
3265 elsif (Is_Real_Type (T1) /= Is_Real_Type (T2)) then
3266 return False;
3267
3268 -- Here we check the bounds
3269
3270 else
3271 declare
3272 LB1 : constant Node_Id := Type_Low_Bound (T1);
3273 HB1 : constant Node_Id := Type_High_Bound (T1);
3274 LB2 : constant Node_Id := Type_Low_Bound (T2);
3275 HB2 : constant Node_Id := Type_High_Bound (T2);
3276
3277 begin
3278 if Is_Real_Type (T1) then
3279 return
3280 (Expr_Value_R (LB1) > Expr_Value_R (HB1))
3281 or else
3282 (Expr_Value_R (LB2) <= Expr_Value_R (LB1)
3283 and then
3284 Expr_Value_R (HB1) <= Expr_Value_R (HB2));
3285
3286 else
3287 return
3288 (Expr_Value (LB1) > Expr_Value (HB1))
3289 or else
3290 (Expr_Value (LB2) <= Expr_Value (LB1)
3291 and then
3292 Expr_Value (HB1) <= Expr_Value (HB2));
3293 end if;
3294 end;
3295 end if;
3296
3297 elsif Is_Access_Type (T1) then
3298 return not Is_Constrained (T2)
3299 or else Subtypes_Statically_Match
3300 (Designated_Type (T1), Designated_Type (T2));
3301
3302 else
3303 return (Is_Composite_Type (T1) and then not Is_Constrained (T2))
3304 or else Subtypes_Statically_Match (T1, T2);
3305 end if;
3306 end Subtypes_Statically_Compatible;
3307
3308 -------------------------------
3309 -- Subtypes_Statically_Match --
3310 -------------------------------
3311
3312 -- Subtypes statically match if they have statically matching constraints
3313 -- (RM 4.9.1(2)). Constraints statically match if there are none, or if
3314 -- they are the same identical constraint, or if they are static and the
3315 -- values match (RM 4.9.1(1)).
3316
3317 function Subtypes_Statically_Match (T1, T2 : Entity_Id) return Boolean is
3318 begin
3319 -- A type always statically matches itself
3320
3321 if T1 = T2 then
3322 return True;
3323
3324 -- Scalar types
3325
3326 elsif Is_Scalar_Type (T1) then
3327
3328 -- Base types must be the same
3329
3330 if Base_Type (T1) /= Base_Type (T2) then
3331 return False;
3332 end if;
3333
3334 -- A constrained numeric subtype never matches an unconstrained
3335 -- subtype, i.e. both types must be constrained or unconstrained.
3336
3337 -- To understand the requirement for this test, see RM 4.9.1(1).
3338 -- As is made clear in RM 3.5.4(11), type Integer, for example
3339 -- is a constrained subtype with constraint bounds matching the
3340 -- bounds of its corresponding uncontrained base type. In this
3341 -- situation, Integer and Integer'Base do not statically match,
3342 -- even though they have the same bounds.
3343
3344 -- We only apply this test to types in Standard and types that
3345 -- appear in user programs. That way, we do not have to be
3346 -- too careful about setting Is_Constrained right for itypes.
3347
3348 if Is_Numeric_Type (T1)
3349 and then (Is_Constrained (T1) /= Is_Constrained (T2))
3350 and then (Scope (T1) = Standard_Standard
3351 or else Comes_From_Source (T1))
3352 and then (Scope (T2) = Standard_Standard
3353 or else Comes_From_Source (T2))
3354 then
3355 return False;
3356 end if;
3357
3358 -- If there was an error in either range, then just assume
3359 -- the types statically match to avoid further junk errors
3360
3361 if Error_Posted (Scalar_Range (T1))
3362 or else
3363 Error_Posted (Scalar_Range (T2))
3364 then
3365 return True;
3366 end if;
3367
3368 -- Otherwise both types have bound that can be compared
3369
3370 declare
3371 LB1 : constant Node_Id := Type_Low_Bound (T1);
3372 HB1 : constant Node_Id := Type_High_Bound (T1);
3373 LB2 : constant Node_Id := Type_Low_Bound (T2);
3374 HB2 : constant Node_Id := Type_High_Bound (T2);
3375
3376 begin
3377 -- If the bounds are the same tree node, then match
3378
3379 if LB1 = LB2 and then HB1 = HB2 then
3380 return True;
3381
3382 -- Otherwise bounds must be static and identical value
3383
3384 else
3385 if not Is_Static_Subtype (T1)
3386 or else not Is_Static_Subtype (T2)
3387 then
3388 return False;
3389
3390 -- If either type has constraint error bounds, then say
3391 -- that they match to avoid junk cascaded errors here.
3392
3393 elsif not Is_OK_Static_Subtype (T1)
3394 or else not Is_OK_Static_Subtype (T2)
3395 then
3396 return True;
3397
3398 elsif Is_Real_Type (T1) then
3399 return
3400 (Expr_Value_R (LB1) = Expr_Value_R (LB2))
3401 and then
3402 (Expr_Value_R (HB1) = Expr_Value_R (HB2));
3403
3404 else
3405 return
3406 Expr_Value (LB1) = Expr_Value (LB2)
3407 and then
3408 Expr_Value (HB1) = Expr_Value (HB2);
3409 end if;
3410 end if;
3411 end;
3412
3413 -- Type with discriminants
3414
3415 elsif Has_Discriminants (T1) or else Has_Discriminants (T2) then
3416 if Has_Discriminants (T1) /= Has_Discriminants (T2) then
3417 return False;
3418 end if;
3419
3420 declare
3421 DL1 : constant Elist_Id := Discriminant_Constraint (T1);
3422 DL2 : constant Elist_Id := Discriminant_Constraint (T2);
3423
3424 DA1 : Elmt_Id := First_Elmt (DL1);
3425 DA2 : Elmt_Id := First_Elmt (DL2);
3426
3427 begin
3428 if DL1 = DL2 then
3429 return True;
3430
3431 elsif Is_Constrained (T1) /= Is_Constrained (T2) then
3432 return False;
3433 end if;
3434
3435 while Present (DA1) loop
3436 declare
3437 Expr1 : constant Node_Id := Node (DA1);
3438 Expr2 : constant Node_Id := Node (DA2);
3439
3440 begin
3441 if not Is_Static_Expression (Expr1)
3442 or else not Is_Static_Expression (Expr2)
3443 then
3444 return False;
3445
3446 -- If either expression raised a constraint error,
3447 -- consider the expressions as matching, since this
3448 -- helps to prevent cascading errors.
3449
3450 elsif Raises_Constraint_Error (Expr1)
3451 or else Raises_Constraint_Error (Expr2)
3452 then
3453 null;
3454
3455 elsif Expr_Value (Expr1) /= Expr_Value (Expr2) then
3456 return False;
3457 end if;
3458 end;
3459
3460 Next_Elmt (DA1);
3461 Next_Elmt (DA2);
3462 end loop;
3463 end;
3464
3465 return True;
3466
3467 -- A definite type does not match an indefinite or classwide type.
3468
3469 elsif
3470 Has_Unknown_Discriminants (T1) /= Has_Unknown_Discriminants (T2)
3471 then
3472 return False;
3473
3474 -- Array type
3475
3476 elsif Is_Array_Type (T1) then
3477
3478 -- If either subtype is unconstrained then both must be,
3479 -- and if both are unconstrained then no further checking
3480 -- is needed.
3481
3482 if not Is_Constrained (T1) or else not Is_Constrained (T2) then
3483 return not (Is_Constrained (T1) or else Is_Constrained (T2));
3484 end if;
3485
3486 -- Both subtypes are constrained, so check that the index
3487 -- subtypes statically match.
3488
3489 declare
3490 Index1 : Node_Id := First_Index (T1);
3491 Index2 : Node_Id := First_Index (T2);
3492
3493 begin
3494 while Present (Index1) loop
3495 if not
3496 Subtypes_Statically_Match (Etype (Index1), Etype (Index2))
3497 then
3498 return False;
3499 end if;
3500
3501 Next_Index (Index1);
3502 Next_Index (Index2);
3503 end loop;
3504
3505 return True;
3506 end;
3507
3508 elsif Is_Access_Type (T1) then
3509 return Subtypes_Statically_Match
3510 (Designated_Type (T1),
3511 Designated_Type (T2));
3512
3513 -- All other types definitely match
3514
3515 else
3516 return True;
3517 end if;
3518 end Subtypes_Statically_Match;
3519
3520 ----------
3521 -- Test --
3522 ----------
3523
3524 function Test (Cond : Boolean) return Uint is
3525 begin
3526 if Cond then
3527 return Uint_1;
3528 else
3529 return Uint_0;
3530 end if;
3531 end Test;
3532
3533 ---------------------------------
3534 -- Test_Expression_Is_Foldable --
3535 ---------------------------------
3536
3537 -- One operand case
3538
3539 procedure Test_Expression_Is_Foldable
3540 (N : Node_Id;
3541 Op1 : Node_Id;
3542 Stat : out Boolean;
3543 Fold : out Boolean)
3544 is
3545 begin
3546 Stat := False;
3547
3548 -- If operand is Any_Type, just propagate to result and do not
3549 -- try to fold, this prevents cascaded errors.
3550
3551 if Etype (Op1) = Any_Type then
3552 Set_Etype (N, Any_Type);
3553 Fold := False;
3554 return;
3555
3556 -- If operand raises constraint error, then replace node N with the
3557 -- raise constraint error node, and we are obviously not foldable.
3558 -- Note that this replacement inherits the Is_Static_Expression flag
3559 -- from the operand.
3560
3561 elsif Raises_Constraint_Error (Op1) then
3562 Rewrite_In_Raise_CE (N, Op1);
3563 Fold := False;
3564 return;
3565
3566 -- If the operand is not static, then the result is not static, and
3567 -- all we have to do is to check the operand since it is now known
3568 -- to appear in a non-static context.
3569
3570 elsif not Is_Static_Expression (Op1) then
3571 Check_Non_Static_Context (Op1);
3572 Fold := Compile_Time_Known_Value (Op1);
3573 return;
3574
3575 -- An expression of a formal modular type is not foldable because
3576 -- the modulus is unknown.
3577
3578 elsif Is_Modular_Integer_Type (Etype (Op1))
3579 and then Is_Generic_Type (Etype (Op1))
3580 then
3581 Check_Non_Static_Context (Op1);
3582 Fold := False;
3583 return;
3584
3585 -- Here we have the case of an operand whose type is OK, which is
3586 -- static, and which does not raise constraint error, we can fold.
3587
3588 else
3589 Set_Is_Static_Expression (N);
3590 Fold := True;
3591 Stat := True;
3592 end if;
3593 end Test_Expression_Is_Foldable;
3594
3595 -- Two operand case
3596
3597 procedure Test_Expression_Is_Foldable
3598 (N : Node_Id;
3599 Op1 : Node_Id;
3600 Op2 : Node_Id;
3601 Stat : out Boolean;
3602 Fold : out Boolean)
3603 is
3604 Rstat : constant Boolean := Is_Static_Expression (Op1)
3605 and then Is_Static_Expression (Op2);
3606
3607 begin
3608 Stat := False;
3609
3610 -- If either operand is Any_Type, just propagate to result and
3611 -- do not try to fold, this prevents cascaded errors.
3612
3613 if Etype (Op1) = Any_Type or else Etype (Op2) = Any_Type then
3614 Set_Etype (N, Any_Type);
3615 Fold := False;
3616 return;
3617
3618 -- If left operand raises constraint error, then replace node N with
3619 -- the raise constraint error node, and we are obviously not foldable.
3620 -- Is_Static_Expression is set from the two operands in the normal way,
3621 -- and we check the right operand if it is in a non-static context.
3622
3623 elsif Raises_Constraint_Error (Op1) then
3624 if not Rstat then
3625 Check_Non_Static_Context (Op2);
3626 end if;
3627
3628 Rewrite_In_Raise_CE (N, Op1);
3629 Set_Is_Static_Expression (N, Rstat);
3630 Fold := False;
3631 return;
3632
3633 -- Similar processing for the case of the right operand. Note that
3634 -- we don't use this routine for the short-circuit case, so we do
3635 -- not have to worry about that special case here.
3636
3637 elsif Raises_Constraint_Error (Op2) then
3638 if not Rstat then
3639 Check_Non_Static_Context (Op1);
3640 end if;
3641
3642 Rewrite_In_Raise_CE (N, Op2);
3643 Set_Is_Static_Expression (N, Rstat);
3644 Fold := False;
3645 return;
3646
3647 -- Exclude expressions of a generic modular type, as above.
3648
3649 elsif Is_Modular_Integer_Type (Etype (Op1))
3650 and then Is_Generic_Type (Etype (Op1))
3651 then
3652 Check_Non_Static_Context (Op1);
3653 Fold := False;
3654 return;
3655
3656 -- If result is not static, then check non-static contexts on operands
3657 -- since one of them may be static and the other one may not be static
3658
3659 elsif not Rstat then
3660 Check_Non_Static_Context (Op1);
3661 Check_Non_Static_Context (Op2);
3662 Fold := Compile_Time_Known_Value (Op1)
3663 and then Compile_Time_Known_Value (Op2);
3664 return;
3665
3666 -- Else result is static and foldable. Both operands are static,
3667 -- and neither raises constraint error, so we can definitely fold.
3668
3669 else
3670 Set_Is_Static_Expression (N);
3671 Fold := True;
3672 Stat := True;
3673 return;
3674 end if;
3675 end Test_Expression_Is_Foldable;
3676
3677 --------------
3678 -- To_Bits --
3679 --------------
3680
3681 procedure To_Bits (U : Uint; B : out Bits) is
3682 begin
3683 for J in 0 .. B'Last loop
3684 B (J) := (U / (2 ** J)) mod 2 /= 0;
3685 end loop;
3686 end To_Bits;
3687
3688end Sem_Eval;