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