* gimplify.c (find_single_pointer_decl_1): New static function.
[official-gcc.git] / gcc / ada / sem_eval.adb
blob396027d39b4a0d2241e4af7d12f45f6b42bb02ab
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-2005 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, 51 Franklin Street, Fifth Floor, --
20 -- Boston, MA 02110-1301, 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 ------------------------------------------------------------------------------
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;
51 package body Sem_Eval is
53 -----------------------------------------
54 -- Handling of Compile Time Evaluation --
55 -----------------------------------------
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.
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.
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.
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.
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).
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.
92 ----------------
93 -- Local Data --
94 ----------------
96 type Bits is array (Nat range <>) of Boolean;
97 -- Used to convert unsigned (modular) values for folding logical ops
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).
106 CV_Bits : constant := 5;
107 -- Number of low order bits of Node_Id value used to reference entries
108 -- in the cache table.
110 CV_Cache_Size : constant Nat := 2 ** CV_Bits;
111 -- Size of cache for compile time values
113 subtype CV_Range is Nat range 0 .. CV_Cache_Size;
115 type CV_Entry is record
116 N : Node_Id;
117 V : Uint;
118 end record;
120 type CV_Cache_Array is array (CV_Range) of CV_Entry;
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.
126 -----------------------
127 -- Local Subprograms --
128 -----------------------
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).
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).
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).
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.
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.
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.
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
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).
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.
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.
204 procedure To_Bits (U : Uint; B : out Bits);
205 -- Converts a Uint value to a bit string of length B'Length
207 ------------------------------
208 -- Check_Non_Static_Context --
209 ------------------------------
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);
217 begin
218 -- Ignore cases of non-scalar types or error types
220 if T = Any_Type or else not Is_Scalar_Type (T) then
221 return;
222 end if;
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.
228 if Raises_Constraint_Error (N) then
229 return;
230 end if;
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.
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;
248 return;
249 end if;
251 -- Here we have the case of outer level static expression of
252 -- scalar type, where the processing of this procedure is needed.
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.
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.
272 if Is_Out_Of_Range (N, Base_Type (T)) then
273 Out_Of_Range (N);
274 return;
275 end if;
277 -- Note: we have to copy the node, to avoid problems with conformance
278 -- of very similar numbers (see ACVC tests B4A010C and B63103A).
280 Rewrite (N, New_Copy (N));
282 if not Is_Floating_Point_Type (T) then
283 Set_Realval
284 (N, Corresponding_Integer_Value (N) * Small_Value (T));
286 elsif not UR_Is_Zero (Realval (N)) then
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.
295 Set_Realval
296 (N, Machine (Base_Type (T), Realval (N), Round_Even, N));
297 end if;
299 Set_Is_Machine_Number (N);
300 end if;
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.
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.
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);
324 -- Check out of range of base type
326 elsif Is_Out_Of_Range (N, Base_Type (T)) then
327 Out_Of_Range (N);
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).
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;
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);
344 elsif Checks_On then
345 Enable_Range_Check (N);
347 else
348 Set_Do_Range_Check (N, False);
349 end if;
350 end if;
351 end Check_Non_Static_Context;
353 ---------------------------------
354 -- Check_String_Literal_Length --
355 ---------------------------------
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
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;
374 --------------------------
375 -- Compile_Time_Compare --
376 --------------------------
378 function Compile_Time_Compare
379 (L, R : Node_Id;
380 Rec : Boolean := False) return Compare_Result
382 Ltyp : constant Entity_Id := Etype (L);
383 Rtyp : constant Entity_Id := Etype (R);
385 procedure Compare_Decompose
386 (N : Node_Id;
387 R : out Node_Id;
388 V : out Uint);
389 -- This procedure decomposes the node N into an expression node
390 -- and a signed offset, so that the value of N is equal to the
391 -- value of R plus the value V (which may be negative). If no
392 -- such decomposition is possible, then on return R is a copy
393 -- of N, and V is set to zero.
395 function Compare_Fixup (N : Node_Id) return Node_Id;
396 -- This function deals with replacing 'Last and 'First references
397 -- with their corresponding type bounds, which we then can compare.
398 -- The argument is the original node, the result is the identity,
399 -- unless we have a 'Last/'First reference in which case the value
400 -- returned is the appropriate type bound.
402 function Is_Same_Value (L, R : Node_Id) return Boolean;
403 -- Returns True iff L and R represent expressions that definitely
404 -- have identical (but not necessarily compile time known) values
405 -- Indeed the caller is expected to have already dealt with the
406 -- cases of compile time known values, so these are not tested here.
408 -----------------------
409 -- Compare_Decompose --
410 -----------------------
412 procedure Compare_Decompose
413 (N : Node_Id;
414 R : out Node_Id;
415 V : out Uint)
417 begin
418 if Nkind (N) = N_Op_Add
419 and then Nkind (Right_Opnd (N)) = N_Integer_Literal
420 then
421 R := Left_Opnd (N);
422 V := Intval (Right_Opnd (N));
423 return;
425 elsif Nkind (N) = N_Op_Subtract
426 and then Nkind (Right_Opnd (N)) = N_Integer_Literal
427 then
428 R := Left_Opnd (N);
429 V := UI_Negate (Intval (Right_Opnd (N)));
430 return;
432 elsif Nkind (N) = N_Attribute_Reference then
434 if Attribute_Name (N) = Name_Succ then
435 R := First (Expressions (N));
436 V := Uint_1;
437 return;
439 elsif Attribute_Name (N) = Name_Pred then
440 R := First (Expressions (N));
441 V := Uint_Minus_1;
442 return;
443 end if;
444 end if;
446 R := N;
447 V := Uint_0;
448 end Compare_Decompose;
450 -------------------
451 -- Compare_Fixup --
452 -------------------
454 function Compare_Fixup (N : Node_Id) return Node_Id is
455 Indx : Node_Id;
456 Xtyp : Entity_Id;
457 Subs : Nat;
459 begin
460 if Nkind (N) = N_Attribute_Reference
461 and then (Attribute_Name (N) = Name_First
462 or else
463 Attribute_Name (N) = Name_Last)
464 then
465 Xtyp := Etype (Prefix (N));
467 -- If we have no type, then just abandon the attempt to do
468 -- a fixup, this is probably the result of some other error.
470 if No (Xtyp) then
471 return N;
472 end if;
474 -- Dereference an access type
476 if Is_Access_Type (Xtyp) then
477 Xtyp := Designated_Type (Xtyp);
478 end if;
480 -- If we don't have an array type at this stage, something
481 -- is peculiar, e.g. another error, and we abandon the attempt
482 -- at a fixup.
484 if not Is_Array_Type (Xtyp) then
485 return N;
486 end if;
488 -- Ignore unconstrained array, since bounds are not meaningful
490 if not Is_Constrained (Xtyp) then
491 return N;
492 end if;
494 if Ekind (Xtyp) = E_String_Literal_Subtype then
495 if Attribute_Name (N) = Name_First then
496 return String_Literal_Low_Bound (Xtyp);
498 else -- Attribute_Name (N) = Name_Last
499 return Make_Integer_Literal (Sloc (N),
500 Intval => Intval (String_Literal_Low_Bound (Xtyp))
501 + String_Literal_Length (Xtyp));
502 end if;
503 end if;
505 -- Find correct index type
507 Indx := First_Index (Xtyp);
509 if Present (Expressions (N)) then
510 Subs := UI_To_Int (Expr_Value (First (Expressions (N))));
512 for J in 2 .. Subs loop
513 Indx := Next_Index (Indx);
514 end loop;
515 end if;
517 Xtyp := Etype (Indx);
519 if Attribute_Name (N) = Name_First then
520 return Type_Low_Bound (Xtyp);
522 else -- Attribute_Name (N) = Name_Last
523 return Type_High_Bound (Xtyp);
524 end if;
525 end if;
527 return N;
528 end Compare_Fixup;
530 -------------------
531 -- Is_Same_Value --
532 -------------------
534 function Is_Same_Value (L, R : Node_Id) return Boolean is
535 Lf : constant Node_Id := Compare_Fixup (L);
536 Rf : constant Node_Id := Compare_Fixup (R);
538 function Is_Same_Subscript (L, R : List_Id) return Boolean;
539 -- L, R are the Expressions values from two attribute nodes
540 -- for First or Last attributes. Either may be set to No_List
541 -- if no expressions are present (indicating subscript 1).
542 -- The result is True if both expressions represent the same
543 -- subscript (note that one case is where one subscript is
544 -- missing and the other is explicitly set to 1).
546 -----------------------
547 -- Is_Same_Subscript --
548 -----------------------
550 function Is_Same_Subscript (L, R : List_Id) return Boolean is
551 begin
552 if L = No_List then
553 if R = No_List then
554 return True;
555 else
556 return Expr_Value (First (R)) = Uint_1;
557 end if;
559 else
560 if R = No_List then
561 return Expr_Value (First (L)) = Uint_1;
562 else
563 return Expr_Value (First (L)) = Expr_Value (First (R));
564 end if;
565 end if;
566 end Is_Same_Subscript;
568 -- Start of processing for Is_Same_Value
570 begin
571 -- Values are the same if they are the same identifier and the
572 -- identifier refers to a constant object (E_Constant). This
573 -- does not however apply to Float types, since we may have two
574 -- NaN values and they should never compare equal.
576 if Nkind (Lf) = N_Identifier and then Nkind (Rf) = N_Identifier
577 and then Entity (Lf) = Entity (Rf)
578 and then not Is_Floating_Point_Type (Etype (L))
579 and then (Ekind (Entity (Lf)) = E_Constant or else
580 Ekind (Entity (Lf)) = E_In_Parameter or else
581 Ekind (Entity (Lf)) = E_Loop_Parameter)
582 then
583 return True;
585 -- Or if they are compile time known and identical
587 elsif Compile_Time_Known_Value (Lf)
588 and then
589 Compile_Time_Known_Value (Rf)
590 and then Expr_Value (Lf) = Expr_Value (Rf)
591 then
592 return True;
594 -- Or if they are both 'First or 'Last values applying to the
595 -- same entity (first and last don't change even if value does)
597 elsif Nkind (Lf) = N_Attribute_Reference
598 and then
599 Nkind (Rf) = N_Attribute_Reference
600 and then Attribute_Name (Lf) = Attribute_Name (Rf)
601 and then (Attribute_Name (Lf) = Name_First
602 or else
603 Attribute_Name (Lf) = Name_Last)
604 and then Is_Entity_Name (Prefix (Lf))
605 and then Is_Entity_Name (Prefix (Rf))
606 and then Entity (Prefix (Lf)) = Entity (Prefix (Rf))
607 and then Is_Same_Subscript (Expressions (Lf), Expressions (Rf))
608 then
609 return True;
611 -- All other cases, we can't tell
613 else
614 return False;
615 end if;
616 end Is_Same_Value;
618 -- Start of processing for Compile_Time_Compare
620 begin
621 -- If either operand could raise constraint error, then we cannot
622 -- know the result at compile time (since CE may be raised!)
624 if not (Cannot_Raise_Constraint_Error (L)
625 and then
626 Cannot_Raise_Constraint_Error (R))
627 then
628 return Unknown;
629 end if;
631 -- Identical operands are most certainly equal
633 if L = R then
634 return EQ;
636 -- If expressions have no types, then do not attempt to determine
637 -- if they are the same, since something funny is going on. One
638 -- case in which this happens is during generic template analysis,
639 -- when bounds are not fully analyzed.
641 elsif No (Ltyp) or else No (Rtyp) then
642 return Unknown;
644 -- We only attempt compile time analysis for scalar values, and
645 -- not for packed arrays represented as modular types, where the
646 -- semantics of comparison is quite different.
648 elsif not Is_Scalar_Type (Ltyp)
649 or else Is_Packed_Array_Type (Ltyp)
650 then
651 return Unknown;
653 -- Case where comparison involves two compile time known values
655 elsif Compile_Time_Known_Value (L)
656 and then Compile_Time_Known_Value (R)
657 then
658 -- For the floating-point case, we have to be a little careful, since
659 -- at compile time we are dealing with universal exact values, but at
660 -- runtime, these will be in non-exact target form. That's why the
661 -- returned results are LE and GE below instead of LT and GT.
663 if Is_Floating_Point_Type (Ltyp)
664 or else
665 Is_Floating_Point_Type (Rtyp)
666 then
667 declare
668 Lo : constant Ureal := Expr_Value_R (L);
669 Hi : constant Ureal := Expr_Value_R (R);
671 begin
672 if Lo < Hi then
673 return LE;
674 elsif Lo = Hi then
675 return EQ;
676 else
677 return GE;
678 end if;
679 end;
681 -- For the integer case we know exactly (note that this includes the
682 -- fixed-point case, where we know the run time integer values now)
684 else
685 declare
686 Lo : constant Uint := Expr_Value (L);
687 Hi : constant Uint := Expr_Value (R);
689 begin
690 if Lo < Hi then
691 return LT;
692 elsif Lo = Hi then
693 return EQ;
694 else
695 return GT;
696 end if;
697 end;
698 end if;
700 -- Cases where at least one operand is not known at compile time
702 else
703 -- Here is where we check for comparisons against maximum bounds of
704 -- types, where we know that no value can be outside the bounds of
705 -- the subtype. Note that this routine is allowed to assume that all
706 -- expressions are within their subtype bounds. Callers wishing to
707 -- deal with possibly invalid values must in any case take special
708 -- steps (e.g. conversions to larger types) to avoid this kind of
709 -- optimization, which is always considered to be valid. We do not
710 -- attempt this optimization with generic types, since the type
711 -- bounds may not be meaningful in this case.
713 -- We are in danger of an infinite recursion here. It does not seem
714 -- useful to go more than one level deep, so the parameter Rec is
715 -- used to protect ourselves against this infinite recursion.
717 if not Rec
718 and then Is_Discrete_Type (Ltyp)
719 and then Is_Discrete_Type (Rtyp)
720 and then not Is_Generic_Type (Ltyp)
721 and then not Is_Generic_Type (Rtyp)
722 then
723 -- See if we can get a decisive check against one operand and
724 -- a bound of the other operand (four possible tests here).
726 case Compile_Time_Compare (L, Type_Low_Bound (Rtyp), True) is
727 when LT => return LT;
728 when LE => return LE;
729 when EQ => return LE;
730 when others => null;
731 end case;
733 case Compile_Time_Compare (L, Type_High_Bound (Rtyp), True) is
734 when GT => return GT;
735 when GE => return GE;
736 when EQ => return GE;
737 when others => null;
738 end case;
740 case Compile_Time_Compare (Type_Low_Bound (Ltyp), R, True) is
741 when GT => return GT;
742 when GE => return GE;
743 when EQ => return GE;
744 when others => null;
745 end case;
747 case Compile_Time_Compare (Type_High_Bound (Ltyp), R, True) is
748 when LT => return LT;
749 when LE => return LE;
750 when EQ => return LE;
751 when others => null;
752 end case;
753 end if;
755 -- Next attempt is to decompose the expressions to extract
756 -- a constant offset resulting from the use of any of the forms:
758 -- expr + literal
759 -- expr - literal
760 -- typ'Succ (expr)
761 -- typ'Pred (expr)
763 -- Then we see if the two expressions are the same value, and if so
764 -- the result is obtained by comparing the offsets.
766 declare
767 Lnode : Node_Id;
768 Loffs : Uint;
769 Rnode : Node_Id;
770 Roffs : Uint;
772 begin
773 Compare_Decompose (L, Lnode, Loffs);
774 Compare_Decompose (R, Rnode, Roffs);
776 if Is_Same_Value (Lnode, Rnode) then
777 if Loffs = Roffs then
778 return EQ;
780 elsif Loffs < Roffs then
781 return LT;
783 else
784 return GT;
785 end if;
787 -- If the expressions are different, we cannot say at compile
788 -- time how they compare, so we return the Unknown indication.
790 else
791 return Unknown;
792 end if;
793 end;
794 end if;
795 end Compile_Time_Compare;
797 -------------------------------
798 -- Compile_Time_Known_Bounds --
799 -------------------------------
801 function Compile_Time_Known_Bounds (T : Entity_Id) return Boolean is
802 Indx : Node_Id;
803 Typ : Entity_Id;
805 begin
806 if not Is_Array_Type (T) then
807 return False;
808 end if;
810 Indx := First_Index (T);
811 while Present (Indx) loop
812 Typ := Underlying_Type (Etype (Indx));
813 if not Compile_Time_Known_Value (Type_Low_Bound (Typ)) then
814 return False;
815 elsif not Compile_Time_Known_Value (Type_High_Bound (Typ)) then
816 return False;
817 else
818 Next_Index (Indx);
819 end if;
820 end loop;
822 return True;
823 end Compile_Time_Known_Bounds;
825 ------------------------------
826 -- Compile_Time_Known_Value --
827 ------------------------------
829 function Compile_Time_Known_Value (Op : Node_Id) return Boolean is
830 K : constant Node_Kind := Nkind (Op);
831 CV_Ent : CV_Entry renames CV_Cache (Nat (Op) mod CV_Cache_Size);
833 begin
834 -- Never known at compile time if bad type or raises constraint error
835 -- or empty (latter case occurs only as a result of a previous error)
837 if No (Op)
838 or else Op = Error
839 or else Etype (Op) = Any_Type
840 or else Raises_Constraint_Error (Op)
841 then
842 return False;
843 end if;
845 -- If this is not a static expression and we are in configurable run
846 -- time mode, then we consider it not known at compile time. This
847 -- avoids anomalies where whether something is permitted with a given
848 -- configurable run-time library depends on how good the compiler is
849 -- at optimizing and knowing that things are constant when they
850 -- are non-static.
852 if Configurable_Run_Time_Mode and then not Is_Static_Expression (Op) then
853 return False;
854 end if;
856 -- If we have an entity name, then see if it is the name of a constant
857 -- and if so, test the corresponding constant value, or the name of
858 -- an enumeration literal, which is always a constant.
860 if Present (Etype (Op)) and then Is_Entity_Name (Op) then
861 declare
862 E : constant Entity_Id := Entity (Op);
863 V : Node_Id;
865 begin
866 -- Never known at compile time if it is a packed array value.
867 -- We might want to try to evaluate these at compile time one
868 -- day, but we do not make that attempt now.
870 if Is_Packed_Array_Type (Etype (Op)) then
871 return False;
872 end if;
874 if Ekind (E) = E_Enumeration_Literal then
875 return True;
877 elsif Ekind (E) = E_Constant then
878 V := Constant_Value (E);
879 return Present (V) and then Compile_Time_Known_Value (V);
880 end if;
881 end;
883 -- We have a value, see if it is compile time known
885 else
886 -- Integer literals are worth storing in the cache
888 if K = N_Integer_Literal then
889 CV_Ent.N := Op;
890 CV_Ent.V := Intval (Op);
891 return True;
893 -- Other literals and NULL are known at compile time
895 elsif
896 K = N_Character_Literal
897 or else
898 K = N_Real_Literal
899 or else
900 K = N_String_Literal
901 or else
902 K = N_Null
903 then
904 return True;
906 -- Any reference to Null_Parameter is known at compile time. No
907 -- other attribute references (that have not already been folded)
908 -- are known at compile time.
910 elsif K = N_Attribute_Reference then
911 return Attribute_Name (Op) = Name_Null_Parameter;
912 end if;
913 end if;
915 -- If we fall through, not known at compile time
917 return False;
919 -- If we get an exception while trying to do this test, then some error
920 -- has occurred, and we simply say that the value is not known after all
922 exception
923 when others =>
924 return False;
925 end Compile_Time_Known_Value;
927 --------------------------------------
928 -- Compile_Time_Known_Value_Or_Aggr --
929 --------------------------------------
931 function Compile_Time_Known_Value_Or_Aggr (Op : Node_Id) return Boolean is
932 begin
933 -- If we have an entity name, then see if it is the name of a constant
934 -- and if so, test the corresponding constant value, or the name of
935 -- an enumeration literal, which is always a constant.
937 if Is_Entity_Name (Op) then
938 declare
939 E : constant Entity_Id := Entity (Op);
940 V : Node_Id;
942 begin
943 if Ekind (E) = E_Enumeration_Literal then
944 return True;
946 elsif Ekind (E) /= E_Constant then
947 return False;
949 else
950 V := Constant_Value (E);
951 return Present (V)
952 and then Compile_Time_Known_Value_Or_Aggr (V);
953 end if;
954 end;
956 -- We have a value, see if it is compile time known
958 else
959 if Compile_Time_Known_Value (Op) then
960 return True;
962 elsif Nkind (Op) = N_Aggregate then
964 if Present (Expressions (Op)) then
965 declare
966 Expr : Node_Id;
968 begin
969 Expr := First (Expressions (Op));
970 while Present (Expr) loop
971 if not Compile_Time_Known_Value_Or_Aggr (Expr) then
972 return False;
973 end if;
975 Next (Expr);
976 end loop;
977 end;
978 end if;
980 if Present (Component_Associations (Op)) then
981 declare
982 Cass : Node_Id;
984 begin
985 Cass := First (Component_Associations (Op));
986 while Present (Cass) loop
987 if not
988 Compile_Time_Known_Value_Or_Aggr (Expression (Cass))
989 then
990 return False;
991 end if;
993 Next (Cass);
994 end loop;
995 end;
996 end if;
998 return True;
1000 -- All other types of values are not known at compile time
1002 else
1003 return False;
1004 end if;
1006 end if;
1007 end Compile_Time_Known_Value_Or_Aggr;
1009 -----------------
1010 -- Eval_Actual --
1011 -----------------
1013 -- This is only called for actuals of functions that are not predefined
1014 -- operators (which have already been rewritten as operators at this
1015 -- stage), so the call can never be folded, and all that needs doing for
1016 -- the actual is to do the check for a non-static context.
1018 procedure Eval_Actual (N : Node_Id) is
1019 begin
1020 Check_Non_Static_Context (N);
1021 end Eval_Actual;
1023 --------------------
1024 -- Eval_Allocator --
1025 --------------------
1027 -- Allocators are never static, so all we have to do is to do the
1028 -- check for a non-static context if an expression is present.
1030 procedure Eval_Allocator (N : Node_Id) is
1031 Expr : constant Node_Id := Expression (N);
1033 begin
1034 if Nkind (Expr) = N_Qualified_Expression then
1035 Check_Non_Static_Context (Expression (Expr));
1036 end if;
1037 end Eval_Allocator;
1039 ------------------------
1040 -- Eval_Arithmetic_Op --
1041 ------------------------
1043 -- Arithmetic operations are static functions, so the result is static
1044 -- if both operands are static (RM 4.9(7), 4.9(20)).
1046 procedure Eval_Arithmetic_Op (N : Node_Id) is
1047 Left : constant Node_Id := Left_Opnd (N);
1048 Right : constant Node_Id := Right_Opnd (N);
1049 Ltype : constant Entity_Id := Etype (Left);
1050 Rtype : constant Entity_Id := Etype (Right);
1051 Stat : Boolean;
1052 Fold : Boolean;
1054 begin
1055 -- If not foldable we are done
1057 Test_Expression_Is_Foldable (N, Left, Right, Stat, Fold);
1059 if not Fold then
1060 return;
1061 end if;
1063 -- Fold for cases where both operands are of integer type
1065 if Is_Integer_Type (Ltype) and then Is_Integer_Type (Rtype) then
1066 declare
1067 Left_Int : constant Uint := Expr_Value (Left);
1068 Right_Int : constant Uint := Expr_Value (Right);
1069 Result : Uint;
1071 begin
1072 case Nkind (N) is
1074 when N_Op_Add =>
1075 Result := Left_Int + Right_Int;
1077 when N_Op_Subtract =>
1078 Result := Left_Int - Right_Int;
1080 when N_Op_Multiply =>
1081 if OK_Bits
1082 (N, UI_From_Int
1083 (Num_Bits (Left_Int) + Num_Bits (Right_Int)))
1084 then
1085 Result := Left_Int * Right_Int;
1086 else
1087 Result := Left_Int;
1088 end if;
1090 when N_Op_Divide =>
1092 -- The exception Constraint_Error is raised by integer
1093 -- division, rem and mod if the right operand is zero.
1095 if Right_Int = 0 then
1096 Apply_Compile_Time_Constraint_Error
1097 (N, "division by zero",
1098 CE_Divide_By_Zero,
1099 Warn => not Stat);
1100 return;
1102 else
1103 Result := Left_Int / Right_Int;
1104 end if;
1106 when N_Op_Mod =>
1108 -- The exception Constraint_Error is raised by integer
1109 -- division, rem and mod if the right operand is zero.
1111 if Right_Int = 0 then
1112 Apply_Compile_Time_Constraint_Error
1113 (N, "mod with zero divisor",
1114 CE_Divide_By_Zero,
1115 Warn => not Stat);
1116 return;
1117 else
1118 Result := Left_Int mod Right_Int;
1119 end if;
1121 when N_Op_Rem =>
1123 -- The exception Constraint_Error is raised by integer
1124 -- division, rem and mod if the right operand is zero.
1126 if Right_Int = 0 then
1127 Apply_Compile_Time_Constraint_Error
1128 (N, "rem with zero divisor",
1129 CE_Divide_By_Zero,
1130 Warn => not Stat);
1131 return;
1133 else
1134 Result := Left_Int rem Right_Int;
1135 end if;
1137 when others =>
1138 raise Program_Error;
1139 end case;
1141 -- Adjust the result by the modulus if the type is a modular type
1143 if Is_Modular_Integer_Type (Ltype) then
1144 Result := Result mod Modulus (Ltype);
1146 -- For a signed integer type, check non-static overflow
1148 elsif (not Stat) and then Is_Signed_Integer_Type (Ltype) then
1149 declare
1150 BT : constant Entity_Id := Base_Type (Ltype);
1151 Lo : constant Uint := Expr_Value (Type_Low_Bound (BT));
1152 Hi : constant Uint := Expr_Value (Type_High_Bound (BT));
1153 begin
1154 if Result < Lo or else Result > Hi then
1155 Apply_Compile_Time_Constraint_Error
1156 (N, "value not in range of }?",
1157 CE_Overflow_Check_Failed,
1158 Ent => BT);
1159 return;
1160 end if;
1161 end;
1162 end if;
1164 -- If we get here we can fold the result
1166 Fold_Uint (N, Result, Stat);
1167 end;
1169 -- Cases where at least one operand is a real. We handle the cases
1170 -- of both reals, or mixed/real integer cases (the latter happen
1171 -- only for divide and multiply, and the result is always real).
1173 elsif Is_Real_Type (Ltype) or else Is_Real_Type (Rtype) then
1174 declare
1175 Left_Real : Ureal;
1176 Right_Real : Ureal;
1177 Result : Ureal;
1179 begin
1180 if Is_Real_Type (Ltype) then
1181 Left_Real := Expr_Value_R (Left);
1182 else
1183 Left_Real := UR_From_Uint (Expr_Value (Left));
1184 end if;
1186 if Is_Real_Type (Rtype) then
1187 Right_Real := Expr_Value_R (Right);
1188 else
1189 Right_Real := UR_From_Uint (Expr_Value (Right));
1190 end if;
1192 if Nkind (N) = N_Op_Add then
1193 Result := Left_Real + Right_Real;
1195 elsif Nkind (N) = N_Op_Subtract then
1196 Result := Left_Real - Right_Real;
1198 elsif Nkind (N) = N_Op_Multiply then
1199 Result := Left_Real * Right_Real;
1201 else pragma Assert (Nkind (N) = N_Op_Divide);
1202 if UR_Is_Zero (Right_Real) then
1203 Apply_Compile_Time_Constraint_Error
1204 (N, "division by zero", CE_Divide_By_Zero);
1205 return;
1206 end if;
1208 Result := Left_Real / Right_Real;
1209 end if;
1211 Fold_Ureal (N, Result, Stat);
1212 end;
1213 end if;
1214 end Eval_Arithmetic_Op;
1216 ----------------------------
1217 -- Eval_Character_Literal --
1218 ----------------------------
1220 -- Nothing to be done!
1222 procedure Eval_Character_Literal (N : Node_Id) is
1223 pragma Warnings (Off, N);
1224 begin
1225 null;
1226 end Eval_Character_Literal;
1228 ---------------
1229 -- Eval_Call --
1230 ---------------
1232 -- Static function calls are either calls to predefined operators
1233 -- with static arguments, or calls to functions that rename a literal.
1234 -- Only the latter case is handled here, predefined operators are
1235 -- constant-folded elsewhere.
1236 -- If the function is itself inherited (see 7423-001) the literal of
1237 -- the parent type must be explicitly converted to the return type
1238 -- of the function.
1240 procedure Eval_Call (N : Node_Id) is
1241 Loc : constant Source_Ptr := Sloc (N);
1242 Typ : constant Entity_Id := Etype (N);
1243 Lit : Entity_Id;
1245 begin
1246 if Nkind (N) = N_Function_Call
1247 and then No (Parameter_Associations (N))
1248 and then Is_Entity_Name (Name (N))
1249 and then Present (Alias (Entity (Name (N))))
1250 and then Is_Enumeration_Type (Base_Type (Typ))
1251 then
1252 Lit := Alias (Entity (Name (N)));
1254 while Present (Alias (Lit)) loop
1255 Lit := Alias (Lit);
1256 end loop;
1258 if Ekind (Lit) = E_Enumeration_Literal then
1259 if Base_Type (Etype (Lit)) /= Base_Type (Typ) then
1260 Rewrite
1261 (N, Convert_To (Typ, New_Occurrence_Of (Lit, Loc)));
1262 else
1263 Rewrite (N, New_Occurrence_Of (Lit, Loc));
1264 end if;
1266 Resolve (N, Typ);
1267 end if;
1268 end if;
1269 end Eval_Call;
1271 ------------------------
1272 -- Eval_Concatenation --
1273 ------------------------
1275 -- Concatenation is a static function, so the result is static if
1276 -- both operands are static (RM 4.9(7), 4.9(21)).
1278 procedure Eval_Concatenation (N : Node_Id) is
1279 Left : constant Node_Id := Left_Opnd (N);
1280 Right : constant Node_Id := Right_Opnd (N);
1281 C_Typ : constant Entity_Id := Root_Type (Component_Type (Etype (N)));
1282 Stat : Boolean;
1283 Fold : Boolean;
1285 begin
1286 -- Concatenation is never static in Ada 83, so if Ada 83
1287 -- check operand non-static context
1289 if Ada_Version = Ada_83
1290 and then Comes_From_Source (N)
1291 then
1292 Check_Non_Static_Context (Left);
1293 Check_Non_Static_Context (Right);
1294 return;
1295 end if;
1297 -- If not foldable we are done. In principle concatenation that yields
1298 -- any string type is static (i.e. an array type of character types).
1299 -- However, character types can include enumeration literals, and
1300 -- concatenation in that case cannot be described by a literal, so we
1301 -- only consider the operation static if the result is an array of
1302 -- (a descendant of) a predefined character type.
1304 Test_Expression_Is_Foldable (N, Left, Right, Stat, Fold);
1306 if (C_Typ = Standard_Character
1307 or else C_Typ = Standard_Wide_Character
1308 or else C_Typ = Standard_Wide_Wide_Character)
1309 and then Fold
1310 then
1311 null;
1312 else
1313 Set_Is_Static_Expression (N, False);
1314 return;
1315 end if;
1317 -- Compile time string concatenation
1319 -- ??? Note that operands that are aggregates can be marked as
1320 -- static, so we should attempt at a later stage to fold
1321 -- concatenations with such aggregates.
1323 declare
1324 Left_Str : constant Node_Id := Get_String_Val (Left);
1325 Left_Len : Nat;
1326 Right_Str : constant Node_Id := Get_String_Val (Right);
1328 begin
1329 -- Establish new string literal, and store left operand. We make
1330 -- sure to use the special Start_String that takes an operand if
1331 -- the left operand is a string literal. Since this is optimized
1332 -- in the case where that is the most recently created string
1333 -- literal, we ensure efficient time/space behavior for the
1334 -- case of a concatenation of a series of string literals.
1336 if Nkind (Left_Str) = N_String_Literal then
1337 Left_Len := String_Length (Strval (Left_Str));
1338 Start_String (Strval (Left_Str));
1339 else
1340 Start_String;
1341 Store_String_Char (UI_To_CC (Char_Literal_Value (Left_Str)));
1342 Left_Len := 1;
1343 end if;
1345 -- Now append the characters of the right operand
1347 if Nkind (Right_Str) = N_String_Literal then
1348 declare
1349 S : constant String_Id := Strval (Right_Str);
1351 begin
1352 for J in 1 .. String_Length (S) loop
1353 Store_String_Char (Get_String_Char (S, J));
1354 end loop;
1355 end;
1356 else
1357 Store_String_Char (UI_To_CC (Char_Literal_Value (Right_Str)));
1358 end if;
1360 Set_Is_Static_Expression (N, Stat);
1362 if Stat then
1364 -- If left operand is the empty string, the result is the
1365 -- right operand, including its bounds if anomalous.
1367 if Left_Len = 0
1368 and then Is_Array_Type (Etype (Right))
1369 and then Etype (Right) /= Any_String
1370 then
1371 Set_Etype (N, Etype (Right));
1372 end if;
1374 Fold_Str (N, End_String, True);
1375 end if;
1376 end;
1377 end Eval_Concatenation;
1379 ---------------------------------
1380 -- Eval_Conditional_Expression --
1381 ---------------------------------
1383 -- This GNAT internal construct can never be statically folded, so the
1384 -- only required processing is to do the check for non-static context
1385 -- for the two expression operands.
1387 procedure Eval_Conditional_Expression (N : Node_Id) is
1388 Condition : constant Node_Id := First (Expressions (N));
1389 Then_Expr : constant Node_Id := Next (Condition);
1390 Else_Expr : constant Node_Id := Next (Then_Expr);
1392 begin
1393 Check_Non_Static_Context (Then_Expr);
1394 Check_Non_Static_Context (Else_Expr);
1395 end Eval_Conditional_Expression;
1397 ----------------------
1398 -- Eval_Entity_Name --
1399 ----------------------
1401 -- This procedure is used for identifiers and expanded names other than
1402 -- named numbers (see Eval_Named_Integer, Eval_Named_Real. These are
1403 -- static if they denote a static constant (RM 4.9(6)) or if the name
1404 -- denotes an enumeration literal (RM 4.9(22)).
1406 procedure Eval_Entity_Name (N : Node_Id) is
1407 Def_Id : constant Entity_Id := Entity (N);
1408 Val : Node_Id;
1410 begin
1411 -- Enumeration literals are always considered to be constants
1412 -- and cannot raise constraint error (RM 4.9(22)).
1414 if Ekind (Def_Id) = E_Enumeration_Literal then
1415 Set_Is_Static_Expression (N);
1416 return;
1418 -- A name is static if it denotes a static constant (RM 4.9(5)), and
1419 -- we also copy Raise_Constraint_Error. Notice that even if non-static,
1420 -- it does not violate 10.2.1(8) here, since this is not a variable.
1422 elsif Ekind (Def_Id) = E_Constant then
1424 -- Deferred constants must always be treated as nonstatic
1425 -- outside the scope of their full view.
1427 if Present (Full_View (Def_Id))
1428 and then not In_Open_Scopes (Scope (Def_Id))
1429 then
1430 Val := Empty;
1431 else
1432 Val := Constant_Value (Def_Id);
1433 end if;
1435 if Present (Val) then
1436 Set_Is_Static_Expression
1437 (N, Is_Static_Expression (Val)
1438 and then Is_Static_Subtype (Etype (Def_Id)));
1439 Set_Raises_Constraint_Error (N, Raises_Constraint_Error (Val));
1441 if not Is_Static_Expression (N)
1442 and then not Is_Generic_Type (Etype (N))
1443 then
1444 Validate_Static_Object_Name (N);
1445 end if;
1447 return;
1448 end if;
1449 end if;
1451 -- Fall through if the name is not static
1453 Validate_Static_Object_Name (N);
1454 end Eval_Entity_Name;
1456 ----------------------------
1457 -- Eval_Indexed_Component --
1458 ----------------------------
1460 -- Indexed components are never static, so we need to perform the check
1461 -- for non-static context on the index values. Then, we check if the
1462 -- value can be obtained at compile time, even though it is non-static.
1464 procedure Eval_Indexed_Component (N : Node_Id) is
1465 Expr : Node_Id;
1467 begin
1468 -- Check for non-static context on index values
1470 Expr := First (Expressions (N));
1471 while Present (Expr) loop
1472 Check_Non_Static_Context (Expr);
1473 Next (Expr);
1474 end loop;
1476 -- If the indexed component appears in an object renaming declaration
1477 -- then we do not want to try to evaluate it, since in this case we
1478 -- need the identity of the array element.
1480 if Nkind (Parent (N)) = N_Object_Renaming_Declaration then
1481 return;
1483 -- Similarly if the indexed component appears as the prefix of an
1484 -- attribute we don't want to evaluate it, because at least for
1485 -- some cases of attributes we need the identify (e.g. Access, Size)
1487 elsif Nkind (Parent (N)) = N_Attribute_Reference then
1488 return;
1489 end if;
1491 -- Note: there are other cases, such as the left side of an assignment,
1492 -- or an OUT parameter for a call, where the replacement results in the
1493 -- illegal use of a constant, But these cases are illegal in the first
1494 -- place, so the replacement, though silly, is harmless.
1496 -- Now see if this is a constant array reference
1498 if List_Length (Expressions (N)) = 1
1499 and then Is_Entity_Name (Prefix (N))
1500 and then Ekind (Entity (Prefix (N))) = E_Constant
1501 and then Present (Constant_Value (Entity (Prefix (N))))
1502 then
1503 declare
1504 Loc : constant Source_Ptr := Sloc (N);
1505 Arr : constant Node_Id := Constant_Value (Entity (Prefix (N)));
1506 Sub : constant Node_Id := First (Expressions (N));
1508 Atyp : Entity_Id;
1509 -- Type of array
1511 Lin : Nat;
1512 -- Linear one's origin subscript value for array reference
1514 Lbd : Node_Id;
1515 -- Lower bound of the first array index
1517 Elm : Node_Id;
1518 -- Value from constant array
1520 begin
1521 Atyp := Etype (Arr);
1523 if Is_Access_Type (Atyp) then
1524 Atyp := Designated_Type (Atyp);
1525 end if;
1527 -- If we have an array type (we should have but perhaps there
1528 -- are error cases where this is not the case), then see if we
1529 -- can do a constant evaluation of the array reference.
1531 if Is_Array_Type (Atyp) then
1532 if Ekind (Atyp) = E_String_Literal_Subtype then
1533 Lbd := String_Literal_Low_Bound (Atyp);
1534 else
1535 Lbd := Type_Low_Bound (Etype (First_Index (Atyp)));
1536 end if;
1538 if Compile_Time_Known_Value (Sub)
1539 and then Nkind (Arr) = N_Aggregate
1540 and then Compile_Time_Known_Value (Lbd)
1541 and then Is_Discrete_Type (Component_Type (Atyp))
1542 then
1543 Lin := UI_To_Int (Expr_Value (Sub) - Expr_Value (Lbd)) + 1;
1545 if List_Length (Expressions (Arr)) >= Lin then
1546 Elm := Pick (Expressions (Arr), Lin);
1548 -- If the resulting expression is compile time known,
1549 -- then we can rewrite the indexed component with this
1550 -- value, being sure to mark the result as non-static.
1551 -- We also reset the Sloc, in case this generates an
1552 -- error later on (e.g. 136'Access).
1554 if Compile_Time_Known_Value (Elm) then
1555 Rewrite (N, Duplicate_Subexpr_No_Checks (Elm));
1556 Set_Is_Static_Expression (N, False);
1557 Set_Sloc (N, Loc);
1558 end if;
1559 end if;
1560 end if;
1561 end if;
1562 end;
1563 end if;
1564 end Eval_Indexed_Component;
1566 --------------------------
1567 -- Eval_Integer_Literal --
1568 --------------------------
1570 -- Numeric literals are static (RM 4.9(1)), and have already been marked
1571 -- as static by the analyzer. The reason we did it that early is to allow
1572 -- the possibility of turning off the Is_Static_Expression flag after
1573 -- analysis, but before resolution, when integer literals are generated
1574 -- in the expander that do not correspond to static expressions.
1576 procedure Eval_Integer_Literal (N : Node_Id) is
1577 T : constant Entity_Id := Etype (N);
1579 function In_Any_Integer_Context return Boolean;
1580 -- If the literal is resolved with a specific type in a context
1581 -- where the expected type is Any_Integer, there are no range checks
1582 -- on the literal. By the time the literal is evaluated, it carries
1583 -- the type imposed by the enclosing expression, and we must recover
1584 -- the context to determine that Any_Integer is meant.
1586 ----------------------------
1587 -- To_Any_Integer_Context --
1588 ----------------------------
1590 function In_Any_Integer_Context return Boolean is
1591 Par : constant Node_Id := Parent (N);
1592 K : constant Node_Kind := Nkind (Par);
1594 begin
1595 -- Any_Integer also appears in digits specifications for real types,
1596 -- but those have bounds smaller that those of any integer base
1597 -- type, so we can safely ignore these cases.
1599 return K = N_Number_Declaration
1600 or else K = N_Attribute_Reference
1601 or else K = N_Attribute_Definition_Clause
1602 or else K = N_Modular_Type_Definition
1603 or else K = N_Signed_Integer_Type_Definition;
1604 end In_Any_Integer_Context;
1606 -- Start of processing for Eval_Integer_Literal
1608 begin
1610 -- If the literal appears in a non-expression context, then it is
1611 -- certainly appearing in a non-static context, so check it. This
1612 -- is actually a redundant check, since Check_Non_Static_Context
1613 -- would check it, but it seems worth while avoiding the call.
1615 if Nkind (Parent (N)) not in N_Subexpr
1616 and then not In_Any_Integer_Context
1617 then
1618 Check_Non_Static_Context (N);
1619 end if;
1621 -- Modular integer literals must be in their base range
1623 if Is_Modular_Integer_Type (T)
1624 and then Is_Out_Of_Range (N, Base_Type (T))
1625 then
1626 Out_Of_Range (N);
1627 end if;
1628 end Eval_Integer_Literal;
1630 ---------------------
1631 -- Eval_Logical_Op --
1632 ---------------------
1634 -- Logical operations are static functions, so the result is potentially
1635 -- static if both operands are potentially static (RM 4.9(7), 4.9(20)).
1637 procedure Eval_Logical_Op (N : Node_Id) is
1638 Left : constant Node_Id := Left_Opnd (N);
1639 Right : constant Node_Id := Right_Opnd (N);
1640 Stat : Boolean;
1641 Fold : Boolean;
1643 begin
1644 -- If not foldable we are done
1646 Test_Expression_Is_Foldable (N, Left, Right, Stat, Fold);
1648 if not Fold then
1649 return;
1650 end if;
1652 -- Compile time evaluation of logical operation
1654 declare
1655 Left_Int : constant Uint := Expr_Value (Left);
1656 Right_Int : constant Uint := Expr_Value (Right);
1658 begin
1659 if Is_Modular_Integer_Type (Etype (N)) then
1660 declare
1661 Left_Bits : Bits (0 .. UI_To_Int (Esize (Etype (N))) - 1);
1662 Right_Bits : Bits (0 .. UI_To_Int (Esize (Etype (N))) - 1);
1664 begin
1665 To_Bits (Left_Int, Left_Bits);
1666 To_Bits (Right_Int, Right_Bits);
1668 -- Note: should really be able to use array ops instead of
1669 -- these loops, but they weren't working at the time ???
1671 if Nkind (N) = N_Op_And then
1672 for J in Left_Bits'Range loop
1673 Left_Bits (J) := Left_Bits (J) and Right_Bits (J);
1674 end loop;
1676 elsif Nkind (N) = N_Op_Or then
1677 for J in Left_Bits'Range loop
1678 Left_Bits (J) := Left_Bits (J) or Right_Bits (J);
1679 end loop;
1681 else
1682 pragma Assert (Nkind (N) = N_Op_Xor);
1684 for J in Left_Bits'Range loop
1685 Left_Bits (J) := Left_Bits (J) xor Right_Bits (J);
1686 end loop;
1687 end if;
1689 Fold_Uint (N, From_Bits (Left_Bits, Etype (N)), Stat);
1690 end;
1692 else
1693 pragma Assert (Is_Boolean_Type (Etype (N)));
1695 if Nkind (N) = N_Op_And then
1696 Fold_Uint (N,
1697 Test (Is_True (Left_Int) and then Is_True (Right_Int)), Stat);
1699 elsif Nkind (N) = N_Op_Or then
1700 Fold_Uint (N,
1701 Test (Is_True (Left_Int) or else Is_True (Right_Int)), Stat);
1703 else
1704 pragma Assert (Nkind (N) = N_Op_Xor);
1705 Fold_Uint (N,
1706 Test (Is_True (Left_Int) xor Is_True (Right_Int)), Stat);
1707 end if;
1708 end if;
1709 end;
1710 end Eval_Logical_Op;
1712 ------------------------
1713 -- Eval_Membership_Op --
1714 ------------------------
1716 -- A membership test is potentially static if the expression is static,
1717 -- and the range is a potentially static range, or is a subtype mark
1718 -- denoting a static subtype (RM 4.9(12)).
1720 procedure Eval_Membership_Op (N : Node_Id) is
1721 Left : constant Node_Id := Left_Opnd (N);
1722 Right : constant Node_Id := Right_Opnd (N);
1723 Def_Id : Entity_Id;
1724 Lo : Node_Id;
1725 Hi : Node_Id;
1726 Result : Boolean;
1727 Stat : Boolean;
1728 Fold : Boolean;
1730 begin
1731 -- Ignore if error in either operand, except to make sure that
1732 -- Any_Type is properly propagated to avoid junk cascaded errors.
1734 if Etype (Left) = Any_Type
1735 or else Etype (Right) = Any_Type
1736 then
1737 Set_Etype (N, Any_Type);
1738 return;
1739 end if;
1741 -- Case of right operand is a subtype name
1743 if Is_Entity_Name (Right) then
1744 Def_Id := Entity (Right);
1746 if (Is_Scalar_Type (Def_Id) or else Is_String_Type (Def_Id))
1747 and then Is_OK_Static_Subtype (Def_Id)
1748 then
1749 Test_Expression_Is_Foldable (N, Left, Stat, Fold);
1751 if not Fold or else not Stat then
1752 return;
1753 end if;
1754 else
1755 Check_Non_Static_Context (Left);
1756 return;
1757 end if;
1759 -- For string membership tests we will check the length
1760 -- further below.
1762 if not Is_String_Type (Def_Id) then
1763 Lo := Type_Low_Bound (Def_Id);
1764 Hi := Type_High_Bound (Def_Id);
1766 else
1767 Lo := Empty;
1768 Hi := Empty;
1769 end if;
1771 -- Case of right operand is a range
1773 else
1774 if Is_Static_Range (Right) then
1775 Test_Expression_Is_Foldable (N, Left, Stat, Fold);
1777 if not Fold or else not Stat then
1778 return;
1780 -- If one bound of range raises CE, then don't try to fold
1782 elsif not Is_OK_Static_Range (Right) then
1783 Check_Non_Static_Context (Left);
1784 return;
1785 end if;
1787 else
1788 Check_Non_Static_Context (Left);
1789 return;
1790 end if;
1792 -- Here we know range is an OK static range
1794 Lo := Low_Bound (Right);
1795 Hi := High_Bound (Right);
1796 end if;
1798 -- For strings we check that the length of the string expression is
1799 -- compatible with the string subtype if the subtype is constrained,
1800 -- or if unconstrained then the test is always true.
1802 if Is_String_Type (Etype (Right)) then
1803 if not Is_Constrained (Etype (Right)) then
1804 Result := True;
1806 else
1807 declare
1808 Typlen : constant Uint := String_Type_Len (Etype (Right));
1809 Strlen : constant Uint :=
1810 UI_From_Int (String_Length (Strval (Get_String_Val (Left))));
1811 begin
1812 Result := (Typlen = Strlen);
1813 end;
1814 end if;
1816 -- Fold the membership test. We know we have a static range and Lo
1817 -- and Hi are set to the expressions for the end points of this range.
1819 elsif Is_Real_Type (Etype (Right)) then
1820 declare
1821 Leftval : constant Ureal := Expr_Value_R (Left);
1823 begin
1824 Result := Expr_Value_R (Lo) <= Leftval
1825 and then Leftval <= Expr_Value_R (Hi);
1826 end;
1828 else
1829 declare
1830 Leftval : constant Uint := Expr_Value (Left);
1832 begin
1833 Result := Expr_Value (Lo) <= Leftval
1834 and then Leftval <= Expr_Value (Hi);
1835 end;
1836 end if;
1838 if Nkind (N) = N_Not_In then
1839 Result := not Result;
1840 end if;
1842 Fold_Uint (N, Test (Result), True);
1843 Warn_On_Known_Condition (N);
1844 end Eval_Membership_Op;
1846 ------------------------
1847 -- Eval_Named_Integer --
1848 ------------------------
1850 procedure Eval_Named_Integer (N : Node_Id) is
1851 begin
1852 Fold_Uint (N,
1853 Expr_Value (Expression (Declaration_Node (Entity (N)))), True);
1854 end Eval_Named_Integer;
1856 ---------------------
1857 -- Eval_Named_Real --
1858 ---------------------
1860 procedure Eval_Named_Real (N : Node_Id) is
1861 begin
1862 Fold_Ureal (N,
1863 Expr_Value_R (Expression (Declaration_Node (Entity (N)))), True);
1864 end Eval_Named_Real;
1866 -------------------
1867 -- Eval_Op_Expon --
1868 -------------------
1870 -- Exponentiation is a static functions, so the result is potentially
1871 -- static if both operands are potentially static (RM 4.9(7), 4.9(20)).
1873 procedure Eval_Op_Expon (N : Node_Id) is
1874 Left : constant Node_Id := Left_Opnd (N);
1875 Right : constant Node_Id := Right_Opnd (N);
1876 Stat : Boolean;
1877 Fold : Boolean;
1879 begin
1880 -- If not foldable we are done
1882 Test_Expression_Is_Foldable (N, Left, Right, Stat, Fold);
1884 if not Fold then
1885 return;
1886 end if;
1888 -- Fold exponentiation operation
1890 declare
1891 Right_Int : constant Uint := Expr_Value (Right);
1893 begin
1894 -- Integer case
1896 if Is_Integer_Type (Etype (Left)) then
1897 declare
1898 Left_Int : constant Uint := Expr_Value (Left);
1899 Result : Uint;
1901 begin
1902 -- Exponentiation of an integer raises the exception
1903 -- Constraint_Error for a negative exponent (RM 4.5.6)
1905 if Right_Int < 0 then
1906 Apply_Compile_Time_Constraint_Error
1907 (N, "integer exponent negative",
1908 CE_Range_Check_Failed,
1909 Warn => not Stat);
1910 return;
1912 else
1913 if OK_Bits (N, Num_Bits (Left_Int) * Right_Int) then
1914 Result := Left_Int ** Right_Int;
1915 else
1916 Result := Left_Int;
1917 end if;
1919 if Is_Modular_Integer_Type (Etype (N)) then
1920 Result := Result mod Modulus (Etype (N));
1921 end if;
1923 Fold_Uint (N, Result, Stat);
1924 end if;
1925 end;
1927 -- Real case
1929 else
1930 declare
1931 Left_Real : constant Ureal := Expr_Value_R (Left);
1933 begin
1934 -- Cannot have a zero base with a negative exponent
1936 if UR_Is_Zero (Left_Real) then
1938 if Right_Int < 0 then
1939 Apply_Compile_Time_Constraint_Error
1940 (N, "zero ** negative integer",
1941 CE_Range_Check_Failed,
1942 Warn => not Stat);
1943 return;
1944 else
1945 Fold_Ureal (N, Ureal_0, Stat);
1946 end if;
1948 else
1949 Fold_Ureal (N, Left_Real ** Right_Int, Stat);
1950 end if;
1951 end;
1952 end if;
1953 end;
1954 end Eval_Op_Expon;
1956 -----------------
1957 -- Eval_Op_Not --
1958 -----------------
1960 -- The not operation is a static functions, so the result is potentially
1961 -- static if the operand is potentially static (RM 4.9(7), 4.9(20)).
1963 procedure Eval_Op_Not (N : Node_Id) is
1964 Right : constant Node_Id := Right_Opnd (N);
1965 Stat : Boolean;
1966 Fold : Boolean;
1968 begin
1969 -- If not foldable we are done
1971 Test_Expression_Is_Foldable (N, Right, Stat, Fold);
1973 if not Fold then
1974 return;
1975 end if;
1977 -- Fold not operation
1979 declare
1980 Rint : constant Uint := Expr_Value (Right);
1981 Typ : constant Entity_Id := Etype (N);
1983 begin
1984 -- Negation is equivalent to subtracting from the modulus minus
1985 -- one. For a binary modulus this is equivalent to the ones-
1986 -- component of the original value. For non-binary modulus this
1987 -- is an arbitrary but consistent definition.
1989 if Is_Modular_Integer_Type (Typ) then
1990 Fold_Uint (N, Modulus (Typ) - 1 - Rint, Stat);
1992 else
1993 pragma Assert (Is_Boolean_Type (Typ));
1994 Fold_Uint (N, Test (not Is_True (Rint)), Stat);
1995 end if;
1997 Set_Is_Static_Expression (N, Stat);
1998 end;
1999 end Eval_Op_Not;
2001 -------------------------------
2002 -- Eval_Qualified_Expression --
2003 -------------------------------
2005 -- A qualified expression is potentially static if its subtype mark denotes
2006 -- a static subtype and its expression is potentially static (RM 4.9 (11)).
2008 procedure Eval_Qualified_Expression (N : Node_Id) is
2009 Operand : constant Node_Id := Expression (N);
2010 Target_Type : constant Entity_Id := Entity (Subtype_Mark (N));
2012 Stat : Boolean;
2013 Fold : Boolean;
2014 Hex : Boolean;
2016 begin
2017 -- Can only fold if target is string or scalar and subtype is static
2018 -- Also, do not fold if our parent is an allocator (this is because
2019 -- the qualified expression is really part of the syntactic structure
2020 -- of an allocator, and we do not want to end up with something that
2021 -- corresponds to "new 1" where the 1 is the result of folding a
2022 -- qualified expression).
2024 if not Is_Static_Subtype (Target_Type)
2025 or else Nkind (Parent (N)) = N_Allocator
2026 then
2027 Check_Non_Static_Context (Operand);
2029 -- If operand is known to raise constraint_error, set the
2030 -- flag on the expression so it does not get optimized away.
2032 if Nkind (Operand) = N_Raise_Constraint_Error then
2033 Set_Raises_Constraint_Error (N);
2034 end if;
2036 return;
2037 end if;
2039 -- If not foldable we are done
2041 Test_Expression_Is_Foldable (N, Operand, Stat, Fold);
2043 if not Fold then
2044 return;
2046 -- Don't try fold if target type has constraint error bounds
2048 elsif not Is_OK_Static_Subtype (Target_Type) then
2049 Set_Raises_Constraint_Error (N);
2050 return;
2051 end if;
2053 -- Here we will fold, save Print_In_Hex indication
2055 Hex := Nkind (Operand) = N_Integer_Literal
2056 and then Print_In_Hex (Operand);
2058 -- Fold the result of qualification
2060 if Is_Discrete_Type (Target_Type) then
2061 Fold_Uint (N, Expr_Value (Operand), Stat);
2063 -- Preserve Print_In_Hex indication
2065 if Hex and then Nkind (N) = N_Integer_Literal then
2066 Set_Print_In_Hex (N);
2067 end if;
2069 elsif Is_Real_Type (Target_Type) then
2070 Fold_Ureal (N, Expr_Value_R (Operand), Stat);
2072 else
2073 Fold_Str (N, Strval (Get_String_Val (Operand)), Stat);
2075 if not Stat then
2076 Set_Is_Static_Expression (N, False);
2077 else
2078 Check_String_Literal_Length (N, Target_Type);
2079 end if;
2081 return;
2082 end if;
2084 -- The expression may be foldable but not static
2086 Set_Is_Static_Expression (N, Stat);
2088 if Is_Out_Of_Range (N, Etype (N)) then
2089 Out_Of_Range (N);
2090 end if;
2091 end Eval_Qualified_Expression;
2093 -----------------------
2094 -- Eval_Real_Literal --
2095 -----------------------
2097 -- Numeric literals are static (RM 4.9(1)), and have already been marked
2098 -- as static by the analyzer. The reason we did it that early is to allow
2099 -- the possibility of turning off the Is_Static_Expression flag after
2100 -- analysis, but before resolution, when integer literals are generated
2101 -- in the expander that do not correspond to static expressions.
2103 procedure Eval_Real_Literal (N : Node_Id) is
2104 begin
2105 -- If the literal appears in a non-expression context, then it is
2106 -- certainly appearing in a non-static context, so check it.
2108 if Nkind (Parent (N)) not in N_Subexpr then
2109 Check_Non_Static_Context (N);
2110 end if;
2112 end Eval_Real_Literal;
2114 ------------------------
2115 -- Eval_Relational_Op --
2116 ------------------------
2118 -- Relational operations are static functions, so the result is static
2119 -- if both operands are static (RM 4.9(7), 4.9(20)).
2121 procedure Eval_Relational_Op (N : Node_Id) is
2122 Left : constant Node_Id := Left_Opnd (N);
2123 Right : constant Node_Id := Right_Opnd (N);
2124 Typ : constant Entity_Id := Etype (Left);
2125 Result : Boolean;
2126 Stat : Boolean;
2127 Fold : Boolean;
2129 begin
2130 -- One special case to deal with first. If we can tell that
2131 -- the result will be false because the lengths of one or
2132 -- more index subtypes are compile time known and different,
2133 -- then we can replace the entire result by False. We only
2134 -- do this for one dimensional arrays, because the case of
2135 -- multi-dimensional arrays is rare and too much trouble!
2137 if Is_Array_Type (Typ)
2138 and then Number_Dimensions (Typ) = 1
2139 and then (Nkind (N) = N_Op_Eq
2140 or else Nkind (N) = N_Op_Ne)
2141 then
2142 if Raises_Constraint_Error (Left)
2143 or else Raises_Constraint_Error (Right)
2144 then
2145 return;
2146 end if;
2148 declare
2149 procedure Get_Static_Length (Op : Node_Id; Len : out Uint);
2150 -- If Op is an expression for a constrained array with a
2151 -- known at compile time length, then Len is set to this
2152 -- (non-negative length). Otherwise Len is set to minus 1.
2154 -----------------------
2155 -- Get_Static_Length --
2156 -----------------------
2158 procedure Get_Static_Length (Op : Node_Id; Len : out Uint) is
2159 T : Entity_Id;
2161 begin
2162 if Nkind (Op) = N_String_Literal then
2163 Len := UI_From_Int (String_Length (Strval (Op)));
2165 elsif not Is_Constrained (Etype (Op)) then
2166 Len := Uint_Minus_1;
2168 else
2169 T := Etype (First_Index (Etype (Op)));
2171 if Is_Discrete_Type (T)
2172 and then
2173 Compile_Time_Known_Value (Type_Low_Bound (T))
2174 and then
2175 Compile_Time_Known_Value (Type_High_Bound (T))
2176 then
2177 Len := UI_Max (Uint_0,
2178 Expr_Value (Type_High_Bound (T)) -
2179 Expr_Value (Type_Low_Bound (T)) + 1);
2180 else
2181 Len := Uint_Minus_1;
2182 end if;
2183 end if;
2184 end Get_Static_Length;
2186 Len_L : Uint;
2187 Len_R : Uint;
2189 begin
2190 Get_Static_Length (Left, Len_L);
2191 Get_Static_Length (Right, Len_R);
2193 if Len_L /= Uint_Minus_1
2194 and then Len_R /= Uint_Minus_1
2195 and then Len_L /= Len_R
2196 then
2197 Fold_Uint (N, Test (Nkind (N) = N_Op_Ne), False);
2198 Warn_On_Known_Condition (N);
2199 return;
2200 end if;
2201 end;
2203 -- Another special case: comparisons against null for pointers that
2204 -- are known to be non-null. This is useful when migrating from Ada95
2205 -- code when non-null restrictions are added to type declarations and
2206 -- parameter specifications.
2208 elsif Is_Access_Type (Typ)
2209 and then Comes_From_Source (N)
2210 and then
2211 ((Is_Entity_Name (Left)
2212 and then Is_Known_Non_Null (Entity (Left))
2213 and then Nkind (Right) = N_Null)
2214 or else
2215 (Is_Entity_Name (Right)
2216 and then Is_Known_Non_Null (Entity (Right))
2217 and then Nkind (Left) = N_Null))
2218 then
2219 Fold_Uint (N, Test (Nkind (N) = N_Op_Ne), False);
2220 Warn_On_Known_Condition (N);
2221 return;
2222 end if;
2224 -- Can only fold if type is scalar (don't fold string ops)
2226 if not Is_Scalar_Type (Typ) then
2227 Check_Non_Static_Context (Left);
2228 Check_Non_Static_Context (Right);
2229 return;
2230 end if;
2232 -- If not foldable we are done
2234 Test_Expression_Is_Foldable (N, Left, Right, Stat, Fold);
2236 if not Fold then
2237 return;
2238 end if;
2240 -- Integer and Enumeration (discrete) type cases
2242 if Is_Discrete_Type (Typ) then
2243 declare
2244 Left_Int : constant Uint := Expr_Value (Left);
2245 Right_Int : constant Uint := Expr_Value (Right);
2247 begin
2248 case Nkind (N) is
2249 when N_Op_Eq => Result := Left_Int = Right_Int;
2250 when N_Op_Ne => Result := Left_Int /= Right_Int;
2251 when N_Op_Lt => Result := Left_Int < Right_Int;
2252 when N_Op_Le => Result := Left_Int <= Right_Int;
2253 when N_Op_Gt => Result := Left_Int > Right_Int;
2254 when N_Op_Ge => Result := Left_Int >= Right_Int;
2256 when others =>
2257 raise Program_Error;
2258 end case;
2260 Fold_Uint (N, Test (Result), Stat);
2261 end;
2263 -- Real type case
2265 else
2266 pragma Assert (Is_Real_Type (Typ));
2268 declare
2269 Left_Real : constant Ureal := Expr_Value_R (Left);
2270 Right_Real : constant Ureal := Expr_Value_R (Right);
2272 begin
2273 case Nkind (N) is
2274 when N_Op_Eq => Result := (Left_Real = Right_Real);
2275 when N_Op_Ne => Result := (Left_Real /= Right_Real);
2276 when N_Op_Lt => Result := (Left_Real < Right_Real);
2277 when N_Op_Le => Result := (Left_Real <= Right_Real);
2278 when N_Op_Gt => Result := (Left_Real > Right_Real);
2279 when N_Op_Ge => Result := (Left_Real >= Right_Real);
2281 when others =>
2282 raise Program_Error;
2283 end case;
2285 Fold_Uint (N, Test (Result), Stat);
2286 end;
2287 end if;
2289 Warn_On_Known_Condition (N);
2290 end Eval_Relational_Op;
2292 ----------------
2293 -- Eval_Shift --
2294 ----------------
2296 -- Shift operations are intrinsic operations that can never be static,
2297 -- so the only processing required is to perform the required check for
2298 -- a non static context for the two operands.
2300 -- Actually we could do some compile time evaluation here some time ???
2302 procedure Eval_Shift (N : Node_Id) is
2303 begin
2304 Check_Non_Static_Context (Left_Opnd (N));
2305 Check_Non_Static_Context (Right_Opnd (N));
2306 end Eval_Shift;
2308 ------------------------
2309 -- Eval_Short_Circuit --
2310 ------------------------
2312 -- A short circuit operation is potentially static if both operands
2313 -- are potentially static (RM 4.9 (13))
2315 procedure Eval_Short_Circuit (N : Node_Id) is
2316 Kind : constant Node_Kind := Nkind (N);
2317 Left : constant Node_Id := Left_Opnd (N);
2318 Right : constant Node_Id := Right_Opnd (N);
2319 Left_Int : Uint;
2320 Rstat : constant Boolean :=
2321 Is_Static_Expression (Left)
2322 and then Is_Static_Expression (Right);
2324 begin
2325 -- Short circuit operations are never static in Ada 83
2327 if Ada_Version = Ada_83
2328 and then Comes_From_Source (N)
2329 then
2330 Check_Non_Static_Context (Left);
2331 Check_Non_Static_Context (Right);
2332 return;
2333 end if;
2335 -- Now look at the operands, we can't quite use the normal call to
2336 -- Test_Expression_Is_Foldable here because short circuit operations
2337 -- are a special case, they can still be foldable, even if the right
2338 -- operand raises constraint error.
2340 -- If either operand is Any_Type, just propagate to result and
2341 -- do not try to fold, this prevents cascaded errors.
2343 if Etype (Left) = Any_Type or else Etype (Right) = Any_Type then
2344 Set_Etype (N, Any_Type);
2345 return;
2347 -- If left operand raises constraint error, then replace node N with
2348 -- the raise constraint error node, and we are obviously not foldable.
2349 -- Is_Static_Expression is set from the two operands in the normal way,
2350 -- and we check the right operand if it is in a non-static context.
2352 elsif Raises_Constraint_Error (Left) then
2353 if not Rstat then
2354 Check_Non_Static_Context (Right);
2355 end if;
2357 Rewrite_In_Raise_CE (N, Left);
2358 Set_Is_Static_Expression (N, Rstat);
2359 return;
2361 -- If the result is not static, then we won't in any case fold
2363 elsif not Rstat then
2364 Check_Non_Static_Context (Left);
2365 Check_Non_Static_Context (Right);
2366 return;
2367 end if;
2369 -- Here the result is static, note that, unlike the normal processing
2370 -- in Test_Expression_Is_Foldable, we did *not* check above to see if
2371 -- the right operand raises constraint error, that's because it is not
2372 -- significant if the left operand is decisive.
2374 Set_Is_Static_Expression (N);
2376 -- It does not matter if the right operand raises constraint error if
2377 -- it will not be evaluated. So deal specially with the cases where
2378 -- the right operand is not evaluated. Note that we will fold these
2379 -- cases even if the right operand is non-static, which is fine, but
2380 -- of course in these cases the result is not potentially static.
2382 Left_Int := Expr_Value (Left);
2384 if (Kind = N_And_Then and then Is_False (Left_Int))
2385 or else (Kind = N_Or_Else and Is_True (Left_Int))
2386 then
2387 Fold_Uint (N, Left_Int, Rstat);
2388 return;
2389 end if;
2391 -- If first operand not decisive, then it does matter if the right
2392 -- operand raises constraint error, since it will be evaluated, so
2393 -- we simply replace the node with the right operand. Note that this
2394 -- properly propagates Is_Static_Expression and Raises_Constraint_Error
2395 -- (both are set to True in Right).
2397 if Raises_Constraint_Error (Right) then
2398 Rewrite_In_Raise_CE (N, Right);
2399 Check_Non_Static_Context (Left);
2400 return;
2401 end if;
2403 -- Otherwise the result depends on the right operand
2405 Fold_Uint (N, Expr_Value (Right), Rstat);
2406 return;
2407 end Eval_Short_Circuit;
2409 ----------------
2410 -- Eval_Slice --
2411 ----------------
2413 -- Slices can never be static, so the only processing required is to
2414 -- check for non-static context if an explicit range is given.
2416 procedure Eval_Slice (N : Node_Id) is
2417 Drange : constant Node_Id := Discrete_Range (N);
2419 begin
2420 if Nkind (Drange) = N_Range then
2421 Check_Non_Static_Context (Low_Bound (Drange));
2422 Check_Non_Static_Context (High_Bound (Drange));
2423 end if;
2424 end Eval_Slice;
2426 -------------------------
2427 -- Eval_String_Literal --
2428 -------------------------
2430 procedure Eval_String_Literal (N : Node_Id) is
2431 Typ : constant Entity_Id := Etype (N);
2432 Bas : constant Entity_Id := Base_Type (Typ);
2433 Xtp : Entity_Id;
2434 Len : Nat;
2435 Lo : Node_Id;
2437 begin
2438 -- Nothing to do if error type (handles cases like default expressions
2439 -- or generics where we have not yet fully resolved the type)
2441 if Bas = Any_Type or else Bas = Any_String then
2442 return;
2443 end if;
2445 -- String literals are static if the subtype is static (RM 4.9(2)), so
2446 -- reset the static expression flag (it was set unconditionally in
2447 -- Analyze_String_Literal) if the subtype is non-static. We tell if
2448 -- the subtype is static by looking at the lower bound.
2450 if Ekind (Typ) = E_String_Literal_Subtype then
2451 if not Is_OK_Static_Expression (String_Literal_Low_Bound (Typ)) then
2452 Set_Is_Static_Expression (N, False);
2453 return;
2454 end if;
2456 -- Here if Etype of string literal is normal Etype (not yet possible,
2457 -- but may be possible in future!)
2459 elsif not Is_OK_Static_Expression
2460 (Type_Low_Bound (Etype (First_Index (Typ))))
2461 then
2462 Set_Is_Static_Expression (N, False);
2463 return;
2464 end if;
2466 -- If original node was a type conversion, then result if non-static
2468 if Nkind (Original_Node (N)) = N_Type_Conversion then
2469 Set_Is_Static_Expression (N, False);
2470 return;
2471 end if;
2473 -- Test for illegal Ada 95 cases. A string literal is illegal in
2474 -- Ada 95 if its bounds are outside the index base type and this
2475 -- index type is static. This can happen in only two ways. Either
2476 -- the string literal is too long, or it is null, and the lower
2477 -- bound is type'First. In either case it is the upper bound that
2478 -- is out of range of the index type.
2480 if Ada_Version >= Ada_95 then
2481 if Root_Type (Bas) = Standard_String
2482 or else
2483 Root_Type (Bas) = Standard_Wide_String
2484 then
2485 Xtp := Standard_Positive;
2486 else
2487 Xtp := Etype (First_Index (Bas));
2488 end if;
2490 if Ekind (Typ) = E_String_Literal_Subtype then
2491 Lo := String_Literal_Low_Bound (Typ);
2492 else
2493 Lo := Type_Low_Bound (Etype (First_Index (Typ)));
2494 end if;
2496 Len := String_Length (Strval (N));
2498 if UI_From_Int (Len) > String_Type_Len (Bas) then
2499 Apply_Compile_Time_Constraint_Error
2500 (N, "string literal too long for}", CE_Length_Check_Failed,
2501 Ent => Bas,
2502 Typ => First_Subtype (Bas));
2504 elsif Len = 0
2505 and then not Is_Generic_Type (Xtp)
2506 and then
2507 Expr_Value (Lo) = Expr_Value (Type_Low_Bound (Base_Type (Xtp)))
2508 then
2509 Apply_Compile_Time_Constraint_Error
2510 (N, "null string literal not allowed for}",
2511 CE_Length_Check_Failed,
2512 Ent => Bas,
2513 Typ => First_Subtype (Bas));
2514 end if;
2515 end if;
2516 end Eval_String_Literal;
2518 --------------------------
2519 -- Eval_Type_Conversion --
2520 --------------------------
2522 -- A type conversion is potentially static if its subtype mark is for a
2523 -- static scalar subtype, and its operand expression is potentially static
2524 -- (RM 4.9 (10))
2526 procedure Eval_Type_Conversion (N : Node_Id) is
2527 Operand : constant Node_Id := Expression (N);
2528 Source_Type : constant Entity_Id := Etype (Operand);
2529 Target_Type : constant Entity_Id := Etype (N);
2531 Stat : Boolean;
2532 Fold : Boolean;
2534 function To_Be_Treated_As_Integer (T : Entity_Id) return Boolean;
2535 -- Returns true if type T is an integer type, or if it is a
2536 -- fixed-point type to be treated as an integer (i.e. the flag
2537 -- Conversion_OK is set on the conversion node).
2539 function To_Be_Treated_As_Real (T : Entity_Id) return Boolean;
2540 -- Returns true if type T is a floating-point type, or if it is a
2541 -- fixed-point type that is not to be treated as an integer (i.e. the
2542 -- flag Conversion_OK is not set on the conversion node).
2544 ------------------------------
2545 -- To_Be_Treated_As_Integer --
2546 ------------------------------
2548 function To_Be_Treated_As_Integer (T : Entity_Id) return Boolean is
2549 begin
2550 return
2551 Is_Integer_Type (T)
2552 or else (Is_Fixed_Point_Type (T) and then Conversion_OK (N));
2553 end To_Be_Treated_As_Integer;
2555 ---------------------------
2556 -- To_Be_Treated_As_Real --
2557 ---------------------------
2559 function To_Be_Treated_As_Real (T : Entity_Id) return Boolean is
2560 begin
2561 return
2562 Is_Floating_Point_Type (T)
2563 or else (Is_Fixed_Point_Type (T) and then not Conversion_OK (N));
2564 end To_Be_Treated_As_Real;
2566 -- Start of processing for Eval_Type_Conversion
2568 begin
2569 -- Cannot fold if target type is non-static or if semantic error
2571 if not Is_Static_Subtype (Target_Type) then
2572 Check_Non_Static_Context (Operand);
2573 return;
2575 elsif Error_Posted (N) then
2576 return;
2577 end if;
2579 -- If not foldable we are done
2581 Test_Expression_Is_Foldable (N, Operand, Stat, Fold);
2583 if not Fold then
2584 return;
2586 -- Don't try fold if target type has constraint error bounds
2588 elsif not Is_OK_Static_Subtype (Target_Type) then
2589 Set_Raises_Constraint_Error (N);
2590 return;
2591 end if;
2593 -- Remaining processing depends on operand types. Note that in the
2594 -- following type test, fixed-point counts as real unless the flag
2595 -- Conversion_OK is set, in which case it counts as integer.
2597 -- Fold conversion, case of string type. The result is not static
2599 if Is_String_Type (Target_Type) then
2600 Fold_Str (N, Strval (Get_String_Val (Operand)), False);
2602 return;
2604 -- Fold conversion, case of integer target type
2606 elsif To_Be_Treated_As_Integer (Target_Type) then
2607 declare
2608 Result : Uint;
2610 begin
2611 -- Integer to integer conversion
2613 if To_Be_Treated_As_Integer (Source_Type) then
2614 Result := Expr_Value (Operand);
2616 -- Real to integer conversion
2618 else
2619 Result := UR_To_Uint (Expr_Value_R (Operand));
2620 end if;
2622 -- If fixed-point type (Conversion_OK must be set), then the
2623 -- result is logically an integer, but we must replace the
2624 -- conversion with the corresponding real literal, since the
2625 -- type from a semantic point of view is still fixed-point.
2627 if Is_Fixed_Point_Type (Target_Type) then
2628 Fold_Ureal
2629 (N, UR_From_Uint (Result) * Small_Value (Target_Type), Stat);
2631 -- Otherwise result is integer literal
2633 else
2634 Fold_Uint (N, Result, Stat);
2635 end if;
2636 end;
2638 -- Fold conversion, case of real target type
2640 elsif To_Be_Treated_As_Real (Target_Type) then
2641 declare
2642 Result : Ureal;
2644 begin
2645 if To_Be_Treated_As_Real (Source_Type) then
2646 Result := Expr_Value_R (Operand);
2647 else
2648 Result := UR_From_Uint (Expr_Value (Operand));
2649 end if;
2651 Fold_Ureal (N, Result, Stat);
2652 end;
2654 -- Enumeration types
2656 else
2657 Fold_Uint (N, Expr_Value (Operand), Stat);
2658 end if;
2660 if Is_Out_Of_Range (N, Etype (N)) then
2661 Out_Of_Range (N);
2662 end if;
2664 end Eval_Type_Conversion;
2666 -------------------
2667 -- Eval_Unary_Op --
2668 -------------------
2670 -- Predefined unary operators are static functions (RM 4.9(20)) and thus
2671 -- are potentially static if the operand is potentially static (RM 4.9(7))
2673 procedure Eval_Unary_Op (N : Node_Id) is
2674 Right : constant Node_Id := Right_Opnd (N);
2675 Stat : Boolean;
2676 Fold : Boolean;
2678 begin
2679 -- If not foldable we are done
2681 Test_Expression_Is_Foldable (N, Right, Stat, Fold);
2683 if not Fold then
2684 return;
2685 end if;
2687 -- Fold for integer case
2689 if Is_Integer_Type (Etype (N)) then
2690 declare
2691 Rint : constant Uint := Expr_Value (Right);
2692 Result : Uint;
2694 begin
2695 -- In the case of modular unary plus and abs there is no need
2696 -- to adjust the result of the operation since if the original
2697 -- operand was in bounds the result will be in the bounds of the
2698 -- modular type. However, in the case of modular unary minus the
2699 -- result may go out of the bounds of the modular type and needs
2700 -- adjustment.
2702 if Nkind (N) = N_Op_Plus then
2703 Result := Rint;
2705 elsif Nkind (N) = N_Op_Minus then
2706 if Is_Modular_Integer_Type (Etype (N)) then
2707 Result := (-Rint) mod Modulus (Etype (N));
2708 else
2709 Result := (-Rint);
2710 end if;
2712 else
2713 pragma Assert (Nkind (N) = N_Op_Abs);
2714 Result := abs Rint;
2715 end if;
2717 Fold_Uint (N, Result, Stat);
2718 end;
2720 -- Fold for real case
2722 elsif Is_Real_Type (Etype (N)) then
2723 declare
2724 Rreal : constant Ureal := Expr_Value_R (Right);
2725 Result : Ureal;
2727 begin
2728 if Nkind (N) = N_Op_Plus then
2729 Result := Rreal;
2731 elsif Nkind (N) = N_Op_Minus then
2732 Result := UR_Negate (Rreal);
2734 else
2735 pragma Assert (Nkind (N) = N_Op_Abs);
2736 Result := abs Rreal;
2737 end if;
2739 Fold_Ureal (N, Result, Stat);
2740 end;
2741 end if;
2742 end Eval_Unary_Op;
2744 -------------------------------
2745 -- Eval_Unchecked_Conversion --
2746 -------------------------------
2748 -- Unchecked conversions can never be static, so the only required
2749 -- processing is to check for a non-static context for the operand.
2751 procedure Eval_Unchecked_Conversion (N : Node_Id) is
2752 begin
2753 Check_Non_Static_Context (Expression (N));
2754 end Eval_Unchecked_Conversion;
2756 --------------------
2757 -- Expr_Rep_Value --
2758 --------------------
2760 function Expr_Rep_Value (N : Node_Id) return Uint is
2761 Kind : constant Node_Kind := Nkind (N);
2762 Ent : Entity_Id;
2764 begin
2765 if Is_Entity_Name (N) then
2766 Ent := Entity (N);
2768 -- An enumeration literal that was either in the source or
2769 -- created as a result of static evaluation.
2771 if Ekind (Ent) = E_Enumeration_Literal then
2772 return Enumeration_Rep (Ent);
2774 -- A user defined static constant
2776 else
2777 pragma Assert (Ekind (Ent) = E_Constant);
2778 return Expr_Rep_Value (Constant_Value (Ent));
2779 end if;
2781 -- An integer literal that was either in the source or created
2782 -- as a result of static evaluation.
2784 elsif Kind = N_Integer_Literal then
2785 return Intval (N);
2787 -- A real literal for a fixed-point type. This must be the fixed-point
2788 -- case, either the literal is of a fixed-point type, or it is a bound
2789 -- of a fixed-point type, with type universal real. In either case we
2790 -- obtain the desired value from Corresponding_Integer_Value.
2792 elsif Kind = N_Real_Literal then
2793 pragma Assert (Is_Fixed_Point_Type (Underlying_Type (Etype (N))));
2794 return Corresponding_Integer_Value (N);
2796 -- Peculiar VMS case, if we have xxx'Null_Parameter, return zero
2798 elsif Kind = N_Attribute_Reference
2799 and then Attribute_Name (N) = Name_Null_Parameter
2800 then
2801 return Uint_0;
2803 -- Otherwise must be character literal
2805 else
2806 pragma Assert (Kind = N_Character_Literal);
2807 Ent := Entity (N);
2809 -- Since Character literals of type Standard.Character don't
2810 -- have any defining character literals built for them, they
2811 -- do not have their Entity set, so just use their Char
2812 -- code. Otherwise for user-defined character literals use
2813 -- their Pos value as usual which is the same as the Rep value.
2815 if No (Ent) then
2816 return Char_Literal_Value (N);
2817 else
2818 return Enumeration_Rep (Ent);
2819 end if;
2820 end if;
2821 end Expr_Rep_Value;
2823 ----------------
2824 -- Expr_Value --
2825 ----------------
2827 function Expr_Value (N : Node_Id) return Uint is
2828 Kind : constant Node_Kind := Nkind (N);
2829 CV_Ent : CV_Entry renames CV_Cache (Nat (N) mod CV_Cache_Size);
2830 Ent : Entity_Id;
2831 Val : Uint;
2833 begin
2834 -- If already in cache, then we know it's compile time known and
2835 -- we can return the value that was previously stored in the cache
2836 -- since compile time known values cannot change :-)
2838 if CV_Ent.N = N then
2839 return CV_Ent.V;
2840 end if;
2842 -- Otherwise proceed to test value
2844 if Is_Entity_Name (N) then
2845 Ent := Entity (N);
2847 -- An enumeration literal that was either in the source or
2848 -- created as a result of static evaluation.
2850 if Ekind (Ent) = E_Enumeration_Literal then
2851 Val := Enumeration_Pos (Ent);
2853 -- A user defined static constant
2855 else
2856 pragma Assert (Ekind (Ent) = E_Constant);
2857 Val := Expr_Value (Constant_Value (Ent));
2858 end if;
2860 -- An integer literal that was either in the source or created
2861 -- as a result of static evaluation.
2863 elsif Kind = N_Integer_Literal then
2864 Val := Intval (N);
2866 -- A real literal for a fixed-point type. This must be the fixed-point
2867 -- case, either the literal is of a fixed-point type, or it is a bound
2868 -- of a fixed-point type, with type universal real. In either case we
2869 -- obtain the desired value from Corresponding_Integer_Value.
2871 elsif Kind = N_Real_Literal then
2873 pragma Assert (Is_Fixed_Point_Type (Underlying_Type (Etype (N))));
2874 Val := Corresponding_Integer_Value (N);
2876 -- Peculiar VMS case, if we have xxx'Null_Parameter, return zero
2878 elsif Kind = N_Attribute_Reference
2879 and then Attribute_Name (N) = Name_Null_Parameter
2880 then
2881 Val := Uint_0;
2883 -- Otherwise must be character literal
2885 else
2886 pragma Assert (Kind = N_Character_Literal);
2887 Ent := Entity (N);
2889 -- Since Character literals of type Standard.Character don't
2890 -- have any defining character literals built for them, they
2891 -- do not have their Entity set, so just use their Char
2892 -- code. Otherwise for user-defined character literals use
2893 -- their Pos value as usual.
2895 if No (Ent) then
2896 Val := Char_Literal_Value (N);
2897 else
2898 Val := Enumeration_Pos (Ent);
2899 end if;
2900 end if;
2902 -- Come here with Val set to value to be returned, set cache
2904 CV_Ent.N := N;
2905 CV_Ent.V := Val;
2906 return Val;
2907 end Expr_Value;
2909 ------------------
2910 -- Expr_Value_E --
2911 ------------------
2913 function Expr_Value_E (N : Node_Id) return Entity_Id is
2914 Ent : constant Entity_Id := Entity (N);
2916 begin
2917 if Ekind (Ent) = E_Enumeration_Literal then
2918 return Ent;
2919 else
2920 pragma Assert (Ekind (Ent) = E_Constant);
2921 return Expr_Value_E (Constant_Value (Ent));
2922 end if;
2923 end Expr_Value_E;
2925 ------------------
2926 -- Expr_Value_R --
2927 ------------------
2929 function Expr_Value_R (N : Node_Id) return Ureal is
2930 Kind : constant Node_Kind := Nkind (N);
2931 Ent : Entity_Id;
2932 Expr : Node_Id;
2934 begin
2935 if Kind = N_Real_Literal then
2936 return Realval (N);
2938 elsif Kind = N_Identifier or else Kind = N_Expanded_Name then
2939 Ent := Entity (N);
2940 pragma Assert (Ekind (Ent) = E_Constant);
2941 return Expr_Value_R (Constant_Value (Ent));
2943 elsif Kind = N_Integer_Literal then
2944 return UR_From_Uint (Expr_Value (N));
2946 -- Strange case of VAX literals, which are at this stage transformed
2947 -- into Vax_Type!x_To_y(IEEE_Literal). See Expand_N_Real_Literal in
2948 -- Exp_Vfpt for further details.
2950 elsif Vax_Float (Etype (N))
2951 and then Nkind (N) = N_Unchecked_Type_Conversion
2952 then
2953 Expr := Expression (N);
2955 if Nkind (Expr) = N_Function_Call
2956 and then Present (Parameter_Associations (Expr))
2957 then
2958 Expr := First (Parameter_Associations (Expr));
2960 if Nkind (Expr) = N_Real_Literal then
2961 return Realval (Expr);
2962 end if;
2963 end if;
2965 -- Peculiar VMS case, if we have xxx'Null_Parameter, return 0.0
2967 elsif Kind = N_Attribute_Reference
2968 and then Attribute_Name (N) = Name_Null_Parameter
2969 then
2970 return Ureal_0;
2971 end if;
2973 -- If we fall through, we have a node that cannot be interepreted
2974 -- as a compile time constant. That is definitely an error.
2976 raise Program_Error;
2977 end Expr_Value_R;
2979 ------------------
2980 -- Expr_Value_S --
2981 ------------------
2983 function Expr_Value_S (N : Node_Id) return Node_Id is
2984 begin
2985 if Nkind (N) = N_String_Literal then
2986 return N;
2987 else
2988 pragma Assert (Ekind (Entity (N)) = E_Constant);
2989 return Expr_Value_S (Constant_Value (Entity (N)));
2990 end if;
2991 end Expr_Value_S;
2993 --------------------------
2994 -- Flag_Non_Static_Expr --
2995 --------------------------
2997 procedure Flag_Non_Static_Expr (Msg : String; Expr : Node_Id) is
2998 begin
2999 if Error_Posted (Expr) and then not All_Errors_Mode then
3000 return;
3001 else
3002 Error_Msg_F (Msg, Expr);
3003 Why_Not_Static (Expr);
3004 end if;
3005 end Flag_Non_Static_Expr;
3007 --------------
3008 -- Fold_Str --
3009 --------------
3011 procedure Fold_Str (N : Node_Id; Val : String_Id; Static : Boolean) is
3012 Loc : constant Source_Ptr := Sloc (N);
3013 Typ : constant Entity_Id := Etype (N);
3015 begin
3016 Rewrite (N, Make_String_Literal (Loc, Strval => Val));
3018 -- We now have the literal with the right value, both the actual type
3019 -- and the expected type of this literal are taken from the expression
3020 -- that was evaluated.
3022 Analyze (N);
3023 Set_Is_Static_Expression (N, Static);
3024 Set_Etype (N, Typ);
3025 Resolve (N);
3026 end Fold_Str;
3028 ---------------
3029 -- Fold_Uint --
3030 ---------------
3032 procedure Fold_Uint (N : Node_Id; Val : Uint; Static : Boolean) is
3033 Loc : constant Source_Ptr := Sloc (N);
3034 Typ : Entity_Id := Etype (N);
3035 Ent : Entity_Id;
3037 begin
3038 -- If we are folding a named number, retain the entity in the
3039 -- literal, for ASIS use.
3041 if Is_Entity_Name (N)
3042 and then Ekind (Entity (N)) = E_Named_Integer
3043 then
3044 Ent := Entity (N);
3045 else
3046 Ent := Empty;
3047 end if;
3049 if Is_Private_Type (Typ) then
3050 Typ := Full_View (Typ);
3051 end if;
3053 -- For a result of type integer, subsitute an N_Integer_Literal node
3054 -- for the result of the compile time evaluation of the expression.
3056 if Is_Integer_Type (Typ) then
3057 Rewrite (N, Make_Integer_Literal (Loc, Val));
3058 Set_Original_Entity (N, Ent);
3060 -- Otherwise we have an enumeration type, and we substitute either
3061 -- an N_Identifier or N_Character_Literal to represent the enumeration
3062 -- literal corresponding to the given value, which must always be in
3063 -- range, because appropriate tests have already been made for this.
3065 else pragma Assert (Is_Enumeration_Type (Typ));
3066 Rewrite (N, Get_Enum_Lit_From_Pos (Etype (N), Val, Loc));
3067 end if;
3069 -- We now have the literal with the right value, both the actual type
3070 -- and the expected type of this literal are taken from the expression
3071 -- that was evaluated.
3073 Analyze (N);
3074 Set_Is_Static_Expression (N, Static);
3075 Set_Etype (N, Typ);
3076 Resolve (N);
3077 end Fold_Uint;
3079 ----------------
3080 -- Fold_Ureal --
3081 ----------------
3083 procedure Fold_Ureal (N : Node_Id; Val : Ureal; Static : Boolean) is
3084 Loc : constant Source_Ptr := Sloc (N);
3085 Typ : constant Entity_Id := Etype (N);
3086 Ent : Entity_Id;
3088 begin
3089 -- If we are folding a named number, retain the entity in the
3090 -- literal, for ASIS use.
3092 if Is_Entity_Name (N)
3093 and then Ekind (Entity (N)) = E_Named_Real
3094 then
3095 Ent := Entity (N);
3096 else
3097 Ent := Empty;
3098 end if;
3100 Rewrite (N, Make_Real_Literal (Loc, Realval => Val));
3101 Set_Original_Entity (N, Ent);
3103 -- Both the actual and expected type comes from the original expression
3105 Analyze (N);
3106 Set_Is_Static_Expression (N, Static);
3107 Set_Etype (N, Typ);
3108 Resolve (N);
3109 end Fold_Ureal;
3111 ---------------
3112 -- From_Bits --
3113 ---------------
3115 function From_Bits (B : Bits; T : Entity_Id) return Uint is
3116 V : Uint := Uint_0;
3118 begin
3119 for J in 0 .. B'Last loop
3120 if B (J) then
3121 V := V + 2 ** J;
3122 end if;
3123 end loop;
3125 if Non_Binary_Modulus (T) then
3126 V := V mod Modulus (T);
3127 end if;
3129 return V;
3130 end From_Bits;
3132 --------------------
3133 -- Get_String_Val --
3134 --------------------
3136 function Get_String_Val (N : Node_Id) return Node_Id is
3137 begin
3138 if Nkind (N) = N_String_Literal then
3139 return N;
3141 elsif Nkind (N) = N_Character_Literal then
3142 return N;
3144 else
3145 pragma Assert (Is_Entity_Name (N));
3146 return Get_String_Val (Constant_Value (Entity (N)));
3147 end if;
3148 end Get_String_Val;
3150 ----------------
3151 -- Initialize --
3152 ----------------
3154 procedure Initialize is
3155 begin
3156 CV_Cache := (others => (Node_High_Bound, Uint_0));
3157 end Initialize;
3159 --------------------
3160 -- In_Subrange_Of --
3161 --------------------
3163 function In_Subrange_Of
3164 (T1 : Entity_Id;
3165 T2 : Entity_Id;
3166 Fixed_Int : Boolean := False) return Boolean
3168 L1 : Node_Id;
3169 H1 : Node_Id;
3171 L2 : Node_Id;
3172 H2 : Node_Id;
3174 begin
3175 if T1 = T2 or else Is_Subtype_Of (T1, T2) then
3176 return True;
3178 -- Never in range if both types are not scalar. Don't know if this can
3179 -- actually happen, but just in case.
3181 elsif not Is_Scalar_Type (T1) or else not Is_Scalar_Type (T1) then
3182 return False;
3184 else
3185 L1 := Type_Low_Bound (T1);
3186 H1 := Type_High_Bound (T1);
3188 L2 := Type_Low_Bound (T2);
3189 H2 := Type_High_Bound (T2);
3191 -- Check bounds to see if comparison possible at compile time
3193 if Compile_Time_Compare (L1, L2) in Compare_GE
3194 and then
3195 Compile_Time_Compare (H1, H2) in Compare_LE
3196 then
3197 return True;
3198 end if;
3200 -- If bounds not comparable at compile time, then the bounds of T2
3201 -- must be compile time known or we cannot answer the query.
3203 if not Compile_Time_Known_Value (L2)
3204 or else not Compile_Time_Known_Value (H2)
3205 then
3206 return False;
3207 end if;
3209 -- If the bounds of T1 are know at compile time then use these
3210 -- ones, otherwise use the bounds of the base type (which are of
3211 -- course always static).
3213 if not Compile_Time_Known_Value (L1) then
3214 L1 := Type_Low_Bound (Base_Type (T1));
3215 end if;
3217 if not Compile_Time_Known_Value (H1) then
3218 H1 := Type_High_Bound (Base_Type (T1));
3219 end if;
3221 -- Fixed point types should be considered as such only if
3222 -- flag Fixed_Int is set to False.
3224 if Is_Floating_Point_Type (T1) or else Is_Floating_Point_Type (T2)
3225 or else (Is_Fixed_Point_Type (T1) and then not Fixed_Int)
3226 or else (Is_Fixed_Point_Type (T2) and then not Fixed_Int)
3227 then
3228 return
3229 Expr_Value_R (L2) <= Expr_Value_R (L1)
3230 and then
3231 Expr_Value_R (H2) >= Expr_Value_R (H1);
3233 else
3234 return
3235 Expr_Value (L2) <= Expr_Value (L1)
3236 and then
3237 Expr_Value (H2) >= Expr_Value (H1);
3239 end if;
3240 end if;
3242 -- If any exception occurs, it means that we have some bug in the compiler
3243 -- possibly triggered by a previous error, or by some unforseen peculiar
3244 -- occurrence. However, this is only an optimization attempt, so there is
3245 -- really no point in crashing the compiler. Instead we just decide, too
3246 -- bad, we can't figure out the answer in this case after all.
3248 exception
3249 when others =>
3251 -- Debug flag K disables this behavior (useful for debugging)
3253 if Debug_Flag_K then
3254 raise;
3255 else
3256 return False;
3257 end if;
3258 end In_Subrange_Of;
3260 -----------------
3261 -- Is_In_Range --
3262 -----------------
3264 function Is_In_Range
3265 (N : Node_Id;
3266 Typ : Entity_Id;
3267 Fixed_Int : Boolean := False;
3268 Int_Real : Boolean := False) return Boolean
3270 Val : Uint;
3271 Valr : Ureal;
3273 begin
3274 -- Universal types have no range limits, so always in range
3276 if Typ = Universal_Integer or else Typ = Universal_Real then
3277 return True;
3279 -- Never in range if not scalar type. Don't know if this can
3280 -- actually happen, but our spec allows it, so we must check!
3282 elsif not Is_Scalar_Type (Typ) then
3283 return False;
3285 -- Never in range unless we have a compile time known value
3287 elsif not Compile_Time_Known_Value (N) then
3288 return False;
3290 else
3291 declare
3292 Lo : constant Node_Id := Type_Low_Bound (Typ);
3293 Hi : constant Node_Id := Type_High_Bound (Typ);
3294 LB_Known : constant Boolean := Compile_Time_Known_Value (Lo);
3295 UB_Known : constant Boolean := Compile_Time_Known_Value (Hi);
3297 begin
3298 -- Fixed point types should be considered as such only in
3299 -- flag Fixed_Int is set to False.
3301 if Is_Floating_Point_Type (Typ)
3302 or else (Is_Fixed_Point_Type (Typ) and then not Fixed_Int)
3303 or else Int_Real
3304 then
3305 Valr := Expr_Value_R (N);
3307 if LB_Known and then Valr >= Expr_Value_R (Lo)
3308 and then UB_Known and then Valr <= Expr_Value_R (Hi)
3309 then
3310 return True;
3311 else
3312 return False;
3313 end if;
3315 else
3316 Val := Expr_Value (N);
3318 if LB_Known and then Val >= Expr_Value (Lo)
3319 and then UB_Known and then Val <= Expr_Value (Hi)
3320 then
3321 return True;
3322 else
3323 return False;
3324 end if;
3325 end if;
3326 end;
3327 end if;
3328 end Is_In_Range;
3330 -------------------
3331 -- Is_Null_Range --
3332 -------------------
3334 function Is_Null_Range (Lo : Node_Id; Hi : Node_Id) return Boolean is
3335 Typ : constant Entity_Id := Etype (Lo);
3337 begin
3338 if not Compile_Time_Known_Value (Lo)
3339 or else not Compile_Time_Known_Value (Hi)
3340 then
3341 return False;
3342 end if;
3344 if Is_Discrete_Type (Typ) then
3345 return Expr_Value (Lo) > Expr_Value (Hi);
3347 else
3348 pragma Assert (Is_Real_Type (Typ));
3349 return Expr_Value_R (Lo) > Expr_Value_R (Hi);
3350 end if;
3351 end Is_Null_Range;
3353 -----------------------------
3354 -- Is_OK_Static_Expression --
3355 -----------------------------
3357 function Is_OK_Static_Expression (N : Node_Id) return Boolean is
3358 begin
3359 return Is_Static_Expression (N)
3360 and then not Raises_Constraint_Error (N);
3361 end Is_OK_Static_Expression;
3363 ------------------------
3364 -- Is_OK_Static_Range --
3365 ------------------------
3367 -- A static range is a range whose bounds are static expressions, or a
3368 -- Range_Attribute_Reference equivalent to such a range (RM 4.9(26)).
3369 -- We have already converted range attribute references, so we get the
3370 -- "or" part of this rule without needing a special test.
3372 function Is_OK_Static_Range (N : Node_Id) return Boolean is
3373 begin
3374 return Is_OK_Static_Expression (Low_Bound (N))
3375 and then Is_OK_Static_Expression (High_Bound (N));
3376 end Is_OK_Static_Range;
3378 --------------------------
3379 -- Is_OK_Static_Subtype --
3380 --------------------------
3382 -- Determines if Typ is a static subtype as defined in (RM 4.9(26))
3383 -- where neither bound raises constraint error when evaluated.
3385 function Is_OK_Static_Subtype (Typ : Entity_Id) return Boolean is
3386 Base_T : constant Entity_Id := Base_Type (Typ);
3387 Anc_Subt : Entity_Id;
3389 begin
3390 -- First a quick check on the non static subtype flag. As described
3391 -- in further detail in Einfo, this flag is not decisive in all cases,
3392 -- but if it is set, then the subtype is definitely non-static.
3394 if Is_Non_Static_Subtype (Typ) then
3395 return False;
3396 end if;
3398 Anc_Subt := Ancestor_Subtype (Typ);
3400 if Anc_Subt = Empty then
3401 Anc_Subt := Base_T;
3402 end if;
3404 if Is_Generic_Type (Root_Type (Base_T))
3405 or else Is_Generic_Actual_Type (Base_T)
3406 then
3407 return False;
3409 -- String types
3411 elsif Is_String_Type (Typ) then
3412 return
3413 Ekind (Typ) = E_String_Literal_Subtype
3414 or else
3415 (Is_OK_Static_Subtype (Component_Type (Typ))
3416 and then Is_OK_Static_Subtype (Etype (First_Index (Typ))));
3418 -- Scalar types
3420 elsif Is_Scalar_Type (Typ) then
3421 if Base_T = Typ then
3422 return True;
3424 else
3425 -- Scalar_Range (Typ) might be an N_Subtype_Indication, so
3426 -- use Get_Type_Low,High_Bound.
3428 return Is_OK_Static_Subtype (Anc_Subt)
3429 and then Is_OK_Static_Expression (Type_Low_Bound (Typ))
3430 and then Is_OK_Static_Expression (Type_High_Bound (Typ));
3431 end if;
3433 -- Types other than string and scalar types are never static
3435 else
3436 return False;
3437 end if;
3438 end Is_OK_Static_Subtype;
3440 ---------------------
3441 -- Is_Out_Of_Range --
3442 ---------------------
3444 function Is_Out_Of_Range
3445 (N : Node_Id;
3446 Typ : Entity_Id;
3447 Fixed_Int : Boolean := False;
3448 Int_Real : Boolean := False) return Boolean
3450 Val : Uint;
3451 Valr : Ureal;
3453 begin
3454 -- Universal types have no range limits, so always in range
3456 if Typ = Universal_Integer or else Typ = Universal_Real then
3457 return False;
3459 -- Never out of range if not scalar type. Don't know if this can
3460 -- actually happen, but our spec allows it, so we must check!
3462 elsif not Is_Scalar_Type (Typ) then
3463 return False;
3465 -- Never out of range if this is a generic type, since the bounds
3466 -- of generic types are junk. Note that if we only checked for
3467 -- static expressions (instead of compile time known values) below,
3468 -- we would not need this check, because values of a generic type
3469 -- can never be static, but they can be known at compile time.
3471 elsif Is_Generic_Type (Typ) then
3472 return False;
3474 -- Never out of range unless we have a compile time known value
3476 elsif not Compile_Time_Known_Value (N) then
3477 return False;
3479 else
3480 declare
3481 Lo : constant Node_Id := Type_Low_Bound (Typ);
3482 Hi : constant Node_Id := Type_High_Bound (Typ);
3483 LB_Known : constant Boolean := Compile_Time_Known_Value (Lo);
3484 UB_Known : constant Boolean := Compile_Time_Known_Value (Hi);
3486 begin
3487 -- Real types (note that fixed-point types are not treated
3488 -- as being of a real type if the flag Fixed_Int is set,
3489 -- since in that case they are regarded as integer types).
3491 if Is_Floating_Point_Type (Typ)
3492 or else (Is_Fixed_Point_Type (Typ) and then not Fixed_Int)
3493 or else Int_Real
3494 then
3495 Valr := Expr_Value_R (N);
3497 if LB_Known and then Valr < Expr_Value_R (Lo) then
3498 return True;
3500 elsif UB_Known and then Expr_Value_R (Hi) < Valr then
3501 return True;
3503 else
3504 return False;
3505 end if;
3507 else
3508 Val := Expr_Value (N);
3510 if LB_Known and then Val < Expr_Value (Lo) then
3511 return True;
3513 elsif UB_Known and then Expr_Value (Hi) < Val then
3514 return True;
3516 else
3517 return False;
3518 end if;
3519 end if;
3520 end;
3521 end if;
3522 end Is_Out_Of_Range;
3524 ---------------------
3525 -- Is_Static_Range --
3526 ---------------------
3528 -- A static range is a range whose bounds are static expressions, or a
3529 -- Range_Attribute_Reference equivalent to such a range (RM 4.9(26)).
3530 -- We have already converted range attribute references, so we get the
3531 -- "or" part of this rule without needing a special test.
3533 function Is_Static_Range (N : Node_Id) return Boolean is
3534 begin
3535 return Is_Static_Expression (Low_Bound (N))
3536 and then Is_Static_Expression (High_Bound (N));
3537 end Is_Static_Range;
3539 -----------------------
3540 -- Is_Static_Subtype --
3541 -----------------------
3543 -- Determines if Typ is a static subtype as defined in (RM 4.9(26))
3545 function Is_Static_Subtype (Typ : Entity_Id) return Boolean is
3546 Base_T : constant Entity_Id := Base_Type (Typ);
3547 Anc_Subt : Entity_Id;
3549 begin
3550 -- First a quick check on the non static subtype flag. As described
3551 -- in further detail in Einfo, this flag is not decisive in all cases,
3552 -- but if it is set, then the subtype is definitely non-static.
3554 if Is_Non_Static_Subtype (Typ) then
3555 return False;
3556 end if;
3558 Anc_Subt := Ancestor_Subtype (Typ);
3560 if Anc_Subt = Empty then
3561 Anc_Subt := Base_T;
3562 end if;
3564 if Is_Generic_Type (Root_Type (Base_T))
3565 or else Is_Generic_Actual_Type (Base_T)
3566 then
3567 return False;
3569 -- String types
3571 elsif Is_String_Type (Typ) then
3572 return
3573 Ekind (Typ) = E_String_Literal_Subtype
3574 or else
3575 (Is_Static_Subtype (Component_Type (Typ))
3576 and then Is_Static_Subtype (Etype (First_Index (Typ))));
3578 -- Scalar types
3580 elsif Is_Scalar_Type (Typ) then
3581 if Base_T = Typ then
3582 return True;
3584 else
3585 return Is_Static_Subtype (Anc_Subt)
3586 and then Is_Static_Expression (Type_Low_Bound (Typ))
3587 and then Is_Static_Expression (Type_High_Bound (Typ));
3588 end if;
3590 -- Types other than string and scalar types are never static
3592 else
3593 return False;
3594 end if;
3595 end Is_Static_Subtype;
3597 --------------------
3598 -- Not_Null_Range --
3599 --------------------
3601 function Not_Null_Range (Lo : Node_Id; Hi : Node_Id) return Boolean is
3602 Typ : constant Entity_Id := Etype (Lo);
3604 begin
3605 if not Compile_Time_Known_Value (Lo)
3606 or else not Compile_Time_Known_Value (Hi)
3607 then
3608 return False;
3609 end if;
3611 if Is_Discrete_Type (Typ) then
3612 return Expr_Value (Lo) <= Expr_Value (Hi);
3614 else
3615 pragma Assert (Is_Real_Type (Typ));
3617 return Expr_Value_R (Lo) <= Expr_Value_R (Hi);
3618 end if;
3619 end Not_Null_Range;
3621 -------------
3622 -- OK_Bits --
3623 -------------
3625 function OK_Bits (N : Node_Id; Bits : Uint) return Boolean is
3626 begin
3627 -- We allow a maximum of 500,000 bits which seems a reasonable limit
3629 if Bits < 500_000 then
3630 return True;
3632 else
3633 Error_Msg_N ("static value too large, capacity exceeded", N);
3634 return False;
3635 end if;
3636 end OK_Bits;
3638 ------------------
3639 -- Out_Of_Range --
3640 ------------------
3642 procedure Out_Of_Range (N : Node_Id) is
3643 begin
3644 -- If we have the static expression case, then this is an illegality
3645 -- in Ada 95 mode, except that in an instance, we never generate an
3646 -- error (if the error is legitimate, it was already diagnosed in
3647 -- the template). The expression to compute the length of a packed
3648 -- array is attached to the array type itself, and deserves a separate
3649 -- message.
3651 if Is_Static_Expression (N)
3652 and then not In_Instance
3653 and then not In_Inlined_Body
3654 and then Ada_Version >= Ada_95
3655 then
3656 if Nkind (Parent (N)) = N_Defining_Identifier
3657 and then Is_Array_Type (Parent (N))
3658 and then Present (Packed_Array_Type (Parent (N)))
3659 and then Present (First_Rep_Item (Parent (N)))
3660 then
3661 Error_Msg_N
3662 ("length of packed array must not exceed Integer''Last",
3663 First_Rep_Item (Parent (N)));
3664 Rewrite (N, Make_Integer_Literal (Sloc (N), Uint_1));
3666 else
3667 Apply_Compile_Time_Constraint_Error
3668 (N, "value not in range of}", CE_Range_Check_Failed);
3669 end if;
3671 -- Here we generate a warning for the Ada 83 case, or when we are
3672 -- in an instance, or when we have a non-static expression case.
3674 else
3675 Apply_Compile_Time_Constraint_Error
3676 (N, "value not in range of}?", CE_Range_Check_Failed);
3677 end if;
3678 end Out_Of_Range;
3680 -------------------------
3681 -- Rewrite_In_Raise_CE --
3682 -------------------------
3684 procedure Rewrite_In_Raise_CE (N : Node_Id; Exp : Node_Id) is
3685 Typ : constant Entity_Id := Etype (N);
3687 begin
3688 -- If we want to raise CE in the condition of a raise_CE node
3689 -- we may as well get rid of the condition
3691 if Present (Parent (N))
3692 and then Nkind (Parent (N)) = N_Raise_Constraint_Error
3693 then
3694 Set_Condition (Parent (N), Empty);
3696 -- If the expression raising CE is a N_Raise_CE node, we can use
3697 -- that one. We just preserve the type of the context
3699 elsif Nkind (Exp) = N_Raise_Constraint_Error then
3700 Rewrite (N, Exp);
3701 Set_Etype (N, Typ);
3703 -- We have to build an explicit raise_ce node
3705 else
3706 Rewrite (N,
3707 Make_Raise_Constraint_Error (Sloc (Exp),
3708 Reason => CE_Range_Check_Failed));
3709 Set_Raises_Constraint_Error (N);
3710 Set_Etype (N, Typ);
3711 end if;
3712 end Rewrite_In_Raise_CE;
3714 ---------------------
3715 -- String_Type_Len --
3716 ---------------------
3718 function String_Type_Len (Stype : Entity_Id) return Uint is
3719 NT : constant Entity_Id := Etype (First_Index (Stype));
3720 T : Entity_Id;
3722 begin
3723 if Is_OK_Static_Subtype (NT) then
3724 T := NT;
3725 else
3726 T := Base_Type (NT);
3727 end if;
3729 return Expr_Value (Type_High_Bound (T)) -
3730 Expr_Value (Type_Low_Bound (T)) + 1;
3731 end String_Type_Len;
3733 ------------------------------------
3734 -- Subtypes_Statically_Compatible --
3735 ------------------------------------
3737 function Subtypes_Statically_Compatible
3738 (T1 : Entity_Id;
3739 T2 : Entity_Id) return Boolean
3741 begin
3742 if Is_Scalar_Type (T1) then
3744 -- Definitely compatible if we match
3746 if Subtypes_Statically_Match (T1, T2) then
3747 return True;
3749 -- If either subtype is nonstatic then they're not compatible
3751 elsif not Is_Static_Subtype (T1)
3752 or else not Is_Static_Subtype (T2)
3753 then
3754 return False;
3756 -- If either type has constraint error bounds, then consider that
3757 -- they match to avoid junk cascaded errors here.
3759 elsif not Is_OK_Static_Subtype (T1)
3760 or else not Is_OK_Static_Subtype (T2)
3761 then
3762 return True;
3764 -- Base types must match, but we don't check that (should
3765 -- we???) but we do at least check that both types are
3766 -- real, or both types are not real.
3768 elsif Is_Real_Type (T1) /= Is_Real_Type (T2) then
3769 return False;
3771 -- Here we check the bounds
3773 else
3774 declare
3775 LB1 : constant Node_Id := Type_Low_Bound (T1);
3776 HB1 : constant Node_Id := Type_High_Bound (T1);
3777 LB2 : constant Node_Id := Type_Low_Bound (T2);
3778 HB2 : constant Node_Id := Type_High_Bound (T2);
3780 begin
3781 if Is_Real_Type (T1) then
3782 return
3783 (Expr_Value_R (LB1) > Expr_Value_R (HB1))
3784 or else
3785 (Expr_Value_R (LB2) <= Expr_Value_R (LB1)
3786 and then
3787 Expr_Value_R (HB1) <= Expr_Value_R (HB2));
3789 else
3790 return
3791 (Expr_Value (LB1) > Expr_Value (HB1))
3792 or else
3793 (Expr_Value (LB2) <= Expr_Value (LB1)
3794 and then
3795 Expr_Value (HB1) <= Expr_Value (HB2));
3796 end if;
3797 end;
3798 end if;
3800 elsif Is_Access_Type (T1) then
3801 return not Is_Constrained (T2)
3802 or else Subtypes_Statically_Match
3803 (Designated_Type (T1), Designated_Type (T2));
3805 else
3806 return (Is_Composite_Type (T1) and then not Is_Constrained (T2))
3807 or else Subtypes_Statically_Match (T1, T2);
3808 end if;
3809 end Subtypes_Statically_Compatible;
3811 -------------------------------
3812 -- Subtypes_Statically_Match --
3813 -------------------------------
3815 -- Subtypes statically match if they have statically matching constraints
3816 -- (RM 4.9.1(2)). Constraints statically match if there are none, or if
3817 -- they are the same identical constraint, or if they are static and the
3818 -- values match (RM 4.9.1(1)).
3820 function Subtypes_Statically_Match (T1, T2 : Entity_Id) return Boolean is
3821 begin
3822 -- A type always statically matches itself
3824 if T1 = T2 then
3825 return True;
3827 -- Scalar types
3829 elsif Is_Scalar_Type (T1) then
3831 -- Base types must be the same
3833 if Base_Type (T1) /= Base_Type (T2) then
3834 return False;
3835 end if;
3837 -- A constrained numeric subtype never matches an unconstrained
3838 -- subtype, i.e. both types must be constrained or unconstrained.
3840 -- To understand the requirement for this test, see RM 4.9.1(1).
3841 -- As is made clear in RM 3.5.4(11), type Integer, for example
3842 -- is a constrained subtype with constraint bounds matching the
3843 -- bounds of its corresponding uncontrained base type. In this
3844 -- situation, Integer and Integer'Base do not statically match,
3845 -- even though they have the same bounds.
3847 -- We only apply this test to types in Standard and types that
3848 -- appear in user programs. That way, we do not have to be
3849 -- too careful about setting Is_Constrained right for itypes.
3851 if Is_Numeric_Type (T1)
3852 and then (Is_Constrained (T1) /= Is_Constrained (T2))
3853 and then (Scope (T1) = Standard_Standard
3854 or else Comes_From_Source (T1))
3855 and then (Scope (T2) = Standard_Standard
3856 or else Comes_From_Source (T2))
3857 then
3858 return False;
3860 -- A generic scalar type does not statically match its base
3861 -- type (AI-311). In this case we make sure that the formals,
3862 -- which are first subtypes of their bases, are constrained.
3864 elsif Is_Generic_Type (T1)
3865 and then Is_Generic_Type (T2)
3866 and then (Is_Constrained (T1) /= Is_Constrained (T2))
3867 then
3868 return False;
3869 end if;
3871 -- If there was an error in either range, then just assume
3872 -- the types statically match to avoid further junk errors
3874 if Error_Posted (Scalar_Range (T1))
3875 or else
3876 Error_Posted (Scalar_Range (T2))
3877 then
3878 return True;
3879 end if;
3881 -- Otherwise both types have bound that can be compared
3883 declare
3884 LB1 : constant Node_Id := Type_Low_Bound (T1);
3885 HB1 : constant Node_Id := Type_High_Bound (T1);
3886 LB2 : constant Node_Id := Type_Low_Bound (T2);
3887 HB2 : constant Node_Id := Type_High_Bound (T2);
3889 begin
3890 -- If the bounds are the same tree node, then match
3892 if LB1 = LB2 and then HB1 = HB2 then
3893 return True;
3895 -- Otherwise bounds must be static and identical value
3897 else
3898 if not Is_Static_Subtype (T1)
3899 or else not Is_Static_Subtype (T2)
3900 then
3901 return False;
3903 -- If either type has constraint error bounds, then say
3904 -- that they match to avoid junk cascaded errors here.
3906 elsif not Is_OK_Static_Subtype (T1)
3907 or else not Is_OK_Static_Subtype (T2)
3908 then
3909 return True;
3911 elsif Is_Real_Type (T1) then
3912 return
3913 (Expr_Value_R (LB1) = Expr_Value_R (LB2))
3914 and then
3915 (Expr_Value_R (HB1) = Expr_Value_R (HB2));
3917 else
3918 return
3919 Expr_Value (LB1) = Expr_Value (LB2)
3920 and then
3921 Expr_Value (HB1) = Expr_Value (HB2);
3922 end if;
3923 end if;
3924 end;
3926 -- Type with discriminants
3928 elsif Has_Discriminants (T1) or else Has_Discriminants (T2) then
3930 -- Because of view exchanges in multiple instantiations, conformance
3931 -- checking might try to match a partial view of a type with no
3932 -- discriminants with a full view that has defaulted discriminants.
3933 -- In such a case, use the discriminant constraint of the full view,
3934 -- which must exist because we know that the two subtypes have the
3935 -- same base type.
3937 if Has_Discriminants (T1) /= Has_Discriminants (T2) then
3938 if In_Instance then
3939 if Is_Private_Type (T2)
3940 and then Present (Full_View (T2))
3941 and then Has_Discriminants (Full_View (T2))
3942 then
3943 return Subtypes_Statically_Match (T1, Full_View (T2));
3945 elsif Is_Private_Type (T1)
3946 and then Present (Full_View (T1))
3947 and then Has_Discriminants (Full_View (T1))
3948 then
3949 return Subtypes_Statically_Match (Full_View (T1), T2);
3951 else
3952 return False;
3953 end if;
3954 else
3955 return False;
3956 end if;
3957 end if;
3959 declare
3960 DL1 : constant Elist_Id := Discriminant_Constraint (T1);
3961 DL2 : constant Elist_Id := Discriminant_Constraint (T2);
3963 DA1 : Elmt_Id := First_Elmt (DL1);
3964 DA2 : Elmt_Id := First_Elmt (DL2);
3966 begin
3967 if DL1 = DL2 then
3968 return True;
3970 elsif Is_Constrained (T1) /= Is_Constrained (T2) then
3971 return False;
3972 end if;
3974 while Present (DA1) loop
3975 declare
3976 Expr1 : constant Node_Id := Node (DA1);
3977 Expr2 : constant Node_Id := Node (DA2);
3979 begin
3980 if not Is_Static_Expression (Expr1)
3981 or else not Is_Static_Expression (Expr2)
3982 then
3983 return False;
3985 -- If either expression raised a constraint error,
3986 -- consider the expressions as matching, since this
3987 -- helps to prevent cascading errors.
3989 elsif Raises_Constraint_Error (Expr1)
3990 or else Raises_Constraint_Error (Expr2)
3991 then
3992 null;
3994 elsif Expr_Value (Expr1) /= Expr_Value (Expr2) then
3995 return False;
3996 end if;
3997 end;
3999 Next_Elmt (DA1);
4000 Next_Elmt (DA2);
4001 end loop;
4002 end;
4004 return True;
4006 -- A definite type does not match an indefinite or classwide type
4008 elsif
4009 Has_Unknown_Discriminants (T1) /= Has_Unknown_Discriminants (T2)
4010 then
4011 return False;
4013 -- Array type
4015 elsif Is_Array_Type (T1) then
4017 -- If either subtype is unconstrained then both must be,
4018 -- and if both are unconstrained then no further checking
4019 -- is needed.
4021 if not Is_Constrained (T1) or else not Is_Constrained (T2) then
4022 return not (Is_Constrained (T1) or else Is_Constrained (T2));
4023 end if;
4025 -- Both subtypes are constrained, so check that the index
4026 -- subtypes statically match.
4028 declare
4029 Index1 : Node_Id := First_Index (T1);
4030 Index2 : Node_Id := First_Index (T2);
4032 begin
4033 while Present (Index1) loop
4034 if not
4035 Subtypes_Statically_Match (Etype (Index1), Etype (Index2))
4036 then
4037 return False;
4038 end if;
4040 Next_Index (Index1);
4041 Next_Index (Index2);
4042 end loop;
4044 return True;
4045 end;
4047 elsif Is_Access_Type (T1) then
4048 return Subtypes_Statically_Match
4049 (Designated_Type (T1),
4050 Designated_Type (T2));
4052 -- All other types definitely match
4054 else
4055 return True;
4056 end if;
4057 end Subtypes_Statically_Match;
4059 ----------
4060 -- Test --
4061 ----------
4063 function Test (Cond : Boolean) return Uint is
4064 begin
4065 if Cond then
4066 return Uint_1;
4067 else
4068 return Uint_0;
4069 end if;
4070 end Test;
4072 ---------------------------------
4073 -- Test_Expression_Is_Foldable --
4074 ---------------------------------
4076 -- One operand case
4078 procedure Test_Expression_Is_Foldable
4079 (N : Node_Id;
4080 Op1 : Node_Id;
4081 Stat : out Boolean;
4082 Fold : out Boolean)
4084 begin
4085 Stat := False;
4087 -- If operand is Any_Type, just propagate to result and do not
4088 -- try to fold, this prevents cascaded errors.
4090 if Etype (Op1) = Any_Type then
4091 Set_Etype (N, Any_Type);
4092 Fold := False;
4093 return;
4095 -- If operand raises constraint error, then replace node N with the
4096 -- raise constraint error node, and we are obviously not foldable.
4097 -- Note that this replacement inherits the Is_Static_Expression flag
4098 -- from the operand.
4100 elsif Raises_Constraint_Error (Op1) then
4101 Rewrite_In_Raise_CE (N, Op1);
4102 Fold := False;
4103 return;
4105 -- If the operand is not static, then the result is not static, and
4106 -- all we have to do is to check the operand since it is now known
4107 -- to appear in a non-static context.
4109 elsif not Is_Static_Expression (Op1) then
4110 Check_Non_Static_Context (Op1);
4111 Fold := Compile_Time_Known_Value (Op1);
4112 return;
4114 -- An expression of a formal modular type is not foldable because
4115 -- the modulus is unknown.
4117 elsif Is_Modular_Integer_Type (Etype (Op1))
4118 and then Is_Generic_Type (Etype (Op1))
4119 then
4120 Check_Non_Static_Context (Op1);
4121 Fold := False;
4122 return;
4124 -- Here we have the case of an operand whose type is OK, which is
4125 -- static, and which does not raise constraint error, we can fold.
4127 else
4128 Set_Is_Static_Expression (N);
4129 Fold := True;
4130 Stat := True;
4131 end if;
4132 end Test_Expression_Is_Foldable;
4134 -- Two operand case
4136 procedure Test_Expression_Is_Foldable
4137 (N : Node_Id;
4138 Op1 : Node_Id;
4139 Op2 : Node_Id;
4140 Stat : out Boolean;
4141 Fold : out Boolean)
4143 Rstat : constant Boolean := Is_Static_Expression (Op1)
4144 and then Is_Static_Expression (Op2);
4146 begin
4147 Stat := False;
4149 -- If either operand is Any_Type, just propagate to result and
4150 -- do not try to fold, this prevents cascaded errors.
4152 if Etype (Op1) = Any_Type or else Etype (Op2) = Any_Type then
4153 Set_Etype (N, Any_Type);
4154 Fold := False;
4155 return;
4157 -- If left operand raises constraint error, then replace node N with
4158 -- the raise constraint error node, and we are obviously not foldable.
4159 -- Is_Static_Expression is set from the two operands in the normal way,
4160 -- and we check the right operand if it is in a non-static context.
4162 elsif Raises_Constraint_Error (Op1) then
4163 if not Rstat then
4164 Check_Non_Static_Context (Op2);
4165 end if;
4167 Rewrite_In_Raise_CE (N, Op1);
4168 Set_Is_Static_Expression (N, Rstat);
4169 Fold := False;
4170 return;
4172 -- Similar processing for the case of the right operand. Note that
4173 -- we don't use this routine for the short-circuit case, so we do
4174 -- not have to worry about that special case here.
4176 elsif Raises_Constraint_Error (Op2) then
4177 if not Rstat then
4178 Check_Non_Static_Context (Op1);
4179 end if;
4181 Rewrite_In_Raise_CE (N, Op2);
4182 Set_Is_Static_Expression (N, Rstat);
4183 Fold := False;
4184 return;
4186 -- Exclude expressions of a generic modular type, as above
4188 elsif Is_Modular_Integer_Type (Etype (Op1))
4189 and then Is_Generic_Type (Etype (Op1))
4190 then
4191 Check_Non_Static_Context (Op1);
4192 Fold := False;
4193 return;
4195 -- If result is not static, then check non-static contexts on operands
4196 -- since one of them may be static and the other one may not be static
4198 elsif not Rstat then
4199 Check_Non_Static_Context (Op1);
4200 Check_Non_Static_Context (Op2);
4201 Fold := Compile_Time_Known_Value (Op1)
4202 and then Compile_Time_Known_Value (Op2);
4203 return;
4205 -- Else result is static and foldable. Both operands are static,
4206 -- and neither raises constraint error, so we can definitely fold.
4208 else
4209 Set_Is_Static_Expression (N);
4210 Fold := True;
4211 Stat := True;
4212 return;
4213 end if;
4214 end Test_Expression_Is_Foldable;
4216 --------------
4217 -- To_Bits --
4218 --------------
4220 procedure To_Bits (U : Uint; B : out Bits) is
4221 begin
4222 for J in 0 .. B'Last loop
4223 B (J) := (U / (2 ** J)) mod 2 /= 0;
4224 end loop;
4225 end To_Bits;
4227 --------------------
4228 -- Why_Not_Static --
4229 --------------------
4231 procedure Why_Not_Static (Expr : Node_Id) is
4232 N : constant Node_Id := Original_Node (Expr);
4233 Typ : Entity_Id;
4234 E : Entity_Id;
4236 procedure Why_Not_Static_List (L : List_Id);
4237 -- A version that can be called on a list of expressions. Finds
4238 -- all non-static violations in any element of the list.
4240 -------------------------
4241 -- Why_Not_Static_List --
4242 -------------------------
4244 procedure Why_Not_Static_List (L : List_Id) is
4245 N : Node_Id;
4247 begin
4248 if Is_Non_Empty_List (L) then
4249 N := First (L);
4250 while Present (N) loop
4251 Why_Not_Static (N);
4252 Next (N);
4253 end loop;
4254 end if;
4255 end Why_Not_Static_List;
4257 -- Start of processing for Why_Not_Static
4259 begin
4260 -- If in ACATS mode (debug flag 2), then suppress all these
4261 -- messages, this avoids massive updates to the ACATS base line.
4263 if Debug_Flag_2 then
4264 return;
4265 end if;
4267 -- Ignore call on error or empty node
4269 if No (Expr) or else Nkind (Expr) = N_Error then
4270 return;
4271 end if;
4273 -- Preprocessing for sub expressions
4275 if Nkind (Expr) in N_Subexpr then
4277 -- Nothing to do if expression is static
4279 if Is_OK_Static_Expression (Expr) then
4280 return;
4281 end if;
4283 -- Test for constraint error raised
4285 if Raises_Constraint_Error (Expr) then
4286 Error_Msg_N
4287 ("expression raises exception, cannot be static " &
4288 "('R'M 4.9(34))!", N);
4289 return;
4290 end if;
4292 -- If no type, then something is pretty wrong, so ignore
4294 Typ := Etype (Expr);
4296 if No (Typ) then
4297 return;
4298 end if;
4300 -- Type must be scalar or string type
4302 if not Is_Scalar_Type (Typ)
4303 and then not Is_String_Type (Typ)
4304 then
4305 Error_Msg_N
4306 ("static expression must have scalar or string type " &
4307 "('R'M 4.9(2))!", N);
4308 return;
4309 end if;
4310 end if;
4312 -- If we got through those checks, test particular node kind
4314 case Nkind (N) is
4315 when N_Expanded_Name | N_Identifier | N_Operator_Symbol =>
4316 E := Entity (N);
4318 if Is_Named_Number (E) then
4319 null;
4321 elsif Ekind (E) = E_Constant then
4322 if not Is_Static_Expression (Constant_Value (E)) then
4323 Error_Msg_NE
4324 ("& is not a static constant ('R'M 4.9(5))!", N, E);
4325 end if;
4327 else
4328 Error_Msg_NE
4329 ("& is not static constant or named number " &
4330 "('R'M 4.9(5))!", N, E);
4331 end if;
4333 when N_Binary_Op | N_And_Then | N_Or_Else | N_In | N_Not_In =>
4334 if Nkind (N) in N_Op_Shift then
4335 Error_Msg_N
4336 ("shift functions are never static ('R'M 4.9(6,18))!", N);
4338 else
4339 Why_Not_Static (Left_Opnd (N));
4340 Why_Not_Static (Right_Opnd (N));
4341 end if;
4343 when N_Unary_Op =>
4344 Why_Not_Static (Right_Opnd (N));
4346 when N_Attribute_Reference =>
4347 Why_Not_Static_List (Expressions (N));
4349 E := Etype (Prefix (N));
4351 if E = Standard_Void_Type then
4352 return;
4353 end if;
4355 -- Special case non-scalar'Size since this is a common error
4357 if Attribute_Name (N) = Name_Size then
4358 Error_Msg_N
4359 ("size attribute is only static for scalar type " &
4360 "('R'M 4.9(7,8))", N);
4362 -- Flag array cases
4364 elsif Is_Array_Type (E) then
4365 if Attribute_Name (N) /= Name_First
4366 and then
4367 Attribute_Name (N) /= Name_Last
4368 and then
4369 Attribute_Name (N) /= Name_Length
4370 then
4371 Error_Msg_N
4372 ("static array attribute must be Length, First, or Last " &
4373 "('R'M 4.9(8))!", N);
4375 -- Since we know the expression is not-static (we already
4376 -- tested for this, must mean array is not static).
4378 else
4379 Error_Msg_N
4380 ("prefix is non-static array ('R'M 4.9(8))!", Prefix (N));
4381 end if;
4383 return;
4385 -- Special case generic types, since again this is a common
4386 -- source of confusion.
4388 elsif Is_Generic_Actual_Type (E)
4389 or else
4390 Is_Generic_Type (E)
4391 then
4392 Error_Msg_N
4393 ("attribute of generic type is never static " &
4394 "('R'M 4.9(7,8))!", N);
4396 elsif Is_Static_Subtype (E) then
4397 null;
4399 elsif Is_Scalar_Type (E) then
4400 Error_Msg_N
4401 ("prefix type for attribute is not static scalar subtype " &
4402 "('R'M 4.9(7))!", N);
4404 else
4405 Error_Msg_N
4406 ("static attribute must apply to array/scalar type " &
4407 "('R'M 4.9(7,8))!", N);
4408 end if;
4410 when N_String_Literal =>
4411 Error_Msg_N
4412 ("subtype of string literal is non-static ('R'M 4.9(4))!", N);
4414 when N_Explicit_Dereference =>
4415 Error_Msg_N
4416 ("explicit dereference is never static ('R'M 4.9)!", N);
4418 when N_Function_Call =>
4419 Why_Not_Static_List (Parameter_Associations (N));
4420 Error_Msg_N ("non-static function call ('R'M 4.9(6,18))!", N);
4422 when N_Parameter_Association =>
4423 Why_Not_Static (Explicit_Actual_Parameter (N));
4425 when N_Indexed_Component =>
4426 Error_Msg_N
4427 ("indexed component is never static ('R'M 4.9)!", N);
4429 when N_Procedure_Call_Statement =>
4430 Error_Msg_N
4431 ("procedure call is never static ('R'M 4.9)!", N);
4433 when N_Qualified_Expression =>
4434 Why_Not_Static (Expression (N));
4436 when N_Aggregate | N_Extension_Aggregate =>
4437 Error_Msg_N
4438 ("an aggregate is never static ('R'M 4.9)!", N);
4440 when N_Range =>
4441 Why_Not_Static (Low_Bound (N));
4442 Why_Not_Static (High_Bound (N));
4444 when N_Range_Constraint =>
4445 Why_Not_Static (Range_Expression (N));
4447 when N_Subtype_Indication =>
4448 Why_Not_Static (Constraint (N));
4450 when N_Selected_Component =>
4451 Error_Msg_N
4452 ("selected component is never static ('R'M 4.9)!", N);
4454 when N_Slice =>
4455 Error_Msg_N
4456 ("slice is never static ('R'M 4.9)!", N);
4458 when N_Type_Conversion =>
4459 Why_Not_Static (Expression (N));
4461 if not Is_Scalar_Type (Etype (Prefix (N)))
4462 or else not Is_Static_Subtype (Etype (Prefix (N)))
4463 then
4464 Error_Msg_N
4465 ("static conversion requires static scalar subtype result " &
4466 "('R'M 4.9(9))!", N);
4467 end if;
4469 when N_Unchecked_Type_Conversion =>
4470 Error_Msg_N
4471 ("unchecked type conversion is never static ('R'M 4.9)!", N);
4473 when others =>
4474 null;
4476 end case;
4477 end Why_Not_Static;
4479 end Sem_Eval;