Daily bump.
[official-gcc.git] / gcc / ada / sem_res.adb
bloba741c4676480d2d6a16b904c54bd6e70f0912522
1 ------------------------------------------------------------------------------
2 -- --
3 -- GNAT COMPILER COMPONENTS --
4 -- --
5 -- S E M _ R E S --
6 -- --
7 -- B o d y --
8 -- --
9 -- Copyright (C) 1992-2007, 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 3, 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 COPYING3. If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license. --
20 -- --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
23 -- --
24 ------------------------------------------------------------------------------
26 with Atree; use Atree;
27 with Checks; use Checks;
28 with Debug; use Debug;
29 with Debug_A; use Debug_A;
30 with Einfo; use Einfo;
31 with Elists; use Elists;
32 with Errout; use Errout;
33 with Expander; use Expander;
34 with Exp_Disp; use Exp_Disp;
35 with Exp_Ch6; use Exp_Ch6;
36 with Exp_Ch7; use Exp_Ch7;
37 with Exp_Tss; use Exp_Tss;
38 with Exp_Util; use Exp_Util;
39 with Fname; use Fname;
40 with Freeze; use Freeze;
41 with Itypes; use Itypes;
42 with Lib; use Lib;
43 with Lib.Xref; use Lib.Xref;
44 with Namet; use Namet;
45 with Nmake; use Nmake;
46 with Nlists; use Nlists;
47 with Opt; use Opt;
48 with Output; use Output;
49 with Restrict; use Restrict;
50 with Rident; use Rident;
51 with Rtsfind; use Rtsfind;
52 with Sem; use Sem;
53 with Sem_Aggr; use Sem_Aggr;
54 with Sem_Attr; use Sem_Attr;
55 with Sem_Cat; use Sem_Cat;
56 with Sem_Ch4; use Sem_Ch4;
57 with Sem_Ch6; use Sem_Ch6;
58 with Sem_Ch8; use Sem_Ch8;
59 with Sem_Disp; use Sem_Disp;
60 with Sem_Dist; use Sem_Dist;
61 with Sem_Elab; use Sem_Elab;
62 with Sem_Eval; use Sem_Eval;
63 with Sem_Intr; use Sem_Intr;
64 with Sem_Util; use Sem_Util;
65 with Sem_Type; use Sem_Type;
66 with Sem_Warn; use Sem_Warn;
67 with Sinfo; use Sinfo;
68 with Snames; use Snames;
69 with Stand; use Stand;
70 with Stringt; use Stringt;
71 with Targparm; use Targparm;
72 with Tbuild; use Tbuild;
73 with Uintp; use Uintp;
74 with Urealp; use Urealp;
76 package body Sem_Res is
78 -----------------------
79 -- Local Subprograms --
80 -----------------------
82 -- Second pass (top-down) type checking and overload resolution procedures
83 -- Typ is the type required by context. These procedures propagate the
84 -- type information recursively to the descendants of N. If the node
85 -- is not overloaded, its Etype is established in the first pass. If
86 -- overloaded, the Resolve routines set the correct type. For arith.
87 -- operators, the Etype is the base type of the context.
89 -- Note that Resolve_Attribute is separated off in Sem_Attr
91 procedure Check_Discriminant_Use (N : Node_Id);
92 -- Enforce the restrictions on the use of discriminants when constraining
93 -- a component of a discriminated type (record or concurrent type).
95 procedure Check_For_Visible_Operator (N : Node_Id; T : Entity_Id);
96 -- Given a node for an operator associated with type T, check that
97 -- the operator is visible. Operators all of whose operands are
98 -- universal must be checked for visibility during resolution
99 -- because their type is not determinable based on their operands.
101 procedure Check_Fully_Declared_Prefix
102 (Typ : Entity_Id;
103 Pref : Node_Id);
104 -- Check that the type of the prefix of a dereference is not incomplete
106 function Check_Infinite_Recursion (N : Node_Id) return Boolean;
107 -- Given a call node, N, which is known to occur immediately within the
108 -- subprogram being called, determines whether it is a detectable case of
109 -- an infinite recursion, and if so, outputs appropriate messages. Returns
110 -- True if an infinite recursion is detected, and False otherwise.
112 procedure Check_Initialization_Call (N : Entity_Id; Nam : Entity_Id);
113 -- If the type of the object being initialized uses the secondary stack
114 -- directly or indirectly, create a transient scope for the call to the
115 -- init proc. This is because we do not create transient scopes for the
116 -- initialization of individual components within the init proc itself.
117 -- Could be optimized away perhaps?
119 function Is_Definite_Access_Type (E : Entity_Id) return Boolean;
120 -- Determine whether E is an access type declared by an access
121 -- declaration, and not an (anonymous) allocator type.
123 function Is_Predefined_Op (Nam : Entity_Id) return Boolean;
124 -- Utility to check whether the name in the call is a predefined
125 -- operator, in which case the call is made into an operator node.
126 -- An instance of an intrinsic conversion operation may be given
127 -- an operator name, but is not treated like an operator.
129 procedure Replace_Actual_Discriminants (N : Node_Id; Default : Node_Id);
130 -- If a default expression in entry call N depends on the discriminants
131 -- of the task, it must be replaced with a reference to the discriminant
132 -- of the task being called.
134 procedure Resolve_Op_Concat_Arg
135 (N : Node_Id;
136 Arg : Node_Id;
137 Typ : Entity_Id;
138 Is_Comp : Boolean);
139 -- Internal procedure for Resolve_Op_Concat to resolve one operand of
140 -- concatenation operator. The operand is either of the array type or of
141 -- the component type. If the operand is an aggregate, and the component
142 -- type is composite, this is ambiguous if component type has aggregates.
144 procedure Resolve_Op_Concat_First (N : Node_Id; Typ : Entity_Id);
145 -- Does the first part of the work of Resolve_Op_Concat
147 procedure Resolve_Op_Concat_Rest (N : Node_Id; Typ : Entity_Id);
148 -- Does the "rest" of the work of Resolve_Op_Concat, after the left operand
149 -- has been resolved. See Resolve_Op_Concat for details.
151 procedure Resolve_Allocator (N : Node_Id; Typ : Entity_Id);
152 procedure Resolve_Arithmetic_Op (N : Node_Id; Typ : Entity_Id);
153 procedure Resolve_Call (N : Node_Id; Typ : Entity_Id);
154 procedure Resolve_Character_Literal (N : Node_Id; Typ : Entity_Id);
155 procedure Resolve_Comparison_Op (N : Node_Id; Typ : Entity_Id);
156 procedure Resolve_Conditional_Expression (N : Node_Id; Typ : Entity_Id);
157 procedure Resolve_Equality_Op (N : Node_Id; Typ : Entity_Id);
158 procedure Resolve_Explicit_Dereference (N : Node_Id; Typ : Entity_Id);
159 procedure Resolve_Entity_Name (N : Node_Id; Typ : Entity_Id);
160 procedure Resolve_Indexed_Component (N : Node_Id; Typ : Entity_Id);
161 procedure Resolve_Integer_Literal (N : Node_Id; Typ : Entity_Id);
162 procedure Resolve_Logical_Op (N : Node_Id; Typ : Entity_Id);
163 procedure Resolve_Membership_Op (N : Node_Id; Typ : Entity_Id);
164 procedure Resolve_Null (N : Node_Id; Typ : Entity_Id);
165 procedure Resolve_Operator_Symbol (N : Node_Id; Typ : Entity_Id);
166 procedure Resolve_Op_Concat (N : Node_Id; Typ : Entity_Id);
167 procedure Resolve_Op_Expon (N : Node_Id; Typ : Entity_Id);
168 procedure Resolve_Op_Not (N : Node_Id; Typ : Entity_Id);
169 procedure Resolve_Qualified_Expression (N : Node_Id; Typ : Entity_Id);
170 procedure Resolve_Range (N : Node_Id; Typ : Entity_Id);
171 procedure Resolve_Real_Literal (N : Node_Id; Typ : Entity_Id);
172 procedure Resolve_Reference (N : Node_Id; Typ : Entity_Id);
173 procedure Resolve_Selected_Component (N : Node_Id; Typ : Entity_Id);
174 procedure Resolve_Shift (N : Node_Id; Typ : Entity_Id);
175 procedure Resolve_Short_Circuit (N : Node_Id; Typ : Entity_Id);
176 procedure Resolve_Slice (N : Node_Id; Typ : Entity_Id);
177 procedure Resolve_String_Literal (N : Node_Id; Typ : Entity_Id);
178 procedure Resolve_Subprogram_Info (N : Node_Id; Typ : Entity_Id);
179 procedure Resolve_Type_Conversion (N : Node_Id; Typ : Entity_Id);
180 procedure Resolve_Unary_Op (N : Node_Id; Typ : Entity_Id);
181 procedure Resolve_Unchecked_Expression (N : Node_Id; Typ : Entity_Id);
182 procedure Resolve_Unchecked_Type_Conversion (N : Node_Id; Typ : Entity_Id);
184 function Operator_Kind
185 (Op_Name : Name_Id;
186 Is_Binary : Boolean) return Node_Kind;
187 -- Utility to map the name of an operator into the corresponding Node. Used
188 -- by other node rewriting procedures.
190 procedure Resolve_Actuals (N : Node_Id; Nam : Entity_Id);
191 -- Resolve actuals of call, and add default expressions for missing ones.
192 -- N is the Node_Id for the subprogram call, and Nam is the entity of the
193 -- called subprogram.
195 procedure Resolve_Entry_Call (N : Node_Id; Typ : Entity_Id);
196 -- Called from Resolve_Call, when the prefix denotes an entry or element
197 -- of entry family. Actuals are resolved as for subprograms, and the node
198 -- is rebuilt as an entry call. Also called for protected operations. Typ
199 -- is the context type, which is used when the operation is a protected
200 -- function with no arguments, and the return value is indexed.
202 procedure Resolve_Intrinsic_Operator (N : Node_Id; Typ : Entity_Id);
203 -- A call to a user-defined intrinsic operator is rewritten as a call
204 -- to the corresponding predefined operator, with suitable conversions.
206 procedure Resolve_Intrinsic_Unary_Operator (N : Node_Id; Typ : Entity_Id);
207 -- Ditto, for unary operators (only arithmetic ones)
209 procedure Rewrite_Operator_As_Call (N : Node_Id; Nam : Entity_Id);
210 -- If an operator node resolves to a call to a user-defined operator,
211 -- rewrite the node as a function call.
213 procedure Make_Call_Into_Operator
214 (N : Node_Id;
215 Typ : Entity_Id;
216 Op_Id : Entity_Id);
217 -- Inverse transformation: if an operator is given in functional notation,
218 -- then after resolving the node, transform into an operator node, so
219 -- that operands are resolved properly. Recall that predefined operators
220 -- do not have a full signature and special resolution rules apply.
222 procedure Rewrite_Renamed_Operator
223 (N : Node_Id;
224 Op : Entity_Id;
225 Typ : Entity_Id);
226 -- An operator can rename another, e.g. in an instantiation. In that
227 -- case, the proper operator node must be constructed and resolved.
229 procedure Set_String_Literal_Subtype (N : Node_Id; Typ : Entity_Id);
230 -- The String_Literal_Subtype is built for all strings that are not
231 -- operands of a static concatenation operation. If the argument is
232 -- not a N_String_Literal node, then the call has no effect.
234 procedure Set_Slice_Subtype (N : Node_Id);
235 -- Build subtype of array type, with the range specified by the slice
237 procedure Simplify_Type_Conversion (N : Node_Id);
238 -- Called after N has been resolved and evaluated, but before range checks
239 -- have been applied. Currently simplifies a combination of floating-point
240 -- to integer conversion and Truncation attribute.
242 function Unique_Fixed_Point_Type (N : Node_Id) return Entity_Id;
243 -- A universal_fixed expression in an universal context is unambiguous
244 -- if there is only one applicable fixed point type. Determining whether
245 -- there is only one requires a search over all visible entities, and
246 -- happens only in very pathological cases (see 6115-006).
248 function Valid_Conversion
249 (N : Node_Id;
250 Target : Entity_Id;
251 Operand : Node_Id) return Boolean;
252 -- Verify legality rules given in 4.6 (8-23). Target is the target
253 -- type of the conversion, which may be an implicit conversion of
254 -- an actual parameter to an anonymous access type (in which case
255 -- N denotes the actual parameter and N = Operand).
257 -------------------------
258 -- Ambiguous_Character --
259 -------------------------
261 procedure Ambiguous_Character (C : Node_Id) is
262 E : Entity_Id;
264 begin
265 if Nkind (C) = N_Character_Literal then
266 Error_Msg_N ("ambiguous character literal", C);
268 -- First the ones in Standard
270 Error_Msg_N
271 ("\\possible interpretation: Character!", C);
272 Error_Msg_N
273 ("\\possible interpretation: Wide_Character!", C);
275 -- Include Wide_Wide_Character in Ada 2005 mode
277 if Ada_Version >= Ada_05 then
278 Error_Msg_N
279 ("\\possible interpretation: Wide_Wide_Character!", C);
280 end if;
282 -- Now any other types that match
284 E := Current_Entity (C);
285 while Present (E) loop
286 Error_Msg_NE ("\\possible interpretation:}!", C, Etype (E));
287 E := Homonym (E);
288 end loop;
289 end if;
290 end Ambiguous_Character;
292 -------------------------
293 -- Analyze_And_Resolve --
294 -------------------------
296 procedure Analyze_And_Resolve (N : Node_Id) is
297 begin
298 Analyze (N);
299 Resolve (N);
300 end Analyze_And_Resolve;
302 procedure Analyze_And_Resolve (N : Node_Id; Typ : Entity_Id) is
303 begin
304 Analyze (N);
305 Resolve (N, Typ);
306 end Analyze_And_Resolve;
308 -- Version withs check(s) suppressed
310 procedure Analyze_And_Resolve
311 (N : Node_Id;
312 Typ : Entity_Id;
313 Suppress : Check_Id)
315 Scop : constant Entity_Id := Current_Scope;
317 begin
318 if Suppress = All_Checks then
319 declare
320 Svg : constant Suppress_Array := Scope_Suppress;
321 begin
322 Scope_Suppress := (others => True);
323 Analyze_And_Resolve (N, Typ);
324 Scope_Suppress := Svg;
325 end;
327 else
328 declare
329 Svg : constant Boolean := Scope_Suppress (Suppress);
331 begin
332 Scope_Suppress (Suppress) := True;
333 Analyze_And_Resolve (N, Typ);
334 Scope_Suppress (Suppress) := Svg;
335 end;
336 end if;
338 if Current_Scope /= Scop
339 and then Scope_Is_Transient
340 then
341 -- This can only happen if a transient scope was created
342 -- for an inner expression, which will be removed upon
343 -- completion of the analysis of an enclosing construct.
344 -- The transient scope must have the suppress status of
345 -- the enclosing environment, not of this Analyze call.
347 Scope_Stack.Table (Scope_Stack.Last).Save_Scope_Suppress :=
348 Scope_Suppress;
349 end if;
350 end Analyze_And_Resolve;
352 procedure Analyze_And_Resolve
353 (N : Node_Id;
354 Suppress : Check_Id)
356 Scop : constant Entity_Id := Current_Scope;
358 begin
359 if Suppress = All_Checks then
360 declare
361 Svg : constant Suppress_Array := Scope_Suppress;
362 begin
363 Scope_Suppress := (others => True);
364 Analyze_And_Resolve (N);
365 Scope_Suppress := Svg;
366 end;
368 else
369 declare
370 Svg : constant Boolean := Scope_Suppress (Suppress);
372 begin
373 Scope_Suppress (Suppress) := True;
374 Analyze_And_Resolve (N);
375 Scope_Suppress (Suppress) := Svg;
376 end;
377 end if;
379 if Current_Scope /= Scop
380 and then Scope_Is_Transient
381 then
382 Scope_Stack.Table (Scope_Stack.Last).Save_Scope_Suppress :=
383 Scope_Suppress;
384 end if;
385 end Analyze_And_Resolve;
387 ----------------------------
388 -- Check_Discriminant_Use --
389 ----------------------------
391 procedure Check_Discriminant_Use (N : Node_Id) is
392 PN : constant Node_Id := Parent (N);
393 Disc : constant Entity_Id := Entity (N);
394 P : Node_Id;
395 D : Node_Id;
397 begin
398 -- Any use in a default expression is legal
400 if In_Default_Expression then
401 null;
403 elsif Nkind (PN) = N_Range then
405 -- Discriminant cannot be used to constrain a scalar type
407 P := Parent (PN);
409 if Nkind (P) = N_Range_Constraint
410 and then Nkind (Parent (P)) = N_Subtype_Indication
411 and then Nkind (Parent (Parent (P))) = N_Component_Definition
412 then
413 Error_Msg_N ("discriminant cannot constrain scalar type", N);
415 elsif Nkind (P) = N_Index_Or_Discriminant_Constraint then
417 -- The following check catches the unusual case where
418 -- a discriminant appears within an index constraint
419 -- that is part of a larger expression within a constraint
420 -- on a component, e.g. "C : Int range 1 .. F (new A(1 .. D))".
421 -- For now we only check case of record components, and
422 -- note that a similar check should also apply in the
423 -- case of discriminant constraints below. ???
425 -- Note that the check for N_Subtype_Declaration below is to
426 -- detect the valid use of discriminants in the constraints of a
427 -- subtype declaration when this subtype declaration appears
428 -- inside the scope of a record type (which is syntactically
429 -- illegal, but which may be created as part of derived type
430 -- processing for records). See Sem_Ch3.Build_Derived_Record_Type
431 -- for more info.
433 if Ekind (Current_Scope) = E_Record_Type
434 and then Scope (Disc) = Current_Scope
435 and then not
436 (Nkind (Parent (P)) = N_Subtype_Indication
437 and then
438 (Nkind (Parent (Parent (P))) = N_Component_Definition
439 or else
440 Nkind (Parent (Parent (P))) = N_Subtype_Declaration)
441 and then Paren_Count (N) = 0)
442 then
443 Error_Msg_N
444 ("discriminant must appear alone in component constraint", N);
445 return;
446 end if;
448 -- Detect a common beginner error:
450 -- type R (D : Positive := 100) is record
451 -- Name : String (1 .. D);
452 -- end record;
454 -- The default value causes an object of type R to be
455 -- allocated with room for Positive'Last characters.
457 declare
458 SI : Node_Id;
459 T : Entity_Id;
460 TB : Node_Id;
461 CB : Entity_Id;
463 function Large_Storage_Type (T : Entity_Id) return Boolean;
464 -- Return True if type T has a large enough range that
465 -- any array whose index type covered the whole range of
466 -- the type would likely raise Storage_Error.
468 ------------------------
469 -- Large_Storage_Type --
470 ------------------------
472 function Large_Storage_Type (T : Entity_Id) return Boolean is
473 begin
474 return
475 T = Standard_Integer
476 or else
477 T = Standard_Positive
478 or else
479 T = Standard_Natural;
480 end Large_Storage_Type;
482 begin
483 -- Check that the Disc has a large range
485 if not Large_Storage_Type (Etype (Disc)) then
486 goto No_Danger;
487 end if;
489 -- If the enclosing type is limited, we allocate only the
490 -- default value, not the maximum, and there is no need for
491 -- a warning.
493 if Is_Limited_Type (Scope (Disc)) then
494 goto No_Danger;
495 end if;
497 -- Check that it is the high bound
499 if N /= High_Bound (PN)
500 or else No (Discriminant_Default_Value (Disc))
501 then
502 goto No_Danger;
503 end if;
505 -- Check the array allows a large range at this bound.
506 -- First find the array
508 SI := Parent (P);
510 if Nkind (SI) /= N_Subtype_Indication then
511 goto No_Danger;
512 end if;
514 T := Entity (Subtype_Mark (SI));
516 if not Is_Array_Type (T) then
517 goto No_Danger;
518 end if;
520 -- Next, find the dimension
522 TB := First_Index (T);
523 CB := First (Constraints (P));
524 while True
525 and then Present (TB)
526 and then Present (CB)
527 and then CB /= PN
528 loop
529 Next_Index (TB);
530 Next (CB);
531 end loop;
533 if CB /= PN then
534 goto No_Danger;
535 end if;
537 -- Now, check the dimension has a large range
539 if not Large_Storage_Type (Etype (TB)) then
540 goto No_Danger;
541 end if;
543 -- Warn about the danger
545 Error_Msg_N
546 ("?creation of & object may raise Storage_Error!",
547 Scope (Disc));
549 <<No_Danger>>
550 null;
552 end;
553 end if;
555 -- Legal case is in index or discriminant constraint
557 elsif Nkind (PN) = N_Index_Or_Discriminant_Constraint
558 or else Nkind (PN) = N_Discriminant_Association
559 then
560 if Paren_Count (N) > 0 then
561 Error_Msg_N
562 ("discriminant in constraint must appear alone", N);
564 elsif Nkind (N) = N_Expanded_Name
565 and then Comes_From_Source (N)
566 then
567 Error_Msg_N
568 ("discriminant must appear alone as a direct name", N);
569 end if;
571 return;
573 -- Otherwise, context is an expression. It should not be within
574 -- (i.e. a subexpression of) a constraint for a component.
576 else
577 D := PN;
578 P := Parent (PN);
579 while Nkind (P) /= N_Component_Declaration
580 and then Nkind (P) /= N_Subtype_Indication
581 and then Nkind (P) /= N_Entry_Declaration
582 loop
583 D := P;
584 P := Parent (P);
585 exit when No (P);
586 end loop;
588 -- If the discriminant is used in an expression that is a bound
589 -- of a scalar type, an Itype is created and the bounds are attached
590 -- to its range, not to the original subtype indication. Such use
591 -- is of course a double fault.
593 if (Nkind (P) = N_Subtype_Indication
594 and then
595 (Nkind (Parent (P)) = N_Component_Definition
596 or else
597 Nkind (Parent (P)) = N_Derived_Type_Definition)
598 and then D = Constraint (P))
600 -- The constraint itself may be given by a subtype indication,
601 -- rather than by a more common discrete range.
603 or else (Nkind (P) = N_Subtype_Indication
604 and then
605 Nkind (Parent (P)) = N_Index_Or_Discriminant_Constraint)
606 or else Nkind (P) = N_Entry_Declaration
607 or else Nkind (D) = N_Defining_Identifier
608 then
609 Error_Msg_N
610 ("discriminant in constraint must appear alone", N);
611 end if;
612 end if;
613 end Check_Discriminant_Use;
615 --------------------------------
616 -- Check_For_Visible_Operator --
617 --------------------------------
619 procedure Check_For_Visible_Operator (N : Node_Id; T : Entity_Id) is
620 begin
621 if Is_Invisible_Operator (N, T) then
622 Error_Msg_NE
623 ("operator for} is not directly visible!", N, First_Subtype (T));
624 Error_Msg_N ("use clause would make operation legal!", N);
625 end if;
626 end Check_For_Visible_Operator;
628 ----------------------------------
629 -- Check_Fully_Declared_Prefix --
630 ----------------------------------
632 procedure Check_Fully_Declared_Prefix
633 (Typ : Entity_Id;
634 Pref : Node_Id)
636 begin
637 -- Check that the designated type of the prefix of a dereference is
638 -- not an incomplete type. This cannot be done unconditionally, because
639 -- dereferences of private types are legal in default expressions. This
640 -- case is taken care of in Check_Fully_Declared, called below. There
641 -- are also 2005 cases where it is legal for the prefix to be unfrozen.
643 -- This consideration also applies to similar checks for allocators,
644 -- qualified expressions, and type conversions.
646 -- An additional exception concerns other per-object expressions that
647 -- are not directly related to component declarations, in particular
648 -- representation pragmas for tasks. These will be per-object
649 -- expressions if they depend on discriminants or some global entity.
650 -- If the task has access discriminants, the designated type may be
651 -- incomplete at the point the expression is resolved. This resolution
652 -- takes place within the body of the initialization procedure, where
653 -- the discriminant is replaced by its discriminal.
655 if Is_Entity_Name (Pref)
656 and then Ekind (Entity (Pref)) = E_In_Parameter
657 then
658 null;
660 -- Ada 2005 (AI-326): Tagged incomplete types allowed. The wrong usages
661 -- are handled by Analyze_Access_Attribute, Analyze_Assignment,
662 -- Analyze_Object_Renaming, and Freeze_Entity.
664 elsif Ada_Version >= Ada_05
665 and then Is_Entity_Name (Pref)
666 and then Ekind (Directly_Designated_Type (Etype (Pref))) =
667 E_Incomplete_Type
668 and then Is_Tagged_Type (Directly_Designated_Type (Etype (Pref)))
669 then
670 null;
671 else
672 Check_Fully_Declared (Typ, Parent (Pref));
673 end if;
674 end Check_Fully_Declared_Prefix;
676 ------------------------------
677 -- Check_Infinite_Recursion --
678 ------------------------------
680 function Check_Infinite_Recursion (N : Node_Id) return Boolean is
681 P : Node_Id;
682 C : Node_Id;
684 function Same_Argument_List return Boolean;
685 -- Check whether list of actuals is identical to list of formals
686 -- of called function (which is also the enclosing scope).
688 ------------------------
689 -- Same_Argument_List --
690 ------------------------
692 function Same_Argument_List return Boolean is
693 A : Node_Id;
694 F : Entity_Id;
695 Subp : Entity_Id;
697 begin
698 if not Is_Entity_Name (Name (N)) then
699 return False;
700 else
701 Subp := Entity (Name (N));
702 end if;
704 F := First_Formal (Subp);
705 A := First_Actual (N);
706 while Present (F) and then Present (A) loop
707 if not Is_Entity_Name (A)
708 or else Entity (A) /= F
709 then
710 return False;
711 end if;
713 Next_Actual (A);
714 Next_Formal (F);
715 end loop;
717 return True;
718 end Same_Argument_List;
720 -- Start of processing for Check_Infinite_Recursion
722 begin
723 -- Loop moving up tree, quitting if something tells us we are
724 -- definitely not in an infinite recursion situation.
726 C := N;
727 loop
728 P := Parent (C);
729 exit when Nkind (P) = N_Subprogram_Body;
731 if Nkind (P) = N_Or_Else or else
732 Nkind (P) = N_And_Then or else
733 Nkind (P) = N_If_Statement or else
734 Nkind (P) = N_Case_Statement
735 then
736 return False;
738 elsif Nkind (P) = N_Handled_Sequence_Of_Statements
739 and then C /= First (Statements (P))
740 then
741 -- If the call is the expression of a return statement and
742 -- the actuals are identical to the formals, it's worth a
743 -- warning. However, we skip this if there is an immediately
744 -- preceding raise statement, since the call is never executed.
746 -- Furthermore, this corresponds to a common idiom:
748 -- function F (L : Thing) return Boolean is
749 -- begin
750 -- raise Program_Error;
751 -- return F (L);
752 -- end F;
754 -- for generating a stub function
756 if Nkind (Parent (N)) = N_Simple_Return_Statement
757 and then Same_Argument_List
758 then
759 exit when not Is_List_Member (Parent (N));
761 -- OK, return statement is in a statement list, look for raise
763 declare
764 Nod : Node_Id;
766 begin
767 -- Skip past N_Freeze_Entity nodes generated by expansion
769 Nod := Prev (Parent (N));
770 while Present (Nod)
771 and then Nkind (Nod) = N_Freeze_Entity
772 loop
773 Prev (Nod);
774 end loop;
776 -- If no raise statement, give warning
778 exit when Nkind (Nod) /= N_Raise_Statement
779 and then
780 (Nkind (Nod) not in N_Raise_xxx_Error
781 or else Present (Condition (Nod)));
782 end;
783 end if;
785 return False;
787 else
788 C := P;
789 end if;
790 end loop;
792 Error_Msg_N ("!?possible infinite recursion", N);
793 Error_Msg_N ("\!?Storage_Error may be raised at run time", N);
795 return True;
796 end Check_Infinite_Recursion;
798 -------------------------------
799 -- Check_Initialization_Call --
800 -------------------------------
802 procedure Check_Initialization_Call (N : Entity_Id; Nam : Entity_Id) is
803 Typ : constant Entity_Id := Etype (First_Formal (Nam));
805 function Uses_SS (T : Entity_Id) return Boolean;
806 -- Check whether the creation of an object of the type will involve
807 -- use of the secondary stack. If T is a record type, this is true
808 -- if the expression for some component uses the secondary stack, eg.
809 -- through a call to a function that returns an unconstrained value.
810 -- False if T is controlled, because cleanups occur elsewhere.
812 -------------
813 -- Uses_SS --
814 -------------
816 function Uses_SS (T : Entity_Id) return Boolean is
817 Comp : Entity_Id;
818 Expr : Node_Id;
819 Full_Type : Entity_Id := Underlying_Type (T);
821 begin
822 -- Normally we want to use the underlying type, but if it's not set
823 -- then continue with T.
825 if not Present (Full_Type) then
826 Full_Type := T;
827 end if;
829 if Is_Controlled (Full_Type) then
830 return False;
832 elsif Is_Array_Type (Full_Type) then
833 return Uses_SS (Component_Type (Full_Type));
835 elsif Is_Record_Type (Full_Type) then
836 Comp := First_Component (Full_Type);
837 while Present (Comp) loop
838 if Ekind (Comp) = E_Component
839 and then Nkind (Parent (Comp)) = N_Component_Declaration
840 then
841 -- The expression for a dynamic component may be rewritten
842 -- as a dereference, so retrieve original node.
844 Expr := Original_Node (Expression (Parent (Comp)));
846 -- Return True if the expression is a call to a function
847 -- (including an attribute function such as Image) with
848 -- a result that requires a transient scope.
850 if (Nkind (Expr) = N_Function_Call
851 or else (Nkind (Expr) = N_Attribute_Reference
852 and then Present (Expressions (Expr))))
853 and then Requires_Transient_Scope (Etype (Expr))
854 then
855 return True;
857 elsif Uses_SS (Etype (Comp)) then
858 return True;
859 end if;
860 end if;
862 Next_Component (Comp);
863 end loop;
865 return False;
867 else
868 return False;
869 end if;
870 end Uses_SS;
872 -- Start of processing for Check_Initialization_Call
874 begin
875 -- Establish a transient scope if the type needs it
877 if Uses_SS (Typ) then
878 Establish_Transient_Scope (First_Actual (N), Sec_Stack => True);
879 end if;
880 end Check_Initialization_Call;
882 ------------------------------
883 -- Check_Parameterless_Call --
884 ------------------------------
886 procedure Check_Parameterless_Call (N : Node_Id) is
887 Nam : Node_Id;
889 function Prefix_Is_Access_Subp return Boolean;
890 -- If the prefix is of an access_to_subprogram type, the node must be
891 -- rewritten as a call. Ditto if the prefix is overloaded and all its
892 -- interpretations are access to subprograms.
894 ---------------------------
895 -- Prefix_Is_Access_Subp --
896 ---------------------------
898 function Prefix_Is_Access_Subp return Boolean is
899 I : Interp_Index;
900 It : Interp;
902 begin
903 if not Is_Overloaded (N) then
904 return
905 Ekind (Etype (N)) = E_Subprogram_Type
906 and then Base_Type (Etype (Etype (N))) /= Standard_Void_Type;
907 else
908 Get_First_Interp (N, I, It);
909 while Present (It.Typ) loop
910 if Ekind (It.Typ) /= E_Subprogram_Type
911 or else Base_Type (Etype (It.Typ)) = Standard_Void_Type
912 then
913 return False;
914 end if;
916 Get_Next_Interp (I, It);
917 end loop;
919 return True;
920 end if;
921 end Prefix_Is_Access_Subp;
923 -- Start of processing for Check_Parameterless_Call
925 begin
926 -- Defend against junk stuff if errors already detected
928 if Total_Errors_Detected /= 0 then
929 if Nkind (N) in N_Has_Etype and then Etype (N) = Any_Type then
930 return;
931 elsif Nkind (N) in N_Has_Chars
932 and then Chars (N) in Error_Name_Or_No_Name
933 then
934 return;
935 end if;
937 Require_Entity (N);
938 end if;
940 -- If the context expects a value, and the name is a procedure,
941 -- this is most likely a missing 'Access. Do not try to resolve
942 -- the parameterless call, error will be caught when the outer
943 -- call is analyzed.
945 if Is_Entity_Name (N)
946 and then Ekind (Entity (N)) = E_Procedure
947 and then not Is_Overloaded (N)
948 and then
949 (Nkind (Parent (N)) = N_Parameter_Association
950 or else Nkind (Parent (N)) = N_Function_Call
951 or else Nkind (Parent (N)) = N_Procedure_Call_Statement)
952 then
953 return;
954 end if;
956 -- Rewrite as call if overloadable entity that is (or could be, in
957 -- the overloaded case) a function call. If we know for sure that
958 -- the entity is an enumeration literal, we do not rewrite it.
960 if (Is_Entity_Name (N)
961 and then Is_Overloadable (Entity (N))
962 and then (Ekind (Entity (N)) /= E_Enumeration_Literal
963 or else Is_Overloaded (N)))
965 -- Rewrite as call if it is an explicit deference of an expression of
966 -- a subprogram access type, and the suprogram type is not that of a
967 -- procedure or entry.
969 or else
970 (Nkind (N) = N_Explicit_Dereference and then Prefix_Is_Access_Subp)
972 -- Rewrite as call if it is a selected component which is a function,
973 -- this is the case of a call to a protected function (which may be
974 -- overloaded with other protected operations).
976 or else
977 (Nkind (N) = N_Selected_Component
978 and then (Ekind (Entity (Selector_Name (N))) = E_Function
979 or else
980 ((Ekind (Entity (Selector_Name (N))) = E_Entry
981 or else
982 Ekind (Entity (Selector_Name (N))) = E_Procedure)
983 and then Is_Overloaded (Selector_Name (N)))))
985 -- If one of the above three conditions is met, rewrite as call.
986 -- Apply the rewriting only once.
988 then
989 if Nkind (Parent (N)) /= N_Function_Call
990 or else N /= Name (Parent (N))
991 then
992 Nam := New_Copy (N);
994 -- If overloaded, overload set belongs to new copy
996 Save_Interps (N, Nam);
998 -- Change node to parameterless function call (note that the
999 -- Parameter_Associations associations field is left set to Empty,
1000 -- its normal default value since there are no parameters)
1002 Change_Node (N, N_Function_Call);
1003 Set_Name (N, Nam);
1004 Set_Sloc (N, Sloc (Nam));
1005 Analyze_Call (N);
1006 end if;
1008 elsif Nkind (N) = N_Parameter_Association then
1009 Check_Parameterless_Call (Explicit_Actual_Parameter (N));
1010 end if;
1011 end Check_Parameterless_Call;
1013 -----------------------------
1014 -- Is_Definite_Access_Type --
1015 -----------------------------
1017 function Is_Definite_Access_Type (E : Entity_Id) return Boolean is
1018 Btyp : constant Entity_Id := Base_Type (E);
1019 begin
1020 return Ekind (Btyp) = E_Access_Type
1021 or else (Ekind (Btyp) = E_Access_Subprogram_Type
1022 and then Comes_From_Source (Btyp));
1023 end Is_Definite_Access_Type;
1025 ----------------------
1026 -- Is_Predefined_Op --
1027 ----------------------
1029 function Is_Predefined_Op (Nam : Entity_Id) return Boolean is
1030 begin
1031 return Is_Intrinsic_Subprogram (Nam)
1032 and then not Is_Generic_Instance (Nam)
1033 and then Chars (Nam) in Any_Operator_Name
1034 and then (No (Alias (Nam))
1035 or else Is_Predefined_Op (Alias (Nam)));
1036 end Is_Predefined_Op;
1038 -----------------------------
1039 -- Make_Call_Into_Operator --
1040 -----------------------------
1042 procedure Make_Call_Into_Operator
1043 (N : Node_Id;
1044 Typ : Entity_Id;
1045 Op_Id : Entity_Id)
1047 Op_Name : constant Name_Id := Chars (Op_Id);
1048 Act1 : Node_Id := First_Actual (N);
1049 Act2 : Node_Id := Next_Actual (Act1);
1050 Error : Boolean := False;
1051 Func : constant Entity_Id := Entity (Name (N));
1052 Is_Binary : constant Boolean := Present (Act2);
1053 Op_Node : Node_Id;
1054 Opnd_Type : Entity_Id;
1055 Orig_Type : Entity_Id := Empty;
1056 Pack : Entity_Id;
1058 type Kind_Test is access function (E : Entity_Id) return Boolean;
1060 function Operand_Type_In_Scope (S : Entity_Id) return Boolean;
1061 -- If the operand is not universal, and the operator is given by a
1062 -- expanded name, verify that the operand has an interpretation with
1063 -- a type defined in the given scope of the operator.
1065 function Type_In_P (Test : Kind_Test) return Entity_Id;
1066 -- Find a type of the given class in the package Pack that contains
1067 -- the operator.
1069 ---------------------------
1070 -- Operand_Type_In_Scope --
1071 ---------------------------
1073 function Operand_Type_In_Scope (S : Entity_Id) return Boolean is
1074 Nod : constant Node_Id := Right_Opnd (Op_Node);
1075 I : Interp_Index;
1076 It : Interp;
1078 begin
1079 if not Is_Overloaded (Nod) then
1080 return Scope (Base_Type (Etype (Nod))) = S;
1082 else
1083 Get_First_Interp (Nod, I, It);
1084 while Present (It.Typ) loop
1085 if Scope (Base_Type (It.Typ)) = S then
1086 return True;
1087 end if;
1089 Get_Next_Interp (I, It);
1090 end loop;
1092 return False;
1093 end if;
1094 end Operand_Type_In_Scope;
1096 ---------------
1097 -- Type_In_P --
1098 ---------------
1100 function Type_In_P (Test : Kind_Test) return Entity_Id is
1101 E : Entity_Id;
1103 function In_Decl return Boolean;
1104 -- Verify that node is not part of the type declaration for the
1105 -- candidate type, which would otherwise be invisible.
1107 -------------
1108 -- In_Decl --
1109 -------------
1111 function In_Decl return Boolean is
1112 Decl_Node : constant Node_Id := Parent (E);
1113 N2 : Node_Id;
1115 begin
1116 N2 := N;
1118 if Etype (E) = Any_Type then
1119 return True;
1121 elsif No (Decl_Node) then
1122 return False;
1124 else
1125 while Present (N2)
1126 and then Nkind (N2) /= N_Compilation_Unit
1127 loop
1128 if N2 = Decl_Node then
1129 return True;
1130 else
1131 N2 := Parent (N2);
1132 end if;
1133 end loop;
1135 return False;
1136 end if;
1137 end In_Decl;
1139 -- Start of processing for Type_In_P
1141 begin
1142 -- If the context type is declared in the prefix package, this
1143 -- is the desired base type.
1145 if Scope (Base_Type (Typ)) = Pack
1146 and then Test (Typ)
1147 then
1148 return Base_Type (Typ);
1150 else
1151 E := First_Entity (Pack);
1152 while Present (E) loop
1153 if Test (E)
1154 and then not In_Decl
1155 then
1156 return E;
1157 end if;
1159 Next_Entity (E);
1160 end loop;
1162 return Empty;
1163 end if;
1164 end Type_In_P;
1166 -- Start of processing for Make_Call_Into_Operator
1168 begin
1169 Op_Node := New_Node (Operator_Kind (Op_Name, Is_Binary), Sloc (N));
1171 -- Binary operator
1173 if Is_Binary then
1174 Set_Left_Opnd (Op_Node, Relocate_Node (Act1));
1175 Set_Right_Opnd (Op_Node, Relocate_Node (Act2));
1176 Save_Interps (Act1, Left_Opnd (Op_Node));
1177 Save_Interps (Act2, Right_Opnd (Op_Node));
1178 Act1 := Left_Opnd (Op_Node);
1179 Act2 := Right_Opnd (Op_Node);
1181 -- Unary operator
1183 else
1184 Set_Right_Opnd (Op_Node, Relocate_Node (Act1));
1185 Save_Interps (Act1, Right_Opnd (Op_Node));
1186 Act1 := Right_Opnd (Op_Node);
1187 end if;
1189 -- If the operator is denoted by an expanded name, and the prefix is
1190 -- not Standard, but the operator is a predefined one whose scope is
1191 -- Standard, then this is an implicit_operator, inserted as an
1192 -- interpretation by the procedure of the same name. This procedure
1193 -- overestimates the presence of implicit operators, because it does
1194 -- not examine the type of the operands. Verify now that the operand
1195 -- type appears in the given scope. If right operand is universal,
1196 -- check the other operand. In the case of concatenation, either
1197 -- argument can be the component type, so check the type of the result.
1198 -- If both arguments are literals, look for a type of the right kind
1199 -- defined in the given scope. This elaborate nonsense is brought to
1200 -- you courtesy of b33302a. The type itself must be frozen, so we must
1201 -- find the type of the proper class in the given scope.
1203 -- A final wrinkle is the multiplication operator for fixed point
1204 -- types, which is defined in Standard only, and not in the scope of
1205 -- the fixed_point type itself.
1207 if Nkind (Name (N)) = N_Expanded_Name then
1208 Pack := Entity (Prefix (Name (N)));
1210 -- If the entity being called is defined in the given package,
1211 -- it is a renaming of a predefined operator, and known to be
1212 -- legal.
1214 if Scope (Entity (Name (N))) = Pack
1215 and then Pack /= Standard_Standard
1216 then
1217 null;
1219 -- Visibility does not need to be checked in an instance: if the
1220 -- operator was not visible in the generic it has been diagnosed
1221 -- already, else there is an implicit copy of it in the instance.
1223 elsif In_Instance then
1224 null;
1226 elsif (Op_Name = Name_Op_Multiply
1227 or else Op_Name = Name_Op_Divide)
1228 and then Is_Fixed_Point_Type (Etype (Left_Opnd (Op_Node)))
1229 and then Is_Fixed_Point_Type (Etype (Right_Opnd (Op_Node)))
1230 then
1231 if Pack /= Standard_Standard then
1232 Error := True;
1233 end if;
1235 -- Ada 2005, AI-420: Predefined equality on Universal_Access
1236 -- is available.
1238 elsif Ada_Version >= Ada_05
1239 and then (Op_Name = Name_Op_Eq or else Op_Name = Name_Op_Ne)
1240 and then Ekind (Etype (Act1)) = E_Anonymous_Access_Type
1241 then
1242 null;
1244 else
1245 Opnd_Type := Base_Type (Etype (Right_Opnd (Op_Node)));
1247 if Op_Name = Name_Op_Concat then
1248 Opnd_Type := Base_Type (Typ);
1250 elsif (Scope (Opnd_Type) = Standard_Standard
1251 and then Is_Binary)
1252 or else (Nkind (Right_Opnd (Op_Node)) = N_Attribute_Reference
1253 and then Is_Binary
1254 and then not Comes_From_Source (Opnd_Type))
1255 then
1256 Opnd_Type := Base_Type (Etype (Left_Opnd (Op_Node)));
1257 end if;
1259 if Scope (Opnd_Type) = Standard_Standard then
1261 -- Verify that the scope contains a type that corresponds to
1262 -- the given literal. Optimize the case where Pack is Standard.
1264 if Pack /= Standard_Standard then
1266 if Opnd_Type = Universal_Integer then
1267 Orig_Type := Type_In_P (Is_Integer_Type'Access);
1269 elsif Opnd_Type = Universal_Real then
1270 Orig_Type := Type_In_P (Is_Real_Type'Access);
1272 elsif Opnd_Type = Any_String then
1273 Orig_Type := Type_In_P (Is_String_Type'Access);
1275 elsif Opnd_Type = Any_Access then
1276 Orig_Type := Type_In_P (Is_Definite_Access_Type'Access);
1278 elsif Opnd_Type = Any_Composite then
1279 Orig_Type := Type_In_P (Is_Composite_Type'Access);
1281 if Present (Orig_Type) then
1282 if Has_Private_Component (Orig_Type) then
1283 Orig_Type := Empty;
1284 else
1285 Set_Etype (Act1, Orig_Type);
1287 if Is_Binary then
1288 Set_Etype (Act2, Orig_Type);
1289 end if;
1290 end if;
1291 end if;
1293 else
1294 Orig_Type := Empty;
1295 end if;
1297 Error := No (Orig_Type);
1298 end if;
1300 elsif Ekind (Opnd_Type) = E_Allocator_Type
1301 and then No (Type_In_P (Is_Definite_Access_Type'Access))
1302 then
1303 Error := True;
1305 -- If the type is defined elsewhere, and the operator is not
1306 -- defined in the given scope (by a renaming declaration, e.g.)
1307 -- then this is an error as well. If an extension of System is
1308 -- present, and the type may be defined there, Pack must be
1309 -- System itself.
1311 elsif Scope (Opnd_Type) /= Pack
1312 and then Scope (Op_Id) /= Pack
1313 and then (No (System_Aux_Id)
1314 or else Scope (Opnd_Type) /= System_Aux_Id
1315 or else Pack /= Scope (System_Aux_Id))
1316 then
1317 if not Is_Overloaded (Right_Opnd (Op_Node)) then
1318 Error := True;
1319 else
1320 Error := not Operand_Type_In_Scope (Pack);
1321 end if;
1323 elsif Pack = Standard_Standard
1324 and then not Operand_Type_In_Scope (Standard_Standard)
1325 then
1326 Error := True;
1327 end if;
1328 end if;
1330 if Error then
1331 Error_Msg_Node_2 := Pack;
1332 Error_Msg_NE
1333 ("& not declared in&", N, Selector_Name (Name (N)));
1334 Set_Etype (N, Any_Type);
1335 return;
1336 end if;
1337 end if;
1339 Set_Chars (Op_Node, Op_Name);
1341 if not Is_Private_Type (Etype (N)) then
1342 Set_Etype (Op_Node, Base_Type (Etype (N)));
1343 else
1344 Set_Etype (Op_Node, Etype (N));
1345 end if;
1347 -- If this is a call to a function that renames a predefined equality,
1348 -- the renaming declaration provides a type that must be used to
1349 -- resolve the operands. This must be done now because resolution of
1350 -- the equality node will not resolve any remaining ambiguity, and it
1351 -- assumes that the first operand is not overloaded.
1353 if (Op_Name = Name_Op_Eq or else Op_Name = Name_Op_Ne)
1354 and then Ekind (Func) = E_Function
1355 and then Is_Overloaded (Act1)
1356 then
1357 Resolve (Act1, Base_Type (Etype (First_Formal (Func))));
1358 Resolve (Act2, Base_Type (Etype (First_Formal (Func))));
1359 end if;
1361 Set_Entity (Op_Node, Op_Id);
1362 Generate_Reference (Op_Id, N, ' ');
1363 Rewrite (N, Op_Node);
1365 -- If this is an arithmetic operator and the result type is private,
1366 -- the operands and the result must be wrapped in conversion to
1367 -- expose the underlying numeric type and expand the proper checks,
1368 -- e.g. on division.
1370 if Is_Private_Type (Typ) then
1371 case Nkind (N) is
1372 when N_Op_Add | N_Op_Subtract | N_Op_Multiply | N_Op_Divide |
1373 N_Op_Expon | N_Op_Mod | N_Op_Rem =>
1374 Resolve_Intrinsic_Operator (N, Typ);
1376 when N_Op_Plus | N_Op_Minus | N_Op_Abs =>
1377 Resolve_Intrinsic_Unary_Operator (N, Typ);
1379 when others =>
1380 Resolve (N, Typ);
1381 end case;
1382 else
1383 Resolve (N, Typ);
1384 end if;
1386 -- For predefined operators on literals, the operation freezes
1387 -- their type.
1389 if Present (Orig_Type) then
1390 Set_Etype (Act1, Orig_Type);
1391 Freeze_Expression (Act1);
1392 end if;
1393 end Make_Call_Into_Operator;
1395 -------------------
1396 -- Operator_Kind --
1397 -------------------
1399 function Operator_Kind
1400 (Op_Name : Name_Id;
1401 Is_Binary : Boolean) return Node_Kind
1403 Kind : Node_Kind;
1405 begin
1406 if Is_Binary then
1407 if Op_Name = Name_Op_And then
1408 Kind := N_Op_And;
1409 elsif Op_Name = Name_Op_Or then
1410 Kind := N_Op_Or;
1411 elsif Op_Name = Name_Op_Xor then
1412 Kind := N_Op_Xor;
1413 elsif Op_Name = Name_Op_Eq then
1414 Kind := N_Op_Eq;
1415 elsif Op_Name = Name_Op_Ne then
1416 Kind := N_Op_Ne;
1417 elsif Op_Name = Name_Op_Lt then
1418 Kind := N_Op_Lt;
1419 elsif Op_Name = Name_Op_Le then
1420 Kind := N_Op_Le;
1421 elsif Op_Name = Name_Op_Gt then
1422 Kind := N_Op_Gt;
1423 elsif Op_Name = Name_Op_Ge then
1424 Kind := N_Op_Ge;
1425 elsif Op_Name = Name_Op_Add then
1426 Kind := N_Op_Add;
1427 elsif Op_Name = Name_Op_Subtract then
1428 Kind := N_Op_Subtract;
1429 elsif Op_Name = Name_Op_Concat then
1430 Kind := N_Op_Concat;
1431 elsif Op_Name = Name_Op_Multiply then
1432 Kind := N_Op_Multiply;
1433 elsif Op_Name = Name_Op_Divide then
1434 Kind := N_Op_Divide;
1435 elsif Op_Name = Name_Op_Mod then
1436 Kind := N_Op_Mod;
1437 elsif Op_Name = Name_Op_Rem then
1438 Kind := N_Op_Rem;
1439 elsif Op_Name = Name_Op_Expon then
1440 Kind := N_Op_Expon;
1441 else
1442 raise Program_Error;
1443 end if;
1445 -- Unary operators
1447 else
1448 if Op_Name = Name_Op_Add then
1449 Kind := N_Op_Plus;
1450 elsif Op_Name = Name_Op_Subtract then
1451 Kind := N_Op_Minus;
1452 elsif Op_Name = Name_Op_Abs then
1453 Kind := N_Op_Abs;
1454 elsif Op_Name = Name_Op_Not then
1455 Kind := N_Op_Not;
1456 else
1457 raise Program_Error;
1458 end if;
1459 end if;
1461 return Kind;
1462 end Operator_Kind;
1464 -----------------------------
1465 -- Pre_Analyze_And_Resolve --
1466 -----------------------------
1468 procedure Pre_Analyze_And_Resolve (N : Node_Id; T : Entity_Id) is
1469 Save_Full_Analysis : constant Boolean := Full_Analysis;
1471 begin
1472 Full_Analysis := False;
1473 Expander_Mode_Save_And_Set (False);
1475 -- We suppress all checks for this analysis, since the checks will
1476 -- be applied properly, and in the right location, when the default
1477 -- expression is reanalyzed and reexpanded later on.
1479 Analyze_And_Resolve (N, T, Suppress => All_Checks);
1481 Expander_Mode_Restore;
1482 Full_Analysis := Save_Full_Analysis;
1483 end Pre_Analyze_And_Resolve;
1485 -- Version without context type
1487 procedure Pre_Analyze_And_Resolve (N : Node_Id) is
1488 Save_Full_Analysis : constant Boolean := Full_Analysis;
1490 begin
1491 Full_Analysis := False;
1492 Expander_Mode_Save_And_Set (False);
1494 Analyze (N);
1495 Resolve (N, Etype (N), Suppress => All_Checks);
1497 Expander_Mode_Restore;
1498 Full_Analysis := Save_Full_Analysis;
1499 end Pre_Analyze_And_Resolve;
1501 ----------------------------------
1502 -- Replace_Actual_Discriminants --
1503 ----------------------------------
1505 procedure Replace_Actual_Discriminants (N : Node_Id; Default : Node_Id) is
1506 Loc : constant Source_Ptr := Sloc (N);
1507 Tsk : Node_Id := Empty;
1509 function Process_Discr (Nod : Node_Id) return Traverse_Result;
1511 -------------------
1512 -- Process_Discr --
1513 -------------------
1515 function Process_Discr (Nod : Node_Id) return Traverse_Result is
1516 Ent : Entity_Id;
1518 begin
1519 if Nkind (Nod) = N_Identifier then
1520 Ent := Entity (Nod);
1522 if Present (Ent)
1523 and then Ekind (Ent) = E_Discriminant
1524 then
1525 Rewrite (Nod,
1526 Make_Selected_Component (Loc,
1527 Prefix => New_Copy_Tree (Tsk, New_Sloc => Loc),
1528 Selector_Name => Make_Identifier (Loc, Chars (Ent))));
1530 Set_Etype (Nod, Etype (Ent));
1531 end if;
1533 end if;
1535 return OK;
1536 end Process_Discr;
1538 procedure Replace_Discrs is new Traverse_Proc (Process_Discr);
1540 -- Start of processing for Replace_Actual_Discriminants
1542 begin
1543 if not Expander_Active then
1544 return;
1545 end if;
1547 if Nkind (Name (N)) = N_Selected_Component then
1548 Tsk := Prefix (Name (N));
1550 elsif Nkind (Name (N)) = N_Indexed_Component then
1551 Tsk := Prefix (Prefix (Name (N)));
1552 end if;
1554 if No (Tsk) then
1555 return;
1556 else
1557 Replace_Discrs (Default);
1558 end if;
1559 end Replace_Actual_Discriminants;
1561 -------------
1562 -- Resolve --
1563 -------------
1565 procedure Resolve (N : Node_Id; Typ : Entity_Id) is
1566 Ambiguous : Boolean := False;
1567 Ctx_Type : Entity_Id := Typ;
1568 Expr_Type : Entity_Id := Empty; -- prevent junk warning
1569 Err_Type : Entity_Id := Empty;
1570 Found : Boolean := False;
1571 From_Lib : Boolean;
1572 I : Interp_Index;
1573 I1 : Interp_Index := 0; -- prevent junk warning
1574 It : Interp;
1575 It1 : Interp;
1576 Seen : Entity_Id := Empty; -- prevent junk warning
1578 function Comes_From_Predefined_Lib_Unit (Nod : Node_Id) return Boolean;
1579 -- Determine whether a node comes from a predefined library unit or
1580 -- Standard.
1582 procedure Patch_Up_Value (N : Node_Id; Typ : Entity_Id);
1583 -- Try and fix up a literal so that it matches its expected type. New
1584 -- literals are manufactured if necessary to avoid cascaded errors.
1586 procedure Resolution_Failed;
1587 -- Called when attempt at resolving current expression fails
1589 ------------------------------------
1590 -- Comes_From_Predefined_Lib_Unit --
1591 -------------------------------------
1593 function Comes_From_Predefined_Lib_Unit (Nod : Node_Id) return Boolean is
1594 begin
1595 return
1596 Sloc (Nod) = Standard_Location
1597 or else Is_Predefined_File_Name (Unit_File_Name (
1598 Get_Source_Unit (Sloc (Nod))));
1599 end Comes_From_Predefined_Lib_Unit;
1601 --------------------
1602 -- Patch_Up_Value --
1603 --------------------
1605 procedure Patch_Up_Value (N : Node_Id; Typ : Entity_Id) is
1606 begin
1607 if Nkind (N) = N_Integer_Literal
1608 and then Is_Real_Type (Typ)
1609 then
1610 Rewrite (N,
1611 Make_Real_Literal (Sloc (N),
1612 Realval => UR_From_Uint (Intval (N))));
1613 Set_Etype (N, Universal_Real);
1614 Set_Is_Static_Expression (N);
1616 elsif Nkind (N) = N_Real_Literal
1617 and then Is_Integer_Type (Typ)
1618 then
1619 Rewrite (N,
1620 Make_Integer_Literal (Sloc (N),
1621 Intval => UR_To_Uint (Realval (N))));
1622 Set_Etype (N, Universal_Integer);
1623 Set_Is_Static_Expression (N);
1624 elsif Nkind (N) = N_String_Literal
1625 and then Is_Character_Type (Typ)
1626 then
1627 Set_Character_Literal_Name (Char_Code (Character'Pos ('A')));
1628 Rewrite (N,
1629 Make_Character_Literal (Sloc (N),
1630 Chars => Name_Find,
1631 Char_Literal_Value =>
1632 UI_From_Int (Character'Pos ('A'))));
1633 Set_Etype (N, Any_Character);
1634 Set_Is_Static_Expression (N);
1636 elsif Nkind (N) /= N_String_Literal
1637 and then Is_String_Type (Typ)
1638 then
1639 Rewrite (N,
1640 Make_String_Literal (Sloc (N),
1641 Strval => End_String));
1643 elsif Nkind (N) = N_Range then
1644 Patch_Up_Value (Low_Bound (N), Typ);
1645 Patch_Up_Value (High_Bound (N), Typ);
1646 end if;
1647 end Patch_Up_Value;
1649 -----------------------
1650 -- Resolution_Failed --
1651 -----------------------
1653 procedure Resolution_Failed is
1654 begin
1655 Patch_Up_Value (N, Typ);
1656 Set_Etype (N, Typ);
1657 Debug_A_Exit ("resolving ", N, " (done, resolution failed)");
1658 Set_Is_Overloaded (N, False);
1660 -- The caller will return without calling the expander, so we need
1661 -- to set the analyzed flag. Note that it is fine to set Analyzed
1662 -- to True even if we are in the middle of a shallow analysis,
1663 -- (see the spec of sem for more details) since this is an error
1664 -- situation anyway, and there is no point in repeating the
1665 -- analysis later (indeed it won't work to repeat it later, since
1666 -- we haven't got a clear resolution of which entity is being
1667 -- referenced.)
1669 Set_Analyzed (N, True);
1670 return;
1671 end Resolution_Failed;
1673 -- Start of processing for Resolve
1675 begin
1676 if N = Error then
1677 return;
1678 end if;
1680 -- Access attribute on remote subprogram cannot be used for
1681 -- a non-remote access-to-subprogram type.
1683 if Nkind (N) = N_Attribute_Reference
1684 and then (Attribute_Name (N) = Name_Access
1685 or else Attribute_Name (N) = Name_Unrestricted_Access
1686 or else Attribute_Name (N) = Name_Unchecked_Access)
1687 and then Comes_From_Source (N)
1688 and then Is_Entity_Name (Prefix (N))
1689 and then Is_Subprogram (Entity (Prefix (N)))
1690 and then Is_Remote_Call_Interface (Entity (Prefix (N)))
1691 and then not Is_Remote_Access_To_Subprogram_Type (Typ)
1692 then
1693 Error_Msg_N
1694 ("prefix must statically denote a non-remote subprogram", N);
1695 end if;
1697 From_Lib := Comes_From_Predefined_Lib_Unit (N);
1699 -- If the context is a Remote_Access_To_Subprogram, access attributes
1700 -- must be resolved with the corresponding fat pointer. There is no need
1701 -- to check for the attribute name since the return type of an
1702 -- attribute is never a remote type.
1704 if Nkind (N) = N_Attribute_Reference
1705 and then Comes_From_Source (N)
1706 and then (Is_Remote_Call_Interface (Typ)
1707 or else Is_Remote_Types (Typ))
1708 then
1709 declare
1710 Attr : constant Attribute_Id :=
1711 Get_Attribute_Id (Attribute_Name (N));
1712 Pref : constant Node_Id := Prefix (N);
1713 Decl : Node_Id;
1714 Spec : Node_Id;
1715 Is_Remote : Boolean := True;
1717 begin
1718 -- Check that Typ is a remote access-to-subprogram type
1720 if Is_Remote_Access_To_Subprogram_Type (Typ) then
1721 -- Prefix (N) must statically denote a remote subprogram
1722 -- declared in a package specification.
1724 if Attr = Attribute_Access then
1725 Decl := Unit_Declaration_Node (Entity (Pref));
1727 if Nkind (Decl) = N_Subprogram_Body then
1728 Spec := Corresponding_Spec (Decl);
1730 if not No (Spec) then
1731 Decl := Unit_Declaration_Node (Spec);
1732 end if;
1733 end if;
1735 Spec := Parent (Decl);
1737 if not Is_Entity_Name (Prefix (N))
1738 or else Nkind (Spec) /= N_Package_Specification
1739 or else
1740 not Is_Remote_Call_Interface (Defining_Entity (Spec))
1741 then
1742 Is_Remote := False;
1743 Error_Msg_N
1744 ("prefix must statically denote a remote subprogram ",
1746 end if;
1747 end if;
1749 -- If we are generating code for a distributed program.
1750 -- perform semantic checks against the corresponding
1751 -- remote entities.
1753 if (Attr = Attribute_Access
1754 or else Attr = Attribute_Unchecked_Access
1755 or else Attr = Attribute_Unrestricted_Access)
1756 and then Expander_Active
1757 and then Get_PCS_Name /= Name_No_DSA
1758 then
1759 Check_Subtype_Conformant
1760 (New_Id => Entity (Prefix (N)),
1761 Old_Id => Designated_Type
1762 (Corresponding_Remote_Type (Typ)),
1763 Err_Loc => N);
1765 if Is_Remote then
1766 Process_Remote_AST_Attribute (N, Typ);
1767 end if;
1768 end if;
1769 end if;
1770 end;
1771 end if;
1773 Debug_A_Entry ("resolving ", N);
1775 if Comes_From_Source (N) then
1776 if Is_Fixed_Point_Type (Typ) then
1777 Check_Restriction (No_Fixed_Point, N);
1779 elsif Is_Floating_Point_Type (Typ)
1780 and then Typ /= Universal_Real
1781 and then Typ /= Any_Real
1782 then
1783 Check_Restriction (No_Floating_Point, N);
1784 end if;
1785 end if;
1787 -- Return if already analyzed
1789 if Analyzed (N) then
1790 Debug_A_Exit ("resolving ", N, " (done, already analyzed)");
1791 return;
1793 -- Return if type = Any_Type (previous error encountered)
1795 elsif Etype (N) = Any_Type then
1796 Debug_A_Exit ("resolving ", N, " (done, Etype = Any_Type)");
1797 return;
1798 end if;
1800 Check_Parameterless_Call (N);
1802 -- If not overloaded, then we know the type, and all that needs doing
1803 -- is to check that this type is compatible with the context.
1805 if not Is_Overloaded (N) then
1806 Found := Covers (Typ, Etype (N));
1807 Expr_Type := Etype (N);
1809 -- In the overloaded case, we must select the interpretation that
1810 -- is compatible with the context (i.e. the type passed to Resolve)
1812 else
1813 -- Loop through possible interpretations
1815 Get_First_Interp (N, I, It);
1816 Interp_Loop : while Present (It.Typ) loop
1818 -- We are only interested in interpretations that are compatible
1819 -- with the expected type, any other interpretations are ignored.
1821 if not Covers (Typ, It.Typ) then
1822 if Debug_Flag_V then
1823 Write_Str (" interpretation incompatible with context");
1824 Write_Eol;
1825 end if;
1827 else
1828 -- Skip the current interpretation if it is disabled by an
1829 -- abstract operator. This action is performed only when the
1830 -- type against which we are resolving is the same as the
1831 -- type of the interpretation.
1833 if Ada_Version >= Ada_05
1834 and then It.Typ = Typ
1835 and then Typ /= Universal_Integer
1836 and then Typ /= Universal_Real
1837 and then Present (It.Abstract_Op)
1838 then
1839 goto Continue;
1840 end if;
1842 -- First matching interpretation
1844 if not Found then
1845 Found := True;
1846 I1 := I;
1847 Seen := It.Nam;
1848 Expr_Type := It.Typ;
1850 -- Matching interpretation that is not the first, maybe an
1851 -- error, but there are some cases where preference rules are
1852 -- used to choose between the two possibilities. These and
1853 -- some more obscure cases are handled in Disambiguate.
1855 else
1856 -- If the current statement is part of a predefined library
1857 -- unit, then all interpretations which come from user level
1858 -- packages should not be considered.
1860 if From_Lib
1861 and then not Comes_From_Predefined_Lib_Unit (It.Nam)
1862 then
1863 goto Continue;
1864 end if;
1866 Error_Msg_Sloc := Sloc (Seen);
1867 It1 := Disambiguate (N, I1, I, Typ);
1869 -- Disambiguation has succeeded. Skip the remaining
1870 -- interpretations.
1872 if It1 /= No_Interp then
1873 Seen := It1.Nam;
1874 Expr_Type := It1.Typ;
1876 while Present (It.Typ) loop
1877 Get_Next_Interp (I, It);
1878 end loop;
1880 else
1881 -- Before we issue an ambiguity complaint, check for
1882 -- the case of a subprogram call where at least one
1883 -- of the arguments is Any_Type, and if so, suppress
1884 -- the message, since it is a cascaded error.
1886 if Nkind (N) = N_Function_Call
1887 or else Nkind (N) = N_Procedure_Call_Statement
1888 then
1889 declare
1890 A : Node_Id;
1891 E : Node_Id;
1893 begin
1894 A := First_Actual (N);
1895 while Present (A) loop
1896 E := A;
1898 if Nkind (E) = N_Parameter_Association then
1899 E := Explicit_Actual_Parameter (E);
1900 end if;
1902 if Etype (E) = Any_Type then
1903 if Debug_Flag_V then
1904 Write_Str ("Any_Type in call");
1905 Write_Eol;
1906 end if;
1908 exit Interp_Loop;
1909 end if;
1911 Next_Actual (A);
1912 end loop;
1913 end;
1915 elsif Nkind (N) in N_Binary_Op
1916 and then (Etype (Left_Opnd (N)) = Any_Type
1917 or else Etype (Right_Opnd (N)) = Any_Type)
1918 then
1919 exit Interp_Loop;
1921 elsif Nkind (N) in N_Unary_Op
1922 and then Etype (Right_Opnd (N)) = Any_Type
1923 then
1924 exit Interp_Loop;
1925 end if;
1927 -- Not that special case, so issue message using the
1928 -- flag Ambiguous to control printing of the header
1929 -- message only at the start of an ambiguous set.
1931 if not Ambiguous then
1932 if Nkind (N) = N_Function_Call
1933 and then Nkind (Name (N)) = N_Explicit_Dereference
1934 then
1935 Error_Msg_N
1936 ("ambiguous expression "
1937 & "(cannot resolve indirect call)!", N);
1938 else
1939 Error_Msg_NE
1940 ("ambiguous expression (cannot resolve&)!",
1941 N, It.Nam);
1942 end if;
1944 Ambiguous := True;
1946 if Nkind (Parent (Seen)) = N_Full_Type_Declaration then
1947 Error_Msg_N
1948 ("\\possible interpretation (inherited)#!", N);
1949 else
1950 Error_Msg_N ("\\possible interpretation#!", N);
1951 end if;
1952 end if;
1954 Error_Msg_Sloc := Sloc (It.Nam);
1956 -- By default, the error message refers to the candidate
1957 -- interpretation. But if it is a predefined operator, it
1958 -- is implicitly declared at the declaration of the type
1959 -- of the operand. Recover the sloc of that declaration
1960 -- for the error message.
1962 if Nkind (N) in N_Op
1963 and then Scope (It.Nam) = Standard_Standard
1964 and then not Is_Overloaded (Right_Opnd (N))
1965 and then Scope (Base_Type (Etype (Right_Opnd (N)))) /=
1966 Standard_Standard
1967 then
1968 Err_Type := First_Subtype (Etype (Right_Opnd (N)));
1970 if Comes_From_Source (Err_Type)
1971 and then Present (Parent (Err_Type))
1972 then
1973 Error_Msg_Sloc := Sloc (Parent (Err_Type));
1974 end if;
1976 elsif Nkind (N) in N_Binary_Op
1977 and then Scope (It.Nam) = Standard_Standard
1978 and then not Is_Overloaded (Left_Opnd (N))
1979 and then Scope (Base_Type (Etype (Left_Opnd (N)))) /=
1980 Standard_Standard
1981 then
1982 Err_Type := First_Subtype (Etype (Left_Opnd (N)));
1984 if Comes_From_Source (Err_Type)
1985 and then Present (Parent (Err_Type))
1986 then
1987 Error_Msg_Sloc := Sloc (Parent (Err_Type));
1988 end if;
1990 -- If this is an indirect call, use the subprogram_type
1991 -- in the message, to have a meaningful location.
1992 -- Indicate as well if this is an inherited operation,
1993 -- created by a type declaration.
1995 elsif Nkind (N) = N_Function_Call
1996 and then Nkind (Name (N)) = N_Explicit_Dereference
1997 and then Is_Type (It.Nam)
1998 then
1999 Err_Type := It.Nam;
2000 Error_Msg_Sloc :=
2001 Sloc (Associated_Node_For_Itype (Err_Type));
2002 else
2003 Err_Type := Empty;
2004 end if;
2006 if Nkind (N) in N_Op
2007 and then Scope (It.Nam) = Standard_Standard
2008 and then Present (Err_Type)
2009 then
2010 -- Special-case the message for universal_fixed
2011 -- operators, which are not declared with the type
2012 -- of the operand, but appear forever in Standard.
2014 if It.Typ = Universal_Fixed
2015 and then Scope (It.Nam) = Standard_Standard
2016 then
2017 Error_Msg_N
2018 ("\\possible interpretation as " &
2019 "universal_fixed operation " &
2020 "(RM 4.5.5 (19))", N);
2021 else
2022 Error_Msg_N
2023 ("\\possible interpretation (predefined)#!", N);
2024 end if;
2026 elsif
2027 Nkind (Parent (It.Nam)) = N_Full_Type_Declaration
2028 then
2029 Error_Msg_N
2030 ("\\possible interpretation (inherited)#!", N);
2031 else
2032 Error_Msg_N ("\\possible interpretation#!", N);
2033 end if;
2035 end if;
2036 end if;
2038 -- We have a matching interpretation, Expr_Type is the type
2039 -- from this interpretation, and Seen is the entity.
2041 -- For an operator, just set the entity name. The type will be
2042 -- set by the specific operator resolution routine.
2044 if Nkind (N) in N_Op then
2045 Set_Entity (N, Seen);
2046 Generate_Reference (Seen, N);
2048 elsif Nkind (N) = N_Character_Literal then
2049 Set_Etype (N, Expr_Type);
2051 -- For an explicit dereference, attribute reference, range,
2052 -- short-circuit form (which is not an operator node), or call
2053 -- with a name that is an explicit dereference, there is
2054 -- nothing to be done at this point.
2056 elsif Nkind (N) = N_Explicit_Dereference
2057 or else Nkind (N) = N_Attribute_Reference
2058 or else Nkind (N) = N_And_Then
2059 or else Nkind (N) = N_Indexed_Component
2060 or else Nkind (N) = N_Or_Else
2061 or else Nkind (N) = N_Range
2062 or else Nkind (N) = N_Selected_Component
2063 or else Nkind (N) = N_Slice
2064 or else Nkind (Name (N)) = N_Explicit_Dereference
2065 then
2066 null;
2068 -- For procedure or function calls, set the type of the name,
2069 -- and also the entity pointer for the prefix
2071 elsif (Nkind (N) = N_Procedure_Call_Statement
2072 or else Nkind (N) = N_Function_Call)
2073 and then (Is_Entity_Name (Name (N))
2074 or else Nkind (Name (N)) = N_Operator_Symbol)
2075 then
2076 Set_Etype (Name (N), Expr_Type);
2077 Set_Entity (Name (N), Seen);
2078 Generate_Reference (Seen, Name (N));
2080 elsif Nkind (N) = N_Function_Call
2081 and then Nkind (Name (N)) = N_Selected_Component
2082 then
2083 Set_Etype (Name (N), Expr_Type);
2084 Set_Entity (Selector_Name (Name (N)), Seen);
2085 Generate_Reference (Seen, Selector_Name (Name (N)));
2087 -- For all other cases, just set the type of the Name
2089 else
2090 Set_Etype (Name (N), Expr_Type);
2091 end if;
2093 end if;
2095 <<Continue>>
2097 -- Move to next interpretation
2099 exit Interp_Loop when No (It.Typ);
2101 Get_Next_Interp (I, It);
2102 end loop Interp_Loop;
2103 end if;
2105 -- At this stage Found indicates whether or not an acceptable
2106 -- interpretation exists. If not, then we have an error, except
2107 -- that if the context is Any_Type as a result of some other error,
2108 -- then we suppress the error report.
2110 if not Found then
2111 if Typ /= Any_Type then
2113 -- If type we are looking for is Void, then this is the procedure
2114 -- call case, and the error is simply that what we gave is not a
2115 -- procedure name (we think of procedure calls as expressions with
2116 -- types internally, but the user doesn't think of them this way!)
2118 if Typ = Standard_Void_Type then
2120 -- Special case message if function used as a procedure
2122 if Nkind (N) = N_Procedure_Call_Statement
2123 and then Is_Entity_Name (Name (N))
2124 and then Ekind (Entity (Name (N))) = E_Function
2125 then
2126 Error_Msg_NE
2127 ("cannot use function & in a procedure call",
2128 Name (N), Entity (Name (N)));
2130 -- Otherwise give general message (not clear what cases this
2131 -- covers, but no harm in providing for them!)
2133 else
2134 Error_Msg_N ("expect procedure name in procedure call", N);
2135 end if;
2137 Found := True;
2139 -- Otherwise we do have a subexpression with the wrong type
2141 -- Check for the case of an allocator which uses an access type
2142 -- instead of the designated type. This is a common error and we
2143 -- specialize the message, posting an error on the operand of the
2144 -- allocator, complaining that we expected the designated type of
2145 -- the allocator.
2147 elsif Nkind (N) = N_Allocator
2148 and then Ekind (Typ) in Access_Kind
2149 and then Ekind (Etype (N)) in Access_Kind
2150 and then Designated_Type (Etype (N)) = Typ
2151 then
2152 Wrong_Type (Expression (N), Designated_Type (Typ));
2153 Found := True;
2155 -- Check for view mismatch on Null in instances, for which the
2156 -- view-swapping mechanism has no identifier.
2158 elsif (In_Instance or else In_Inlined_Body)
2159 and then (Nkind (N) = N_Null)
2160 and then Is_Private_Type (Typ)
2161 and then Is_Access_Type (Full_View (Typ))
2162 then
2163 Resolve (N, Full_View (Typ));
2164 Set_Etype (N, Typ);
2165 return;
2167 -- Check for an aggregate. Sometimes we can get bogus aggregates
2168 -- from misuse of parentheses, and we are about to complain about
2169 -- the aggregate without even looking inside it.
2171 -- Instead, if we have an aggregate of type Any_Composite, then
2172 -- analyze and resolve the component fields, and then only issue
2173 -- another message if we get no errors doing this (otherwise
2174 -- assume that the errors in the aggregate caused the problem).
2176 elsif Nkind (N) = N_Aggregate
2177 and then Etype (N) = Any_Composite
2178 then
2179 -- Disable expansion in any case. If there is a type mismatch
2180 -- it may be fatal to try to expand the aggregate. The flag
2181 -- would otherwise be set to false when the error is posted.
2183 Expander_Active := False;
2185 declare
2186 procedure Check_Aggr (Aggr : Node_Id);
2187 -- Check one aggregate, and set Found to True if we have a
2188 -- definite error in any of its elements
2190 procedure Check_Elmt (Aelmt : Node_Id);
2191 -- Check one element of aggregate and set Found to True if
2192 -- we definitely have an error in the element.
2194 ----------------
2195 -- Check_Aggr --
2196 ----------------
2198 procedure Check_Aggr (Aggr : Node_Id) is
2199 Elmt : Node_Id;
2201 begin
2202 if Present (Expressions (Aggr)) then
2203 Elmt := First (Expressions (Aggr));
2204 while Present (Elmt) loop
2205 Check_Elmt (Elmt);
2206 Next (Elmt);
2207 end loop;
2208 end if;
2210 if Present (Component_Associations (Aggr)) then
2211 Elmt := First (Component_Associations (Aggr));
2212 while Present (Elmt) loop
2214 -- If this is a default-initialized component, then
2215 -- there is nothing to check. The box will be
2216 -- replaced by the appropriate call during late
2217 -- expansion.
2219 if not Box_Present (Elmt) then
2220 Check_Elmt (Expression (Elmt));
2221 end if;
2223 Next (Elmt);
2224 end loop;
2225 end if;
2226 end Check_Aggr;
2228 ----------------
2229 -- Check_Elmt --
2230 ----------------
2232 procedure Check_Elmt (Aelmt : Node_Id) is
2233 begin
2234 -- If we have a nested aggregate, go inside it (to
2235 -- attempt a naked analyze-resolve of the aggregate
2236 -- can cause undesirable cascaded errors). Do not
2237 -- resolve expression if it needs a type from context,
2238 -- as for integer * fixed expression.
2240 if Nkind (Aelmt) = N_Aggregate then
2241 Check_Aggr (Aelmt);
2243 else
2244 Analyze (Aelmt);
2246 if not Is_Overloaded (Aelmt)
2247 and then Etype (Aelmt) /= Any_Fixed
2248 then
2249 Resolve (Aelmt);
2250 end if;
2252 if Etype (Aelmt) = Any_Type then
2253 Found := True;
2254 end if;
2255 end if;
2256 end Check_Elmt;
2258 begin
2259 Check_Aggr (N);
2260 end;
2261 end if;
2263 -- If an error message was issued already, Found got reset
2264 -- to True, so if it is still False, issue the standard
2265 -- Wrong_Type message.
2267 if not Found then
2268 if Is_Overloaded (N)
2269 and then Nkind (N) = N_Function_Call
2270 then
2271 declare
2272 Subp_Name : Node_Id;
2273 begin
2274 if Is_Entity_Name (Name (N)) then
2275 Subp_Name := Name (N);
2277 elsif Nkind (Name (N)) = N_Selected_Component then
2279 -- Protected operation: retrieve operation name
2281 Subp_Name := Selector_Name (Name (N));
2282 else
2283 raise Program_Error;
2284 end if;
2286 Error_Msg_Node_2 := Typ;
2287 Error_Msg_NE ("no visible interpretation of&" &
2288 " matches expected type&", N, Subp_Name);
2289 end;
2291 if All_Errors_Mode then
2292 declare
2293 Index : Interp_Index;
2294 It : Interp;
2296 begin
2297 Error_Msg_N ("\\possible interpretations:", N);
2299 Get_First_Interp (Name (N), Index, It);
2300 while Present (It.Nam) loop
2301 Error_Msg_Sloc := Sloc (It.Nam);
2302 Error_Msg_Node_2 := It.Nam;
2303 Error_Msg_NE
2304 ("\\ type& for & declared#", N, It.Typ);
2305 Get_Next_Interp (Index, It);
2306 end loop;
2307 end;
2309 else
2310 Error_Msg_N ("\use -gnatf for details", N);
2311 end if;
2312 else
2313 Wrong_Type (N, Typ);
2314 end if;
2315 end if;
2316 end if;
2318 Resolution_Failed;
2319 return;
2321 -- Test if we have more than one interpretation for the context
2323 elsif Ambiguous then
2324 Resolution_Failed;
2325 return;
2327 -- Here we have an acceptable interpretation for the context
2329 else
2330 -- Propagate type information and normalize tree for various
2331 -- predefined operations. If the context only imposes a class of
2332 -- types, rather than a specific type, propagate the actual type
2333 -- downward.
2335 if Typ = Any_Integer
2336 or else Typ = Any_Boolean
2337 or else Typ = Any_Modular
2338 or else Typ = Any_Real
2339 or else Typ = Any_Discrete
2340 then
2341 Ctx_Type := Expr_Type;
2343 -- Any_Fixed is legal in a real context only if a specific
2344 -- fixed point type is imposed. If Norman Cohen can be
2345 -- confused by this, it deserves a separate message.
2347 if Typ = Any_Real
2348 and then Expr_Type = Any_Fixed
2349 then
2350 Error_Msg_N ("illegal context for mixed mode operation", N);
2351 Set_Etype (N, Universal_Real);
2352 Ctx_Type := Universal_Real;
2353 end if;
2354 end if;
2356 -- A user-defined operator is tranformed into a function call at
2357 -- this point, so that further processing knows that operators are
2358 -- really operators (i.e. are predefined operators). User-defined
2359 -- operators that are intrinsic are just renamings of the predefined
2360 -- ones, and need not be turned into calls either, but if they rename
2361 -- a different operator, we must transform the node accordingly.
2362 -- Instantiations of Unchecked_Conversion are intrinsic but are
2363 -- treated as functions, even if given an operator designator.
2365 if Nkind (N) in N_Op
2366 and then Present (Entity (N))
2367 and then Ekind (Entity (N)) /= E_Operator
2368 then
2370 if not Is_Predefined_Op (Entity (N)) then
2371 Rewrite_Operator_As_Call (N, Entity (N));
2373 elsif Present (Alias (Entity (N)))
2374 and then
2375 Nkind (Parent (Parent (Entity (N))))
2376 = N_Subprogram_Renaming_Declaration
2377 then
2378 Rewrite_Renamed_Operator (N, Alias (Entity (N)), Typ);
2380 -- If the node is rewritten, it will be fully resolved in
2381 -- Rewrite_Renamed_Operator.
2383 if Analyzed (N) then
2384 return;
2385 end if;
2386 end if;
2387 end if;
2389 case N_Subexpr'(Nkind (N)) is
2391 when N_Aggregate => Resolve_Aggregate (N, Ctx_Type);
2393 when N_Allocator => Resolve_Allocator (N, Ctx_Type);
2395 when N_And_Then | N_Or_Else
2396 => Resolve_Short_Circuit (N, Ctx_Type);
2398 when N_Attribute_Reference
2399 => Resolve_Attribute (N, Ctx_Type);
2401 when N_Character_Literal
2402 => Resolve_Character_Literal (N, Ctx_Type);
2404 when N_Conditional_Expression
2405 => Resolve_Conditional_Expression (N, Ctx_Type);
2407 when N_Expanded_Name
2408 => Resolve_Entity_Name (N, Ctx_Type);
2410 when N_Extension_Aggregate
2411 => Resolve_Extension_Aggregate (N, Ctx_Type);
2413 when N_Explicit_Dereference
2414 => Resolve_Explicit_Dereference (N, Ctx_Type);
2416 when N_Function_Call
2417 => Resolve_Call (N, Ctx_Type);
2419 when N_Identifier
2420 => Resolve_Entity_Name (N, Ctx_Type);
2422 when N_Indexed_Component
2423 => Resolve_Indexed_Component (N, Ctx_Type);
2425 when N_Integer_Literal
2426 => Resolve_Integer_Literal (N, Ctx_Type);
2428 when N_Membership_Test
2429 => Resolve_Membership_Op (N, Ctx_Type);
2431 when N_Null => Resolve_Null (N, Ctx_Type);
2433 when N_Op_And | N_Op_Or | N_Op_Xor
2434 => Resolve_Logical_Op (N, Ctx_Type);
2436 when N_Op_Eq | N_Op_Ne
2437 => Resolve_Equality_Op (N, Ctx_Type);
2439 when N_Op_Lt | N_Op_Le | N_Op_Gt | N_Op_Ge
2440 => Resolve_Comparison_Op (N, Ctx_Type);
2442 when N_Op_Not => Resolve_Op_Not (N, Ctx_Type);
2444 when N_Op_Add | N_Op_Subtract | N_Op_Multiply |
2445 N_Op_Divide | N_Op_Mod | N_Op_Rem
2447 => Resolve_Arithmetic_Op (N, Ctx_Type);
2449 when N_Op_Concat => Resolve_Op_Concat (N, Ctx_Type);
2451 when N_Op_Expon => Resolve_Op_Expon (N, Ctx_Type);
2453 when N_Op_Plus | N_Op_Minus | N_Op_Abs
2454 => Resolve_Unary_Op (N, Ctx_Type);
2456 when N_Op_Shift => Resolve_Shift (N, Ctx_Type);
2458 when N_Procedure_Call_Statement
2459 => Resolve_Call (N, Ctx_Type);
2461 when N_Operator_Symbol
2462 => Resolve_Operator_Symbol (N, Ctx_Type);
2464 when N_Qualified_Expression
2465 => Resolve_Qualified_Expression (N, Ctx_Type);
2467 when N_Raise_xxx_Error
2468 => Set_Etype (N, Ctx_Type);
2470 when N_Range => Resolve_Range (N, Ctx_Type);
2472 when N_Real_Literal
2473 => Resolve_Real_Literal (N, Ctx_Type);
2475 when N_Reference => Resolve_Reference (N, Ctx_Type);
2477 when N_Selected_Component
2478 => Resolve_Selected_Component (N, Ctx_Type);
2480 when N_Slice => Resolve_Slice (N, Ctx_Type);
2482 when N_String_Literal
2483 => Resolve_String_Literal (N, Ctx_Type);
2485 when N_Subprogram_Info
2486 => Resolve_Subprogram_Info (N, Ctx_Type);
2488 when N_Type_Conversion
2489 => Resolve_Type_Conversion (N, Ctx_Type);
2491 when N_Unchecked_Expression =>
2492 Resolve_Unchecked_Expression (N, Ctx_Type);
2494 when N_Unchecked_Type_Conversion =>
2495 Resolve_Unchecked_Type_Conversion (N, Ctx_Type);
2497 end case;
2499 -- If the subexpression was replaced by a non-subexpression, then
2500 -- all we do is to expand it. The only legitimate case we know of
2501 -- is converting procedure call statement to entry call statements,
2502 -- but there may be others, so we are making this test general.
2504 if Nkind (N) not in N_Subexpr then
2505 Debug_A_Exit ("resolving ", N, " (done)");
2506 Expand (N);
2507 return;
2508 end if;
2510 -- The expression is definitely NOT overloaded at this point, so
2511 -- we reset the Is_Overloaded flag to avoid any confusion when
2512 -- reanalyzing the node.
2514 Set_Is_Overloaded (N, False);
2516 -- Freeze expression type, entity if it is a name, and designated
2517 -- type if it is an allocator (RM 13.14(10,11,13)).
2519 -- Now that the resolution of the type of the node is complete,
2520 -- and we did not detect an error, we can expand this node. We
2521 -- skip the expand call if we are in a default expression, see
2522 -- section "Handling of Default Expressions" in Sem spec.
2524 Debug_A_Exit ("resolving ", N, " (done)");
2526 -- We unconditionally freeze the expression, even if we are in
2527 -- default expression mode (the Freeze_Expression routine tests
2528 -- this flag and only freezes static types if it is set).
2530 Freeze_Expression (N);
2532 -- Now we can do the expansion
2534 Expand (N);
2535 end if;
2536 end Resolve;
2538 -------------
2539 -- Resolve --
2540 -------------
2542 -- Version with check(s) suppressed
2544 procedure Resolve (N : Node_Id; Typ : Entity_Id; Suppress : Check_Id) is
2545 begin
2546 if Suppress = All_Checks then
2547 declare
2548 Svg : constant Suppress_Array := Scope_Suppress;
2549 begin
2550 Scope_Suppress := (others => True);
2551 Resolve (N, Typ);
2552 Scope_Suppress := Svg;
2553 end;
2555 else
2556 declare
2557 Svg : constant Boolean := Scope_Suppress (Suppress);
2558 begin
2559 Scope_Suppress (Suppress) := True;
2560 Resolve (N, Typ);
2561 Scope_Suppress (Suppress) := Svg;
2562 end;
2563 end if;
2564 end Resolve;
2566 -------------
2567 -- Resolve --
2568 -------------
2570 -- Version with implicit type
2572 procedure Resolve (N : Node_Id) is
2573 begin
2574 Resolve (N, Etype (N));
2575 end Resolve;
2577 ---------------------
2578 -- Resolve_Actuals --
2579 ---------------------
2581 procedure Resolve_Actuals (N : Node_Id; Nam : Entity_Id) is
2582 Loc : constant Source_Ptr := Sloc (N);
2583 A : Node_Id;
2584 F : Entity_Id;
2585 A_Typ : Entity_Id;
2586 F_Typ : Entity_Id;
2587 Prev : Node_Id := Empty;
2588 Orig_A : Node_Id;
2590 procedure Check_Prefixed_Call;
2591 -- If the original node is an overloaded call in prefix notation,
2592 -- insert an 'Access or a dereference as needed over the first actual.
2593 -- Try_Object_Operation has already verified that there is a valid
2594 -- interpretation, but the form of the actual can only be determined
2595 -- once the primitive operation is identified.
2597 procedure Insert_Default;
2598 -- If the actual is missing in a call, insert in the actuals list
2599 -- an instance of the default expression. The insertion is always
2600 -- a named association.
2602 function Same_Ancestor (T1, T2 : Entity_Id) return Boolean;
2603 -- Check whether T1 and T2, or their full views, are derived from a
2604 -- common type. Used to enforce the restrictions on array conversions
2605 -- of AI95-00246.
2607 -------------------------
2608 -- Check_Prefixed_Call --
2609 -------------------------
2611 procedure Check_Prefixed_Call is
2612 Act : constant Node_Id := First_Actual (N);
2613 A_Type : constant Entity_Id := Etype (Act);
2614 F_Type : constant Entity_Id := Etype (First_Formal (Nam));
2615 Orig : constant Node_Id := Original_Node (N);
2616 New_A : Node_Id;
2618 begin
2619 -- Check whether the call is a prefixed call, with or without
2620 -- additional actuals.
2622 if Nkind (Orig) = N_Selected_Component
2623 or else
2624 (Nkind (Orig) = N_Indexed_Component
2625 and then Nkind (Prefix (Orig)) = N_Selected_Component
2626 and then Is_Entity_Name (Prefix (Prefix (Orig)))
2627 and then Is_Entity_Name (Act)
2628 and then Chars (Act) = Chars (Prefix (Prefix (Orig))))
2629 then
2630 if Is_Access_Type (A_Type)
2631 and then not Is_Access_Type (F_Type)
2632 then
2633 -- Introduce dereference on object in prefix
2635 New_A :=
2636 Make_Explicit_Dereference (Sloc (Act),
2637 Prefix => Relocate_Node (Act));
2638 Rewrite (Act, New_A);
2639 Analyze (Act);
2641 elsif Is_Access_Type (F_Type)
2642 and then not Is_Access_Type (A_Type)
2643 then
2644 -- Introduce an implicit 'Access in prefix
2646 if not Is_Aliased_View (Act) then
2647 Error_Msg_NE
2648 ("object in prefixed call to& must be aliased"
2649 & " (RM-2005 4.3.1 (13))",
2650 Prefix (Act), Nam);
2651 end if;
2653 Rewrite (Act,
2654 Make_Attribute_Reference (Loc,
2655 Attribute_Name => Name_Access,
2656 Prefix => Relocate_Node (Act)));
2657 end if;
2659 Analyze (Act);
2660 end if;
2661 end Check_Prefixed_Call;
2663 --------------------
2664 -- Insert_Default --
2665 --------------------
2667 procedure Insert_Default is
2668 Actval : Node_Id;
2669 Assoc : Node_Id;
2671 begin
2672 -- Missing argument in call, nothing to insert
2674 if No (Default_Value (F)) then
2675 return;
2677 else
2678 -- Note that we do a full New_Copy_Tree, so that any associated
2679 -- Itypes are properly copied. This may not be needed any more,
2680 -- but it does no harm as a safety measure! Defaults of a generic
2681 -- formal may be out of bounds of the corresponding actual (see
2682 -- cc1311b) and an additional check may be required.
2684 Actval :=
2685 New_Copy_Tree
2686 (Default_Value (F),
2687 New_Scope => Current_Scope,
2688 New_Sloc => Loc);
2690 if Is_Concurrent_Type (Scope (Nam))
2691 and then Has_Discriminants (Scope (Nam))
2692 then
2693 Replace_Actual_Discriminants (N, Actval);
2694 end if;
2696 if Is_Overloadable (Nam)
2697 and then Present (Alias (Nam))
2698 then
2699 if Base_Type (Etype (F)) /= Base_Type (Etype (Actval))
2700 and then not Is_Tagged_Type (Etype (F))
2701 then
2702 -- If default is a real literal, do not introduce a
2703 -- conversion whose effect may depend on the run-time
2704 -- size of universal real.
2706 if Nkind (Actval) = N_Real_Literal then
2707 Set_Etype (Actval, Base_Type (Etype (F)));
2708 else
2709 Actval := Unchecked_Convert_To (Etype (F), Actval);
2710 end if;
2711 end if;
2713 if Is_Scalar_Type (Etype (F)) then
2714 Enable_Range_Check (Actval);
2715 end if;
2717 Set_Parent (Actval, N);
2719 -- Resolve aggregates with their base type, to avoid scope
2720 -- anomalies: the subtype was first built in the suprogram
2721 -- declaration, and the current call may be nested.
2723 if Nkind (Actval) = N_Aggregate
2724 and then Has_Discriminants (Etype (Actval))
2725 then
2726 Analyze_And_Resolve (Actval, Base_Type (Etype (Actval)));
2727 else
2728 Analyze_And_Resolve (Actval, Etype (Actval));
2729 end if;
2731 else
2732 Set_Parent (Actval, N);
2734 -- See note above concerning aggregates
2736 if Nkind (Actval) = N_Aggregate
2737 and then Has_Discriminants (Etype (Actval))
2738 then
2739 Analyze_And_Resolve (Actval, Base_Type (Etype (Actval)));
2741 -- Resolve entities with their own type, which may differ
2742 -- from the type of a reference in a generic context (the
2743 -- view swapping mechanism did not anticipate the re-analysis
2744 -- of default values in calls).
2746 elsif Is_Entity_Name (Actval) then
2747 Analyze_And_Resolve (Actval, Etype (Entity (Actval)));
2749 else
2750 Analyze_And_Resolve (Actval, Etype (Actval));
2751 end if;
2752 end if;
2754 -- If default is a tag indeterminate function call, propagate
2755 -- tag to obtain proper dispatching.
2757 if Is_Controlling_Formal (F)
2758 and then Nkind (Default_Value (F)) = N_Function_Call
2759 then
2760 Set_Is_Controlling_Actual (Actval);
2761 end if;
2763 end if;
2765 -- If the default expression raises constraint error, then just
2766 -- silently replace it with an N_Raise_Constraint_Error node,
2767 -- since we already gave the warning on the subprogram spec.
2769 if Raises_Constraint_Error (Actval) then
2770 Rewrite (Actval,
2771 Make_Raise_Constraint_Error (Loc,
2772 Reason => CE_Range_Check_Failed));
2773 Set_Raises_Constraint_Error (Actval);
2774 Set_Etype (Actval, Etype (F));
2775 end if;
2777 Assoc :=
2778 Make_Parameter_Association (Loc,
2779 Explicit_Actual_Parameter => Actval,
2780 Selector_Name => Make_Identifier (Loc, Chars (F)));
2782 -- Case of insertion is first named actual
2784 if No (Prev) or else
2785 Nkind (Parent (Prev)) /= N_Parameter_Association
2786 then
2787 Set_Next_Named_Actual (Assoc, First_Named_Actual (N));
2788 Set_First_Named_Actual (N, Actval);
2790 if No (Prev) then
2791 if No (Parameter_Associations (N)) then
2792 Set_Parameter_Associations (N, New_List (Assoc));
2793 else
2794 Append (Assoc, Parameter_Associations (N));
2795 end if;
2797 else
2798 Insert_After (Prev, Assoc);
2799 end if;
2801 -- Case of insertion is not first named actual
2803 else
2804 Set_Next_Named_Actual
2805 (Assoc, Next_Named_Actual (Parent (Prev)));
2806 Set_Next_Named_Actual (Parent (Prev), Actval);
2807 Append (Assoc, Parameter_Associations (N));
2808 end if;
2810 Mark_Rewrite_Insertion (Assoc);
2811 Mark_Rewrite_Insertion (Actval);
2813 Prev := Actval;
2814 end Insert_Default;
2816 -------------------
2817 -- Same_Ancestor --
2818 -------------------
2820 function Same_Ancestor (T1, T2 : Entity_Id) return Boolean is
2821 FT1 : Entity_Id := T1;
2822 FT2 : Entity_Id := T2;
2824 begin
2825 if Is_Private_Type (T1)
2826 and then Present (Full_View (T1))
2827 then
2828 FT1 := Full_View (T1);
2829 end if;
2831 if Is_Private_Type (T2)
2832 and then Present (Full_View (T2))
2833 then
2834 FT2 := Full_View (T2);
2835 end if;
2837 return Root_Type (Base_Type (FT1)) = Root_Type (Base_Type (FT2));
2838 end Same_Ancestor;
2840 -- Start of processing for Resolve_Actuals
2842 begin
2843 if Present (First_Actual (N)) then
2844 Check_Prefixed_Call;
2845 end if;
2847 A := First_Actual (N);
2848 F := First_Formal (Nam);
2849 while Present (F) loop
2850 if No (A) and then Needs_No_Actuals (Nam) then
2851 null;
2853 -- If we have an error in any actual or formal, indicated by
2854 -- a type of Any_Type, then abandon resolution attempt, and
2855 -- set result type to Any_Type.
2857 elsif (Present (A) and then Etype (A) = Any_Type)
2858 or else Etype (F) = Any_Type
2859 then
2860 Set_Etype (N, Any_Type);
2861 return;
2862 end if;
2864 -- Case where actual is present
2866 -- If the actual is an entity, generate a reference to it now. We
2867 -- do this before the actual is resolved, because a formal of some
2868 -- protected subprogram, or a task discriminant, will be rewritten
2869 -- during expansion, and the reference to the source entity may
2870 -- be lost.
2872 if Present (A)
2873 and then Is_Entity_Name (A)
2874 and then Comes_From_Source (N)
2875 then
2876 Orig_A := Entity (A);
2878 if Present (Orig_A) then
2879 if Is_Formal (Orig_A)
2880 and then Ekind (F) /= E_In_Parameter
2881 then
2882 Generate_Reference (Orig_A, A, 'm');
2884 elsif not Is_Overloaded (A) then
2885 Generate_Reference (Orig_A, A);
2886 end if;
2887 end if;
2888 end if;
2890 if Present (A)
2891 and then (Nkind (Parent (A)) /= N_Parameter_Association
2892 or else
2893 Chars (Selector_Name (Parent (A))) = Chars (F))
2894 then
2895 -- If the formal is Out or In_Out, do not resolve and expand the
2896 -- conversion, because it is subsequently expanded into explicit
2897 -- temporaries and assignments. However, the object of the
2898 -- conversion can be resolved. An exception is the case of tagged
2899 -- type conversion with a class-wide actual. In that case we want
2900 -- the tag check to occur and no temporary will be needed (no
2901 -- representation change can occur) and the parameter is passed by
2902 -- reference, so we go ahead and resolve the type conversion.
2903 -- Another exception is the case of reference to component or
2904 -- subcomponent of a bit-packed array, in which case we want to
2905 -- defer expansion to the point the in and out assignments are
2906 -- performed.
2908 if Ekind (F) /= E_In_Parameter
2909 and then Nkind (A) = N_Type_Conversion
2910 and then not Is_Class_Wide_Type (Etype (Expression (A)))
2911 then
2912 if Ekind (F) = E_In_Out_Parameter
2913 and then Is_Array_Type (Etype (F))
2914 then
2915 if Has_Aliased_Components (Etype (Expression (A)))
2916 /= Has_Aliased_Components (Etype (F))
2917 then
2918 if Ada_Version < Ada_05 then
2919 Error_Msg_N
2920 ("both component types in a view conversion must be"
2921 & " aliased, or neither", A);
2923 -- Ada 2005: rule is relaxed (see AI-363)
2925 elsif Has_Aliased_Components (Etype (F))
2926 and then
2927 not Has_Aliased_Components (Etype (Expression (A)))
2928 then
2929 Error_Msg_N
2930 ("view conversion operand must have aliased " &
2931 "components", N);
2932 Error_Msg_N
2933 ("\since target type has aliased components", N);
2934 end if;
2936 elsif not Same_Ancestor (Etype (F), Etype (Expression (A)))
2937 and then
2938 (Is_By_Reference_Type (Etype (F))
2939 or else Is_By_Reference_Type (Etype (Expression (A))))
2940 then
2941 Error_Msg_N
2942 ("view conversion between unrelated by reference " &
2943 "array types not allowed (\'A'I-00246)", A);
2944 end if;
2945 end if;
2947 if (Conversion_OK (A)
2948 or else Valid_Conversion (A, Etype (A), Expression (A)))
2949 and then not Is_Ref_To_Bit_Packed_Array (Expression (A))
2950 then
2951 Resolve (Expression (A));
2952 end if;
2954 -- If the actual is a function call that returns a limited
2955 -- unconstrained object that needs finalization, create a
2956 -- transient scope for it, so that it can receive the proper
2957 -- finalization list.
2959 elsif Nkind (A) = N_Function_Call
2960 and then Is_Limited_Record (Etype (F))
2961 and then not Is_Constrained (Etype (F))
2962 and then Expander_Active
2963 and then
2964 (Is_Controlled (Etype (F)) or else Has_Task (Etype (F)))
2965 then
2966 Establish_Transient_Scope (A, False);
2968 else
2969 if Nkind (A) = N_Type_Conversion
2970 and then Is_Array_Type (Etype (F))
2971 and then not Same_Ancestor (Etype (F), Etype (Expression (A)))
2972 and then
2973 (Is_Limited_Type (Etype (F))
2974 or else Is_Limited_Type (Etype (Expression (A))))
2975 then
2976 Error_Msg_N
2977 ("conversion between unrelated limited array types " &
2978 "not allowed (\A\I-00246)", A);
2980 if Is_Limited_Type (Etype (F)) then
2981 Explain_Limited_Type (Etype (F), A);
2982 end if;
2984 if Is_Limited_Type (Etype (Expression (A))) then
2985 Explain_Limited_Type (Etype (Expression (A)), A);
2986 end if;
2987 end if;
2989 -- (Ada 2005: AI-251): If the actual is an allocator whose
2990 -- directly designated type is a class-wide interface, we build
2991 -- an anonymous access type to use it as the type of the
2992 -- allocator. Later, when the subprogram call is expanded, if
2993 -- the interface has a secondary dispatch table the expander
2994 -- will add a type conversion to force the correct displacement
2995 -- of the pointer.
2997 if Nkind (A) = N_Allocator then
2998 declare
2999 DDT : constant Entity_Id :=
3000 Directly_Designated_Type (Base_Type (Etype (F)));
3001 New_Itype : Entity_Id;
3002 begin
3003 if Is_Class_Wide_Type (DDT)
3004 and then Is_Interface (DDT)
3005 then
3006 New_Itype := Create_Itype (E_Anonymous_Access_Type, A);
3007 Set_Etype (New_Itype, Etype (A));
3008 Init_Size_Align (New_Itype);
3009 Set_Directly_Designated_Type (New_Itype,
3010 Directly_Designated_Type (Etype (A)));
3011 Set_Etype (A, New_Itype);
3012 end if;
3014 -- Ada 2005, AI-162:If the actual is an allocator, the
3015 -- innermost enclosing statement is the master of the
3016 -- created object. This needs to be done with expansion
3017 -- enabled only, otherwise the transient scope will not
3018 -- be removed in the expansion of the wrapped construct.
3020 if (Is_Controlled (DDT)
3021 or else Has_Task (DDT))
3022 and then Expander_Active
3023 then
3024 Establish_Transient_Scope (A, False);
3025 end if;
3026 end;
3027 end if;
3029 -- (Ada 2005): The call may be to a primitive operation of
3030 -- a tagged synchronized type, declared outside of the type.
3031 -- In this case the controlling actual must be converted to
3032 -- its corresponding record type, which is the formal type.
3034 if Is_Concurrent_Type (Etype (A))
3035 and then Etype (F) = Corresponding_Record_Type (Etype (A))
3036 then
3037 Rewrite (A,
3038 Unchecked_Convert_To
3039 (Corresponding_Record_Type (Etype (A)), A));
3040 end if;
3042 Resolve (A, Etype (F));
3043 end if;
3045 A_Typ := Etype (A);
3046 F_Typ := Etype (F);
3048 -- Perform error checks for IN and IN OUT parameters
3050 if Ekind (F) /= E_Out_Parameter then
3052 -- Check unset reference. For scalar parameters, it is clearly
3053 -- wrong to pass an uninitialized value as either an IN or
3054 -- IN-OUT parameter. For composites, it is also clearly an
3055 -- error to pass a completely uninitialized value as an IN
3056 -- parameter, but the case of IN OUT is trickier. We prefer
3057 -- not to give a warning here. For example, suppose there is
3058 -- a routine that sets some component of a record to False.
3059 -- It is perfectly reasonable to make this IN-OUT and allow
3060 -- either initialized or uninitialized records to be passed
3061 -- in this case.
3063 -- For partially initialized composite values, we also avoid
3064 -- warnings, since it is quite likely that we are passing a
3065 -- partially initialized value and only the initialized fields
3066 -- will in fact be read in the subprogram.
3068 if Is_Scalar_Type (A_Typ)
3069 or else (Ekind (F) = E_In_Parameter
3070 and then not Is_Partially_Initialized_Type (A_Typ))
3071 then
3072 Check_Unset_Reference (A);
3073 end if;
3075 -- In Ada 83 we cannot pass an OUT parameter as an IN or IN OUT
3076 -- actual to a nested call, since this is case of reading an
3077 -- out parameter, which is not allowed.
3079 if Ada_Version = Ada_83
3080 and then Is_Entity_Name (A)
3081 and then Ekind (Entity (A)) = E_Out_Parameter
3082 then
3083 Error_Msg_N ("(Ada 83) illegal reading of out parameter", A);
3084 end if;
3085 end if;
3087 -- Case of OUT or IN OUT parameter
3089 if Ekind (F) /= E_In_Parameter then
3091 -- For an Out parameter, check for useless assignment. Note
3092 -- that we can't set Last_Assignment this early, because we
3093 -- may kill current values in Resolve_Call, and that call
3094 -- would clobber the Last_Assignment field.
3096 -- Note: call Warn_On_Useless_Assignment before doing the
3097 -- check below for Is_OK_Variable_For_Out_Formal so that the
3098 -- setting of Referenced_As_LHS/Referenced_As_Out_Formal
3099 -- properly reflects the last assignment, not this one!
3101 if Ekind (F) = E_Out_Parameter then
3102 if Warn_On_Modified_As_Out_Parameter (F)
3103 and then Is_Entity_Name (A)
3104 and then Present (Entity (A))
3105 and then Comes_From_Source (N)
3106 then
3107 Warn_On_Useless_Assignment (Entity (A), A);
3108 end if;
3109 end if;
3111 -- Validate the form of the actual. Note that the call to
3112 -- Is_OK_Variable_For_Out_Formal generates the required
3113 -- reference in this case.
3115 if not Is_OK_Variable_For_Out_Formal (A) then
3116 Error_Msg_NE ("actual for& must be a variable", A, F);
3117 end if;
3119 -- What's the following about???
3121 if Is_Entity_Name (A) then
3122 Kill_Checks (Entity (A));
3123 else
3124 Kill_All_Checks;
3125 end if;
3126 end if;
3128 if Etype (A) = Any_Type then
3129 Set_Etype (N, Any_Type);
3130 return;
3131 end if;
3133 -- Apply appropriate range checks for in, out, and in-out
3134 -- parameters. Out and in-out parameters also need a separate
3135 -- check, if there is a type conversion, to make sure the return
3136 -- value meets the constraints of the variable before the
3137 -- conversion.
3139 -- Gigi looks at the check flag and uses the appropriate types.
3140 -- For now since one flag is used there is an optimization which
3141 -- might not be done in the In Out case since Gigi does not do
3142 -- any analysis. More thought required about this ???
3144 if Ekind (F) = E_In_Parameter
3145 or else Ekind (F) = E_In_Out_Parameter
3146 then
3147 if Is_Scalar_Type (Etype (A)) then
3148 Apply_Scalar_Range_Check (A, F_Typ);
3150 elsif Is_Array_Type (Etype (A)) then
3151 Apply_Length_Check (A, F_Typ);
3153 elsif Is_Record_Type (F_Typ)
3154 and then Has_Discriminants (F_Typ)
3155 and then Is_Constrained (F_Typ)
3156 and then (not Is_Derived_Type (F_Typ)
3157 or else Comes_From_Source (Nam))
3158 then
3159 Apply_Discriminant_Check (A, F_Typ);
3161 elsif Is_Access_Type (F_Typ)
3162 and then Is_Array_Type (Designated_Type (F_Typ))
3163 and then Is_Constrained (Designated_Type (F_Typ))
3164 then
3165 Apply_Length_Check (A, F_Typ);
3167 elsif Is_Access_Type (F_Typ)
3168 and then Has_Discriminants (Designated_Type (F_Typ))
3169 and then Is_Constrained (Designated_Type (F_Typ))
3170 then
3171 Apply_Discriminant_Check (A, F_Typ);
3173 else
3174 Apply_Range_Check (A, F_Typ);
3175 end if;
3177 -- Ada 2005 (AI-231)
3179 if Ada_Version >= Ada_05
3180 and then Is_Access_Type (F_Typ)
3181 and then Can_Never_Be_Null (F_Typ)
3182 and then Known_Null (A)
3183 then
3184 Apply_Compile_Time_Constraint_Error
3185 (N => A,
3186 Msg => "(Ada 2005) null not allowed in "
3187 & "null-excluding formal?",
3188 Reason => CE_Null_Not_Allowed);
3189 end if;
3190 end if;
3192 if Ekind (F) = E_Out_Parameter
3193 or else Ekind (F) = E_In_Out_Parameter
3194 then
3195 if Nkind (A) = N_Type_Conversion then
3196 if Is_Scalar_Type (A_Typ) then
3197 Apply_Scalar_Range_Check
3198 (Expression (A), Etype (Expression (A)), A_Typ);
3199 else
3200 Apply_Range_Check
3201 (Expression (A), Etype (Expression (A)), A_Typ);
3202 end if;
3204 else
3205 if Is_Scalar_Type (F_Typ) then
3206 Apply_Scalar_Range_Check (A, A_Typ, F_Typ);
3208 elsif Is_Array_Type (F_Typ)
3209 and then Ekind (F) = E_Out_Parameter
3210 then
3211 Apply_Length_Check (A, F_Typ);
3213 else
3214 Apply_Range_Check (A, A_Typ, F_Typ);
3215 end if;
3216 end if;
3217 end if;
3219 -- An actual associated with an access parameter is implicitly
3220 -- converted to the anonymous access type of the formal and
3221 -- must satisfy the legality checks for access conversions.
3223 if Ekind (F_Typ) = E_Anonymous_Access_Type then
3224 if not Valid_Conversion (A, F_Typ, A) then
3225 Error_Msg_N
3226 ("invalid implicit conversion for access parameter", A);
3227 end if;
3228 end if;
3230 -- Check bad case of atomic/volatile argument (RM C.6(12))
3232 if Is_By_Reference_Type (Etype (F))
3233 and then Comes_From_Source (N)
3234 then
3235 if Is_Atomic_Object (A)
3236 and then not Is_Atomic (Etype (F))
3237 then
3238 Error_Msg_N
3239 ("cannot pass atomic argument to non-atomic formal",
3242 elsif Is_Volatile_Object (A)
3243 and then not Is_Volatile (Etype (F))
3244 then
3245 Error_Msg_N
3246 ("cannot pass volatile argument to non-volatile formal",
3248 end if;
3249 end if;
3251 -- Check that subprograms don't have improper controlling
3252 -- arguments (RM 3.9.2 (9))
3254 -- A primitive operation may have an access parameter of an
3255 -- incomplete tagged type, but a dispatching call is illegal
3256 -- if the type is still incomplete.
3258 if Is_Controlling_Formal (F) then
3259 Set_Is_Controlling_Actual (A);
3261 if Ekind (Etype (F)) = E_Anonymous_Access_Type then
3262 declare
3263 Desig : constant Entity_Id := Designated_Type (Etype (F));
3264 begin
3265 if Ekind (Desig) = E_Incomplete_Type
3266 and then No (Full_View (Desig))
3267 and then No (Non_Limited_View (Desig))
3268 then
3269 Error_Msg_NE
3270 ("premature use of incomplete type& " &
3271 "in dispatching call", A, Desig);
3272 end if;
3273 end;
3274 end if;
3276 elsif Nkind (A) = N_Explicit_Dereference then
3277 Validate_Remote_Access_To_Class_Wide_Type (A);
3278 end if;
3280 if (Is_Class_Wide_Type (A_Typ) or else Is_Dynamically_Tagged (A))
3281 and then not Is_Class_Wide_Type (F_Typ)
3282 and then not Is_Controlling_Formal (F)
3283 then
3284 Error_Msg_N ("class-wide argument not allowed here!", A);
3286 if Is_Subprogram (Nam)
3287 and then Comes_From_Source (Nam)
3288 then
3289 Error_Msg_Node_2 := F_Typ;
3290 Error_Msg_NE
3291 ("& is not a dispatching operation of &!", A, Nam);
3292 end if;
3294 elsif Is_Access_Type (A_Typ)
3295 and then Is_Access_Type (F_Typ)
3296 and then Ekind (F_Typ) /= E_Access_Subprogram_Type
3297 and then Ekind (F_Typ) /= E_Anonymous_Access_Subprogram_Type
3298 and then (Is_Class_Wide_Type (Designated_Type (A_Typ))
3299 or else (Nkind (A) = N_Attribute_Reference
3300 and then
3301 Is_Class_Wide_Type (Etype (Prefix (A)))))
3302 and then not Is_Class_Wide_Type (Designated_Type (F_Typ))
3303 and then not Is_Controlling_Formal (F)
3304 then
3305 Error_Msg_N
3306 ("access to class-wide argument not allowed here!", A);
3308 if Is_Subprogram (Nam)
3309 and then Comes_From_Source (Nam)
3310 then
3311 Error_Msg_Node_2 := Designated_Type (F_Typ);
3312 Error_Msg_NE
3313 ("& is not a dispatching operation of &!", A, Nam);
3314 end if;
3315 end if;
3317 Eval_Actual (A);
3319 -- If it is a named association, treat the selector_name as
3320 -- a proper identifier, and mark the corresponding entity.
3322 if Nkind (Parent (A)) = N_Parameter_Association then
3323 Set_Entity (Selector_Name (Parent (A)), F);
3324 Generate_Reference (F, Selector_Name (Parent (A)));
3325 Set_Etype (Selector_Name (Parent (A)), F_Typ);
3326 Generate_Reference (F_Typ, N, ' ');
3327 end if;
3329 Prev := A;
3331 if Ekind (F) /= E_Out_Parameter then
3332 Check_Unset_Reference (A);
3333 end if;
3335 Next_Actual (A);
3337 -- Case where actual is not present
3339 else
3340 Insert_Default;
3341 end if;
3343 Next_Formal (F);
3344 end loop;
3345 end Resolve_Actuals;
3347 -----------------------
3348 -- Resolve_Allocator --
3349 -----------------------
3351 procedure Resolve_Allocator (N : Node_Id; Typ : Entity_Id) is
3352 E : constant Node_Id := Expression (N);
3353 Subtyp : Entity_Id;
3354 Discrim : Entity_Id;
3355 Constr : Node_Id;
3356 Aggr : Node_Id;
3357 Assoc : Node_Id := Empty;
3358 Disc_Exp : Node_Id;
3360 procedure Check_Allocator_Discrim_Accessibility
3361 (Disc_Exp : Node_Id;
3362 Alloc_Typ : Entity_Id);
3363 -- Check that accessibility level associated with an access discriminant
3364 -- initialized in an allocator by the expression Disc_Exp is not deeper
3365 -- than the level of the allocator type Alloc_Typ. An error message is
3366 -- issued if this condition is violated. Specialized checks are done for
3367 -- the cases of a constraint expression which is an access attribute or
3368 -- an access discriminant.
3370 function In_Dispatching_Context return Boolean;
3371 -- If the allocator is an actual in a call, it is allowed to be class-
3372 -- wide when the context is not because it is a controlling actual.
3374 procedure Propagate_Coextensions (Root : Node_Id);
3375 -- Propagate all nested coextensions which are located one nesting
3376 -- level down the tree to the node Root. Example:
3378 -- Top_Record
3379 -- Level_1_Coextension
3380 -- Level_2_Coextension
3382 -- The algorithm is paired with delay actions done by the Expander. In
3383 -- the above example, assume all coextensions are controlled types.
3384 -- The cycle of analysis, resolution and expansion will yield:
3386 -- 1) Analyze Top_Record
3387 -- 2) Analyze Level_1_Coextension
3388 -- 3) Analyze Level_2_Coextension
3389 -- 4) Resolve Level_2_Coextnesion. The allocator is marked as a
3390 -- coextension.
3391 -- 5) Expand Level_2_Coextension. A temporary variable Temp_1 is
3392 -- generated to capture the allocated object. Temp_1 is attached
3393 -- to the coextension chain of Level_2_Coextension.
3394 -- 6) Resolve Level_1_Coextension. The allocator is marked as a
3395 -- coextension. A forward tree traversal is performed which finds
3396 -- Level_2_Coextension's list and copies its contents into its
3397 -- own list.
3398 -- 7) Expand Level_1_Coextension. A temporary variable Temp_2 is
3399 -- generated to capture the allocated object. Temp_2 is attached
3400 -- to the coextension chain of Level_1_Coextension. Currently, the
3401 -- contents of the list are [Temp_2, Temp_1].
3402 -- 8) Resolve Top_Record. A forward tree traversal is performed which
3403 -- finds Level_1_Coextension's list and copies its contents into
3404 -- its own list.
3405 -- 9) Expand Top_Record. Generate finalization calls for Temp_1 and
3406 -- Temp_2 and attach them to Top_Record's finalization list.
3408 -------------------------------------------
3409 -- Check_Allocator_Discrim_Accessibility --
3410 -------------------------------------------
3412 procedure Check_Allocator_Discrim_Accessibility
3413 (Disc_Exp : Node_Id;
3414 Alloc_Typ : Entity_Id)
3416 begin
3417 if Type_Access_Level (Etype (Disc_Exp)) >
3418 Type_Access_Level (Alloc_Typ)
3419 then
3420 Error_Msg_N
3421 ("operand type has deeper level than allocator type", Disc_Exp);
3423 -- When the expression is an Access attribute the level of the prefix
3424 -- object must not be deeper than that of the allocator's type.
3426 elsif Nkind (Disc_Exp) = N_Attribute_Reference
3427 and then Get_Attribute_Id (Attribute_Name (Disc_Exp))
3428 = Attribute_Access
3429 and then Object_Access_Level (Prefix (Disc_Exp))
3430 > Type_Access_Level (Alloc_Typ)
3431 then
3432 Error_Msg_N
3433 ("prefix of attribute has deeper level than allocator type",
3434 Disc_Exp);
3436 -- When the expression is an access discriminant the check is against
3437 -- the level of the prefix object.
3439 elsif Ekind (Etype (Disc_Exp)) = E_Anonymous_Access_Type
3440 and then Nkind (Disc_Exp) = N_Selected_Component
3441 and then Object_Access_Level (Prefix (Disc_Exp))
3442 > Type_Access_Level (Alloc_Typ)
3443 then
3444 Error_Msg_N
3445 ("access discriminant has deeper level than allocator type",
3446 Disc_Exp);
3448 -- All other cases are legal
3450 else
3451 null;
3452 end if;
3453 end Check_Allocator_Discrim_Accessibility;
3455 ----------------------------
3456 -- In_Dispatching_Context --
3457 ----------------------------
3459 function In_Dispatching_Context return Boolean is
3460 Par : constant Node_Id := Parent (N);
3461 begin
3462 return (Nkind (Par) = N_Function_Call
3463 or else Nkind (Par) = N_Procedure_Call_Statement)
3464 and then Is_Entity_Name (Name (Par))
3465 and then Is_Dispatching_Operation (Entity (Name (Par)));
3466 end In_Dispatching_Context;
3468 ----------------------------
3469 -- Propagate_Coextensions --
3470 ----------------------------
3472 procedure Propagate_Coextensions (Root : Node_Id) is
3474 procedure Copy_List (From : Elist_Id; To : Elist_Id);
3475 -- Copy the contents of list From into list To, preserving the
3476 -- order of elements.
3478 function Process_Allocator (Nod : Node_Id) return Traverse_Result;
3479 -- Recognize an allocator or a rewritten allocator node and add it
3480 -- allong with its nested coextensions to the list of Root.
3482 ---------------
3483 -- Copy_List --
3484 ---------------
3486 procedure Copy_List (From : Elist_Id; To : Elist_Id) is
3487 From_Elmt : Elmt_Id;
3488 begin
3489 From_Elmt := First_Elmt (From);
3490 while Present (From_Elmt) loop
3491 Append_Elmt (Node (From_Elmt), To);
3492 Next_Elmt (From_Elmt);
3493 end loop;
3494 end Copy_List;
3496 -----------------------
3497 -- Process_Allocator --
3498 -----------------------
3500 function Process_Allocator (Nod : Node_Id) return Traverse_Result is
3501 Orig_Nod : Node_Id := Nod;
3503 begin
3504 -- This is a possible rewritten subtype indication allocator. Any
3505 -- nested coextensions will appear as discriminant constraints.
3507 if Nkind (Nod) = N_Identifier
3508 and then Present (Original_Node (Nod))
3509 and then Nkind (Original_Node (Nod)) = N_Subtype_Indication
3510 then
3511 declare
3512 Discr : Node_Id;
3513 Discr_Elmt : Elmt_Id;
3515 begin
3516 if Is_Record_Type (Entity (Nod)) then
3517 Discr_Elmt :=
3518 First_Elmt (Discriminant_Constraint (Entity (Nod)));
3519 while Present (Discr_Elmt) loop
3520 Discr := Node (Discr_Elmt);
3522 if Nkind (Discr) = N_Identifier
3523 and then Present (Original_Node (Discr))
3524 and then Nkind (Original_Node (Discr)) = N_Allocator
3525 and then Present (Coextensions (
3526 Original_Node (Discr)))
3527 then
3528 if No (Coextensions (Root)) then
3529 Set_Coextensions (Root, New_Elmt_List);
3530 end if;
3532 Copy_List
3533 (From => Coextensions (Original_Node (Discr)),
3534 To => Coextensions (Root));
3535 end if;
3537 Next_Elmt (Discr_Elmt);
3538 end loop;
3540 -- There is no need to continue the traversal of this
3541 -- subtree since all the information has already been
3542 -- propagated.
3544 return Skip;
3545 end if;
3546 end;
3548 -- Case of either a stand alone allocator or a rewritten allocator
3549 -- with an aggregate.
3551 else
3552 if Present (Original_Node (Nod)) then
3553 Orig_Nod := Original_Node (Nod);
3554 end if;
3556 if Nkind (Orig_Nod) = N_Allocator then
3558 -- Propagate the list of nested coextensions to the Root
3559 -- allocator. This is done through list copy since a single
3560 -- allocator may have multiple coextensions. Do not touch
3561 -- coextensions roots.
3563 if not Is_Coextension_Root (Orig_Nod)
3564 and then Present (Coextensions (Orig_Nod))
3565 then
3566 if No (Coextensions (Root)) then
3567 Set_Coextensions (Root, New_Elmt_List);
3568 end if;
3570 Copy_List
3571 (From => Coextensions (Orig_Nod),
3572 To => Coextensions (Root));
3573 end if;
3575 -- There is no need to continue the traversal of this
3576 -- subtree since all the information has already been
3577 -- propagated.
3579 return Skip;
3580 end if;
3581 end if;
3583 -- Keep on traversing, looking for the next allocator
3585 return OK;
3586 end Process_Allocator;
3588 procedure Process_Allocators is
3589 new Traverse_Proc (Process_Allocator);
3591 -- Start of processing for Propagate_Coextensions
3593 begin
3594 Process_Allocators (Expression (Root));
3595 end Propagate_Coextensions;
3597 -- Start of processing for Resolve_Allocator
3599 begin
3600 -- Replace general access with specific type
3602 if Ekind (Etype (N)) = E_Allocator_Type then
3603 Set_Etype (N, Base_Type (Typ));
3604 end if;
3606 if Is_Abstract_Type (Typ) then
3607 Error_Msg_N ("type of allocator cannot be abstract", N);
3608 end if;
3610 -- For qualified expression, resolve the expression using the
3611 -- given subtype (nothing to do for type mark, subtype indication)
3613 if Nkind (E) = N_Qualified_Expression then
3614 if Is_Class_Wide_Type (Etype (E))
3615 and then not Is_Class_Wide_Type (Designated_Type (Typ))
3616 and then not In_Dispatching_Context
3617 then
3618 Error_Msg_N
3619 ("class-wide allocator not allowed for this access type", N);
3620 end if;
3622 Resolve (Expression (E), Etype (E));
3623 Check_Unset_Reference (Expression (E));
3625 -- A qualified expression requires an exact match of the type,
3626 -- class-wide matching is not allowed.
3628 if (Is_Class_Wide_Type (Etype (Expression (E)))
3629 or else Is_Class_Wide_Type (Etype (E)))
3630 and then Base_Type (Etype (Expression (E))) /= Base_Type (Etype (E))
3631 then
3632 Wrong_Type (Expression (E), Etype (E));
3633 end if;
3635 -- A special accessibility check is needed for allocators that
3636 -- constrain access discriminants. The level of the type of the
3637 -- expression used to constrain an access discriminant cannot be
3638 -- deeper than the type of the allocator (in constrast to access
3639 -- parameters, where the level of the actual can be arbitrary).
3641 -- We can't use Valid_Conversion to perform this check because
3642 -- in general the type of the allocator is unrelated to the type
3643 -- of the access discriminant.
3645 if Ekind (Typ) /= E_Anonymous_Access_Type
3646 or else Is_Local_Anonymous_Access (Typ)
3647 then
3648 Subtyp := Entity (Subtype_Mark (E));
3650 Aggr := Original_Node (Expression (E));
3652 if Has_Discriminants (Subtyp)
3653 and then
3654 (Nkind (Aggr) = N_Aggregate
3655 or else
3656 Nkind (Aggr) = N_Extension_Aggregate)
3657 then
3658 Discrim := First_Discriminant (Base_Type (Subtyp));
3660 -- Get the first component expression of the aggregate
3662 if Present (Expressions (Aggr)) then
3663 Disc_Exp := First (Expressions (Aggr));
3665 elsif Present (Component_Associations (Aggr)) then
3666 Assoc := First (Component_Associations (Aggr));
3668 if Present (Assoc) then
3669 Disc_Exp := Expression (Assoc);
3670 else
3671 Disc_Exp := Empty;
3672 end if;
3674 else
3675 Disc_Exp := Empty;
3676 end if;
3678 while Present (Discrim) and then Present (Disc_Exp) loop
3679 if Ekind (Etype (Discrim)) = E_Anonymous_Access_Type then
3680 Check_Allocator_Discrim_Accessibility (Disc_Exp, Typ);
3681 end if;
3683 Next_Discriminant (Discrim);
3685 if Present (Discrim) then
3686 if Present (Assoc) then
3687 Next (Assoc);
3688 Disc_Exp := Expression (Assoc);
3690 elsif Present (Next (Disc_Exp)) then
3691 Next (Disc_Exp);
3693 else
3694 Assoc := First (Component_Associations (Aggr));
3696 if Present (Assoc) then
3697 Disc_Exp := Expression (Assoc);
3698 else
3699 Disc_Exp := Empty;
3700 end if;
3701 end if;
3702 end if;
3703 end loop;
3704 end if;
3705 end if;
3707 -- For a subtype mark or subtype indication, freeze the subtype
3709 else
3710 Freeze_Expression (E);
3712 if Is_Access_Constant (Typ) and then not No_Initialization (N) then
3713 Error_Msg_N
3714 ("initialization required for access-to-constant allocator", N);
3715 end if;
3717 -- A special accessibility check is needed for allocators that
3718 -- constrain access discriminants. The level of the type of the
3719 -- expression used to constrain an access discriminant cannot be
3720 -- deeper than the type of the allocator (in constrast to access
3721 -- parameters, where the level of the actual can be arbitrary).
3722 -- We can't use Valid_Conversion to perform this check because
3723 -- in general the type of the allocator is unrelated to the type
3724 -- of the access discriminant.
3726 if Nkind (Original_Node (E)) = N_Subtype_Indication
3727 and then (Ekind (Typ) /= E_Anonymous_Access_Type
3728 or else Is_Local_Anonymous_Access (Typ))
3729 then
3730 Subtyp := Entity (Subtype_Mark (Original_Node (E)));
3732 if Has_Discriminants (Subtyp) then
3733 Discrim := First_Discriminant (Base_Type (Subtyp));
3734 Constr := First (Constraints (Constraint (Original_Node (E))));
3735 while Present (Discrim) and then Present (Constr) loop
3736 if Ekind (Etype (Discrim)) = E_Anonymous_Access_Type then
3737 if Nkind (Constr) = N_Discriminant_Association then
3738 Disc_Exp := Original_Node (Expression (Constr));
3739 else
3740 Disc_Exp := Original_Node (Constr);
3741 end if;
3743 Check_Allocator_Discrim_Accessibility (Disc_Exp, Typ);
3744 end if;
3746 Next_Discriminant (Discrim);
3747 Next (Constr);
3748 end loop;
3749 end if;
3750 end if;
3751 end if;
3753 -- Ada 2005 (AI-344): A class-wide allocator requires an accessibility
3754 -- check that the level of the type of the created object is not deeper
3755 -- than the level of the allocator's access type, since extensions can
3756 -- now occur at deeper levels than their ancestor types. This is a
3757 -- static accessibility level check; a run-time check is also needed in
3758 -- the case of an initialized allocator with a class-wide argument (see
3759 -- Expand_Allocator_Expression).
3761 if Ada_Version >= Ada_05
3762 and then Is_Class_Wide_Type (Designated_Type (Typ))
3763 then
3764 declare
3765 Exp_Typ : Entity_Id;
3767 begin
3768 if Nkind (E) = N_Qualified_Expression then
3769 Exp_Typ := Etype (E);
3770 elsif Nkind (E) = N_Subtype_Indication then
3771 Exp_Typ := Entity (Subtype_Mark (Original_Node (E)));
3772 else
3773 Exp_Typ := Entity (E);
3774 end if;
3776 if Type_Access_Level (Exp_Typ) > Type_Access_Level (Typ) then
3777 if In_Instance_Body then
3778 Error_Msg_N ("?type in allocator has deeper level than" &
3779 " designated class-wide type", E);
3780 Error_Msg_N ("\?Program_Error will be raised at run time",
3782 Rewrite (N,
3783 Make_Raise_Program_Error (Sloc (N),
3784 Reason => PE_Accessibility_Check_Failed));
3785 Set_Etype (N, Typ);
3787 -- Do not apply Ada 2005 accessibility checks on a class-wide
3788 -- allocator if the type given in the allocator is a formal
3789 -- type. A run-time check will be performed in the instance.
3791 elsif not Is_Generic_Type (Exp_Typ) then
3792 Error_Msg_N ("type in allocator has deeper level than" &
3793 " designated class-wide type", E);
3794 end if;
3795 end if;
3796 end;
3797 end if;
3799 -- Check for allocation from an empty storage pool
3801 if No_Pool_Assigned (Typ) then
3802 declare
3803 Loc : constant Source_Ptr := Sloc (N);
3804 begin
3805 Error_Msg_N ("?allocation from empty storage pool!", N);
3806 Error_Msg_N ("\?Storage_Error will be raised at run time!", N);
3807 Insert_Action (N,
3808 Make_Raise_Storage_Error (Loc,
3809 Reason => SE_Empty_Storage_Pool));
3810 end;
3812 -- If the context is an unchecked conversion, as may happen within
3813 -- an inlined subprogram, the allocator is being resolved with its
3814 -- own anonymous type. In that case, if the target type has a specific
3815 -- storage pool, it must be inherited explicitly by the allocator type.
3817 elsif Nkind (Parent (N)) = N_Unchecked_Type_Conversion
3818 and then No (Associated_Storage_Pool (Typ))
3819 then
3820 Set_Associated_Storage_Pool
3821 (Typ, Associated_Storage_Pool (Etype (Parent (N))));
3822 end if;
3824 -- An erroneous allocator may be rewritten as a raise Program_Error
3825 -- statement.
3827 if Nkind (N) = N_Allocator then
3829 -- An anonymous access discriminant is the definition of a
3830 -- coextension.
3832 if Ekind (Typ) = E_Anonymous_Access_Type
3833 and then Nkind (Associated_Node_For_Itype (Typ)) =
3834 N_Discriminant_Specification
3835 then
3836 -- Avoid marking an allocator as a dynamic coextension if it is
3837 -- within a static construct.
3839 if not Is_Static_Coextension (N) then
3840 Set_Is_Dynamic_Coextension (N);
3841 end if;
3843 -- Cleanup for potential static coextensions
3845 else
3846 Set_Is_Dynamic_Coextension (N, False);
3847 Set_Is_Static_Coextension (N, False);
3848 end if;
3850 -- There is no need to propagate any nested coextensions if they
3851 -- are marked as static since they will be rewritten on the spot.
3853 if not Is_Static_Coextension (N) then
3854 Propagate_Coextensions (N);
3855 end if;
3856 end if;
3857 end Resolve_Allocator;
3859 ---------------------------
3860 -- Resolve_Arithmetic_Op --
3861 ---------------------------
3863 -- Used for resolving all arithmetic operators except exponentiation
3865 procedure Resolve_Arithmetic_Op (N : Node_Id; Typ : Entity_Id) is
3866 L : constant Node_Id := Left_Opnd (N);
3867 R : constant Node_Id := Right_Opnd (N);
3868 TL : constant Entity_Id := Base_Type (Etype (L));
3869 TR : constant Entity_Id := Base_Type (Etype (R));
3870 T : Entity_Id;
3871 Rop : Node_Id;
3873 B_Typ : constant Entity_Id := Base_Type (Typ);
3874 -- We do the resolution using the base type, because intermediate values
3875 -- in expressions always are of the base type, not a subtype of it.
3877 function Expected_Type_Is_Any_Real (N : Node_Id) return Boolean;
3878 -- Returns True if N is in a context that expects "any real type"
3880 function Is_Integer_Or_Universal (N : Node_Id) return Boolean;
3881 -- Return True iff given type is Integer or universal real/integer
3883 procedure Set_Mixed_Mode_Operand (N : Node_Id; T : Entity_Id);
3884 -- Choose type of integer literal in fixed-point operation to conform
3885 -- to available fixed-point type. T is the type of the other operand,
3886 -- which is needed to determine the expected type of N.
3888 procedure Set_Operand_Type (N : Node_Id);
3889 -- Set operand type to T if universal
3891 -------------------------------
3892 -- Expected_Type_Is_Any_Real --
3893 -------------------------------
3895 function Expected_Type_Is_Any_Real (N : Node_Id) return Boolean is
3896 begin
3897 -- N is the expression after "delta" in a fixed_point_definition;
3898 -- see RM-3.5.9(6):
3900 return Nkind (Parent (N)) = N_Ordinary_Fixed_Point_Definition
3901 or else Nkind (Parent (N)) = N_Decimal_Fixed_Point_Definition
3903 -- N is one of the bounds in a real_range_specification;
3904 -- see RM-3.5.7(5):
3906 or else Nkind (Parent (N)) = N_Real_Range_Specification
3908 -- N is the expression of a delta_constraint;
3909 -- see RM-J.3(3):
3911 or else Nkind (Parent (N)) = N_Delta_Constraint;
3912 end Expected_Type_Is_Any_Real;
3914 -----------------------------
3915 -- Is_Integer_Or_Universal --
3916 -----------------------------
3918 function Is_Integer_Or_Universal (N : Node_Id) return Boolean is
3919 T : Entity_Id;
3920 Index : Interp_Index;
3921 It : Interp;
3923 begin
3924 if not Is_Overloaded (N) then
3925 T := Etype (N);
3926 return Base_Type (T) = Base_Type (Standard_Integer)
3927 or else T = Universal_Integer
3928 or else T = Universal_Real;
3929 else
3930 Get_First_Interp (N, Index, It);
3931 while Present (It.Typ) loop
3932 if Base_Type (It.Typ) = Base_Type (Standard_Integer)
3933 or else It.Typ = Universal_Integer
3934 or else It.Typ = Universal_Real
3935 then
3936 return True;
3937 end if;
3939 Get_Next_Interp (Index, It);
3940 end loop;
3941 end if;
3943 return False;
3944 end Is_Integer_Or_Universal;
3946 ----------------------------
3947 -- Set_Mixed_Mode_Operand --
3948 ----------------------------
3950 procedure Set_Mixed_Mode_Operand (N : Node_Id; T : Entity_Id) is
3951 Index : Interp_Index;
3952 It : Interp;
3954 begin
3955 if Universal_Interpretation (N) = Universal_Integer then
3957 -- A universal integer literal is resolved as standard integer
3958 -- except in the case of a fixed-point result, where we leave it
3959 -- as universal (to be handled by Exp_Fixd later on)
3961 if Is_Fixed_Point_Type (T) then
3962 Resolve (N, Universal_Integer);
3963 else
3964 Resolve (N, Standard_Integer);
3965 end if;
3967 elsif Universal_Interpretation (N) = Universal_Real
3968 and then (T = Base_Type (Standard_Integer)
3969 or else T = Universal_Integer
3970 or else T = Universal_Real)
3971 then
3972 -- A universal real can appear in a fixed-type context. We resolve
3973 -- the literal with that context, even though this might raise an
3974 -- exception prematurely (the other operand may be zero).
3976 Resolve (N, B_Typ);
3978 elsif Etype (N) = Base_Type (Standard_Integer)
3979 and then T = Universal_Real
3980 and then Is_Overloaded (N)
3981 then
3982 -- Integer arg in mixed-mode operation. Resolve with universal
3983 -- type, in case preference rule must be applied.
3985 Resolve (N, Universal_Integer);
3987 elsif Etype (N) = T
3988 and then B_Typ /= Universal_Fixed
3989 then
3990 -- Not a mixed-mode operation, resolve with context
3992 Resolve (N, B_Typ);
3994 elsif Etype (N) = Any_Fixed then
3996 -- N may itself be a mixed-mode operation, so use context type
3998 Resolve (N, B_Typ);
4000 elsif Is_Fixed_Point_Type (T)
4001 and then B_Typ = Universal_Fixed
4002 and then Is_Overloaded (N)
4003 then
4004 -- Must be (fixed * fixed) operation, operand must have one
4005 -- compatible interpretation.
4007 Resolve (N, Any_Fixed);
4009 elsif Is_Fixed_Point_Type (B_Typ)
4010 and then (T = Universal_Real
4011 or else Is_Fixed_Point_Type (T))
4012 and then Is_Overloaded (N)
4013 then
4014 -- C * F(X) in a fixed context, where C is a real literal or a
4015 -- fixed-point expression. F must have either a fixed type
4016 -- interpretation or an integer interpretation, but not both.
4018 Get_First_Interp (N, Index, It);
4019 while Present (It.Typ) loop
4020 if Base_Type (It.Typ) = Base_Type (Standard_Integer) then
4022 if Analyzed (N) then
4023 Error_Msg_N ("ambiguous operand in fixed operation", N);
4024 else
4025 Resolve (N, Standard_Integer);
4026 end if;
4028 elsif Is_Fixed_Point_Type (It.Typ) then
4030 if Analyzed (N) then
4031 Error_Msg_N ("ambiguous operand in fixed operation", N);
4032 else
4033 Resolve (N, It.Typ);
4034 end if;
4035 end if;
4037 Get_Next_Interp (Index, It);
4038 end loop;
4040 -- Reanalyze the literal with the fixed type of the context. If
4041 -- context is Universal_Fixed, we are within a conversion, leave
4042 -- the literal as a universal real because there is no usable
4043 -- fixed type, and the target of the conversion plays no role in
4044 -- the resolution.
4046 declare
4047 Op2 : Node_Id;
4048 T2 : Entity_Id;
4050 begin
4051 if N = L then
4052 Op2 := R;
4053 else
4054 Op2 := L;
4055 end if;
4057 if B_Typ = Universal_Fixed
4058 and then Nkind (Op2) = N_Real_Literal
4059 then
4060 T2 := Universal_Real;
4061 else
4062 T2 := B_Typ;
4063 end if;
4065 Set_Analyzed (Op2, False);
4066 Resolve (Op2, T2);
4067 end;
4069 else
4070 Resolve (N);
4071 end if;
4072 end Set_Mixed_Mode_Operand;
4074 ----------------------
4075 -- Set_Operand_Type --
4076 ----------------------
4078 procedure Set_Operand_Type (N : Node_Id) is
4079 begin
4080 if Etype (N) = Universal_Integer
4081 or else Etype (N) = Universal_Real
4082 then
4083 Set_Etype (N, T);
4084 end if;
4085 end Set_Operand_Type;
4087 -- Start of processing for Resolve_Arithmetic_Op
4089 begin
4090 if Comes_From_Source (N)
4091 and then Ekind (Entity (N)) = E_Function
4092 and then Is_Imported (Entity (N))
4093 and then Is_Intrinsic_Subprogram (Entity (N))
4094 then
4095 Resolve_Intrinsic_Operator (N, Typ);
4096 return;
4098 -- Special-case for mixed-mode universal expressions or fixed point
4099 -- type operation: each argument is resolved separately. The same
4100 -- treatment is required if one of the operands of a fixed point
4101 -- operation is universal real, since in this case we don't do a
4102 -- conversion to a specific fixed-point type (instead the expander
4103 -- takes care of the case).
4105 elsif (B_Typ = Universal_Integer
4106 or else B_Typ = Universal_Real)
4107 and then Present (Universal_Interpretation (L))
4108 and then Present (Universal_Interpretation (R))
4109 then
4110 Resolve (L, Universal_Interpretation (L));
4111 Resolve (R, Universal_Interpretation (R));
4112 Set_Etype (N, B_Typ);
4114 elsif (B_Typ = Universal_Real
4115 or else Etype (N) = Universal_Fixed
4116 or else (Etype (N) = Any_Fixed
4117 and then Is_Fixed_Point_Type (B_Typ))
4118 or else (Is_Fixed_Point_Type (B_Typ)
4119 and then (Is_Integer_Or_Universal (L)
4120 or else
4121 Is_Integer_Or_Universal (R))))
4122 and then (Nkind (N) = N_Op_Multiply or else
4123 Nkind (N) = N_Op_Divide)
4124 then
4125 if TL = Universal_Integer or else TR = Universal_Integer then
4126 Check_For_Visible_Operator (N, B_Typ);
4127 end if;
4129 -- If context is a fixed type and one operand is integer, the
4130 -- other is resolved with the type of the context.
4132 if Is_Fixed_Point_Type (B_Typ)
4133 and then (Base_Type (TL) = Base_Type (Standard_Integer)
4134 or else TL = Universal_Integer)
4135 then
4136 Resolve (R, B_Typ);
4137 Resolve (L, TL);
4139 elsif Is_Fixed_Point_Type (B_Typ)
4140 and then (Base_Type (TR) = Base_Type (Standard_Integer)
4141 or else TR = Universal_Integer)
4142 then
4143 Resolve (L, B_Typ);
4144 Resolve (R, TR);
4146 else
4147 Set_Mixed_Mode_Operand (L, TR);
4148 Set_Mixed_Mode_Operand (R, TL);
4149 end if;
4151 -- Check the rule in RM05-4.5.5(19.1/2) disallowing the
4152 -- universal_fixed multiplying operators from being used when the
4153 -- expected type is also universal_fixed. Note that B_Typ will be
4154 -- Universal_Fixed in some cases where the expected type is actually
4155 -- Any_Real; Expected_Type_Is_Any_Real takes care of that case.
4157 if Etype (N) = Universal_Fixed
4158 or else Etype (N) = Any_Fixed
4159 then
4160 if B_Typ = Universal_Fixed
4161 and then not Expected_Type_Is_Any_Real (N)
4162 and then Nkind (Parent (N)) /= N_Type_Conversion
4163 and then Nkind (Parent (N)) /= N_Unchecked_Type_Conversion
4164 then
4165 Error_Msg_N
4166 ("type cannot be determined from context!", N);
4167 Error_Msg_N
4168 ("\explicit conversion to result type required", N);
4170 Set_Etype (L, Any_Type);
4171 Set_Etype (R, Any_Type);
4173 else
4174 if Ada_Version = Ada_83
4175 and then Etype (N) = Universal_Fixed
4176 and then Nkind (Parent (N)) /= N_Type_Conversion
4177 and then Nkind (Parent (N)) /= N_Unchecked_Type_Conversion
4178 then
4179 Error_Msg_N
4180 ("(Ada 83) fixed-point operation " &
4181 "needs explicit conversion",
4183 end if;
4185 -- The expected type is "any real type" in contexts like
4186 -- type T is delta <universal_fixed-expression> ...
4187 -- in which case we need to set the type to Universal_Real
4188 -- so that static expression evaluation will work properly.
4190 if Expected_Type_Is_Any_Real (N) then
4191 Set_Etype (N, Universal_Real);
4192 else
4193 Set_Etype (N, B_Typ);
4194 end if;
4195 end if;
4197 elsif Is_Fixed_Point_Type (B_Typ)
4198 and then (Is_Integer_Or_Universal (L)
4199 or else Nkind (L) = N_Real_Literal
4200 or else Nkind (R) = N_Real_Literal
4201 or else
4202 Is_Integer_Or_Universal (R))
4203 then
4204 Set_Etype (N, B_Typ);
4206 elsif Etype (N) = Any_Fixed then
4208 -- If no previous errors, this is only possible if one operand
4209 -- is overloaded and the context is universal. Resolve as such.
4211 Set_Etype (N, B_Typ);
4212 end if;
4214 else
4215 if (TL = Universal_Integer or else TL = Universal_Real)
4216 and then (TR = Universal_Integer or else TR = Universal_Real)
4217 then
4218 Check_For_Visible_Operator (N, B_Typ);
4219 end if;
4221 -- If the context is Universal_Fixed and the operands are also
4222 -- universal fixed, this is an error, unless there is only one
4223 -- applicable fixed_point type (usually duration).
4225 if B_Typ = Universal_Fixed
4226 and then Etype (L) = Universal_Fixed
4227 then
4228 T := Unique_Fixed_Point_Type (N);
4230 if T = Any_Type then
4231 Set_Etype (N, T);
4232 return;
4233 else
4234 Resolve (L, T);
4235 Resolve (R, T);
4236 end if;
4238 else
4239 Resolve (L, B_Typ);
4240 Resolve (R, B_Typ);
4241 end if;
4243 -- If one of the arguments was resolved to a non-universal type.
4244 -- label the result of the operation itself with the same type.
4245 -- Do the same for the universal argument, if any.
4247 T := Intersect_Types (L, R);
4248 Set_Etype (N, Base_Type (T));
4249 Set_Operand_Type (L);
4250 Set_Operand_Type (R);
4251 end if;
4253 Generate_Operator_Reference (N, Typ);
4254 Eval_Arithmetic_Op (N);
4256 -- Set overflow and division checking bit. Much cleverer code needed
4257 -- here eventually and perhaps the Resolve routines should be separated
4258 -- for the various arithmetic operations, since they will need
4259 -- different processing. ???
4261 if Nkind (N) in N_Op then
4262 if not Overflow_Checks_Suppressed (Etype (N)) then
4263 Enable_Overflow_Check (N);
4264 end if;
4266 -- Give warning if explicit division by zero
4268 if (Nkind (N) = N_Op_Divide
4269 or else Nkind (N) = N_Op_Rem
4270 or else Nkind (N) = N_Op_Mod)
4271 and then not Division_Checks_Suppressed (Etype (N))
4272 then
4273 Rop := Right_Opnd (N);
4275 if Compile_Time_Known_Value (Rop)
4276 and then ((Is_Integer_Type (Etype (Rop))
4277 and then Expr_Value (Rop) = Uint_0)
4278 or else
4279 (Is_Real_Type (Etype (Rop))
4280 and then Expr_Value_R (Rop) = Ureal_0))
4281 then
4282 -- Specialize the warning message according to the operation
4284 case Nkind (N) is
4285 when N_Op_Divide =>
4286 Apply_Compile_Time_Constraint_Error
4287 (N, "division by zero?", CE_Divide_By_Zero,
4288 Loc => Sloc (Right_Opnd (N)));
4290 when N_Op_Rem =>
4291 Apply_Compile_Time_Constraint_Error
4292 (N, "rem with zero divisor?", CE_Divide_By_Zero,
4293 Loc => Sloc (Right_Opnd (N)));
4295 when N_Op_Mod =>
4296 Apply_Compile_Time_Constraint_Error
4297 (N, "mod with zero divisor?", CE_Divide_By_Zero,
4298 Loc => Sloc (Right_Opnd (N)));
4300 -- Division by zero can only happen with division, rem,
4301 -- and mod operations.
4303 when others =>
4304 raise Program_Error;
4305 end case;
4307 -- Otherwise just set the flag to check at run time
4309 else
4310 Activate_Division_Check (N);
4311 end if;
4312 end if;
4313 end if;
4315 Check_Unset_Reference (L);
4316 Check_Unset_Reference (R);
4317 end Resolve_Arithmetic_Op;
4319 ------------------
4320 -- Resolve_Call --
4321 ------------------
4323 procedure Resolve_Call (N : Node_Id; Typ : Entity_Id) is
4324 Loc : constant Source_Ptr := Sloc (N);
4325 Subp : constant Node_Id := Name (N);
4326 Nam : Entity_Id;
4327 I : Interp_Index;
4328 It : Interp;
4329 Norm_OK : Boolean;
4330 Scop : Entity_Id;
4331 Rtype : Entity_Id;
4333 begin
4334 -- The context imposes a unique interpretation with type Typ on a
4335 -- procedure or function call. Find the entity of the subprogram that
4336 -- yields the expected type, and propagate the corresponding formal
4337 -- constraints on the actuals. The caller has established that an
4338 -- interpretation exists, and emitted an error if not unique.
4340 -- First deal with the case of a call to an access-to-subprogram,
4341 -- dereference made explicit in Analyze_Call.
4343 if Ekind (Etype (Subp)) = E_Subprogram_Type then
4344 if not Is_Overloaded (Subp) then
4345 Nam := Etype (Subp);
4347 else
4348 -- Find the interpretation whose type (a subprogram type) has a
4349 -- return type that is compatible with the context. Analysis of
4350 -- the node has established that one exists.
4352 Nam := Empty;
4354 Get_First_Interp (Subp, I, It);
4355 while Present (It.Typ) loop
4356 if Covers (Typ, Etype (It.Typ)) then
4357 Nam := It.Typ;
4358 exit;
4359 end if;
4361 Get_Next_Interp (I, It);
4362 end loop;
4364 if No (Nam) then
4365 raise Program_Error;
4366 end if;
4367 end if;
4369 -- If the prefix is not an entity, then resolve it
4371 if not Is_Entity_Name (Subp) then
4372 Resolve (Subp, Nam);
4373 end if;
4375 -- For an indirect call, we always invalidate checks, since we do not
4376 -- know whether the subprogram is local or global. Yes we could do
4377 -- better here, e.g. by knowing that there are no local subprograms,
4378 -- but it does not seem worth the effort. Similarly, we kill all
4379 -- knowledge of current constant values.
4381 Kill_Current_Values;
4383 -- If this is a procedure call which is really an entry call, do
4384 -- the conversion of the procedure call to an entry call. Protected
4385 -- operations use the same circuitry because the name in the call
4386 -- can be an arbitrary expression with special resolution rules.
4388 elsif Nkind (Subp) = N_Selected_Component
4389 or else Nkind (Subp) = N_Indexed_Component
4390 or else (Is_Entity_Name (Subp)
4391 and then Ekind (Entity (Subp)) = E_Entry)
4392 then
4393 Resolve_Entry_Call (N, Typ);
4394 Check_Elab_Call (N);
4396 -- Kill checks and constant values, as above for indirect case
4397 -- Who knows what happens when another task is activated?
4399 Kill_Current_Values;
4400 return;
4402 -- Normal subprogram call with name established in Resolve
4404 elsif not (Is_Type (Entity (Subp))) then
4405 Nam := Entity (Subp);
4406 Set_Entity_With_Style_Check (Subp, Nam);
4408 -- Otherwise we must have the case of an overloaded call
4410 else
4411 pragma Assert (Is_Overloaded (Subp));
4412 Nam := Empty; -- We know that it will be assigned in loop below
4414 Get_First_Interp (Subp, I, It);
4415 while Present (It.Typ) loop
4416 if Covers (Typ, It.Typ) then
4417 Nam := It.Nam;
4418 Set_Entity_With_Style_Check (Subp, Nam);
4419 exit;
4420 end if;
4422 Get_Next_Interp (I, It);
4423 end loop;
4424 end if;
4426 -- Check that a call to Current_Task does not occur in an entry body
4428 if Is_RTE (Nam, RE_Current_Task) then
4429 declare
4430 P : Node_Id;
4432 begin
4433 P := N;
4434 loop
4435 P := Parent (P);
4436 exit when No (P);
4438 if Nkind (P) = N_Entry_Body
4439 or else (Nkind (P) = N_Subprogram_Body
4440 and then Is_Entry_Barrier_Function (P))
4441 then
4442 Rtype := Etype (N);
4443 Error_Msg_NE
4444 ("?& should not be used in entry body (RM C.7(17))",
4445 N, Nam);
4446 Error_Msg_NE
4447 ("\Program_Error will be raised at run time?", N, Nam);
4448 Rewrite (N,
4449 Make_Raise_Program_Error (Loc,
4450 Reason => PE_Current_Task_In_Entry_Body));
4451 Set_Etype (N, Rtype);
4452 return;
4453 end if;
4454 end loop;
4455 end;
4456 end if;
4458 -- Check that a procedure call does not occur in the context of the
4459 -- entry call statement of a conditional or timed entry call. Note that
4460 -- the case of a call to a subprogram renaming of an entry will also be
4461 -- rejected. The test for N not being an N_Entry_Call_Statement is
4462 -- defensive, covering the possibility that the processing of entry
4463 -- calls might reach this point due to later modifications of the code
4464 -- above.
4466 if Nkind (Parent (N)) = N_Entry_Call_Alternative
4467 and then Nkind (N) /= N_Entry_Call_Statement
4468 and then Entry_Call_Statement (Parent (N)) = N
4469 then
4470 if Ada_Version < Ada_05 then
4471 Error_Msg_N ("entry call required in select statement", N);
4473 -- Ada 2005 (AI-345): If a procedure_call_statement is used
4474 -- for a procedure_or_entry_call, the procedure_name or pro-
4475 -- cedure_prefix of the procedure_call_statement shall denote
4476 -- an entry renamed by a procedure, or (a view of) a primitive
4477 -- subprogram of a limited interface whose first parameter is
4478 -- a controlling parameter.
4480 elsif Nkind (N) = N_Procedure_Call_Statement
4481 and then not Is_Renamed_Entry (Nam)
4482 and then not Is_Controlling_Limited_Procedure (Nam)
4483 then
4484 Error_Msg_N
4485 ("entry call or dispatching primitive of interface required", N);
4486 end if;
4487 end if;
4489 -- Check that this is not a call to a protected procedure or
4490 -- entry from within a protected function.
4492 if Ekind (Current_Scope) = E_Function
4493 and then Ekind (Scope (Current_Scope)) = E_Protected_Type
4494 and then Ekind (Nam) /= E_Function
4495 and then Scope (Nam) = Scope (Current_Scope)
4496 then
4497 Error_Msg_N ("within protected function, protected " &
4498 "object is constant", N);
4499 Error_Msg_N ("\cannot call operation that may modify it", N);
4500 end if;
4502 -- Freeze the subprogram name if not in default expression. Note that we
4503 -- freeze procedure calls as well as function calls. Procedure calls are
4504 -- not frozen according to the rules (RM 13.14(14)) because it is
4505 -- impossible to have a procedure call to a non-frozen procedure in pure
4506 -- Ada, but in the code that we generate in the expander, this rule
4507 -- needs extending because we can generate procedure calls that need
4508 -- freezing.
4510 if Is_Entity_Name (Subp) and then not In_Default_Expression then
4511 Freeze_Expression (Subp);
4512 end if;
4514 -- For a predefined operator, the type of the result is the type imposed
4515 -- by context, except for a predefined operation on universal fixed.
4516 -- Otherwise The type of the call is the type returned by the subprogram
4517 -- being called.
4519 if Is_Predefined_Op (Nam) then
4520 if Etype (N) /= Universal_Fixed then
4521 Set_Etype (N, Typ);
4522 end if;
4524 -- If the subprogram returns an array type, and the context requires the
4525 -- component type of that array type, the node is really an indexing of
4526 -- the parameterless call. Resolve as such. A pathological case occurs
4527 -- when the type of the component is an access to the array type. In
4528 -- this case the call is truly ambiguous.
4530 elsif (Needs_No_Actuals (Nam) or else Needs_One_Actual (Nam))
4531 and then
4532 ((Is_Array_Type (Etype (Nam))
4533 and then Covers (Typ, Component_Type (Etype (Nam))))
4534 or else (Is_Access_Type (Etype (Nam))
4535 and then Is_Array_Type (Designated_Type (Etype (Nam)))
4536 and then
4537 Covers (Typ,
4538 Component_Type (Designated_Type (Etype (Nam))))))
4539 then
4540 declare
4541 Index_Node : Node_Id;
4542 New_Subp : Node_Id;
4543 Ret_Type : constant Entity_Id := Etype (Nam);
4545 begin
4546 if Is_Access_Type (Ret_Type)
4547 and then Ret_Type = Component_Type (Designated_Type (Ret_Type))
4548 then
4549 Error_Msg_N
4550 ("cannot disambiguate function call and indexing", N);
4551 else
4552 New_Subp := Relocate_Node (Subp);
4553 Set_Entity (Subp, Nam);
4555 if Component_Type (Ret_Type) /= Any_Type then
4556 if Needs_No_Actuals (Nam) then
4558 -- Indexed call to a parameterless function
4560 Index_Node :=
4561 Make_Indexed_Component (Loc,
4562 Prefix =>
4563 Make_Function_Call (Loc,
4564 Name => New_Subp),
4565 Expressions => Parameter_Associations (N));
4566 else
4567 -- An Ada 2005 prefixed call to a primitive operation
4568 -- whose first parameter is the prefix. This prefix was
4569 -- prepended to the parameter list, which is actually a
4570 -- list of indices. Remove the prefix in order to build
4571 -- the proper indexed component.
4573 Index_Node :=
4574 Make_Indexed_Component (Loc,
4575 Prefix =>
4576 Make_Function_Call (Loc,
4577 Name => New_Subp,
4578 Parameter_Associations =>
4579 New_List
4580 (Remove_Head (Parameter_Associations (N)))),
4581 Expressions => Parameter_Associations (N));
4582 end if;
4584 -- Since we are correcting a node classification error made
4585 -- by the parser, we call Replace rather than Rewrite.
4587 Replace (N, Index_Node);
4588 Set_Etype (Prefix (N), Ret_Type);
4589 Set_Etype (N, Typ);
4590 Resolve_Indexed_Component (N, Typ);
4591 Check_Elab_Call (Prefix (N));
4592 end if;
4593 end if;
4595 return;
4596 end;
4598 else
4599 Set_Etype (N, Etype (Nam));
4600 end if;
4602 -- In the case where the call is to an overloaded subprogram, Analyze
4603 -- calls Normalize_Actuals once per overloaded subprogram. Therefore in
4604 -- such a case Normalize_Actuals needs to be called once more to order
4605 -- the actuals correctly. Otherwise the call will have the ordering
4606 -- given by the last overloaded subprogram whether this is the correct
4607 -- one being called or not.
4609 if Is_Overloaded (Subp) then
4610 Normalize_Actuals (N, Nam, False, Norm_OK);
4611 pragma Assert (Norm_OK);
4612 end if;
4614 -- In any case, call is fully resolved now. Reset Overload flag, to
4615 -- prevent subsequent overload resolution if node is analyzed again
4617 Set_Is_Overloaded (Subp, False);
4618 Set_Is_Overloaded (N, False);
4620 -- If we are calling the current subprogram from immediately within its
4621 -- body, then that is the case where we can sometimes detect cases of
4622 -- infinite recursion statically. Do not try this in case restriction
4623 -- No_Recursion is in effect anyway, and do it only for source calls.
4625 if Comes_From_Source (N) then
4626 Scop := Current_Scope;
4628 if Nam = Scop
4629 and then not Restriction_Active (No_Recursion)
4630 and then Check_Infinite_Recursion (N)
4631 then
4632 -- Here we detected and flagged an infinite recursion, so we do
4633 -- not need to test the case below for further warnings.
4635 null;
4637 -- If call is to immediately containing subprogram, then check for
4638 -- the case of a possible run-time detectable infinite recursion.
4640 else
4641 Scope_Loop : while Scop /= Standard_Standard loop
4642 if Nam = Scop then
4644 -- Although in general case, recursion is not statically
4645 -- checkable, the case of calling an immediately containing
4646 -- subprogram is easy to catch.
4648 Check_Restriction (No_Recursion, N);
4650 -- If the recursive call is to a parameterless subprogram,
4651 -- then even if we can't statically detect infinite
4652 -- recursion, this is pretty suspicious, and we output a
4653 -- warning. Furthermore, we will try later to detect some
4654 -- cases here at run time by expanding checking code (see
4655 -- Detect_Infinite_Recursion in package Exp_Ch6).
4657 -- If the recursive call is within a handler, do not emit a
4658 -- warning, because this is a common idiom: loop until input
4659 -- is correct, catch illegal input in handler and restart.
4661 if No (First_Formal (Nam))
4662 and then Etype (Nam) = Standard_Void_Type
4663 and then not Error_Posted (N)
4664 and then Nkind (Parent (N)) /= N_Exception_Handler
4665 then
4666 -- For the case of a procedure call. We give the message
4667 -- only if the call is the first statement in a sequence
4668 -- of statements, or if all previous statements are
4669 -- simple assignments. This is simply a heuristic to
4670 -- decrease false positives, without losing too many good
4671 -- warnings. The idea is that these previous statements
4672 -- may affect global variables the procedure depends on.
4674 if Nkind (N) = N_Procedure_Call_Statement
4675 and then Is_List_Member (N)
4676 then
4677 declare
4678 P : Node_Id;
4679 begin
4680 P := Prev (N);
4681 while Present (P) loop
4682 if Nkind (P) /= N_Assignment_Statement then
4683 exit Scope_Loop;
4684 end if;
4686 Prev (P);
4687 end loop;
4688 end;
4689 end if;
4691 -- Do not give warning if we are in a conditional context
4693 declare
4694 K : constant Node_Kind := Nkind (Parent (N));
4695 begin
4696 if (K = N_Loop_Statement
4697 and then Present (Iteration_Scheme (Parent (N))))
4698 or else K = N_If_Statement
4699 or else K = N_Elsif_Part
4700 or else K = N_Case_Statement_Alternative
4701 then
4702 exit Scope_Loop;
4703 end if;
4704 end;
4706 -- Here warning is to be issued
4708 Set_Has_Recursive_Call (Nam);
4709 Error_Msg_N
4710 ("?possible infinite recursion!", N);
4711 Error_Msg_N
4712 ("\?Storage_Error may be raised at run time!", N);
4713 end if;
4715 exit Scope_Loop;
4716 end if;
4718 Scop := Scope (Scop);
4719 end loop Scope_Loop;
4720 end if;
4721 end if;
4723 -- If subprogram name is a predefined operator, it was given in
4724 -- functional notation. Replace call node with operator node, so
4725 -- that actuals can be resolved appropriately.
4727 if Is_Predefined_Op (Nam) or else Ekind (Nam) = E_Operator then
4728 Make_Call_Into_Operator (N, Typ, Entity (Name (N)));
4729 return;
4731 elsif Present (Alias (Nam))
4732 and then Is_Predefined_Op (Alias (Nam))
4733 then
4734 Resolve_Actuals (N, Nam);
4735 Make_Call_Into_Operator (N, Typ, Alias (Nam));
4736 return;
4737 end if;
4739 -- Create a transient scope if the resulting type requires it
4741 -- There are 4 notable exceptions: in init procs, the transient scope
4742 -- overhead is not needed and even incorrect due to the actual expansion
4743 -- of adjust calls; the second case is enumeration literal pseudo calls;
4744 -- the third case is intrinsic subprograms (Unchecked_Conversion and
4745 -- source information functions) that do not use the secondary stack
4746 -- even though the return type is unconstrained; the fourth case is a
4747 -- call to a build-in-place function, since such functions may allocate
4748 -- their result directly in a target object, and cases where the result
4749 -- does get allocated in the secondary stack are checked for within the
4750 -- specialized Exp_Ch6 procedures for expanding build-in-place calls.
4752 -- If this is an initialization call for a type whose initialization
4753 -- uses the secondary stack, we also need to create a transient scope
4754 -- for it, precisely because we will not do it within the init proc
4755 -- itself.
4757 -- If the subprogram is marked Inline_Always, then even if it returns
4758 -- an unconstrained type the call does not require use of the secondary
4759 -- stack.
4761 if Is_Inlined (Nam)
4762 and then Present (First_Rep_Item (Nam))
4763 and then Nkind (First_Rep_Item (Nam)) = N_Pragma
4764 and then Chars (First_Rep_Item (Nam)) = Name_Inline_Always
4765 then
4766 null;
4768 elsif Expander_Active
4769 and then Is_Type (Etype (Nam))
4770 and then Requires_Transient_Scope (Etype (Nam))
4771 and then not Is_Build_In_Place_Function (Nam)
4772 and then Ekind (Nam) /= E_Enumeration_Literal
4773 and then not Within_Init_Proc
4774 and then not Is_Intrinsic_Subprogram (Nam)
4775 then
4776 Establish_Transient_Scope (N, Sec_Stack => True);
4778 -- If the call appears within the bounds of a loop, it will
4779 -- be rewritten and reanalyzed, nothing left to do here.
4781 if Nkind (N) /= N_Function_Call then
4782 return;
4783 end if;
4785 elsif Is_Init_Proc (Nam)
4786 and then not Within_Init_Proc
4787 then
4788 Check_Initialization_Call (N, Nam);
4789 end if;
4791 -- A protected function cannot be called within the definition of the
4792 -- enclosing protected type.
4794 if Is_Protected_Type (Scope (Nam))
4795 and then In_Open_Scopes (Scope (Nam))
4796 and then not Has_Completion (Scope (Nam))
4797 then
4798 Error_Msg_NE
4799 ("& cannot be called before end of protected definition", N, Nam);
4800 end if;
4802 -- Propagate interpretation to actuals, and add default expressions
4803 -- where needed.
4805 if Present (First_Formal (Nam)) then
4806 Resolve_Actuals (N, Nam);
4808 -- Overloaded literals are rewritten as function calls, for
4809 -- purpose of resolution. After resolution, we can replace
4810 -- the call with the literal itself.
4812 elsif Ekind (Nam) = E_Enumeration_Literal then
4813 Copy_Node (Subp, N);
4814 Resolve_Entity_Name (N, Typ);
4816 -- Avoid validation, since it is a static function call
4818 Generate_Reference (Nam, Subp);
4819 return;
4820 end if;
4822 -- If the subprogram is not global, then kill all saved values and
4823 -- checks. This is a bit conservative, since in many cases we could do
4824 -- better, but it is not worth the effort. Similarly, we kill constant
4825 -- values. However we do not need to do this for internal entities
4826 -- (unless they are inherited user-defined subprograms), since they
4827 -- are not in the business of molesting local values.
4829 -- If the flag Suppress_Value_Tracking_On_Calls is set, then we also
4830 -- kill all checks and values for calls to global subprograms. This
4831 -- takes care of the case where an access to a local subprogram is
4832 -- taken, and could be passed directly or indirectly and then called
4833 -- from almost any context.
4835 -- Note: we do not do this step till after resolving the actuals. That
4836 -- way we still take advantage of the current value information while
4837 -- scanning the actuals.
4839 if (not Is_Library_Level_Entity (Nam)
4840 or else Suppress_Value_Tracking_On_Call (Current_Scope))
4841 and then (Comes_From_Source (Nam)
4842 or else (Present (Alias (Nam))
4843 and then Comes_From_Source (Alias (Nam))))
4844 then
4845 Kill_Current_Values;
4846 end if;
4848 -- If we are warning about unread OUT parameters, this is the place to
4849 -- set Last_Assignment for OUT and IN OUT parameters. We have to do this
4850 -- after the above call to Kill_Current_Values (since that call clears
4851 -- the Last_Assignment field of all local variables).
4853 if (Warn_On_Modified_Unread or Warn_On_All_Unread_Out_Parameters)
4854 and then Comes_From_Source (N)
4855 and then In_Extended_Main_Source_Unit (N)
4856 then
4857 declare
4858 F : Entity_Id;
4859 A : Node_Id;
4861 begin
4862 F := First_Formal (Nam);
4863 A := First_Actual (N);
4864 while Present (F) and then Present (A) loop
4865 if (Ekind (F) = E_Out_Parameter
4866 or else Ekind (F) = E_In_Out_Parameter)
4867 and then Warn_On_Modified_As_Out_Parameter (F)
4868 and then Is_Entity_Name (A)
4869 and then Present (Entity (A))
4870 and then Comes_From_Source (N)
4871 and then Safe_To_Capture_Value (N, Entity (A))
4872 then
4873 Set_Last_Assignment (Entity (A), A);
4874 end if;
4876 Next_Formal (F);
4877 Next_Actual (A);
4878 end loop;
4879 end;
4880 end if;
4882 -- If the subprogram is a primitive operation, check whether or not
4883 -- it is a correct dispatching call.
4885 if Is_Overloadable (Nam)
4886 and then Is_Dispatching_Operation (Nam)
4887 then
4888 Check_Dispatching_Call (N);
4890 elsif Ekind (Nam) /= E_Subprogram_Type
4891 and then Is_Abstract_Subprogram (Nam)
4892 and then not In_Instance
4893 then
4894 Error_Msg_NE ("cannot call abstract subprogram &!", N, Nam);
4895 end if;
4897 -- If this is a dispatching call, generate the appropriate reference,
4898 -- for better source navigation in GPS.
4900 if Is_Overloadable (Nam)
4901 and then Present (Controlling_Argument (N))
4902 then
4903 Generate_Reference (Nam, Subp, 'R');
4904 else
4905 Generate_Reference (Nam, Subp);
4906 end if;
4908 if Is_Intrinsic_Subprogram (Nam) then
4909 Check_Intrinsic_Call (N);
4910 end if;
4912 -- All done, evaluate call and deal with elaboration issues
4914 Eval_Call (N);
4915 Check_Elab_Call (N);
4916 end Resolve_Call;
4918 -------------------------------
4919 -- Resolve_Character_Literal --
4920 -------------------------------
4922 procedure Resolve_Character_Literal (N : Node_Id; Typ : Entity_Id) is
4923 B_Typ : constant Entity_Id := Base_Type (Typ);
4924 C : Entity_Id;
4926 begin
4927 -- Verify that the character does belong to the type of the context
4929 Set_Etype (N, B_Typ);
4930 Eval_Character_Literal (N);
4932 -- Wide_Wide_Character literals must always be defined, since the set
4933 -- of wide wide character literals is complete, i.e. if a character
4934 -- literal is accepted by the parser, then it is OK for wide wide
4935 -- character (out of range character literals are rejected).
4937 if Root_Type (B_Typ) = Standard_Wide_Wide_Character then
4938 return;
4940 -- Always accept character literal for type Any_Character, which
4941 -- occurs in error situations and in comparisons of literals, both
4942 -- of which should accept all literals.
4944 elsif B_Typ = Any_Character then
4945 return;
4947 -- For Standard.Character or a type derived from it, check that
4948 -- the literal is in range
4950 elsif Root_Type (B_Typ) = Standard_Character then
4951 if In_Character_Range (UI_To_CC (Char_Literal_Value (N))) then
4952 return;
4953 end if;
4955 -- For Standard.Wide_Character or a type derived from it, check
4956 -- that the literal is in range
4958 elsif Root_Type (B_Typ) = Standard_Wide_Character then
4959 if In_Wide_Character_Range (UI_To_CC (Char_Literal_Value (N))) then
4960 return;
4961 end if;
4963 -- For Standard.Wide_Wide_Character or a type derived from it, we
4964 -- know the literal is in range, since the parser checked!
4966 elsif Root_Type (B_Typ) = Standard_Wide_Wide_Character then
4967 return;
4969 -- If the entity is already set, this has already been resolved in
4970 -- a generic context, or comes from expansion. Nothing else to do.
4972 elsif Present (Entity (N)) then
4973 return;
4975 -- Otherwise we have a user defined character type, and we can use
4976 -- the standard visibility mechanisms to locate the referenced entity
4978 else
4979 C := Current_Entity (N);
4980 while Present (C) loop
4981 if Etype (C) = B_Typ then
4982 Set_Entity_With_Style_Check (N, C);
4983 Generate_Reference (C, N);
4984 return;
4985 end if;
4987 C := Homonym (C);
4988 end loop;
4989 end if;
4991 -- If we fall through, then the literal does not match any of the
4992 -- entries of the enumeration type. This isn't just a constraint
4993 -- error situation, it is an illegality (see RM 4.2).
4995 Error_Msg_NE
4996 ("character not defined for }", N, First_Subtype (B_Typ));
4997 end Resolve_Character_Literal;
4999 ---------------------------
5000 -- Resolve_Comparison_Op --
5001 ---------------------------
5003 -- Context requires a boolean type, and plays no role in resolution.
5004 -- Processing identical to that for equality operators. The result
5005 -- type is the base type, which matters when pathological subtypes of
5006 -- booleans with limited ranges are used.
5008 procedure Resolve_Comparison_Op (N : Node_Id; Typ : Entity_Id) is
5009 L : constant Node_Id := Left_Opnd (N);
5010 R : constant Node_Id := Right_Opnd (N);
5011 T : Entity_Id;
5013 begin
5014 -- If this is an intrinsic operation which is not predefined, use
5015 -- the types of its declared arguments to resolve the possibly
5016 -- overloaded operands. Otherwise the operands are unambiguous and
5017 -- specify the expected type.
5019 if Scope (Entity (N)) /= Standard_Standard then
5020 T := Etype (First_Entity (Entity (N)));
5022 else
5023 T := Find_Unique_Type (L, R);
5025 if T = Any_Fixed then
5026 T := Unique_Fixed_Point_Type (L);
5027 end if;
5028 end if;
5030 Set_Etype (N, Base_Type (Typ));
5031 Generate_Reference (T, N, ' ');
5033 if T /= Any_Type then
5034 if T = Any_String
5035 or else T = Any_Composite
5036 or else T = Any_Character
5037 then
5038 if T = Any_Character then
5039 Ambiguous_Character (L);
5040 else
5041 Error_Msg_N ("ambiguous operands for comparison", N);
5042 end if;
5044 Set_Etype (N, Any_Type);
5045 return;
5047 else
5048 Resolve (L, T);
5049 Resolve (R, T);
5050 Check_Unset_Reference (L);
5051 Check_Unset_Reference (R);
5052 Generate_Operator_Reference (N, T);
5053 Eval_Relational_Op (N);
5054 end if;
5055 end if;
5056 end Resolve_Comparison_Op;
5058 ------------------------------------
5059 -- Resolve_Conditional_Expression --
5060 ------------------------------------
5062 procedure Resolve_Conditional_Expression (N : Node_Id; Typ : Entity_Id) is
5063 Condition : constant Node_Id := First (Expressions (N));
5064 Then_Expr : constant Node_Id := Next (Condition);
5065 Else_Expr : constant Node_Id := Next (Then_Expr);
5067 begin
5068 Resolve (Condition, Standard_Boolean);
5069 Resolve (Then_Expr, Typ);
5070 Resolve (Else_Expr, Typ);
5072 Set_Etype (N, Typ);
5073 Eval_Conditional_Expression (N);
5074 end Resolve_Conditional_Expression;
5076 -----------------------------------------
5077 -- Resolve_Discrete_Subtype_Indication --
5078 -----------------------------------------
5080 procedure Resolve_Discrete_Subtype_Indication
5081 (N : Node_Id;
5082 Typ : Entity_Id)
5084 R : Node_Id;
5085 S : Entity_Id;
5087 begin
5088 Analyze (Subtype_Mark (N));
5089 S := Entity (Subtype_Mark (N));
5091 if Nkind (Constraint (N)) /= N_Range_Constraint then
5092 Error_Msg_N ("expect range constraint for discrete type", N);
5093 Set_Etype (N, Any_Type);
5095 else
5096 R := Range_Expression (Constraint (N));
5098 if R = Error then
5099 return;
5100 end if;
5102 Analyze (R);
5104 if Base_Type (S) /= Base_Type (Typ) then
5105 Error_Msg_NE
5106 ("expect subtype of }", N, First_Subtype (Typ));
5108 -- Rewrite the constraint as a range of Typ
5109 -- to allow compilation to proceed further.
5111 Set_Etype (N, Typ);
5112 Rewrite (Low_Bound (R),
5113 Make_Attribute_Reference (Sloc (Low_Bound (R)),
5114 Prefix => New_Occurrence_Of (Typ, Sloc (R)),
5115 Attribute_Name => Name_First));
5116 Rewrite (High_Bound (R),
5117 Make_Attribute_Reference (Sloc (High_Bound (R)),
5118 Prefix => New_Occurrence_Of (Typ, Sloc (R)),
5119 Attribute_Name => Name_First));
5121 else
5122 Resolve (R, Typ);
5123 Set_Etype (N, Etype (R));
5125 -- Additionally, we must check that the bounds are compatible
5126 -- with the given subtype, which might be different from the
5127 -- type of the context.
5129 Apply_Range_Check (R, S);
5131 -- ??? If the above check statically detects a Constraint_Error
5132 -- it replaces the offending bound(s) of the range R with a
5133 -- Constraint_Error node. When the itype which uses these bounds
5134 -- is frozen the resulting call to Duplicate_Subexpr generates
5135 -- a new temporary for the bounds.
5137 -- Unfortunately there are other itypes that are also made depend
5138 -- on these bounds, so when Duplicate_Subexpr is called they get
5139 -- a forward reference to the newly created temporaries and Gigi
5140 -- aborts on such forward references. This is probably sign of a
5141 -- more fundamental problem somewhere else in either the order of
5142 -- itype freezing or the way certain itypes are constructed.
5144 -- To get around this problem we call Remove_Side_Effects right
5145 -- away if either bounds of R are a Constraint_Error.
5147 declare
5148 L : constant Node_Id := Low_Bound (R);
5149 H : constant Node_Id := High_Bound (R);
5151 begin
5152 if Nkind (L) = N_Raise_Constraint_Error then
5153 Remove_Side_Effects (L);
5154 end if;
5156 if Nkind (H) = N_Raise_Constraint_Error then
5157 Remove_Side_Effects (H);
5158 end if;
5159 end;
5161 Check_Unset_Reference (Low_Bound (R));
5162 Check_Unset_Reference (High_Bound (R));
5163 end if;
5164 end if;
5165 end Resolve_Discrete_Subtype_Indication;
5167 -------------------------
5168 -- Resolve_Entity_Name --
5169 -------------------------
5171 -- Used to resolve identifiers and expanded names
5173 procedure Resolve_Entity_Name (N : Node_Id; Typ : Entity_Id) is
5174 E : constant Entity_Id := Entity (N);
5176 begin
5177 -- If garbage from errors, set to Any_Type and return
5179 if No (E) and then Total_Errors_Detected /= 0 then
5180 Set_Etype (N, Any_Type);
5181 return;
5182 end if;
5184 -- Replace named numbers by corresponding literals. Note that this is
5185 -- the one case where Resolve_Entity_Name must reset the Etype, since
5186 -- it is currently marked as universal.
5188 if Ekind (E) = E_Named_Integer then
5189 Set_Etype (N, Typ);
5190 Eval_Named_Integer (N);
5192 elsif Ekind (E) = E_Named_Real then
5193 Set_Etype (N, Typ);
5194 Eval_Named_Real (N);
5196 -- Allow use of subtype only if it is a concurrent type where we are
5197 -- currently inside the body. This will eventually be expanded
5198 -- into a call to Self (for tasks) or _object (for protected
5199 -- objects). Any other use of a subtype is invalid.
5201 elsif Is_Type (E) then
5202 if Is_Concurrent_Type (E)
5203 and then In_Open_Scopes (E)
5204 then
5205 null;
5206 else
5207 Error_Msg_N
5208 ("invalid use of subtype mark in expression or call", N);
5209 end if;
5211 -- Check discriminant use if entity is discriminant in current scope,
5212 -- i.e. discriminant of record or concurrent type currently being
5213 -- analyzed. Uses in corresponding body are unrestricted.
5215 elsif Ekind (E) = E_Discriminant
5216 and then Scope (E) = Current_Scope
5217 and then not Has_Completion (Current_Scope)
5218 then
5219 Check_Discriminant_Use (N);
5221 -- A parameterless generic function cannot appear in a context that
5222 -- requires resolution.
5224 elsif Ekind (E) = E_Generic_Function then
5225 Error_Msg_N ("illegal use of generic function", N);
5227 elsif Ekind (E) = E_Out_Parameter
5228 and then Ada_Version = Ada_83
5229 and then (Nkind (Parent (N)) in N_Op
5230 or else (Nkind (Parent (N)) = N_Assignment_Statement
5231 and then N = Expression (Parent (N)))
5232 or else Nkind (Parent (N)) = N_Explicit_Dereference)
5233 then
5234 Error_Msg_N ("(Ada 83) illegal reading of out parameter", N);
5236 -- In all other cases, just do the possible static evaluation
5238 else
5239 -- A deferred constant that appears in an expression must have
5240 -- a completion, unless it has been removed by in-place expansion
5241 -- of an aggregate.
5243 if Ekind (E) = E_Constant
5244 and then Comes_From_Source (E)
5245 and then No (Constant_Value (E))
5246 and then Is_Frozen (Etype (E))
5247 and then not In_Default_Expression
5248 and then not Is_Imported (E)
5249 then
5251 if No_Initialization (Parent (E))
5252 or else (Present (Full_View (E))
5253 and then No_Initialization (Parent (Full_View (E))))
5254 then
5255 null;
5256 else
5257 Error_Msg_N (
5258 "deferred constant is frozen before completion", N);
5259 end if;
5260 end if;
5262 Eval_Entity_Name (N);
5263 end if;
5264 end Resolve_Entity_Name;
5266 -------------------
5267 -- Resolve_Entry --
5268 -------------------
5270 procedure Resolve_Entry (Entry_Name : Node_Id) is
5271 Loc : constant Source_Ptr := Sloc (Entry_Name);
5272 Nam : Entity_Id;
5273 New_N : Node_Id;
5274 S : Entity_Id;
5275 Tsk : Entity_Id;
5276 E_Name : Node_Id;
5277 Index : Node_Id;
5279 function Actual_Index_Type (E : Entity_Id) return Entity_Id;
5280 -- If the bounds of the entry family being called depend on task
5281 -- discriminants, build a new index subtype where a discriminant is
5282 -- replaced with the value of the discriminant of the target task.
5283 -- The target task is the prefix of the entry name in the call.
5285 -----------------------
5286 -- Actual_Index_Type --
5287 -----------------------
5289 function Actual_Index_Type (E : Entity_Id) return Entity_Id is
5290 Typ : constant Entity_Id := Entry_Index_Type (E);
5291 Tsk : constant Entity_Id := Scope (E);
5292 Lo : constant Node_Id := Type_Low_Bound (Typ);
5293 Hi : constant Node_Id := Type_High_Bound (Typ);
5294 New_T : Entity_Id;
5296 function Actual_Discriminant_Ref (Bound : Node_Id) return Node_Id;
5297 -- If the bound is given by a discriminant, replace with a reference
5298 -- to the discriminant of the same name in the target task.
5299 -- If the entry name is the target of a requeue statement and the
5300 -- entry is in the current protected object, the bound to be used
5301 -- is the discriminal of the object (see apply_range_checks for
5302 -- details of the transformation).
5304 -----------------------------
5305 -- Actual_Discriminant_Ref --
5306 -----------------------------
5308 function Actual_Discriminant_Ref (Bound : Node_Id) return Node_Id is
5309 Typ : constant Entity_Id := Etype (Bound);
5310 Ref : Node_Id;
5312 begin
5313 Remove_Side_Effects (Bound);
5315 if not Is_Entity_Name (Bound)
5316 or else Ekind (Entity (Bound)) /= E_Discriminant
5317 then
5318 return Bound;
5320 elsif Is_Protected_Type (Tsk)
5321 and then In_Open_Scopes (Tsk)
5322 and then Nkind (Parent (Entry_Name)) = N_Requeue_Statement
5323 then
5324 return New_Occurrence_Of (Discriminal (Entity (Bound)), Loc);
5326 else
5327 Ref :=
5328 Make_Selected_Component (Loc,
5329 Prefix => New_Copy_Tree (Prefix (Prefix (Entry_Name))),
5330 Selector_Name => New_Occurrence_Of (Entity (Bound), Loc));
5331 Analyze (Ref);
5332 Resolve (Ref, Typ);
5333 return Ref;
5334 end if;
5335 end Actual_Discriminant_Ref;
5337 -- Start of processing for Actual_Index_Type
5339 begin
5340 if not Has_Discriminants (Tsk)
5341 or else (not Is_Entity_Name (Lo)
5342 and then not Is_Entity_Name (Hi))
5343 then
5344 return Entry_Index_Type (E);
5346 else
5347 New_T := Create_Itype (Ekind (Typ), Parent (Entry_Name));
5348 Set_Etype (New_T, Base_Type (Typ));
5349 Set_Size_Info (New_T, Typ);
5350 Set_RM_Size (New_T, RM_Size (Typ));
5351 Set_Scalar_Range (New_T,
5352 Make_Range (Sloc (Entry_Name),
5353 Low_Bound => Actual_Discriminant_Ref (Lo),
5354 High_Bound => Actual_Discriminant_Ref (Hi)));
5356 return New_T;
5357 end if;
5358 end Actual_Index_Type;
5360 -- Start of processing of Resolve_Entry
5362 begin
5363 -- Find name of entry being called, and resolve prefix of name
5364 -- with its own type. The prefix can be overloaded, and the name
5365 -- and signature of the entry must be taken into account.
5367 if Nkind (Entry_Name) = N_Indexed_Component then
5369 -- Case of dealing with entry family within the current tasks
5371 E_Name := Prefix (Entry_Name);
5373 else
5374 E_Name := Entry_Name;
5375 end if;
5377 if Is_Entity_Name (E_Name) then
5378 -- Entry call to an entry (or entry family) in the current task.
5379 -- This is legal even though the task will deadlock. Rewrite as
5380 -- call to current task.
5382 -- This can also be a call to an entry in an enclosing task.
5383 -- If this is a single task, we have to retrieve its name,
5384 -- because the scope of the entry is the task type, not the
5385 -- object. If the enclosing task is a task type, the identity
5386 -- of the task is given by its own self variable.
5388 -- Finally this can be a requeue on an entry of the same task
5389 -- or protected object.
5391 S := Scope (Entity (E_Name));
5393 for J in reverse 0 .. Scope_Stack.Last loop
5395 if Is_Task_Type (Scope_Stack.Table (J).Entity)
5396 and then not Comes_From_Source (S)
5397 then
5398 -- S is an enclosing task or protected object. The concurrent
5399 -- declaration has been converted into a type declaration, and
5400 -- the object itself has an object declaration that follows
5401 -- the type in the same declarative part.
5403 Tsk := Next_Entity (S);
5404 while Etype (Tsk) /= S loop
5405 Next_Entity (Tsk);
5406 end loop;
5408 S := Tsk;
5409 exit;
5411 elsif S = Scope_Stack.Table (J).Entity then
5413 -- Call to current task. Will be transformed into call to Self
5415 exit;
5417 end if;
5418 end loop;
5420 New_N :=
5421 Make_Selected_Component (Loc,
5422 Prefix => New_Occurrence_Of (S, Loc),
5423 Selector_Name =>
5424 New_Occurrence_Of (Entity (E_Name), Loc));
5425 Rewrite (E_Name, New_N);
5426 Analyze (E_Name);
5428 elsif Nkind (Entry_Name) = N_Selected_Component
5429 and then Is_Overloaded (Prefix (Entry_Name))
5430 then
5431 -- Use the entry name (which must be unique at this point) to
5432 -- find the prefix that returns the corresponding task type or
5433 -- protected type.
5435 declare
5436 Pref : constant Node_Id := Prefix (Entry_Name);
5437 Ent : constant Entity_Id := Entity (Selector_Name (Entry_Name));
5438 I : Interp_Index;
5439 It : Interp;
5441 begin
5442 Get_First_Interp (Pref, I, It);
5443 while Present (It.Typ) loop
5444 if Scope (Ent) = It.Typ then
5445 Set_Etype (Pref, It.Typ);
5446 exit;
5447 end if;
5449 Get_Next_Interp (I, It);
5450 end loop;
5451 end;
5452 end if;
5454 if Nkind (Entry_Name) = N_Selected_Component then
5455 Resolve (Prefix (Entry_Name));
5457 else pragma Assert (Nkind (Entry_Name) = N_Indexed_Component);
5458 Nam := Entity (Selector_Name (Prefix (Entry_Name)));
5459 Resolve (Prefix (Prefix (Entry_Name)));
5460 Index := First (Expressions (Entry_Name));
5461 Resolve (Index, Entry_Index_Type (Nam));
5463 -- Up to this point the expression could have been the actual
5464 -- in a simple entry call, and be given by a named association.
5466 if Nkind (Index) = N_Parameter_Association then
5467 Error_Msg_N ("expect expression for entry index", Index);
5468 else
5469 Apply_Range_Check (Index, Actual_Index_Type (Nam));
5470 end if;
5471 end if;
5472 end Resolve_Entry;
5474 ------------------------
5475 -- Resolve_Entry_Call --
5476 ------------------------
5478 procedure Resolve_Entry_Call (N : Node_Id; Typ : Entity_Id) is
5479 Entry_Name : constant Node_Id := Name (N);
5480 Loc : constant Source_Ptr := Sloc (Entry_Name);
5481 Actuals : List_Id;
5482 First_Named : Node_Id;
5483 Nam : Entity_Id;
5484 Norm_OK : Boolean;
5485 Obj : Node_Id;
5486 Was_Over : Boolean;
5488 begin
5489 -- We kill all checks here, because it does not seem worth the
5490 -- effort to do anything better, an entry call is a big operation.
5492 Kill_All_Checks;
5494 -- Processing of the name is similar for entry calls and protected
5495 -- operation calls. Once the entity is determined, we can complete
5496 -- the resolution of the actuals.
5498 -- The selector may be overloaded, in the case of a protected object
5499 -- with overloaded functions. The type of the context is used for
5500 -- resolution.
5502 if Nkind (Entry_Name) = N_Selected_Component
5503 and then Is_Overloaded (Selector_Name (Entry_Name))
5504 and then Typ /= Standard_Void_Type
5505 then
5506 declare
5507 I : Interp_Index;
5508 It : Interp;
5510 begin
5511 Get_First_Interp (Selector_Name (Entry_Name), I, It);
5512 while Present (It.Typ) loop
5513 if Covers (Typ, It.Typ) then
5514 Set_Entity (Selector_Name (Entry_Name), It.Nam);
5515 Set_Etype (Entry_Name, It.Typ);
5517 Generate_Reference (It.Typ, N, ' ');
5518 end if;
5520 Get_Next_Interp (I, It);
5521 end loop;
5522 end;
5523 end if;
5525 Resolve_Entry (Entry_Name);
5527 if Nkind (Entry_Name) = N_Selected_Component then
5529 -- Simple entry call
5531 Nam := Entity (Selector_Name (Entry_Name));
5532 Obj := Prefix (Entry_Name);
5533 Was_Over := Is_Overloaded (Selector_Name (Entry_Name));
5535 else pragma Assert (Nkind (Entry_Name) = N_Indexed_Component);
5537 -- Call to member of entry family
5539 Nam := Entity (Selector_Name (Prefix (Entry_Name)));
5540 Obj := Prefix (Prefix (Entry_Name));
5541 Was_Over := Is_Overloaded (Selector_Name (Prefix (Entry_Name)));
5542 end if;
5544 -- We cannot in general check the maximum depth of protected entry
5545 -- calls at compile time. But we can tell that any protected entry
5546 -- call at all violates a specified nesting depth of zero.
5548 if Is_Protected_Type (Scope (Nam)) then
5549 Check_Restriction (Max_Entry_Queue_Length, N);
5550 end if;
5552 -- Use context type to disambiguate a protected function that can be
5553 -- called without actuals and that returns an array type, and where
5554 -- the argument list may be an indexing of the returned value.
5556 if Ekind (Nam) = E_Function
5557 and then Needs_No_Actuals (Nam)
5558 and then Present (Parameter_Associations (N))
5559 and then
5560 ((Is_Array_Type (Etype (Nam))
5561 and then Covers (Typ, Component_Type (Etype (Nam))))
5563 or else (Is_Access_Type (Etype (Nam))
5564 and then Is_Array_Type (Designated_Type (Etype (Nam)))
5565 and then Covers (Typ,
5566 Component_Type (Designated_Type (Etype (Nam))))))
5567 then
5568 declare
5569 Index_Node : Node_Id;
5571 begin
5572 Index_Node :=
5573 Make_Indexed_Component (Loc,
5574 Prefix =>
5575 Make_Function_Call (Loc,
5576 Name => Relocate_Node (Entry_Name)),
5577 Expressions => Parameter_Associations (N));
5579 -- Since we are correcting a node classification error made by
5580 -- the parser, we call Replace rather than Rewrite.
5582 Replace (N, Index_Node);
5583 Set_Etype (Prefix (N), Etype (Nam));
5584 Set_Etype (N, Typ);
5585 Resolve_Indexed_Component (N, Typ);
5586 return;
5587 end;
5588 end if;
5590 -- The operation name may have been overloaded. Order the actuals
5591 -- according to the formals of the resolved entity, and set the
5592 -- return type to that of the operation.
5594 if Was_Over then
5595 Normalize_Actuals (N, Nam, False, Norm_OK);
5596 pragma Assert (Norm_OK);
5597 Set_Etype (N, Etype (Nam));
5598 end if;
5600 Resolve_Actuals (N, Nam);
5601 Generate_Reference (Nam, Entry_Name);
5603 if Ekind (Nam) = E_Entry
5604 or else Ekind (Nam) = E_Entry_Family
5605 then
5606 Check_Potentially_Blocking_Operation (N);
5607 end if;
5609 -- Verify that a procedure call cannot masquerade as an entry
5610 -- call where an entry call is expected.
5612 if Ekind (Nam) = E_Procedure then
5613 if Nkind (Parent (N)) = N_Entry_Call_Alternative
5614 and then N = Entry_Call_Statement (Parent (N))
5615 then
5616 Error_Msg_N ("entry call required in select statement", N);
5618 elsif Nkind (Parent (N)) = N_Triggering_Alternative
5619 and then N = Triggering_Statement (Parent (N))
5620 then
5621 Error_Msg_N ("triggering statement cannot be procedure call", N);
5623 elsif Ekind (Scope (Nam)) = E_Task_Type
5624 and then not In_Open_Scopes (Scope (Nam))
5625 then
5626 Error_Msg_N ("task has no entry with this name", Entry_Name);
5627 end if;
5628 end if;
5630 -- After resolution, entry calls and protected procedure calls
5631 -- are changed into entry calls, for expansion. The structure
5632 -- of the node does not change, so it can safely be done in place.
5633 -- Protected function calls must keep their structure because they
5634 -- are subexpressions.
5636 if Ekind (Nam) /= E_Function then
5638 -- A protected operation that is not a function may modify the
5639 -- corresponding object, and cannot apply to a constant.
5640 -- If this is an internal call, the prefix is the type itself.
5642 if Is_Protected_Type (Scope (Nam))
5643 and then not Is_Variable (Obj)
5644 and then (not Is_Entity_Name (Obj)
5645 or else not Is_Type (Entity (Obj)))
5646 then
5647 Error_Msg_N
5648 ("prefix of protected procedure or entry call must be variable",
5649 Entry_Name);
5650 end if;
5652 Actuals := Parameter_Associations (N);
5653 First_Named := First_Named_Actual (N);
5655 Rewrite (N,
5656 Make_Entry_Call_Statement (Loc,
5657 Name => Entry_Name,
5658 Parameter_Associations => Actuals));
5660 Set_First_Named_Actual (N, First_Named);
5661 Set_Analyzed (N, True);
5663 -- Protected functions can return on the secondary stack, in which
5664 -- case we must trigger the transient scope mechanism.
5666 elsif Expander_Active
5667 and then Requires_Transient_Scope (Etype (Nam))
5668 then
5669 Establish_Transient_Scope (N, Sec_Stack => True);
5670 end if;
5671 end Resolve_Entry_Call;
5673 -------------------------
5674 -- Resolve_Equality_Op --
5675 -------------------------
5677 -- Both arguments must have the same type, and the boolean context
5678 -- does not participate in the resolution. The first pass verifies
5679 -- that the interpretation is not ambiguous, and the type of the left
5680 -- argument is correctly set, or is Any_Type in case of ambiguity.
5681 -- If both arguments are strings or aggregates, allocators, or Null,
5682 -- they are ambiguous even though they carry a single (universal) type.
5683 -- Diagnose this case here.
5685 procedure Resolve_Equality_Op (N : Node_Id; Typ : Entity_Id) is
5686 L : constant Node_Id := Left_Opnd (N);
5687 R : constant Node_Id := Right_Opnd (N);
5688 T : Entity_Id := Find_Unique_Type (L, R);
5690 function Find_Unique_Access_Type return Entity_Id;
5691 -- In the case of allocators, make a last-ditch attempt to find a single
5692 -- access type with the right designated type. This is semantically
5693 -- dubious, and of no interest to any real code, but c48008a makes it
5694 -- all worthwhile.
5696 -----------------------------
5697 -- Find_Unique_Access_Type --
5698 -----------------------------
5700 function Find_Unique_Access_Type return Entity_Id is
5701 Acc : Entity_Id;
5702 E : Entity_Id;
5703 S : Entity_Id;
5705 begin
5706 if Ekind (Etype (R)) = E_Allocator_Type then
5707 Acc := Designated_Type (Etype (R));
5708 elsif Ekind (Etype (L)) = E_Allocator_Type then
5709 Acc := Designated_Type (Etype (L));
5710 else
5711 return Empty;
5712 end if;
5714 S := Current_Scope;
5715 while S /= Standard_Standard loop
5716 E := First_Entity (S);
5717 while Present (E) loop
5718 if Is_Type (E)
5719 and then Is_Access_Type (E)
5720 and then Ekind (E) /= E_Allocator_Type
5721 and then Designated_Type (E) = Base_Type (Acc)
5722 then
5723 return E;
5724 end if;
5726 Next_Entity (E);
5727 end loop;
5729 S := Scope (S);
5730 end loop;
5732 return Empty;
5733 end Find_Unique_Access_Type;
5735 -- Start of processing for Resolve_Equality_Op
5737 begin
5738 Set_Etype (N, Base_Type (Typ));
5739 Generate_Reference (T, N, ' ');
5741 if T = Any_Fixed then
5742 T := Unique_Fixed_Point_Type (L);
5743 end if;
5745 if T /= Any_Type then
5746 if T = Any_String
5747 or else T = Any_Composite
5748 or else T = Any_Character
5749 then
5750 if T = Any_Character then
5751 Ambiguous_Character (L);
5752 else
5753 Error_Msg_N ("ambiguous operands for equality", N);
5754 end if;
5756 Set_Etype (N, Any_Type);
5757 return;
5759 elsif T = Any_Access
5760 or else Ekind (T) = E_Allocator_Type
5761 or else Ekind (T) = E_Access_Attribute_Type
5762 then
5763 T := Find_Unique_Access_Type;
5765 if No (T) then
5766 Error_Msg_N ("ambiguous operands for equality", N);
5767 Set_Etype (N, Any_Type);
5768 return;
5769 end if;
5770 end if;
5772 Resolve (L, T);
5773 Resolve (R, T);
5775 -- If the unique type is a class-wide type then it will be expanded
5776 -- into a dispatching call to the predefined primitive. Therefore we
5777 -- check here for potential violation of such restriction.
5779 if Is_Class_Wide_Type (T) then
5780 Check_Restriction (No_Dispatching_Calls, N);
5781 end if;
5783 if Warn_On_Redundant_Constructs
5784 and then Comes_From_Source (N)
5785 and then Is_Entity_Name (R)
5786 and then Entity (R) = Standard_True
5787 and then Comes_From_Source (R)
5788 then
5789 Error_Msg_N ("?comparison with True is redundant!", R);
5790 end if;
5792 Check_Unset_Reference (L);
5793 Check_Unset_Reference (R);
5794 Generate_Operator_Reference (N, T);
5796 -- If this is an inequality, it may be the implicit inequality
5797 -- created for a user-defined operation, in which case the corres-
5798 -- ponding equality operation is not intrinsic, and the operation
5799 -- cannot be constant-folded. Else fold.
5801 if Nkind (N) = N_Op_Eq
5802 or else Comes_From_Source (Entity (N))
5803 or else Ekind (Entity (N)) = E_Operator
5804 or else Is_Intrinsic_Subprogram
5805 (Corresponding_Equality (Entity (N)))
5806 then
5807 Eval_Relational_Op (N);
5808 elsif Nkind (N) = N_Op_Ne
5809 and then Is_Abstract_Subprogram (Entity (N))
5810 then
5811 Error_Msg_NE ("cannot call abstract subprogram &!", N, Entity (N));
5812 end if;
5814 -- Ada 2005: If one operand is an anonymous access type, convert
5815 -- the other operand to it, to ensure that the underlying types
5816 -- match in the back-end. Same for access_to_subprogram, and the
5817 -- conversion verifies that the types are subtype conformant.
5819 -- We apply the same conversion in the case one of the operands is
5820 -- a private subtype of the type of the other.
5822 -- Why the Expander_Active test here ???
5824 if Expander_Active
5825 and then
5826 (Ekind (T) = E_Anonymous_Access_Type
5827 or else Ekind (T) = E_Anonymous_Access_Subprogram_Type
5828 or else Is_Private_Type (T))
5829 then
5830 if Etype (L) /= T then
5831 Rewrite (L,
5832 Make_Unchecked_Type_Conversion (Sloc (L),
5833 Subtype_Mark => New_Occurrence_Of (T, Sloc (L)),
5834 Expression => Relocate_Node (L)));
5835 Analyze_And_Resolve (L, T);
5836 end if;
5838 if (Etype (R)) /= T then
5839 Rewrite (R,
5840 Make_Unchecked_Type_Conversion (Sloc (R),
5841 Subtype_Mark => New_Occurrence_Of (Etype (L), Sloc (R)),
5842 Expression => Relocate_Node (R)));
5843 Analyze_And_Resolve (R, T);
5844 end if;
5845 end if;
5846 end if;
5847 end Resolve_Equality_Op;
5849 ----------------------------------
5850 -- Resolve_Explicit_Dereference --
5851 ----------------------------------
5853 procedure Resolve_Explicit_Dereference (N : Node_Id; Typ : Entity_Id) is
5854 Loc : constant Source_Ptr := Sloc (N);
5855 New_N : Node_Id;
5856 P : constant Node_Id := Prefix (N);
5857 I : Interp_Index;
5858 It : Interp;
5860 begin
5861 Check_Fully_Declared_Prefix (Typ, P);
5863 if Is_Overloaded (P) then
5865 -- Use the context type to select the prefix that has the correct
5866 -- designated type.
5868 Get_First_Interp (P, I, It);
5869 while Present (It.Typ) loop
5870 exit when Is_Access_Type (It.Typ)
5871 and then Covers (Typ, Designated_Type (It.Typ));
5872 Get_Next_Interp (I, It);
5873 end loop;
5875 if Present (It.Typ) then
5876 Resolve (P, It.Typ);
5877 else
5878 -- If no interpretation covers the designated type of the prefix,
5879 -- this is the pathological case where not all implementations of
5880 -- the prefix allow the interpretation of the node as a call. Now
5881 -- that the expected type is known, Remove other interpretations
5882 -- from prefix, rewrite it as a call, and resolve again, so that
5883 -- the proper call node is generated.
5885 Get_First_Interp (P, I, It);
5886 while Present (It.Typ) loop
5887 if Ekind (It.Typ) /= E_Access_Subprogram_Type then
5888 Remove_Interp (I);
5889 end if;
5891 Get_Next_Interp (I, It);
5892 end loop;
5894 New_N :=
5895 Make_Function_Call (Loc,
5896 Name =>
5897 Make_Explicit_Dereference (Loc,
5898 Prefix => P),
5899 Parameter_Associations => New_List);
5901 Save_Interps (N, New_N);
5902 Rewrite (N, New_N);
5903 Analyze_And_Resolve (N, Typ);
5904 return;
5905 end if;
5907 Set_Etype (N, Designated_Type (It.Typ));
5909 else
5910 Resolve (P);
5911 end if;
5913 if Is_Access_Type (Etype (P)) then
5914 Apply_Access_Check (N);
5915 end if;
5917 -- If the designated type is a packed unconstrained array type, and the
5918 -- explicit dereference is not in the context of an attribute reference,
5919 -- then we must compute and set the actual subtype, since it is needed
5920 -- by Gigi. The reason we exclude the attribute case is that this is
5921 -- handled fine by Gigi, and in fact we use such attributes to build the
5922 -- actual subtype. We also exclude generated code (which builds actual
5923 -- subtypes directly if they are needed).
5925 if Is_Array_Type (Etype (N))
5926 and then Is_Packed (Etype (N))
5927 and then not Is_Constrained (Etype (N))
5928 and then Nkind (Parent (N)) /= N_Attribute_Reference
5929 and then Comes_From_Source (N)
5930 then
5931 Set_Etype (N, Get_Actual_Subtype (N));
5932 end if;
5934 -- Note: there is no Eval processing required for an explicit deference,
5935 -- because the type is known to be an allocators, and allocator
5936 -- expressions can never be static.
5938 end Resolve_Explicit_Dereference;
5940 -------------------------------
5941 -- Resolve_Indexed_Component --
5942 -------------------------------
5944 procedure Resolve_Indexed_Component (N : Node_Id; Typ : Entity_Id) is
5945 Name : constant Node_Id := Prefix (N);
5946 Expr : Node_Id;
5947 Array_Type : Entity_Id := Empty; -- to prevent junk warning
5948 Index : Node_Id;
5950 begin
5951 if Is_Overloaded (Name) then
5953 -- Use the context type to select the prefix that yields the correct
5954 -- component type.
5956 declare
5957 I : Interp_Index;
5958 It : Interp;
5959 I1 : Interp_Index := 0;
5960 P : constant Node_Id := Prefix (N);
5961 Found : Boolean := False;
5963 begin
5964 Get_First_Interp (P, I, It);
5965 while Present (It.Typ) loop
5966 if (Is_Array_Type (It.Typ)
5967 and then Covers (Typ, Component_Type (It.Typ)))
5968 or else (Is_Access_Type (It.Typ)
5969 and then Is_Array_Type (Designated_Type (It.Typ))
5970 and then Covers
5971 (Typ, Component_Type (Designated_Type (It.Typ))))
5972 then
5973 if Found then
5974 It := Disambiguate (P, I1, I, Any_Type);
5976 if It = No_Interp then
5977 Error_Msg_N ("ambiguous prefix for indexing", N);
5978 Set_Etype (N, Typ);
5979 return;
5981 else
5982 Found := True;
5983 Array_Type := It.Typ;
5984 I1 := I;
5985 end if;
5987 else
5988 Found := True;
5989 Array_Type := It.Typ;
5990 I1 := I;
5991 end if;
5992 end if;
5994 Get_Next_Interp (I, It);
5995 end loop;
5996 end;
5998 else
5999 Array_Type := Etype (Name);
6000 end if;
6002 Resolve (Name, Array_Type);
6003 Array_Type := Get_Actual_Subtype_If_Available (Name);
6005 -- If prefix is access type, dereference to get real array type.
6006 -- Note: we do not apply an access check because the expander always
6007 -- introduces an explicit dereference, and the check will happen there.
6009 if Is_Access_Type (Array_Type) then
6010 Array_Type := Designated_Type (Array_Type);
6011 end if;
6013 -- If name was overloaded, set component type correctly now
6014 -- If a misplaced call to an entry family (which has no index typs)
6015 -- return. Error will be diagnosed from calling context.
6017 if Is_Array_Type (Array_Type) then
6018 Set_Etype (N, Component_Type (Array_Type));
6019 else
6020 return;
6021 end if;
6023 Index := First_Index (Array_Type);
6024 Expr := First (Expressions (N));
6026 -- The prefix may have resolved to a string literal, in which case its
6027 -- etype has a special representation. This is only possible currently
6028 -- if the prefix is a static concatenation, written in functional
6029 -- notation.
6031 if Ekind (Array_Type) = E_String_Literal_Subtype then
6032 Resolve (Expr, Standard_Positive);
6034 else
6035 while Present (Index) and Present (Expr) loop
6036 Resolve (Expr, Etype (Index));
6037 Check_Unset_Reference (Expr);
6039 if Is_Scalar_Type (Etype (Expr)) then
6040 Apply_Scalar_Range_Check (Expr, Etype (Index));
6041 else
6042 Apply_Range_Check (Expr, Get_Actual_Subtype (Index));
6043 end if;
6045 Next_Index (Index);
6046 Next (Expr);
6047 end loop;
6048 end if;
6050 -- Do not generate the warning on suspicious index if we are analyzing
6051 -- package Ada.Tags; otherwise we will report the warning with the
6052 -- Prims_Ptr field of the dispatch table.
6054 if Scope (Etype (Prefix (N))) = Standard_Standard
6055 or else not
6056 Is_RTU (Cunit_Entity (Get_Source_Unit (Etype (Prefix (N)))),
6057 Ada_Tags)
6058 then
6059 Warn_On_Suspicious_Index (Name, First (Expressions (N)));
6060 Eval_Indexed_Component (N);
6061 end if;
6062 end Resolve_Indexed_Component;
6064 -----------------------------
6065 -- Resolve_Integer_Literal --
6066 -----------------------------
6068 procedure Resolve_Integer_Literal (N : Node_Id; Typ : Entity_Id) is
6069 begin
6070 Set_Etype (N, Typ);
6071 Eval_Integer_Literal (N);
6072 end Resolve_Integer_Literal;
6074 --------------------------------
6075 -- Resolve_Intrinsic_Operator --
6076 --------------------------------
6078 procedure Resolve_Intrinsic_Operator (N : Node_Id; Typ : Entity_Id) is
6079 Btyp : constant Entity_Id := Base_Type (Underlying_Type (Typ));
6080 Op : Entity_Id;
6081 Arg1 : Node_Id;
6082 Arg2 : Node_Id;
6084 begin
6085 Op := Entity (N);
6086 while Scope (Op) /= Standard_Standard loop
6087 Op := Homonym (Op);
6088 pragma Assert (Present (Op));
6089 end loop;
6091 Set_Entity (N, Op);
6092 Set_Is_Overloaded (N, False);
6094 -- If the operand type is private, rewrite with suitable conversions on
6095 -- the operands and the result, to expose the proper underlying numeric
6096 -- type.
6098 if Is_Private_Type (Typ) then
6099 Arg1 := Unchecked_Convert_To (Btyp, Left_Opnd (N));
6101 if Nkind (N) = N_Op_Expon then
6102 Arg2 := Unchecked_Convert_To (Standard_Integer, Right_Opnd (N));
6103 else
6104 Arg2 := Unchecked_Convert_To (Btyp, Right_Opnd (N));
6105 end if;
6107 Save_Interps (Left_Opnd (N), Expression (Arg1));
6108 Save_Interps (Right_Opnd (N), Expression (Arg2));
6110 Set_Left_Opnd (N, Arg1);
6111 Set_Right_Opnd (N, Arg2);
6113 Set_Etype (N, Btyp);
6114 Rewrite (N, Unchecked_Convert_To (Typ, N));
6115 Resolve (N, Typ);
6117 elsif Typ /= Etype (Left_Opnd (N))
6118 or else Typ /= Etype (Right_Opnd (N))
6119 then
6120 -- Add explicit conversion where needed, and save interpretations
6121 -- in case operands are overloaded.
6123 Arg1 := Convert_To (Typ, Left_Opnd (N));
6124 Arg2 := Convert_To (Typ, Right_Opnd (N));
6126 if Nkind (Arg1) = N_Type_Conversion then
6127 Save_Interps (Left_Opnd (N), Expression (Arg1));
6128 else
6129 Save_Interps (Left_Opnd (N), Arg1);
6130 end if;
6132 if Nkind (Arg2) = N_Type_Conversion then
6133 Save_Interps (Right_Opnd (N), Expression (Arg2));
6134 else
6135 Save_Interps (Right_Opnd (N), Arg2);
6136 end if;
6138 Rewrite (Left_Opnd (N), Arg1);
6139 Rewrite (Right_Opnd (N), Arg2);
6140 Analyze (Arg1);
6141 Analyze (Arg2);
6142 Resolve_Arithmetic_Op (N, Typ);
6144 else
6145 Resolve_Arithmetic_Op (N, Typ);
6146 end if;
6147 end Resolve_Intrinsic_Operator;
6149 --------------------------------------
6150 -- Resolve_Intrinsic_Unary_Operator --
6151 --------------------------------------
6153 procedure Resolve_Intrinsic_Unary_Operator
6154 (N : Node_Id;
6155 Typ : Entity_Id)
6157 Btyp : constant Entity_Id := Base_Type (Underlying_Type (Typ));
6158 Op : Entity_Id;
6159 Arg2 : Node_Id;
6161 begin
6162 Op := Entity (N);
6163 while Scope (Op) /= Standard_Standard loop
6164 Op := Homonym (Op);
6165 pragma Assert (Present (Op));
6166 end loop;
6168 Set_Entity (N, Op);
6170 if Is_Private_Type (Typ) then
6171 Arg2 := Unchecked_Convert_To (Btyp, Right_Opnd (N));
6172 Save_Interps (Right_Opnd (N), Expression (Arg2));
6174 Set_Right_Opnd (N, Arg2);
6176 Set_Etype (N, Btyp);
6177 Rewrite (N, Unchecked_Convert_To (Typ, N));
6178 Resolve (N, Typ);
6180 else
6181 Resolve_Unary_Op (N, Typ);
6182 end if;
6183 end Resolve_Intrinsic_Unary_Operator;
6185 ------------------------
6186 -- Resolve_Logical_Op --
6187 ------------------------
6189 procedure Resolve_Logical_Op (N : Node_Id; Typ : Entity_Id) is
6190 B_Typ : Entity_Id;
6191 N_Opr : constant Node_Kind := Nkind (N);
6193 begin
6194 -- Predefined operations on scalar types yield the base type. On the
6195 -- other hand, logical operations on arrays yield the type of the
6196 -- arguments (and the context).
6198 if Is_Array_Type (Typ) then
6199 B_Typ := Typ;
6200 else
6201 B_Typ := Base_Type (Typ);
6202 end if;
6204 -- The following test is required because the operands of the operation
6205 -- may be literals, in which case the resulting type appears to be
6206 -- compatible with a signed integer type, when in fact it is compatible
6207 -- only with modular types. If the context itself is universal, the
6208 -- operation is illegal.
6210 if not Valid_Boolean_Arg (Typ) then
6211 Error_Msg_N ("invalid context for logical operation", N);
6212 Set_Etype (N, Any_Type);
6213 return;
6215 elsif Typ = Any_Modular then
6216 Error_Msg_N
6217 ("no modular type available in this context", N);
6218 Set_Etype (N, Any_Type);
6219 return;
6220 elsif Is_Modular_Integer_Type (Typ)
6221 and then Etype (Left_Opnd (N)) = Universal_Integer
6222 and then Etype (Right_Opnd (N)) = Universal_Integer
6223 then
6224 Check_For_Visible_Operator (N, B_Typ);
6225 end if;
6227 Resolve (Left_Opnd (N), B_Typ);
6228 Resolve (Right_Opnd (N), B_Typ);
6230 Check_Unset_Reference (Left_Opnd (N));
6231 Check_Unset_Reference (Right_Opnd (N));
6233 Set_Etype (N, B_Typ);
6234 Generate_Operator_Reference (N, B_Typ);
6235 Eval_Logical_Op (N);
6237 -- Check for violation of restriction No_Direct_Boolean_Operators
6238 -- if the operator was not eliminated by the Eval_Logical_Op call.
6240 if Nkind (N) = N_Opr
6241 and then Root_Type (Etype (Left_Opnd (N))) = Standard_Boolean
6242 then
6243 Check_Restriction (No_Direct_Boolean_Operators, N);
6244 end if;
6245 end Resolve_Logical_Op;
6247 ---------------------------
6248 -- Resolve_Membership_Op --
6249 ---------------------------
6251 -- The context can only be a boolean type, and does not determine
6252 -- the arguments. Arguments should be unambiguous, but the preference
6253 -- rule for universal types applies.
6255 procedure Resolve_Membership_Op (N : Node_Id; Typ : Entity_Id) is
6256 pragma Warnings (Off, Typ);
6258 L : constant Node_Id := Left_Opnd (N);
6259 R : constant Node_Id := Right_Opnd (N);
6260 T : Entity_Id;
6262 begin
6263 if L = Error or else R = Error then
6264 return;
6265 end if;
6267 if not Is_Overloaded (R)
6268 and then
6269 (Etype (R) = Universal_Integer or else
6270 Etype (R) = Universal_Real)
6271 and then Is_Overloaded (L)
6272 then
6273 T := Etype (R);
6275 -- Ada 2005 (AI-251): Give support to the following case:
6277 -- type I is interface;
6278 -- type T is tagged ...
6280 -- function Test (O : I'Class) is
6281 -- begin
6282 -- return O in T'Class.
6283 -- end Test;
6285 -- In this case we have nothing else to do; the membership test will be
6286 -- done at run-time.
6288 elsif Ada_Version >= Ada_05
6289 and then Is_Class_Wide_Type (Etype (L))
6290 and then Is_Interface (Etype (L))
6291 and then Is_Class_Wide_Type (Etype (R))
6292 and then not Is_Interface (Etype (R))
6293 then
6294 return;
6296 else
6297 T := Intersect_Types (L, R);
6298 end if;
6300 Resolve (L, T);
6301 Check_Unset_Reference (L);
6303 if Nkind (R) = N_Range
6304 and then not Is_Scalar_Type (T)
6305 then
6306 Error_Msg_N ("scalar type required for range", R);
6307 end if;
6309 if Is_Entity_Name (R) then
6310 Freeze_Expression (R);
6311 else
6312 Resolve (R, T);
6313 Check_Unset_Reference (R);
6314 end if;
6316 Eval_Membership_Op (N);
6317 end Resolve_Membership_Op;
6319 ------------------
6320 -- Resolve_Null --
6321 ------------------
6323 procedure Resolve_Null (N : Node_Id; Typ : Entity_Id) is
6324 begin
6325 -- Handle restriction against anonymous null access values This
6326 -- restriction can be turned off using -gnatdh.
6328 -- Ada 2005 (AI-231): Remove restriction
6330 if Ada_Version < Ada_05
6331 and then not Debug_Flag_J
6332 and then Ekind (Typ) = E_Anonymous_Access_Type
6333 and then Comes_From_Source (N)
6334 then
6335 -- In the common case of a call which uses an explicitly null
6336 -- value for an access parameter, give specialized error msg
6338 if Nkind (Parent (N)) = N_Procedure_Call_Statement
6339 or else
6340 Nkind (Parent (N)) = N_Function_Call
6341 then
6342 Error_Msg_N
6343 ("null is not allowed as argument for an access parameter", N);
6345 -- Standard message for all other cases (are there any?)
6347 else
6348 Error_Msg_N
6349 ("null cannot be of an anonymous access type", N);
6350 end if;
6351 end if;
6353 -- In a distributed context, null for a remote access to subprogram
6354 -- may need to be replaced with a special record aggregate. In this
6355 -- case, return after having done the transformation.
6357 if (Ekind (Typ) = E_Record_Type
6358 or else Is_Remote_Access_To_Subprogram_Type (Typ))
6359 and then Remote_AST_Null_Value (N, Typ)
6360 then
6361 return;
6362 end if;
6364 -- The null literal takes its type from the context
6366 Set_Etype (N, Typ);
6367 end Resolve_Null;
6369 -----------------------
6370 -- Resolve_Op_Concat --
6371 -----------------------
6373 procedure Resolve_Op_Concat (N : Node_Id; Typ : Entity_Id) is
6375 -- We wish to avoid deep recursion, because concatenations are often
6376 -- deeply nested, as in A&B&...&Z. Therefore, we walk down the left
6377 -- operands nonrecursively until we find something that is not a simple
6378 -- concatenation (A in this case). We resolve that, and then walk back
6379 -- up the tree following Parent pointers, calling Resolve_Op_Concat_Rest
6380 -- to do the rest of the work at each level. The Parent pointers allow
6381 -- us to avoid recursion, and thus avoid running out of memory. See also
6382 -- Sem_Ch4.Analyze_Concatenation, where a similar hack is used.
6384 NN : Node_Id := N;
6385 Op1 : Node_Id;
6387 begin
6388 -- The following code is equivalent to:
6390 -- Resolve_Op_Concat_First (NN, Typ);
6391 -- Resolve_Op_Concat_Arg (N, ...);
6392 -- Resolve_Op_Concat_Rest (N, Typ);
6394 -- where the Resolve_Op_Concat_Arg call recurses back here if the left
6395 -- operand is a concatenation.
6397 -- Walk down left operands
6399 loop
6400 Resolve_Op_Concat_First (NN, Typ);
6401 Op1 := Left_Opnd (NN);
6402 exit when not (Nkind (Op1) = N_Op_Concat
6403 and then not Is_Array_Type (Component_Type (Typ))
6404 and then Entity (Op1) = Entity (NN));
6405 NN := Op1;
6406 end loop;
6408 -- Now (given the above example) NN is A&B and Op1 is A
6410 -- First resolve Op1 ...
6412 Resolve_Op_Concat_Arg (NN, Op1, Typ, Is_Component_Left_Opnd (NN));
6414 -- ... then walk NN back up until we reach N (where we started), calling
6415 -- Resolve_Op_Concat_Rest along the way.
6417 loop
6418 Resolve_Op_Concat_Rest (NN, Typ);
6419 exit when NN = N;
6420 NN := Parent (NN);
6421 end loop;
6422 end Resolve_Op_Concat;
6424 ---------------------------
6425 -- Resolve_Op_Concat_Arg --
6426 ---------------------------
6428 procedure Resolve_Op_Concat_Arg
6429 (N : Node_Id;
6430 Arg : Node_Id;
6431 Typ : Entity_Id;
6432 Is_Comp : Boolean)
6434 Btyp : constant Entity_Id := Base_Type (Typ);
6436 begin
6437 if In_Instance then
6438 if Is_Comp
6439 or else (not Is_Overloaded (Arg)
6440 and then Etype (Arg) /= Any_Composite
6441 and then Covers (Component_Type (Typ), Etype (Arg)))
6442 then
6443 Resolve (Arg, Component_Type (Typ));
6444 else
6445 Resolve (Arg, Btyp);
6446 end if;
6448 elsif Has_Compatible_Type (Arg, Component_Type (Typ)) then
6449 if Nkind (Arg) = N_Aggregate
6450 and then Is_Composite_Type (Component_Type (Typ))
6451 then
6452 if Is_Private_Type (Component_Type (Typ)) then
6453 Resolve (Arg, Btyp);
6454 else
6455 Error_Msg_N ("ambiguous aggregate must be qualified", Arg);
6456 Set_Etype (Arg, Any_Type);
6457 end if;
6459 else
6460 if Is_Overloaded (Arg)
6461 and then Has_Compatible_Type (Arg, Typ)
6462 and then Etype (Arg) /= Any_Type
6463 then
6464 declare
6465 I : Interp_Index;
6466 It : Interp;
6467 Func : Entity_Id;
6469 begin
6470 Get_First_Interp (Arg, I, It);
6471 Func := It.Nam;
6472 Get_Next_Interp (I, It);
6474 -- Special-case the error message when the overloading is
6475 -- caused by a function that yields an array and can be
6476 -- called without parameters.
6478 if It.Nam = Func then
6479 Error_Msg_Sloc := Sloc (Func);
6480 Error_Msg_N ("ambiguous call to function#", Arg);
6481 Error_Msg_NE
6482 ("\\interpretation as call yields&", Arg, Typ);
6483 Error_Msg_NE
6484 ("\\interpretation as indexing of call yields&",
6485 Arg, Component_Type (Typ));
6487 else
6488 Error_Msg_N
6489 ("ambiguous operand for concatenation!", Arg);
6490 Get_First_Interp (Arg, I, It);
6491 while Present (It.Nam) loop
6492 Error_Msg_Sloc := Sloc (It.Nam);
6494 if Base_Type (It.Typ) = Base_Type (Typ)
6495 or else Base_Type (It.Typ) =
6496 Base_Type (Component_Type (Typ))
6497 then
6498 Error_Msg_N ("\\possible interpretation#", Arg);
6499 end if;
6501 Get_Next_Interp (I, It);
6502 end loop;
6503 end if;
6504 end;
6505 end if;
6507 Resolve (Arg, Component_Type (Typ));
6509 if Nkind (Arg) = N_String_Literal then
6510 Set_Etype (Arg, Component_Type (Typ));
6511 end if;
6513 if Arg = Left_Opnd (N) then
6514 Set_Is_Component_Left_Opnd (N);
6515 else
6516 Set_Is_Component_Right_Opnd (N);
6517 end if;
6518 end if;
6520 else
6521 Resolve (Arg, Btyp);
6522 end if;
6524 Check_Unset_Reference (Arg);
6525 end Resolve_Op_Concat_Arg;
6527 -----------------------------
6528 -- Resolve_Op_Concat_First --
6529 -----------------------------
6531 procedure Resolve_Op_Concat_First (N : Node_Id; Typ : Entity_Id) is
6532 Btyp : constant Entity_Id := Base_Type (Typ);
6533 Op1 : constant Node_Id := Left_Opnd (N);
6534 Op2 : constant Node_Id := Right_Opnd (N);
6536 begin
6537 -- The parser folds an enormous sequence of concatenations of string
6538 -- literals into "" & "...", where the Is_Folded_In_Parser flag is set
6539 -- in the right. If the expression resolves to a predefined "&"
6540 -- operator, all is well. Otherwise, the parser's folding is wrong, so
6541 -- we give an error. See P_Simple_Expression in Par.Ch4.
6543 if Nkind (Op2) = N_String_Literal
6544 and then Is_Folded_In_Parser (Op2)
6545 and then Ekind (Entity (N)) = E_Function
6546 then
6547 pragma Assert (Nkind (Op1) = N_String_Literal -- should be ""
6548 and then String_Length (Strval (Op1)) = 0);
6549 Error_Msg_N ("too many user-defined concatenations", N);
6550 return;
6551 end if;
6553 Set_Etype (N, Btyp);
6555 if Is_Limited_Composite (Btyp) then
6556 Error_Msg_N ("concatenation not available for limited array", N);
6557 Explain_Limited_Type (Btyp, N);
6558 end if;
6559 end Resolve_Op_Concat_First;
6561 ----------------------------
6562 -- Resolve_Op_Concat_Rest --
6563 ----------------------------
6565 procedure Resolve_Op_Concat_Rest (N : Node_Id; Typ : Entity_Id) is
6566 Op1 : constant Node_Id := Left_Opnd (N);
6567 Op2 : constant Node_Id := Right_Opnd (N);
6569 begin
6570 Resolve_Op_Concat_Arg (N, Op2, Typ, Is_Component_Right_Opnd (N));
6572 Generate_Operator_Reference (N, Typ);
6574 if Is_String_Type (Typ) then
6575 Eval_Concatenation (N);
6576 end if;
6578 -- If this is not a static concatenation, but the result is a
6579 -- string type (and not an array of strings) ensure that static
6580 -- string operands have their subtypes properly constructed.
6582 if Nkind (N) /= N_String_Literal
6583 and then Is_Character_Type (Component_Type (Typ))
6584 then
6585 Set_String_Literal_Subtype (Op1, Typ);
6586 Set_String_Literal_Subtype (Op2, Typ);
6587 end if;
6588 end Resolve_Op_Concat_Rest;
6590 ----------------------
6591 -- Resolve_Op_Expon --
6592 ----------------------
6594 procedure Resolve_Op_Expon (N : Node_Id; Typ : Entity_Id) is
6595 B_Typ : constant Entity_Id := Base_Type (Typ);
6597 begin
6598 -- Catch attempts to do fixed-point exponentation with universal
6599 -- operands, which is a case where the illegality is not caught during
6600 -- normal operator analysis.
6602 if Is_Fixed_Point_Type (Typ) and then Comes_From_Source (N) then
6603 Error_Msg_N ("exponentiation not available for fixed point", N);
6604 return;
6605 end if;
6607 if Comes_From_Source (N)
6608 and then Ekind (Entity (N)) = E_Function
6609 and then Is_Imported (Entity (N))
6610 and then Is_Intrinsic_Subprogram (Entity (N))
6611 then
6612 Resolve_Intrinsic_Operator (N, Typ);
6613 return;
6614 end if;
6616 if Etype (Left_Opnd (N)) = Universal_Integer
6617 or else Etype (Left_Opnd (N)) = Universal_Real
6618 then
6619 Check_For_Visible_Operator (N, B_Typ);
6620 end if;
6622 -- We do the resolution using the base type, because intermediate values
6623 -- in expressions always are of the base type, not a subtype of it.
6625 Resolve (Left_Opnd (N), B_Typ);
6626 Resolve (Right_Opnd (N), Standard_Integer);
6628 Check_Unset_Reference (Left_Opnd (N));
6629 Check_Unset_Reference (Right_Opnd (N));
6631 Set_Etype (N, B_Typ);
6632 Generate_Operator_Reference (N, B_Typ);
6633 Eval_Op_Expon (N);
6635 -- Set overflow checking bit. Much cleverer code needed here eventually
6636 -- and perhaps the Resolve routines should be separated for the various
6637 -- arithmetic operations, since they will need different processing. ???
6639 if Nkind (N) in N_Op then
6640 if not Overflow_Checks_Suppressed (Etype (N)) then
6641 Enable_Overflow_Check (N);
6642 end if;
6643 end if;
6644 end Resolve_Op_Expon;
6646 --------------------
6647 -- Resolve_Op_Not --
6648 --------------------
6650 procedure Resolve_Op_Not (N : Node_Id; Typ : Entity_Id) is
6651 B_Typ : Entity_Id;
6653 function Parent_Is_Boolean return Boolean;
6654 -- This function determines if the parent node is a boolean operator
6655 -- or operation (comparison op, membership test, or short circuit form)
6656 -- and the not in question is the left operand of this operation.
6657 -- Note that if the not is in parens, then false is returned.
6659 -----------------------
6660 -- Parent_Is_Boolean --
6661 -----------------------
6663 function Parent_Is_Boolean return Boolean is
6664 begin
6665 if Paren_Count (N) /= 0 then
6666 return False;
6668 else
6669 case Nkind (Parent (N)) is
6670 when N_Op_And |
6671 N_Op_Eq |
6672 N_Op_Ge |
6673 N_Op_Gt |
6674 N_Op_Le |
6675 N_Op_Lt |
6676 N_Op_Ne |
6677 N_Op_Or |
6678 N_Op_Xor |
6679 N_In |
6680 N_Not_In |
6681 N_And_Then |
6682 N_Or_Else =>
6684 return Left_Opnd (Parent (N)) = N;
6686 when others =>
6687 return False;
6688 end case;
6689 end if;
6690 end Parent_Is_Boolean;
6692 -- Start of processing for Resolve_Op_Not
6694 begin
6695 -- Predefined operations on scalar types yield the base type. On the
6696 -- other hand, logical operations on arrays yield the type of the
6697 -- arguments (and the context).
6699 if Is_Array_Type (Typ) then
6700 B_Typ := Typ;
6701 else
6702 B_Typ := Base_Type (Typ);
6703 end if;
6705 -- Straigtforward case of incorrect arguments
6707 if not Valid_Boolean_Arg (Typ) then
6708 Error_Msg_N ("invalid operand type for operator&", N);
6709 Set_Etype (N, Any_Type);
6710 return;
6712 -- Special case of probable missing parens
6714 elsif Typ = Universal_Integer or else Typ = Any_Modular then
6715 if Parent_Is_Boolean then
6716 Error_Msg_N
6717 ("operand of not must be enclosed in parentheses",
6718 Right_Opnd (N));
6719 else
6720 Error_Msg_N
6721 ("no modular type available in this context", N);
6722 end if;
6724 Set_Etype (N, Any_Type);
6725 return;
6727 -- OK resolution of not
6729 else
6730 -- Warn if non-boolean types involved. This is a case like not a < b
6731 -- where a and b are modular, where we will get (not a) < b and most
6732 -- likely not (a < b) was intended.
6734 if Warn_On_Questionable_Missing_Parens
6735 and then not Is_Boolean_Type (Typ)
6736 and then Parent_Is_Boolean
6737 then
6738 Error_Msg_N ("?not expression should be parenthesized here!", N);
6739 end if;
6741 Resolve (Right_Opnd (N), B_Typ);
6742 Check_Unset_Reference (Right_Opnd (N));
6743 Set_Etype (N, B_Typ);
6744 Generate_Operator_Reference (N, B_Typ);
6745 Eval_Op_Not (N);
6746 end if;
6747 end Resolve_Op_Not;
6749 -----------------------------
6750 -- Resolve_Operator_Symbol --
6751 -----------------------------
6753 -- Nothing to be done, all resolved already
6755 procedure Resolve_Operator_Symbol (N : Node_Id; Typ : Entity_Id) is
6756 pragma Warnings (Off, N);
6757 pragma Warnings (Off, Typ);
6759 begin
6760 null;
6761 end Resolve_Operator_Symbol;
6763 ----------------------------------
6764 -- Resolve_Qualified_Expression --
6765 ----------------------------------
6767 procedure Resolve_Qualified_Expression (N : Node_Id; Typ : Entity_Id) is
6768 pragma Warnings (Off, Typ);
6770 Target_Typ : constant Entity_Id := Entity (Subtype_Mark (N));
6771 Expr : constant Node_Id := Expression (N);
6773 begin
6774 Resolve (Expr, Target_Typ);
6776 -- A qualified expression requires an exact match of the type,
6777 -- class-wide matching is not allowed. However, if the qualifying
6778 -- type is specific and the expression has a class-wide type, it
6779 -- may still be okay, since it can be the result of the expansion
6780 -- of a call to a dispatching function, so we also have to check
6781 -- class-wideness of the type of the expression's original node.
6783 if (Is_Class_Wide_Type (Target_Typ)
6784 or else
6785 (Is_Class_Wide_Type (Etype (Expr))
6786 and then Is_Class_Wide_Type (Etype (Original_Node (Expr)))))
6787 and then Base_Type (Etype (Expr)) /= Base_Type (Target_Typ)
6788 then
6789 Wrong_Type (Expr, Target_Typ);
6790 end if;
6792 -- If the target type is unconstrained, then we reset the type of
6793 -- the result from the type of the expression. For other cases, the
6794 -- actual subtype of the expression is the target type.
6796 if Is_Composite_Type (Target_Typ)
6797 and then not Is_Constrained (Target_Typ)
6798 then
6799 Set_Etype (N, Etype (Expr));
6800 end if;
6802 Eval_Qualified_Expression (N);
6803 end Resolve_Qualified_Expression;
6805 -------------------
6806 -- Resolve_Range --
6807 -------------------
6809 procedure Resolve_Range (N : Node_Id; Typ : Entity_Id) is
6810 L : constant Node_Id := Low_Bound (N);
6811 H : constant Node_Id := High_Bound (N);
6813 begin
6814 Set_Etype (N, Typ);
6815 Resolve (L, Typ);
6816 Resolve (H, Typ);
6818 Check_Unset_Reference (L);
6819 Check_Unset_Reference (H);
6821 -- We have to check the bounds for being within the base range as
6822 -- required for a non-static context. Normally this is automatic and
6823 -- done as part of evaluating expressions, but the N_Range node is an
6824 -- exception, since in GNAT we consider this node to be a subexpression,
6825 -- even though in Ada it is not. The circuit in Sem_Eval could check for
6826 -- this, but that would put the test on the main evaluation path for
6827 -- expressions.
6829 Check_Non_Static_Context (L);
6830 Check_Non_Static_Context (H);
6832 -- Check for an ambiguous range over character literals. This will
6833 -- happen with a membership test involving only literals.
6835 if Typ = Any_Character then
6836 Ambiguous_Character (L);
6837 Set_Etype (N, Any_Type);
6838 return;
6839 end if;
6841 -- If bounds are static, constant-fold them, so size computations
6842 -- are identical between front-end and back-end. Do not perform this
6843 -- transformation while analyzing generic units, as type information
6844 -- would then be lost when reanalyzing the constant node in the
6845 -- instance.
6847 if Is_Discrete_Type (Typ) and then Expander_Active then
6848 if Is_OK_Static_Expression (L) then
6849 Fold_Uint (L, Expr_Value (L), Is_Static_Expression (L));
6850 end if;
6852 if Is_OK_Static_Expression (H) then
6853 Fold_Uint (H, Expr_Value (H), Is_Static_Expression (H));
6854 end if;
6855 end if;
6856 end Resolve_Range;
6858 --------------------------
6859 -- Resolve_Real_Literal --
6860 --------------------------
6862 procedure Resolve_Real_Literal (N : Node_Id; Typ : Entity_Id) is
6863 Actual_Typ : constant Entity_Id := Etype (N);
6865 begin
6866 -- Special processing for fixed-point literals to make sure that the
6867 -- value is an exact multiple of small where this is required. We
6868 -- skip this for the universal real case, and also for generic types.
6870 if Is_Fixed_Point_Type (Typ)
6871 and then Typ /= Universal_Fixed
6872 and then Typ /= Any_Fixed
6873 and then not Is_Generic_Type (Typ)
6874 then
6875 declare
6876 Val : constant Ureal := Realval (N);
6877 Cintr : constant Ureal := Val / Small_Value (Typ);
6878 Cint : constant Uint := UR_Trunc (Cintr);
6879 Den : constant Uint := Norm_Den (Cintr);
6880 Stat : Boolean;
6882 begin
6883 -- Case of literal is not an exact multiple of the Small
6885 if Den /= 1 then
6887 -- For a source program literal for a decimal fixed-point
6888 -- type, this is statically illegal (RM 4.9(36)).
6890 if Is_Decimal_Fixed_Point_Type (Typ)
6891 and then Actual_Typ = Universal_Real
6892 and then Comes_From_Source (N)
6893 then
6894 Error_Msg_N ("value has extraneous low order digits", N);
6895 end if;
6897 -- Generate a warning if literal from source
6899 if Is_Static_Expression (N)
6900 and then Warn_On_Bad_Fixed_Value
6901 then
6902 Error_Msg_N
6903 ("?static fixed-point value is not a multiple of Small!",
6905 end if;
6907 -- Replace literal by a value that is the exact representation
6908 -- of a value of the type, i.e. a multiple of the small value,
6909 -- by truncation, since Machine_Rounds is false for all GNAT
6910 -- fixed-point types (RM 4.9(38)).
6912 Stat := Is_Static_Expression (N);
6913 Rewrite (N,
6914 Make_Real_Literal (Sloc (N),
6915 Realval => Small_Value (Typ) * Cint));
6917 Set_Is_Static_Expression (N, Stat);
6918 end if;
6920 -- In all cases, set the corresponding integer field
6922 Set_Corresponding_Integer_Value (N, Cint);
6923 end;
6924 end if;
6926 -- Now replace the actual type by the expected type as usual
6928 Set_Etype (N, Typ);
6929 Eval_Real_Literal (N);
6930 end Resolve_Real_Literal;
6932 -----------------------
6933 -- Resolve_Reference --
6934 -----------------------
6936 procedure Resolve_Reference (N : Node_Id; Typ : Entity_Id) is
6937 P : constant Node_Id := Prefix (N);
6939 begin
6940 -- Replace general access with specific type
6942 if Ekind (Etype (N)) = E_Allocator_Type then
6943 Set_Etype (N, Base_Type (Typ));
6944 end if;
6946 Resolve (P, Designated_Type (Etype (N)));
6948 -- If we are taking the reference of a volatile entity, then treat
6949 -- it as a potential modification of this entity. This is much too
6950 -- conservative, but is necessary because remove side effects can
6951 -- result in transformations of normal assignments into reference
6952 -- sequences that otherwise fail to notice the modification.
6954 if Is_Entity_Name (P) and then Treat_As_Volatile (Entity (P)) then
6955 Note_Possible_Modification (P);
6956 end if;
6957 end Resolve_Reference;
6959 --------------------------------
6960 -- Resolve_Selected_Component --
6961 --------------------------------
6963 procedure Resolve_Selected_Component (N : Node_Id; Typ : Entity_Id) is
6964 Comp : Entity_Id;
6965 Comp1 : Entity_Id := Empty; -- prevent junk warning
6966 P : constant Node_Id := Prefix (N);
6967 S : constant Node_Id := Selector_Name (N);
6968 T : Entity_Id := Etype (P);
6969 I : Interp_Index;
6970 I1 : Interp_Index := 0; -- prevent junk warning
6971 It : Interp;
6972 It1 : Interp;
6973 Found : Boolean;
6975 function Init_Component return Boolean;
6976 -- Check whether this is the initialization of a component within an
6977 -- init proc (by assignment or call to another init proc). If true,
6978 -- there is no need for a discriminant check.
6980 --------------------
6981 -- Init_Component --
6982 --------------------
6984 function Init_Component return Boolean is
6985 begin
6986 return Inside_Init_Proc
6987 and then Nkind (Prefix (N)) = N_Identifier
6988 and then Chars (Prefix (N)) = Name_uInit
6989 and then Nkind (Parent (Parent (N))) = N_Case_Statement_Alternative;
6990 end Init_Component;
6992 -- Start of processing for Resolve_Selected_Component
6994 begin
6995 if Is_Overloaded (P) then
6997 -- Use the context type to select the prefix that has a selector
6998 -- of the correct name and type.
7000 Found := False;
7001 Get_First_Interp (P, I, It);
7003 Search : while Present (It.Typ) loop
7004 if Is_Access_Type (It.Typ) then
7005 T := Designated_Type (It.Typ);
7006 else
7007 T := It.Typ;
7008 end if;
7010 if Is_Record_Type (T) then
7012 -- The visible components of a class-wide type are those of
7013 -- the root type.
7015 if Is_Class_Wide_Type (T) then
7016 T := Etype (T);
7017 end if;
7019 Comp := First_Entity (T);
7020 while Present (Comp) loop
7021 if Chars (Comp) = Chars (S)
7022 and then Covers (Etype (Comp), Typ)
7023 then
7024 if not Found then
7025 Found := True;
7026 I1 := I;
7027 It1 := It;
7028 Comp1 := Comp;
7030 else
7031 It := Disambiguate (P, I1, I, Any_Type);
7033 if It = No_Interp then
7034 Error_Msg_N
7035 ("ambiguous prefix for selected component", N);
7036 Set_Etype (N, Typ);
7037 return;
7039 else
7040 It1 := It;
7042 -- There may be an implicit dereference. Retrieve
7043 -- designated record type.
7045 if Is_Access_Type (It1.Typ) then
7046 T := Designated_Type (It1.Typ);
7047 else
7048 T := It1.Typ;
7049 end if;
7051 if Scope (Comp1) /= T then
7053 -- Resolution chooses the new interpretation.
7054 -- Find the component with the right name.
7056 Comp1 := First_Entity (T);
7057 while Present (Comp1)
7058 and then Chars (Comp1) /= Chars (S)
7059 loop
7060 Comp1 := Next_Entity (Comp1);
7061 end loop;
7062 end if;
7064 exit Search;
7065 end if;
7066 end if;
7067 end if;
7069 Comp := Next_Entity (Comp);
7070 end loop;
7072 end if;
7074 Get_Next_Interp (I, It);
7075 end loop Search;
7077 Resolve (P, It1.Typ);
7078 Set_Etype (N, Typ);
7079 Set_Entity_With_Style_Check (S, Comp1);
7081 else
7082 -- Resolve prefix with its type
7084 Resolve (P, T);
7085 end if;
7087 -- Generate cross-reference. We needed to wait until full overloading
7088 -- resolution was complete to do this, since otherwise we can't tell if
7089 -- we are an Lvalue of not.
7091 if May_Be_Lvalue (N) then
7092 Generate_Reference (Entity (S), S, 'm');
7093 else
7094 Generate_Reference (Entity (S), S, 'r');
7095 end if;
7097 -- If prefix is an access type, the node will be transformed into an
7098 -- explicit dereference during expansion. The type of the node is the
7099 -- designated type of that of the prefix.
7101 if Is_Access_Type (Etype (P)) then
7102 T := Designated_Type (Etype (P));
7103 Check_Fully_Declared_Prefix (T, P);
7104 else
7105 T := Etype (P);
7106 end if;
7108 if Has_Discriminants (T)
7109 and then (Ekind (Entity (S)) = E_Component
7110 or else
7111 Ekind (Entity (S)) = E_Discriminant)
7112 and then Present (Original_Record_Component (Entity (S)))
7113 and then Ekind (Original_Record_Component (Entity (S))) = E_Component
7114 and then Present (Discriminant_Checking_Func
7115 (Original_Record_Component (Entity (S))))
7116 and then not Discriminant_Checks_Suppressed (T)
7117 and then not Init_Component
7118 then
7119 Set_Do_Discriminant_Check (N);
7120 end if;
7122 if Ekind (Entity (S)) = E_Void then
7123 Error_Msg_N ("premature use of component", S);
7124 end if;
7126 -- If the prefix is a record conversion, this may be a renamed
7127 -- discriminant whose bounds differ from those of the original
7128 -- one, so we must ensure that a range check is performed.
7130 if Nkind (P) = N_Type_Conversion
7131 and then Ekind (Entity (S)) = E_Discriminant
7132 and then Is_Discrete_Type (Typ)
7133 then
7134 Set_Etype (N, Base_Type (Typ));
7135 end if;
7137 -- Note: No Eval processing is required, because the prefix is of a
7138 -- record type, or protected type, and neither can possibly be static.
7140 end Resolve_Selected_Component;
7142 -------------------
7143 -- Resolve_Shift --
7144 -------------------
7146 procedure Resolve_Shift (N : Node_Id; Typ : Entity_Id) is
7147 B_Typ : constant Entity_Id := Base_Type (Typ);
7148 L : constant Node_Id := Left_Opnd (N);
7149 R : constant Node_Id := Right_Opnd (N);
7151 begin
7152 -- We do the resolution using the base type, because intermediate values
7153 -- in expressions always are of the base type, not a subtype of it.
7155 Resolve (L, B_Typ);
7156 Resolve (R, Standard_Natural);
7158 Check_Unset_Reference (L);
7159 Check_Unset_Reference (R);
7161 Set_Etype (N, B_Typ);
7162 Generate_Operator_Reference (N, B_Typ);
7163 Eval_Shift (N);
7164 end Resolve_Shift;
7166 ---------------------------
7167 -- Resolve_Short_Circuit --
7168 ---------------------------
7170 procedure Resolve_Short_Circuit (N : Node_Id; Typ : Entity_Id) is
7171 B_Typ : constant Entity_Id := Base_Type (Typ);
7172 L : constant Node_Id := Left_Opnd (N);
7173 R : constant Node_Id := Right_Opnd (N);
7175 begin
7176 Resolve (L, B_Typ);
7177 Resolve (R, B_Typ);
7179 -- Check for issuing warning for always False assert, this happens
7180 -- when assertions are turned off, in which case the pragma Assert
7181 -- was transformed into:
7183 -- if False and then <condition> then ...
7185 -- and we detect this pattern
7187 if Warn_On_Assertion_Failure
7188 and then Is_Entity_Name (R)
7189 and then Entity (R) = Standard_False
7190 and then Nkind (Parent (N)) = N_If_Statement
7191 and then Nkind (N) = N_And_Then
7192 and then Is_Entity_Name (L)
7193 and then Entity (L) = Standard_False
7194 then
7195 declare
7196 Orig : constant Node_Id := Original_Node (Parent (N));
7197 begin
7198 if Nkind (Orig) = N_Pragma
7199 and then Chars (Orig) = Name_Assert
7200 then
7201 -- Don't want to warn if original condition is explicit False
7203 declare
7204 Expr : constant Node_Id :=
7205 Original_Node
7206 (Expression
7207 (First (Pragma_Argument_Associations (Orig))));
7208 begin
7209 if Is_Entity_Name (Expr)
7210 and then Entity (Expr) = Standard_False
7211 then
7212 null;
7213 else
7214 -- Issue warning. Note that we don't want to make this
7215 -- an unconditional warning, because if the assert is
7216 -- within deleted code we do not want the warning. But
7217 -- we do not want the deletion of the IF/AND-THEN to
7218 -- take this message with it. We achieve this by making
7219 -- sure that the expanded code points to the Sloc of
7220 -- the expression, not the original pragma.
7222 Error_Msg_N ("?assertion would fail at run-time", Orig);
7223 end if;
7224 end;
7225 end if;
7226 end;
7227 end if;
7229 -- Continue with processing of short circuit
7231 Check_Unset_Reference (L);
7232 Check_Unset_Reference (R);
7234 Set_Etype (N, B_Typ);
7235 Eval_Short_Circuit (N);
7236 end Resolve_Short_Circuit;
7238 -------------------
7239 -- Resolve_Slice --
7240 -------------------
7242 procedure Resolve_Slice (N : Node_Id; Typ : Entity_Id) is
7243 Name : constant Node_Id := Prefix (N);
7244 Drange : constant Node_Id := Discrete_Range (N);
7245 Array_Type : Entity_Id := Empty;
7246 Index : Node_Id;
7248 begin
7249 if Is_Overloaded (Name) then
7251 -- Use the context type to select the prefix that yields the
7252 -- correct array type.
7254 declare
7255 I : Interp_Index;
7256 I1 : Interp_Index := 0;
7257 It : Interp;
7258 P : constant Node_Id := Prefix (N);
7259 Found : Boolean := False;
7261 begin
7262 Get_First_Interp (P, I, It);
7263 while Present (It.Typ) loop
7264 if (Is_Array_Type (It.Typ)
7265 and then Covers (Typ, It.Typ))
7266 or else (Is_Access_Type (It.Typ)
7267 and then Is_Array_Type (Designated_Type (It.Typ))
7268 and then Covers (Typ, Designated_Type (It.Typ)))
7269 then
7270 if Found then
7271 It := Disambiguate (P, I1, I, Any_Type);
7273 if It = No_Interp then
7274 Error_Msg_N ("ambiguous prefix for slicing", N);
7275 Set_Etype (N, Typ);
7276 return;
7277 else
7278 Found := True;
7279 Array_Type := It.Typ;
7280 I1 := I;
7281 end if;
7282 else
7283 Found := True;
7284 Array_Type := It.Typ;
7285 I1 := I;
7286 end if;
7287 end if;
7289 Get_Next_Interp (I, It);
7290 end loop;
7291 end;
7293 else
7294 Array_Type := Etype (Name);
7295 end if;
7297 Resolve (Name, Array_Type);
7299 if Is_Access_Type (Array_Type) then
7300 Apply_Access_Check (N);
7301 Array_Type := Designated_Type (Array_Type);
7303 -- If the prefix is an access to an unconstrained array, we must use
7304 -- the actual subtype of the object to perform the index checks. The
7305 -- object denoted by the prefix is implicit in the node, so we build
7306 -- an explicit representation for it in order to compute the actual
7307 -- subtype.
7309 if not Is_Constrained (Array_Type) then
7310 Remove_Side_Effects (Prefix (N));
7312 declare
7313 Obj : constant Node_Id :=
7314 Make_Explicit_Dereference (Sloc (N),
7315 Prefix => New_Copy_Tree (Prefix (N)));
7316 begin
7317 Set_Etype (Obj, Array_Type);
7318 Set_Parent (Obj, Parent (N));
7319 Array_Type := Get_Actual_Subtype (Obj);
7320 end;
7321 end if;
7323 elsif Is_Entity_Name (Name)
7324 or else (Nkind (Name) = N_Function_Call
7325 and then not Is_Constrained (Etype (Name)))
7326 then
7327 Array_Type := Get_Actual_Subtype (Name);
7329 -- If the name is a selected component that depends on discriminants,
7330 -- build an actual subtype for it. This can happen only when the name
7331 -- itself is overloaded; otherwise the actual subtype is created when
7332 -- the selected component is analyzed.
7334 elsif Nkind (Name) = N_Selected_Component
7335 and then Full_Analysis
7336 and then Depends_On_Discriminant (First_Index (Array_Type))
7337 then
7338 declare
7339 Act_Decl : constant Node_Id :=
7340 Build_Actual_Subtype_Of_Component (Array_Type, Name);
7341 begin
7342 Insert_Action (N, Act_Decl);
7343 Array_Type := Defining_Identifier (Act_Decl);
7344 end;
7345 end if;
7347 -- If name was overloaded, set slice type correctly now
7349 Set_Etype (N, Array_Type);
7351 -- If the range is specified by a subtype mark, no resolution is
7352 -- necessary. Else resolve the bounds, and apply needed checks.
7354 if not Is_Entity_Name (Drange) then
7355 Index := First_Index (Array_Type);
7356 Resolve (Drange, Base_Type (Etype (Index)));
7358 if Nkind (Drange) = N_Range
7360 -- Do not apply the range check to nodes associated with the
7361 -- frontend expansion of the dispatch table. We first check
7362 -- if Ada.Tags is already loaded to void the addition of an
7363 -- undesired dependence on such run-time unit.
7365 and then
7366 (VM_Target /= No_VM
7367 or else not
7368 (RTU_Loaded (Ada_Tags)
7369 and then Nkind (Prefix (N)) = N_Selected_Component
7370 and then Present (Entity (Selector_Name (Prefix (N))))
7371 and then Entity (Selector_Name (Prefix (N))) =
7372 RTE_Record_Component (RE_Prims_Ptr)))
7373 then
7374 Apply_Range_Check (Drange, Etype (Index));
7375 end if;
7376 end if;
7378 Set_Slice_Subtype (N);
7380 if Nkind (Drange) = N_Range then
7381 Warn_On_Suspicious_Index (Name, Low_Bound (Drange));
7382 Warn_On_Suspicious_Index (Name, High_Bound (Drange));
7383 end if;
7385 Eval_Slice (N);
7386 end Resolve_Slice;
7388 ----------------------------
7389 -- Resolve_String_Literal --
7390 ----------------------------
7392 procedure Resolve_String_Literal (N : Node_Id; Typ : Entity_Id) is
7393 C_Typ : constant Entity_Id := Component_Type (Typ);
7394 R_Typ : constant Entity_Id := Root_Type (C_Typ);
7395 Loc : constant Source_Ptr := Sloc (N);
7396 Str : constant String_Id := Strval (N);
7397 Strlen : constant Nat := String_Length (Str);
7398 Subtype_Id : Entity_Id;
7399 Need_Check : Boolean;
7401 begin
7402 -- For a string appearing in a concatenation, defer creation of the
7403 -- string_literal_subtype until the end of the resolution of the
7404 -- concatenation, because the literal may be constant-folded away. This
7405 -- is a useful optimization for long concatenation expressions.
7407 -- If the string is an aggregate built for a single character (which
7408 -- happens in a non-static context) or a is null string to which special
7409 -- checks may apply, we build the subtype. Wide strings must also get a
7410 -- string subtype if they come from a one character aggregate. Strings
7411 -- generated by attributes might be static, but it is often hard to
7412 -- determine whether the enclosing context is static, so we generate
7413 -- subtypes for them as well, thus losing some rarer optimizations ???
7414 -- Same for strings that come from a static conversion.
7416 Need_Check :=
7417 (Strlen = 0 and then Typ /= Standard_String)
7418 or else Nkind (Parent (N)) /= N_Op_Concat
7419 or else (N /= Left_Opnd (Parent (N))
7420 and then N /= Right_Opnd (Parent (N)))
7421 or else ((Typ = Standard_Wide_String
7422 or else Typ = Standard_Wide_Wide_String)
7423 and then Nkind (Original_Node (N)) /= N_String_Literal);
7425 -- If the resolving type is itself a string literal subtype, we
7426 -- can just reuse it, since there is no point in creating another.
7428 if Ekind (Typ) = E_String_Literal_Subtype then
7429 Subtype_Id := Typ;
7431 elsif Nkind (Parent (N)) = N_Op_Concat
7432 and then not Need_Check
7433 and then Nkind (Original_Node (N)) /= N_Character_Literal
7434 and then Nkind (Original_Node (N)) /= N_Attribute_Reference
7435 and then Nkind (Original_Node (N)) /= N_Qualified_Expression
7436 and then Nkind (Original_Node (N)) /= N_Type_Conversion
7437 then
7438 Subtype_Id := Typ;
7440 -- Otherwise we must create a string literal subtype. Note that the
7441 -- whole idea of string literal subtypes is simply to avoid the need
7442 -- for building a full fledged array subtype for each literal.
7443 else
7444 Set_String_Literal_Subtype (N, Typ);
7445 Subtype_Id := Etype (N);
7446 end if;
7448 if Nkind (Parent (N)) /= N_Op_Concat
7449 or else Need_Check
7450 then
7451 Set_Etype (N, Subtype_Id);
7452 Eval_String_Literal (N);
7453 end if;
7455 if Is_Limited_Composite (Typ)
7456 or else Is_Private_Composite (Typ)
7457 then
7458 Error_Msg_N ("string literal not available for private array", N);
7459 Set_Etype (N, Any_Type);
7460 return;
7461 end if;
7463 -- The validity of a null string has been checked in the
7464 -- call to Eval_String_Literal.
7466 if Strlen = 0 then
7467 return;
7469 -- Always accept string literal with component type Any_Character, which
7470 -- occurs in error situations and in comparisons of literals, both of
7471 -- which should accept all literals.
7473 elsif R_Typ = Any_Character then
7474 return;
7476 -- If the type is bit-packed, then we always tranform the string literal
7477 -- into a full fledged aggregate.
7479 elsif Is_Bit_Packed_Array (Typ) then
7480 null;
7482 -- Deal with cases of Wide_Wide_String, Wide_String, and String
7484 else
7485 -- For Standard.Wide_Wide_String, or any other type whose component
7486 -- type is Standard.Wide_Wide_Character, we know that all the
7487 -- characters in the string must be acceptable, since the parser
7488 -- accepted the characters as valid character literals.
7490 if R_Typ = Standard_Wide_Wide_Character then
7491 null;
7493 -- For the case of Standard.String, or any other type whose component
7494 -- type is Standard.Character, we must make sure that there are no
7495 -- wide characters in the string, i.e. that it is entirely composed
7496 -- of characters in range of type Character.
7498 -- If the string literal is the result of a static concatenation, the
7499 -- test has already been performed on the components, and need not be
7500 -- repeated.
7502 elsif R_Typ = Standard_Character
7503 and then Nkind (Original_Node (N)) /= N_Op_Concat
7504 then
7505 for J in 1 .. Strlen loop
7506 if not In_Character_Range (Get_String_Char (Str, J)) then
7508 -- If we are out of range, post error. This is one of the
7509 -- very few places that we place the flag in the middle of
7510 -- a token, right under the offending wide character.
7512 Error_Msg
7513 ("literal out of range of type Standard.Character",
7514 Source_Ptr (Int (Loc) + J));
7515 return;
7516 end if;
7517 end loop;
7519 -- For the case of Standard.Wide_String, or any other type whose
7520 -- component type is Standard.Wide_Character, we must make sure that
7521 -- there are no wide characters in the string, i.e. that it is
7522 -- entirely composed of characters in range of type Wide_Character.
7524 -- If the string literal is the result of a static concatenation,
7525 -- the test has already been performed on the components, and need
7526 -- not be repeated.
7528 elsif R_Typ = Standard_Wide_Character
7529 and then Nkind (Original_Node (N)) /= N_Op_Concat
7530 then
7531 for J in 1 .. Strlen loop
7532 if not In_Wide_Character_Range (Get_String_Char (Str, J)) then
7534 -- If we are out of range, post error. This is one of the
7535 -- very few places that we place the flag in the middle of
7536 -- a token, right under the offending wide character.
7538 -- This is not quite right, because characters in general
7539 -- will take more than one character position ???
7541 Error_Msg
7542 ("literal out of range of type Standard.Wide_Character",
7543 Source_Ptr (Int (Loc) + J));
7544 return;
7545 end if;
7546 end loop;
7548 -- If the root type is not a standard character, then we will convert
7549 -- the string into an aggregate and will let the aggregate code do
7550 -- the checking. Standard Wide_Wide_Character is also OK here.
7552 else
7553 null;
7554 end if;
7556 -- See if the component type of the array corresponding to the string
7557 -- has compile time known bounds. If yes we can directly check
7558 -- whether the evaluation of the string will raise constraint error.
7559 -- Otherwise we need to transform the string literal into the
7560 -- corresponding character aggregate and let the aggregate
7561 -- code do the checking.
7563 if R_Typ = Standard_Character
7564 or else R_Typ = Standard_Wide_Character
7565 or else R_Typ = Standard_Wide_Wide_Character
7566 then
7567 -- Check for the case of full range, where we are definitely OK
7569 if Component_Type (Typ) = Base_Type (Component_Type (Typ)) then
7570 return;
7571 end if;
7573 -- Here the range is not the complete base type range, so check
7575 declare
7576 Comp_Typ_Lo : constant Node_Id :=
7577 Type_Low_Bound (Component_Type (Typ));
7578 Comp_Typ_Hi : constant Node_Id :=
7579 Type_High_Bound (Component_Type (Typ));
7581 Char_Val : Uint;
7583 begin
7584 if Compile_Time_Known_Value (Comp_Typ_Lo)
7585 and then Compile_Time_Known_Value (Comp_Typ_Hi)
7586 then
7587 for J in 1 .. Strlen loop
7588 Char_Val := UI_From_Int (Int (Get_String_Char (Str, J)));
7590 if Char_Val < Expr_Value (Comp_Typ_Lo)
7591 or else Char_Val > Expr_Value (Comp_Typ_Hi)
7592 then
7593 Apply_Compile_Time_Constraint_Error
7594 (N, "character out of range?", CE_Range_Check_Failed,
7595 Loc => Source_Ptr (Int (Loc) + J));
7596 end if;
7597 end loop;
7599 return;
7600 end if;
7601 end;
7602 end if;
7603 end if;
7605 -- If we got here we meed to transform the string literal into the
7606 -- equivalent qualified positional array aggregate. This is rather
7607 -- heavy artillery for this situation, but it is hard work to avoid.
7609 declare
7610 Lits : constant List_Id := New_List;
7611 P : Source_Ptr := Loc + 1;
7612 C : Char_Code;
7614 begin
7615 -- Build the character literals, we give them source locations that
7616 -- correspond to the string positions, which is a bit tricky given
7617 -- the possible presence of wide character escape sequences.
7619 for J in 1 .. Strlen loop
7620 C := Get_String_Char (Str, J);
7621 Set_Character_Literal_Name (C);
7623 Append_To (Lits,
7624 Make_Character_Literal (P,
7625 Chars => Name_Find,
7626 Char_Literal_Value => UI_From_CC (C)));
7628 if In_Character_Range (C) then
7629 P := P + 1;
7631 -- Should we have a call to Skip_Wide here ???
7632 -- ??? else
7633 -- Skip_Wide (P);
7635 end if;
7636 end loop;
7638 Rewrite (N,
7639 Make_Qualified_Expression (Loc,
7640 Subtype_Mark => New_Reference_To (Typ, Loc),
7641 Expression =>
7642 Make_Aggregate (Loc, Expressions => Lits)));
7644 Analyze_And_Resolve (N, Typ);
7645 end;
7646 end Resolve_String_Literal;
7648 -----------------------------
7649 -- Resolve_Subprogram_Info --
7650 -----------------------------
7652 procedure Resolve_Subprogram_Info (N : Node_Id; Typ : Entity_Id) is
7653 begin
7654 Set_Etype (N, Typ);
7655 end Resolve_Subprogram_Info;
7657 -----------------------------
7658 -- Resolve_Type_Conversion --
7659 -----------------------------
7661 procedure Resolve_Type_Conversion (N : Node_Id; Typ : Entity_Id) is
7662 Conv_OK : constant Boolean := Conversion_OK (N);
7663 Operand : constant Node_Id := Expression (N);
7664 Operand_Typ : constant Entity_Id := Etype (Operand);
7665 Target_Typ : constant Entity_Id := Etype (N);
7666 Rop : Node_Id;
7667 Orig_N : Node_Id;
7668 Orig_T : Node_Id;
7670 begin
7671 if not Conv_OK
7672 and then not Valid_Conversion (N, Target_Typ, Operand)
7673 then
7674 return;
7675 end if;
7677 if Etype (Operand) = Any_Fixed then
7679 -- Mixed-mode operation involving a literal. Context must be a fixed
7680 -- type which is applied to the literal subsequently.
7682 if Is_Fixed_Point_Type (Typ) then
7683 Set_Etype (Operand, Universal_Real);
7685 elsif Is_Numeric_Type (Typ)
7686 and then (Nkind (Operand) = N_Op_Multiply
7687 or else Nkind (Operand) = N_Op_Divide)
7688 and then (Etype (Right_Opnd (Operand)) = Universal_Real
7689 or else Etype (Left_Opnd (Operand)) = Universal_Real)
7690 then
7691 -- Return if expression is ambiguous
7693 if Unique_Fixed_Point_Type (N) = Any_Type then
7694 return;
7696 -- If nothing else, the available fixed type is Duration
7698 else
7699 Set_Etype (Operand, Standard_Duration);
7700 end if;
7702 -- Resolve the real operand with largest available precision
7704 if Etype (Right_Opnd (Operand)) = Universal_Real then
7705 Rop := New_Copy_Tree (Right_Opnd (Operand));
7706 else
7707 Rop := New_Copy_Tree (Left_Opnd (Operand));
7708 end if;
7710 Resolve (Rop, Universal_Real);
7712 -- If the operand is a literal (it could be a non-static and
7713 -- illegal exponentiation) check whether the use of Duration
7714 -- is potentially inaccurate.
7716 if Nkind (Rop) = N_Real_Literal
7717 and then Realval (Rop) /= Ureal_0
7718 and then abs (Realval (Rop)) < Delta_Value (Standard_Duration)
7719 then
7720 Error_Msg_N
7721 ("?universal real operand can only " &
7722 "be interpreted as Duration!",
7723 Rop);
7724 Error_Msg_N
7725 ("\?precision will be lost in the conversion!", Rop);
7726 end if;
7728 elsif Is_Numeric_Type (Typ)
7729 and then Nkind (Operand) in N_Op
7730 and then Unique_Fixed_Point_Type (N) /= Any_Type
7731 then
7732 Set_Etype (Operand, Standard_Duration);
7734 else
7735 Error_Msg_N ("invalid context for mixed mode operation", N);
7736 Set_Etype (Operand, Any_Type);
7737 return;
7738 end if;
7739 end if;
7741 Resolve (Operand);
7743 -- Note: we do the Eval_Type_Conversion call before applying the
7744 -- required checks for a subtype conversion. This is important,
7745 -- since both are prepared under certain circumstances to change
7746 -- the type conversion to a constraint error node, but in the case
7747 -- of Eval_Type_Conversion this may reflect an illegality in the
7748 -- static case, and we would miss the illegality (getting only a
7749 -- warning message), if we applied the type conversion checks first.
7751 Eval_Type_Conversion (N);
7753 -- Even when evaluation is not possible, we may be able to simplify
7754 -- the conversion or its expression. This needs to be done before
7755 -- applying checks, since otherwise the checks may use the original
7756 -- expression and defeat the simplifications. This is specifically
7757 -- the case for elimination of the floating-point Truncation
7758 -- attribute in float-to-int conversions.
7760 Simplify_Type_Conversion (N);
7762 -- If after evaluation we still have a type conversion, then we
7763 -- may need to apply checks required for a subtype conversion.
7765 -- Skip these type conversion checks if universal fixed operands
7766 -- operands involved, since range checks are handled separately for
7767 -- these cases (in the appropriate Expand routines in unit Exp_Fixd).
7769 if Nkind (N) = N_Type_Conversion
7770 and then not Is_Generic_Type (Root_Type (Target_Typ))
7771 and then Target_Typ /= Universal_Fixed
7772 and then Operand_Typ /= Universal_Fixed
7773 then
7774 Apply_Type_Conversion_Checks (N);
7775 end if;
7777 -- Issue warning for conversion of simple object to its own type
7778 -- We have to test the original nodes, since they may have been
7779 -- rewritten by various optimizations.
7781 Orig_N := Original_Node (N);
7783 if Warn_On_Redundant_Constructs
7784 and then Comes_From_Source (Orig_N)
7785 and then Nkind (Orig_N) = N_Type_Conversion
7786 and then not In_Instance
7787 then
7788 Orig_N := Original_Node (Expression (Orig_N));
7789 Orig_T := Target_Typ;
7791 -- If the node is part of a larger expression, the Target_Type
7792 -- may not be the original type of the node if the context is a
7793 -- condition. Recover original type to see if conversion is needed.
7795 if Is_Boolean_Type (Orig_T)
7796 and then Nkind (Parent (N)) in N_Op
7797 then
7798 Orig_T := Etype (Parent (N));
7799 end if;
7801 if Is_Entity_Name (Orig_N)
7802 and then
7803 (Etype (Entity (Orig_N)) = Orig_T
7804 or else
7805 (Ekind (Entity (Orig_N)) = E_Loop_Parameter
7806 and then Covers (Orig_T, Etype (Entity (Orig_N)))))
7807 then
7808 Error_Msg_Node_2 := Orig_T;
7809 Error_Msg_NE
7810 ("?redundant conversion, & is of type &!", N, Entity (Orig_N));
7811 end if;
7812 end if;
7814 -- Ada 2005 (AI-251): Handle class-wide interface type conversions.
7815 -- No need to perform any interface conversion if the type of the
7816 -- expression coincides with the target type.
7818 if Ada_Version >= Ada_05
7819 and then Expander_Active
7820 and then Operand_Typ /= Target_Typ
7821 then
7822 declare
7823 Opnd : Entity_Id := Operand_Typ;
7824 Target : Entity_Id := Target_Typ;
7826 begin
7827 if Is_Access_Type (Opnd) then
7828 Opnd := Directly_Designated_Type (Opnd);
7829 end if;
7831 if Is_Access_Type (Target_Typ) then
7832 Target := Directly_Designated_Type (Target);
7833 end if;
7835 if Opnd = Target then
7836 null;
7838 -- Conversion from interface type
7840 elsif Is_Interface (Opnd) then
7842 -- Ada 2005 (AI-217): Handle entities from limited views
7844 if From_With_Type (Opnd) then
7845 Error_Msg_Qual_Level := 99;
7846 Error_Msg_NE ("missing with-clause on package &", N,
7847 Cunit_Entity (Get_Source_Unit (Base_Type (Opnd))));
7848 Error_Msg_N
7849 ("type conversions require visibility of the full view",
7852 elsif From_With_Type (Target)
7853 and then not
7854 (Is_Access_Type (Target_Typ)
7855 and then Present (Non_Limited_View (Etype (Target))))
7856 then
7857 Error_Msg_Qual_Level := 99;
7858 Error_Msg_NE ("missing with-clause on package &", N,
7859 Cunit_Entity (Get_Source_Unit (Base_Type (Target))));
7860 Error_Msg_N
7861 ("type conversions require visibility of the full view",
7864 else
7865 Expand_Interface_Conversion (N, Is_Static => False);
7866 end if;
7868 -- Conversion to interface type
7870 elsif Is_Interface (Target) then
7872 -- Handle subtypes
7874 if Ekind (Opnd) = E_Protected_Subtype
7875 or else Ekind (Opnd) = E_Task_Subtype
7876 then
7877 Opnd := Etype (Opnd);
7878 end if;
7880 if not Interface_Present_In_Ancestor
7881 (Typ => Opnd,
7882 Iface => Target)
7883 then
7884 if Is_Class_Wide_Type (Opnd) then
7886 -- The static analysis is not enough to know if the
7887 -- interface is implemented or not. Hence we must pass
7888 -- the work to the expander to generate code to evaluate
7889 -- the conversion at run-time.
7891 Expand_Interface_Conversion (N, Is_Static => False);
7893 else
7894 Error_Msg_Name_1 := Chars (Etype (Target));
7895 Error_Msg_Name_2 := Chars (Opnd);
7896 Error_Msg_N
7897 ("wrong interface conversion (% is not a progenitor " &
7898 "of %)", N);
7899 end if;
7901 else
7902 Expand_Interface_Conversion (N);
7903 end if;
7904 end if;
7905 end;
7906 end if;
7907 end Resolve_Type_Conversion;
7909 ----------------------
7910 -- Resolve_Unary_Op --
7911 ----------------------
7913 procedure Resolve_Unary_Op (N : Node_Id; Typ : Entity_Id) is
7914 B_Typ : constant Entity_Id := Base_Type (Typ);
7915 R : constant Node_Id := Right_Opnd (N);
7916 OK : Boolean;
7917 Lo : Uint;
7918 Hi : Uint;
7920 begin
7921 -- Deal with intrinsic unary operators
7923 if Comes_From_Source (N)
7924 and then Ekind (Entity (N)) = E_Function
7925 and then Is_Imported (Entity (N))
7926 and then Is_Intrinsic_Subprogram (Entity (N))
7927 then
7928 Resolve_Intrinsic_Unary_Operator (N, Typ);
7929 return;
7930 end if;
7932 -- Deal with universal cases
7934 if Etype (R) = Universal_Integer
7935 or else
7936 Etype (R) = Universal_Real
7937 then
7938 Check_For_Visible_Operator (N, B_Typ);
7939 end if;
7941 Set_Etype (N, B_Typ);
7942 Resolve (R, B_Typ);
7944 -- Generate warning for expressions like abs (x mod 2)
7946 if Warn_On_Redundant_Constructs
7947 and then Nkind (N) = N_Op_Abs
7948 then
7949 Determine_Range (Right_Opnd (N), OK, Lo, Hi);
7951 if OK and then Hi >= Lo and then Lo >= 0 then
7952 Error_Msg_N
7953 ("?abs applied to known non-negative value has no effect", N);
7954 end if;
7955 end if;
7957 -- Deal with reference generation
7959 Check_Unset_Reference (R);
7960 Generate_Operator_Reference (N, B_Typ);
7961 Eval_Unary_Op (N);
7963 -- Set overflow checking bit. Much cleverer code needed here eventually
7964 -- and perhaps the Resolve routines should be separated for the various
7965 -- arithmetic operations, since they will need different processing ???
7967 if Nkind (N) in N_Op then
7968 if not Overflow_Checks_Suppressed (Etype (N)) then
7969 Enable_Overflow_Check (N);
7970 end if;
7971 end if;
7973 -- Generate warning for expressions like -5 mod 3 for integers. No
7974 -- need to worry in the floating-point case, since parens do not affect
7975 -- the result so there is no point in giving in a warning.
7977 declare
7978 Norig : constant Node_Id := Original_Node (N);
7979 Rorig : Node_Id;
7980 Val : Uint;
7981 HB : Uint;
7982 LB : Uint;
7983 Lval : Uint;
7984 Opnd : Node_Id;
7986 begin
7987 if Warn_On_Questionable_Missing_Parens
7988 and then Comes_From_Source (Norig)
7989 and then Is_Integer_Type (Typ)
7990 and then Nkind (Norig) = N_Op_Minus
7991 then
7992 Rorig := Original_Node (Right_Opnd (Norig));
7994 -- We are looking for cases where the right operand is not
7995 -- parenthesized, and is a bianry operator, multiply, divide, or
7996 -- mod. These are the cases where the grouping can affect results.
7998 if Paren_Count (Rorig) = 0
7999 and then (Nkind (Rorig) = N_Op_Mod
8000 or else
8001 Nkind (Rorig) = N_Op_Multiply
8002 or else
8003 Nkind (Rorig) = N_Op_Divide)
8004 then
8005 -- For mod, we always give the warning, since the value is
8006 -- affected by the parenthesization (e.g. (-5) mod 315 /=
8007 -- (5 mod 315)). But for the other cases, the only concern is
8008 -- overflow, e.g. for the case of 8 big signed (-(2 * 64)
8009 -- overflows, but (-2) * 64 does not). So we try to give the
8010 -- message only when overflow is possible.
8012 if Nkind (Rorig) /= N_Op_Mod
8013 and then Compile_Time_Known_Value (R)
8014 then
8015 Val := Expr_Value (R);
8017 if Compile_Time_Known_Value (Type_High_Bound (Typ)) then
8018 HB := Expr_Value (Type_High_Bound (Typ));
8019 else
8020 HB := Expr_Value (Type_High_Bound (Base_Type (Typ)));
8021 end if;
8023 if Compile_Time_Known_Value (Type_Low_Bound (Typ)) then
8024 LB := Expr_Value (Type_Low_Bound (Typ));
8025 else
8026 LB := Expr_Value (Type_Low_Bound (Base_Type (Typ)));
8027 end if;
8029 -- Note that the test below is deliberately excluding
8030 -- the largest negative number, since that is a potentially
8031 -- troublesome case (e.g. -2 * x, where the result is the
8032 -- largest negative integer has an overflow with 2 * x).
8034 if Val > LB and then Val <= HB then
8035 return;
8036 end if;
8037 end if;
8039 -- For the multiplication case, the only case we have to worry
8040 -- about is when (-a)*b is exactly the largest negative number
8041 -- so that -(a*b) can cause overflow. This can only happen if
8042 -- a is a power of 2, and more generally if any operand is a
8043 -- constant that is not a power of 2, then the parentheses
8044 -- cannot affect whether overflow occurs. We only bother to
8045 -- test the left most operand
8047 -- Loop looking at left operands for one that has known value
8049 Opnd := Rorig;
8050 Opnd_Loop : while Nkind (Opnd) = N_Op_Multiply loop
8051 if Compile_Time_Known_Value (Left_Opnd (Opnd)) then
8052 Lval := UI_Abs (Expr_Value (Left_Opnd (Opnd)));
8054 -- Operand value of 0 or 1 skips warning
8056 if Lval <= 1 then
8057 return;
8059 -- Otherwise check power of 2, if power of 2, warn, if
8060 -- anything else, skip warning.
8062 else
8063 while Lval /= 2 loop
8064 if Lval mod 2 = 1 then
8065 return;
8066 else
8067 Lval := Lval / 2;
8068 end if;
8069 end loop;
8071 exit Opnd_Loop;
8072 end if;
8073 end if;
8075 -- Keep looking at left operands
8077 Opnd := Left_Opnd (Opnd);
8078 end loop Opnd_Loop;
8080 -- For rem or "/" we can only have a problematic situation
8081 -- if the divisor has a value of minus one or one. Otherwise
8082 -- overflow is impossible (divisor > 1) or we have a case of
8083 -- division by zero in any case.
8085 if (Nkind (Rorig) = N_Op_Divide
8086 or else
8087 Nkind (Rorig) = N_Op_Rem)
8088 and then Compile_Time_Known_Value (Right_Opnd (Rorig))
8089 and then UI_Abs (Expr_Value (Right_Opnd (Rorig))) /= 1
8090 then
8091 return;
8092 end if;
8094 -- If we fall through warning should be issued
8096 Error_Msg_N
8097 ("?unary minus expression should be parenthesized here!", N);
8098 end if;
8099 end if;
8100 end;
8101 end Resolve_Unary_Op;
8103 ----------------------------------
8104 -- Resolve_Unchecked_Expression --
8105 ----------------------------------
8107 procedure Resolve_Unchecked_Expression
8108 (N : Node_Id;
8109 Typ : Entity_Id)
8111 begin
8112 Resolve (Expression (N), Typ, Suppress => All_Checks);
8113 Set_Etype (N, Typ);
8114 end Resolve_Unchecked_Expression;
8116 ---------------------------------------
8117 -- Resolve_Unchecked_Type_Conversion --
8118 ---------------------------------------
8120 procedure Resolve_Unchecked_Type_Conversion
8121 (N : Node_Id;
8122 Typ : Entity_Id)
8124 pragma Warnings (Off, Typ);
8126 Operand : constant Node_Id := Expression (N);
8127 Opnd_Type : constant Entity_Id := Etype (Operand);
8129 begin
8130 -- Resolve operand using its own type
8132 Resolve (Operand, Opnd_Type);
8133 Eval_Unchecked_Conversion (N);
8135 end Resolve_Unchecked_Type_Conversion;
8137 ------------------------------
8138 -- Rewrite_Operator_As_Call --
8139 ------------------------------
8141 procedure Rewrite_Operator_As_Call (N : Node_Id; Nam : Entity_Id) is
8142 Loc : constant Source_Ptr := Sloc (N);
8143 Actuals : constant List_Id := New_List;
8144 New_N : Node_Id;
8146 begin
8147 if Nkind (N) in N_Binary_Op then
8148 Append (Left_Opnd (N), Actuals);
8149 end if;
8151 Append (Right_Opnd (N), Actuals);
8153 New_N :=
8154 Make_Function_Call (Sloc => Loc,
8155 Name => New_Occurrence_Of (Nam, Loc),
8156 Parameter_Associations => Actuals);
8158 Preserve_Comes_From_Source (New_N, N);
8159 Preserve_Comes_From_Source (Name (New_N), N);
8160 Rewrite (N, New_N);
8161 Set_Etype (N, Etype (Nam));
8162 end Rewrite_Operator_As_Call;
8164 ------------------------------
8165 -- Rewrite_Renamed_Operator --
8166 ------------------------------
8168 procedure Rewrite_Renamed_Operator
8169 (N : Node_Id;
8170 Op : Entity_Id;
8171 Typ : Entity_Id)
8173 Nam : constant Name_Id := Chars (Op);
8174 Is_Binary : constant Boolean := Nkind (N) in N_Binary_Op;
8175 Op_Node : Node_Id;
8177 begin
8178 -- Rewrite the operator node using the real operator, not its
8179 -- renaming. Exclude user-defined intrinsic operations of the same
8180 -- name, which are treated separately and rewritten as calls.
8182 if Ekind (Op) /= E_Function
8183 or else Chars (N) /= Nam
8184 then
8185 Op_Node := New_Node (Operator_Kind (Nam, Is_Binary), Sloc (N));
8186 Set_Chars (Op_Node, Nam);
8187 Set_Etype (Op_Node, Etype (N));
8188 Set_Entity (Op_Node, Op);
8189 Set_Right_Opnd (Op_Node, Right_Opnd (N));
8191 -- Indicate that both the original entity and its renaming are
8192 -- referenced at this point.
8194 Generate_Reference (Entity (N), N);
8195 Generate_Reference (Op, N);
8197 if Is_Binary then
8198 Set_Left_Opnd (Op_Node, Left_Opnd (N));
8199 end if;
8201 Rewrite (N, Op_Node);
8203 -- If the context type is private, add the appropriate conversions
8204 -- so that the operator is applied to the full view. This is done
8205 -- in the routines that resolve intrinsic operators,
8207 if Is_Intrinsic_Subprogram (Op)
8208 and then Is_Private_Type (Typ)
8209 then
8210 case Nkind (N) is
8211 when N_Op_Add | N_Op_Subtract | N_Op_Multiply | N_Op_Divide |
8212 N_Op_Expon | N_Op_Mod | N_Op_Rem =>
8213 Resolve_Intrinsic_Operator (N, Typ);
8215 when N_Op_Plus | N_Op_Minus | N_Op_Abs =>
8216 Resolve_Intrinsic_Unary_Operator (N, Typ);
8218 when others =>
8219 Resolve (N, Typ);
8220 end case;
8221 end if;
8223 elsif Ekind (Op) = E_Function
8224 and then Is_Intrinsic_Subprogram (Op)
8225 then
8226 -- Operator renames a user-defined operator of the same name. Use
8227 -- the original operator in the node, which is the one that Gigi
8228 -- knows about.
8230 Set_Entity (N, Op);
8231 Set_Is_Overloaded (N, False);
8232 end if;
8233 end Rewrite_Renamed_Operator;
8235 -----------------------
8236 -- Set_Slice_Subtype --
8237 -----------------------
8239 -- Build an implicit subtype declaration to represent the type delivered
8240 -- by the slice. This is an abbreviated version of an array subtype. We
8241 -- define an index subtype for the slice, using either the subtype name
8242 -- or the discrete range of the slice. To be consistent with index usage
8243 -- elsewhere, we create a list header to hold the single index. This list
8244 -- is not otherwise attached to the syntax tree.
8246 procedure Set_Slice_Subtype (N : Node_Id) is
8247 Loc : constant Source_Ptr := Sloc (N);
8248 Index_List : constant List_Id := New_List;
8249 Index : Node_Id;
8250 Index_Subtype : Entity_Id;
8251 Index_Type : Entity_Id;
8252 Slice_Subtype : Entity_Id;
8253 Drange : constant Node_Id := Discrete_Range (N);
8255 begin
8256 if Is_Entity_Name (Drange) then
8257 Index_Subtype := Entity (Drange);
8259 else
8260 -- We force the evaluation of a range. This is definitely needed in
8261 -- the renamed case, and seems safer to do unconditionally. Note in
8262 -- any case that since we will create and insert an Itype referring
8263 -- to this range, we must make sure any side effect removal actions
8264 -- are inserted before the Itype definition.
8266 if Nkind (Drange) = N_Range then
8267 Force_Evaluation (Low_Bound (Drange));
8268 Force_Evaluation (High_Bound (Drange));
8269 end if;
8271 Index_Type := Base_Type (Etype (Drange));
8273 Index_Subtype := Create_Itype (Subtype_Kind (Ekind (Index_Type)), N);
8275 Set_Scalar_Range (Index_Subtype, Drange);
8276 Set_Etype (Index_Subtype, Index_Type);
8277 Set_Size_Info (Index_Subtype, Index_Type);
8278 Set_RM_Size (Index_Subtype, RM_Size (Index_Type));
8279 end if;
8281 Slice_Subtype := Create_Itype (E_Array_Subtype, N);
8283 Index := New_Occurrence_Of (Index_Subtype, Loc);
8284 Set_Etype (Index, Index_Subtype);
8285 Append (Index, Index_List);
8287 Set_First_Index (Slice_Subtype, Index);
8288 Set_Etype (Slice_Subtype, Base_Type (Etype (N)));
8289 Set_Is_Constrained (Slice_Subtype, True);
8290 Init_Size_Align (Slice_Subtype);
8292 Check_Compile_Time_Size (Slice_Subtype);
8294 -- The Etype of the existing Slice node is reset to this slice subtype.
8295 -- Its bounds are obtained from its first index.
8297 Set_Etype (N, Slice_Subtype);
8299 -- In the packed case, this must be immediately frozen
8301 -- Couldn't we always freeze here??? and if we did, then the above
8302 -- call to Check_Compile_Time_Size could be eliminated, which would
8303 -- be nice, because then that routine could be made private to Freeze.
8305 if Is_Packed (Slice_Subtype) and not In_Default_Expression then
8306 Freeze_Itype (Slice_Subtype, N);
8307 end if;
8309 end Set_Slice_Subtype;
8311 --------------------------------
8312 -- Set_String_Literal_Subtype --
8313 --------------------------------
8315 procedure Set_String_Literal_Subtype (N : Node_Id; Typ : Entity_Id) is
8316 Loc : constant Source_Ptr := Sloc (N);
8317 Low_Bound : constant Node_Id :=
8318 Type_Low_Bound (Etype (First_Index (Typ)));
8319 Subtype_Id : Entity_Id;
8321 begin
8322 if Nkind (N) /= N_String_Literal then
8323 return;
8324 end if;
8326 Subtype_Id := Create_Itype (E_String_Literal_Subtype, N);
8327 Set_String_Literal_Length (Subtype_Id, UI_From_Int
8328 (String_Length (Strval (N))));
8329 Set_Etype (Subtype_Id, Base_Type (Typ));
8330 Set_Is_Constrained (Subtype_Id);
8331 Set_Etype (N, Subtype_Id);
8333 if Is_OK_Static_Expression (Low_Bound) then
8335 -- The low bound is set from the low bound of the corresponding
8336 -- index type. Note that we do not store the high bound in the
8337 -- string literal subtype, but it can be deduced if necessary
8338 -- from the length and the low bound.
8340 Set_String_Literal_Low_Bound (Subtype_Id, Low_Bound);
8342 else
8343 Set_String_Literal_Low_Bound
8344 (Subtype_Id, Make_Integer_Literal (Loc, 1));
8345 Set_Etype (String_Literal_Low_Bound (Subtype_Id), Standard_Positive);
8347 -- Build bona fide subtype for the string, and wrap it in an
8348 -- unchecked conversion, because the backend expects the
8349 -- String_Literal_Subtype to have a static lower bound.
8351 declare
8352 Index_List : constant List_Id := New_List;
8353 Index_Type : constant Entity_Id := Etype (First_Index (Typ));
8354 High_Bound : constant Node_Id :=
8355 Make_Op_Add (Loc,
8356 Left_Opnd => New_Copy_Tree (Low_Bound),
8357 Right_Opnd =>
8358 Make_Integer_Literal (Loc,
8359 String_Length (Strval (N)) - 1));
8360 Array_Subtype : Entity_Id;
8361 Index_Subtype : Entity_Id;
8362 Drange : Node_Id;
8363 Index : Node_Id;
8365 begin
8366 Index_Subtype :=
8367 Create_Itype (Subtype_Kind (Ekind (Index_Type)), N);
8368 Drange := Make_Range (Loc, New_Copy_Tree (Low_Bound), High_Bound);
8369 Set_Scalar_Range (Index_Subtype, Drange);
8370 Set_Parent (Drange, N);
8371 Analyze_And_Resolve (Drange, Index_Type);
8373 -- In the context, the Index_Type may already have a constraint,
8374 -- so use common base type on string subtype. The base type may
8375 -- be used when generating attributes of the string, for example
8376 -- in the context of a slice assignment.
8378 Set_Etype (Index_Subtype, Base_Type (Index_Type));
8379 Set_Size_Info (Index_Subtype, Index_Type);
8380 Set_RM_Size (Index_Subtype, RM_Size (Index_Type));
8382 Array_Subtype := Create_Itype (E_Array_Subtype, N);
8384 Index := New_Occurrence_Of (Index_Subtype, Loc);
8385 Set_Etype (Index, Index_Subtype);
8386 Append (Index, Index_List);
8388 Set_First_Index (Array_Subtype, Index);
8389 Set_Etype (Array_Subtype, Base_Type (Typ));
8390 Set_Is_Constrained (Array_Subtype, True);
8391 Init_Size_Align (Array_Subtype);
8393 Rewrite (N,
8394 Make_Unchecked_Type_Conversion (Loc,
8395 Subtype_Mark => New_Occurrence_Of (Array_Subtype, Loc),
8396 Expression => Relocate_Node (N)));
8397 Set_Etype (N, Array_Subtype);
8398 end;
8399 end if;
8400 end Set_String_Literal_Subtype;
8402 ------------------------------
8403 -- Simplify_Type_Conversion --
8404 ------------------------------
8406 procedure Simplify_Type_Conversion (N : Node_Id) is
8407 begin
8408 if Nkind (N) = N_Type_Conversion then
8409 declare
8410 Operand : constant Node_Id := Expression (N);
8411 Target_Typ : constant Entity_Id := Etype (N);
8412 Opnd_Typ : constant Entity_Id := Etype (Operand);
8414 begin
8415 if Is_Floating_Point_Type (Opnd_Typ)
8416 and then
8417 (Is_Integer_Type (Target_Typ)
8418 or else (Is_Fixed_Point_Type (Target_Typ)
8419 and then Conversion_OK (N)))
8420 and then Nkind (Operand) = N_Attribute_Reference
8421 and then Attribute_Name (Operand) = Name_Truncation
8423 -- Special processing required if the conversion is the expression
8424 -- of a Truncation attribute reference. In this case we replace:
8426 -- ityp (ftyp'Truncation (x))
8428 -- by
8430 -- ityp (x)
8432 -- with the Float_Truncate flag set, which is more efficient
8434 then
8435 Rewrite (Operand,
8436 Relocate_Node (First (Expressions (Operand))));
8437 Set_Float_Truncate (N, True);
8438 end if;
8439 end;
8440 end if;
8441 end Simplify_Type_Conversion;
8443 -----------------------------
8444 -- Unique_Fixed_Point_Type --
8445 -----------------------------
8447 function Unique_Fixed_Point_Type (N : Node_Id) return Entity_Id is
8448 T1 : Entity_Id := Empty;
8449 T2 : Entity_Id;
8450 Item : Node_Id;
8451 Scop : Entity_Id;
8453 procedure Fixed_Point_Error;
8454 -- If true ambiguity, give details
8456 -----------------------
8457 -- Fixed_Point_Error --
8458 -----------------------
8460 procedure Fixed_Point_Error is
8461 begin
8462 Error_Msg_N ("ambiguous universal_fixed_expression", N);
8463 Error_Msg_NE ("\\possible interpretation as}", N, T1);
8464 Error_Msg_NE ("\\possible interpretation as}", N, T2);
8465 end Fixed_Point_Error;
8467 -- Start of processing for Unique_Fixed_Point_Type
8469 begin
8470 -- The operations on Duration are visible, so Duration is always a
8471 -- possible interpretation.
8473 T1 := Standard_Duration;
8475 -- Look for fixed-point types in enclosing scopes
8477 Scop := Current_Scope;
8478 while Scop /= Standard_Standard loop
8479 T2 := First_Entity (Scop);
8480 while Present (T2) loop
8481 if Is_Fixed_Point_Type (T2)
8482 and then Current_Entity (T2) = T2
8483 and then Scope (Base_Type (T2)) = Scop
8484 then
8485 if Present (T1) then
8486 Fixed_Point_Error;
8487 return Any_Type;
8488 else
8489 T1 := T2;
8490 end if;
8491 end if;
8493 Next_Entity (T2);
8494 end loop;
8496 Scop := Scope (Scop);
8497 end loop;
8499 -- Look for visible fixed type declarations in the context
8501 Item := First (Context_Items (Cunit (Current_Sem_Unit)));
8502 while Present (Item) loop
8503 if Nkind (Item) = N_With_Clause then
8504 Scop := Entity (Name (Item));
8505 T2 := First_Entity (Scop);
8506 while Present (T2) loop
8507 if Is_Fixed_Point_Type (T2)
8508 and then Scope (Base_Type (T2)) = Scop
8509 and then (Is_Potentially_Use_Visible (T2)
8510 or else In_Use (T2))
8511 then
8512 if Present (T1) then
8513 Fixed_Point_Error;
8514 return Any_Type;
8515 else
8516 T1 := T2;
8517 end if;
8518 end if;
8520 Next_Entity (T2);
8521 end loop;
8522 end if;
8524 Next (Item);
8525 end loop;
8527 if Nkind (N) = N_Real_Literal then
8528 Error_Msg_NE ("?real literal interpreted as }!", N, T1);
8530 else
8531 Error_Msg_NE ("?universal_fixed expression interpreted as }!", N, T1);
8532 end if;
8534 return T1;
8535 end Unique_Fixed_Point_Type;
8537 ----------------------
8538 -- Valid_Conversion --
8539 ----------------------
8541 function Valid_Conversion
8542 (N : Node_Id;
8543 Target : Entity_Id;
8544 Operand : Node_Id) return Boolean
8546 Target_Type : constant Entity_Id := Base_Type (Target);
8547 Opnd_Type : Entity_Id := Etype (Operand);
8549 function Conversion_Check
8550 (Valid : Boolean;
8551 Msg : String) return Boolean;
8552 -- Little routine to post Msg if Valid is False, returns Valid value
8554 function Valid_Tagged_Conversion
8555 (Target_Type : Entity_Id;
8556 Opnd_Type : Entity_Id) return Boolean;
8557 -- Specifically test for validity of tagged conversions
8559 function Valid_Array_Conversion return Boolean;
8560 -- Check index and component conformance, and accessibility levels
8561 -- if the component types are anonymous access types (Ada 2005)
8563 ----------------------
8564 -- Conversion_Check --
8565 ----------------------
8567 function Conversion_Check
8568 (Valid : Boolean;
8569 Msg : String) return Boolean
8571 begin
8572 if not Valid then
8573 Error_Msg_N (Msg, Operand);
8574 end if;
8576 return Valid;
8577 end Conversion_Check;
8579 ----------------------------
8580 -- Valid_Array_Conversion --
8581 ----------------------------
8583 function Valid_Array_Conversion return Boolean
8585 Opnd_Comp_Type : constant Entity_Id := Component_Type (Opnd_Type);
8586 Opnd_Comp_Base : constant Entity_Id := Base_Type (Opnd_Comp_Type);
8588 Opnd_Index : Node_Id;
8589 Opnd_Index_Type : Entity_Id;
8591 Target_Comp_Type : constant Entity_Id :=
8592 Component_Type (Target_Type);
8593 Target_Comp_Base : constant Entity_Id :=
8594 Base_Type (Target_Comp_Type);
8596 Target_Index : Node_Id;
8597 Target_Index_Type : Entity_Id;
8599 begin
8600 -- Error if wrong number of dimensions
8603 Number_Dimensions (Target_Type) /= Number_Dimensions (Opnd_Type)
8604 then
8605 Error_Msg_N
8606 ("incompatible number of dimensions for conversion", Operand);
8607 return False;
8609 -- Number of dimensions matches
8611 else
8612 -- Loop through indexes of the two arrays
8614 Target_Index := First_Index (Target_Type);
8615 Opnd_Index := First_Index (Opnd_Type);
8616 while Present (Target_Index) and then Present (Opnd_Index) loop
8617 Target_Index_Type := Etype (Target_Index);
8618 Opnd_Index_Type := Etype (Opnd_Index);
8620 -- Error if index types are incompatible
8622 if not (Is_Integer_Type (Target_Index_Type)
8623 and then Is_Integer_Type (Opnd_Index_Type))
8624 and then (Root_Type (Target_Index_Type)
8625 /= Root_Type (Opnd_Index_Type))
8626 then
8627 Error_Msg_N
8628 ("incompatible index types for array conversion",
8629 Operand);
8630 return False;
8631 end if;
8633 Next_Index (Target_Index);
8634 Next_Index (Opnd_Index);
8635 end loop;
8637 -- If component types have same base type, all set
8639 if Target_Comp_Base = Opnd_Comp_Base then
8640 null;
8642 -- Here if base types of components are not the same. The only
8643 -- time this is allowed is if we have anonymous access types.
8645 -- The conversion of arrays of anonymous access types can lead
8646 -- to dangling pointers. AI-392 formalizes the accessibility
8647 -- checks that must be applied to such conversions to prevent
8648 -- out-of-scope references.
8650 elsif
8651 (Ekind (Target_Comp_Base) = E_Anonymous_Access_Type
8652 or else
8653 Ekind (Target_Comp_Base) = E_Anonymous_Access_Subprogram_Type)
8654 and then Ekind (Opnd_Comp_Base) = Ekind (Target_Comp_Base)
8655 and then
8656 Subtypes_Statically_Match (Target_Comp_Type, Opnd_Comp_Type)
8657 then
8658 if Type_Access_Level (Target_Type) <
8659 Type_Access_Level (Opnd_Type)
8660 then
8661 if In_Instance_Body then
8662 Error_Msg_N ("?source array type " &
8663 "has deeper accessibility level than target", Operand);
8664 Error_Msg_N ("\?Program_Error will be raised at run time",
8665 Operand);
8666 Rewrite (N,
8667 Make_Raise_Program_Error (Sloc (N),
8668 Reason => PE_Accessibility_Check_Failed));
8669 Set_Etype (N, Target_Type);
8670 return False;
8672 -- Conversion not allowed because of accessibility levels
8674 else
8675 Error_Msg_N ("source array type " &
8676 "has deeper accessibility level than target", Operand);
8677 return False;
8678 end if;
8679 else
8680 null;
8681 end if;
8683 -- All other cases where component base types do not match
8685 else
8686 Error_Msg_N
8687 ("incompatible component types for array conversion",
8688 Operand);
8689 return False;
8690 end if;
8692 -- Check that component subtypes statically match
8694 if Is_Constrained (Target_Comp_Type) /=
8695 Is_Constrained (Opnd_Comp_Type)
8696 or else not Subtypes_Statically_Match
8697 (Target_Comp_Type, Opnd_Comp_Type)
8698 then
8699 Error_Msg_N
8700 ("component subtypes must statically match", Operand);
8701 return False;
8702 end if;
8703 end if;
8705 return True;
8706 end Valid_Array_Conversion;
8708 -----------------------------
8709 -- Valid_Tagged_Conversion --
8710 -----------------------------
8712 function Valid_Tagged_Conversion
8713 (Target_Type : Entity_Id;
8714 Opnd_Type : Entity_Id) return Boolean
8716 begin
8717 -- Upward conversions are allowed (RM 4.6(22))
8719 if Covers (Target_Type, Opnd_Type)
8720 or else Is_Ancestor (Target_Type, Opnd_Type)
8721 then
8722 return True;
8724 -- Downward conversion are allowed if the operand is class-wide
8725 -- (RM 4.6(23)).
8727 elsif Is_Class_Wide_Type (Opnd_Type)
8728 and then Covers (Opnd_Type, Target_Type)
8729 then
8730 return True;
8732 elsif Covers (Opnd_Type, Target_Type)
8733 or else Is_Ancestor (Opnd_Type, Target_Type)
8734 then
8735 return
8736 Conversion_Check (False,
8737 "downward conversion of tagged objects not allowed");
8739 -- Ada 2005 (AI-251): The conversion to/from interface types is
8740 -- always valid
8742 elsif Is_Interface (Target_Type) or else Is_Interface (Opnd_Type) then
8743 return True;
8745 -- If the operand is a class-wide type obtained through a limited_
8746 -- with clause, and the context includes the non-limited view, use
8747 -- it to determine whether the conversion is legal.
8749 elsif Is_Class_Wide_Type (Opnd_Type)
8750 and then From_With_Type (Opnd_Type)
8751 and then Present (Non_Limited_View (Etype (Opnd_Type)))
8752 and then Is_Interface (Non_Limited_View (Etype (Opnd_Type)))
8753 then
8754 return True;
8756 elsif Is_Access_Type (Opnd_Type)
8757 and then Is_Interface (Directly_Designated_Type (Opnd_Type))
8758 then
8759 return True;
8761 else
8762 Error_Msg_NE
8763 ("invalid tagged conversion, not compatible with}",
8764 N, First_Subtype (Opnd_Type));
8765 return False;
8766 end if;
8767 end Valid_Tagged_Conversion;
8769 -- Start of processing for Valid_Conversion
8771 begin
8772 Check_Parameterless_Call (Operand);
8774 if Is_Overloaded (Operand) then
8775 declare
8776 I : Interp_Index;
8777 I1 : Interp_Index;
8778 It : Interp;
8779 It1 : Interp;
8780 N1 : Entity_Id;
8782 begin
8783 -- Remove procedure calls, which syntactically cannot appear
8784 -- in this context, but which cannot be removed by type checking,
8785 -- because the context does not impose a type.
8787 -- When compiling for VMS, spurious ambiguities can be produced
8788 -- when arithmetic operations have a literal operand and return
8789 -- System.Address or a descendant of it. These ambiguities are
8790 -- otherwise resolved by the context, but for conversions there
8791 -- is no context type and the removal of the spurious operations
8792 -- must be done explicitly here.
8794 -- The node may be labelled overloaded, but still contain only
8795 -- one interpretation because others were discarded in previous
8796 -- filters. If this is the case, retain the single interpretation
8797 -- if legal.
8799 Get_First_Interp (Operand, I, It);
8800 Opnd_Type := It.Typ;
8801 Get_Next_Interp (I, It);
8803 if Present (It.Typ)
8804 and then Opnd_Type /= Standard_Void_Type
8805 then
8806 -- More than one candidate interpretation is available
8808 Get_First_Interp (Operand, I, It);
8809 while Present (It.Typ) loop
8810 if It.Typ = Standard_Void_Type then
8811 Remove_Interp (I);
8812 end if;
8814 if Present (System_Aux_Id)
8815 and then Is_Descendent_Of_Address (It.Typ)
8816 then
8817 Remove_Interp (I);
8818 end if;
8820 Get_Next_Interp (I, It);
8821 end loop;
8822 end if;
8824 Get_First_Interp (Operand, I, It);
8825 I1 := I;
8826 It1 := It;
8828 if No (It.Typ) then
8829 Error_Msg_N ("illegal operand in conversion", Operand);
8830 return False;
8831 end if;
8833 Get_Next_Interp (I, It);
8835 if Present (It.Typ) then
8836 N1 := It1.Nam;
8837 It1 := Disambiguate (Operand, I1, I, Any_Type);
8839 if It1 = No_Interp then
8840 Error_Msg_N ("ambiguous operand in conversion", Operand);
8842 Error_Msg_Sloc := Sloc (It.Nam);
8843 Error_Msg_N ("\\possible interpretation#!", Operand);
8845 Error_Msg_Sloc := Sloc (N1);
8846 Error_Msg_N ("\\possible interpretation#!", Operand);
8848 return False;
8849 end if;
8850 end if;
8852 Set_Etype (Operand, It1.Typ);
8853 Opnd_Type := It1.Typ;
8854 end;
8855 end if;
8857 -- Numeric types
8859 if Is_Numeric_Type (Target_Type) then
8861 -- A universal fixed expression can be converted to any numeric type
8863 if Opnd_Type = Universal_Fixed then
8864 return True;
8866 -- Also no need to check when in an instance or inlined body, because
8867 -- the legality has been established when the template was analyzed.
8868 -- Furthermore, numeric conversions may occur where only a private
8869 -- view of the operand type is visible at the instanciation point.
8870 -- This results in a spurious error if we check that the operand type
8871 -- is a numeric type.
8873 -- Note: in a previous version of this unit, the following tests were
8874 -- applied only for generated code (Comes_From_Source set to False),
8875 -- but in fact the test is required for source code as well, since
8876 -- this situation can arise in source code.
8878 elsif In_Instance or else In_Inlined_Body then
8879 return True;
8881 -- Otherwise we need the conversion check
8883 else
8884 return Conversion_Check
8885 (Is_Numeric_Type (Opnd_Type),
8886 "illegal operand for numeric conversion");
8887 end if;
8889 -- Array types
8891 elsif Is_Array_Type (Target_Type) then
8892 if not Is_Array_Type (Opnd_Type)
8893 or else Opnd_Type = Any_Composite
8894 or else Opnd_Type = Any_String
8895 then
8896 Error_Msg_N
8897 ("illegal operand for array conversion", Operand);
8898 return False;
8899 else
8900 return Valid_Array_Conversion;
8901 end if;
8903 -- Ada 2005 (AI-251): Anonymous access types where target references an
8904 -- interface type.
8906 elsif (Ekind (Target_Type) = E_General_Access_Type
8907 or else
8908 Ekind (Target_Type) = E_Anonymous_Access_Type)
8909 and then Is_Interface (Directly_Designated_Type (Target_Type))
8910 then
8911 -- Check the static accessibility rule of 4.6(17). Note that the
8912 -- check is not enforced when within an instance body, since the RM
8913 -- requires such cases to be caught at run time.
8915 if Ekind (Target_Type) /= E_Anonymous_Access_Type then
8916 if Type_Access_Level (Opnd_Type) >
8917 Type_Access_Level (Target_Type)
8918 then
8919 -- In an instance, this is a run-time check, but one we know
8920 -- will fail, so generate an appropriate warning. The raise
8921 -- will be generated by Expand_N_Type_Conversion.
8923 if In_Instance_Body then
8924 Error_Msg_N
8925 ("?cannot convert local pointer to non-local access type",
8926 Operand);
8927 Error_Msg_N
8928 ("\?Program_Error will be raised at run time", Operand);
8929 else
8930 Error_Msg_N
8931 ("cannot convert local pointer to non-local access type",
8932 Operand);
8933 return False;
8934 end if;
8936 -- Special accessibility checks are needed in the case of access
8937 -- discriminants declared for a limited type.
8939 elsif Ekind (Opnd_Type) = E_Anonymous_Access_Type
8940 and then not Is_Local_Anonymous_Access (Opnd_Type)
8941 then
8942 -- When the operand is a selected access discriminant the check
8943 -- needs to be made against the level of the object denoted by
8944 -- the prefix of the selected name. (Object_Access_Level
8945 -- handles checking the prefix of the operand for this case.)
8947 if Nkind (Operand) = N_Selected_Component
8948 and then Object_Access_Level (Operand) >
8949 Type_Access_Level (Target_Type)
8950 then
8951 -- In an instance, this is a run-time check, but one we
8952 -- know will fail, so generate an appropriate warning.
8953 -- The raise will be generated by Expand_N_Type_Conversion.
8955 if In_Instance_Body then
8956 Error_Msg_N
8957 ("?cannot convert access discriminant to non-local" &
8958 " access type", Operand);
8959 Error_Msg_N
8960 ("\?Program_Error will be raised at run time", Operand);
8961 else
8962 Error_Msg_N
8963 ("cannot convert access discriminant to non-local" &
8964 " access type", Operand);
8965 return False;
8966 end if;
8967 end if;
8969 -- The case of a reference to an access discriminant from
8970 -- within a limited type declaration (which will appear as
8971 -- a discriminal) is always illegal because the level of the
8972 -- discriminant is considered to be deeper than any (namable)
8973 -- access type.
8975 if Is_Entity_Name (Operand)
8976 and then not Is_Local_Anonymous_Access (Opnd_Type)
8977 and then (Ekind (Entity (Operand)) = E_In_Parameter
8978 or else Ekind (Entity (Operand)) = E_Constant)
8979 and then Present (Discriminal_Link (Entity (Operand)))
8980 then
8981 Error_Msg_N
8982 ("discriminant has deeper accessibility level than target",
8983 Operand);
8984 return False;
8985 end if;
8986 end if;
8987 end if;
8989 return True;
8991 -- General and anonymous access types
8993 elsif (Ekind (Target_Type) = E_General_Access_Type
8994 or else Ekind (Target_Type) = E_Anonymous_Access_Type)
8995 and then
8996 Conversion_Check
8997 (Is_Access_Type (Opnd_Type)
8998 and then Ekind (Opnd_Type) /=
8999 E_Access_Subprogram_Type
9000 and then Ekind (Opnd_Type) /=
9001 E_Access_Protected_Subprogram_Type,
9002 "must be an access-to-object type")
9003 then
9004 if Is_Access_Constant (Opnd_Type)
9005 and then not Is_Access_Constant (Target_Type)
9006 then
9007 Error_Msg_N
9008 ("access-to-constant operand type not allowed", Operand);
9009 return False;
9010 end if;
9012 -- Check the static accessibility rule of 4.6(17). Note that the
9013 -- check is not enforced when within an instance body, since the RM
9014 -- requires such cases to be caught at run time.
9016 if Ekind (Target_Type) /= E_Anonymous_Access_Type
9017 or else Is_Local_Anonymous_Access (Target_Type)
9018 then
9019 if Type_Access_Level (Opnd_Type)
9020 > Type_Access_Level (Target_Type)
9021 then
9022 -- In an instance, this is a run-time check, but one we
9023 -- know will fail, so generate an appropriate warning.
9024 -- The raise will be generated by Expand_N_Type_Conversion.
9026 if In_Instance_Body then
9027 Error_Msg_N
9028 ("?cannot convert local pointer to non-local access type",
9029 Operand);
9030 Error_Msg_N
9031 ("\?Program_Error will be raised at run time", Operand);
9033 else
9034 -- Avoid generation of spurious error message
9036 if not Error_Posted (N) then
9037 Error_Msg_N
9038 ("cannot convert local pointer to non-local access type",
9039 Operand);
9040 end if;
9042 return False;
9043 end if;
9045 -- Special accessibility checks are needed in the case of access
9046 -- discriminants declared for a limited type.
9048 elsif Ekind (Opnd_Type) = E_Anonymous_Access_Type
9049 and then not Is_Local_Anonymous_Access (Opnd_Type)
9050 then
9052 -- When the operand is a selected access discriminant the check
9053 -- needs to be made against the level of the object denoted by
9054 -- the prefix of the selected name. (Object_Access_Level
9055 -- handles checking the prefix of the operand for this case.)
9057 if Nkind (Operand) = N_Selected_Component
9058 and then Object_Access_Level (Operand)
9059 > Type_Access_Level (Target_Type)
9060 then
9061 -- In an instance, this is a run-time check, but one we
9062 -- know will fail, so generate an appropriate warning.
9063 -- The raise will be generated by Expand_N_Type_Conversion.
9065 if In_Instance_Body then
9066 Error_Msg_N
9067 ("?cannot convert access discriminant to non-local" &
9068 " access type", Operand);
9069 Error_Msg_N
9070 ("\?Program_Error will be raised at run time",
9071 Operand);
9073 else
9074 Error_Msg_N
9075 ("cannot convert access discriminant to non-local" &
9076 " access type", Operand);
9077 return False;
9078 end if;
9079 end if;
9081 -- The case of a reference to an access discriminant from
9082 -- within a limited type declaration (which will appear as
9083 -- a discriminal) is always illegal because the level of the
9084 -- discriminant is considered to be deeper than any (namable)
9085 -- access type.
9087 if Is_Entity_Name (Operand)
9088 and then (Ekind (Entity (Operand)) = E_In_Parameter
9089 or else Ekind (Entity (Operand)) = E_Constant)
9090 and then Present (Discriminal_Link (Entity (Operand)))
9091 then
9092 Error_Msg_N
9093 ("discriminant has deeper accessibility level than target",
9094 Operand);
9095 return False;
9096 end if;
9097 end if;
9098 end if;
9100 declare
9101 function Full_Designated_Type (T : Entity_Id) return Entity_Id;
9102 -- Helper function to handle limited views
9104 --------------------------
9105 -- Full_Designated_Type --
9106 --------------------------
9108 function Full_Designated_Type (T : Entity_Id) return Entity_Id is
9109 Desig : constant Entity_Id := Designated_Type (T);
9110 begin
9111 if From_With_Type (Desig)
9112 and then Is_Incomplete_Type (Desig)
9113 and then Present (Non_Limited_View (Desig))
9114 then
9115 return Non_Limited_View (Desig);
9116 else
9117 return Desig;
9118 end if;
9119 end Full_Designated_Type;
9121 Target : constant Entity_Id := Full_Designated_Type (Target_Type);
9122 Opnd : constant Entity_Id := Full_Designated_Type (Opnd_Type);
9124 Same_Base : constant Boolean :=
9125 Base_Type (Target) = Base_Type (Opnd);
9127 begin
9128 if Is_Tagged_Type (Target) then
9129 return Valid_Tagged_Conversion (Target, Opnd);
9131 else
9132 if not Same_Base then
9133 Error_Msg_NE
9134 ("target designated type not compatible with }",
9135 N, Base_Type (Opnd));
9136 return False;
9138 -- Ada 2005 AI-384: legality rule is symmetric in both
9139 -- designated types. The conversion is legal (with possible
9140 -- constraint check) if either designated type is
9141 -- unconstrained.
9143 elsif Subtypes_Statically_Match (Target, Opnd)
9144 or else
9145 (Has_Discriminants (Target)
9146 and then
9147 (not Is_Constrained (Opnd)
9148 or else not Is_Constrained (Target)))
9149 then
9150 return True;
9152 else
9153 Error_Msg_NE
9154 ("target designated subtype not compatible with }",
9155 N, Opnd);
9156 return False;
9157 end if;
9158 end if;
9159 end;
9161 -- Subprogram access types
9163 elsif (Ekind (Target_Type) = E_Access_Subprogram_Type
9164 or else
9165 Ekind (Target_Type) = E_Anonymous_Access_Subprogram_Type)
9166 and then No (Corresponding_Remote_Type (Opnd_Type))
9167 then
9169 Ekind (Base_Type (Opnd_Type)) = E_Anonymous_Access_Subprogram_Type
9170 then
9171 Error_Msg_N
9172 ("illegal attempt to store anonymous access to subprogram",
9173 Operand);
9174 Error_Msg_N
9175 ("\value has deeper accessibility than any master " &
9176 "(RM 3.10.2 (13))",
9177 Operand);
9179 if Is_Entity_Name (Operand)
9180 and then Ekind (Entity (Operand)) = E_In_Parameter
9181 then
9182 Error_Msg_NE
9183 ("\use named access type for& instead of access parameter",
9184 Operand, Entity (Operand));
9185 end if;
9186 end if;
9188 -- Check that the designated types are subtype conformant
9190 Check_Subtype_Conformant (New_Id => Designated_Type (Target_Type),
9191 Old_Id => Designated_Type (Opnd_Type),
9192 Err_Loc => N);
9194 -- Check the static accessibility rule of 4.6(20)
9196 if Type_Access_Level (Opnd_Type) >
9197 Type_Access_Level (Target_Type)
9198 then
9199 Error_Msg_N
9200 ("operand type has deeper accessibility level than target",
9201 Operand);
9203 -- Check that if the operand type is declared in a generic body,
9204 -- then the target type must be declared within that same body
9205 -- (enforces last sentence of 4.6(20)).
9207 elsif Present (Enclosing_Generic_Body (Opnd_Type)) then
9208 declare
9209 O_Gen : constant Node_Id :=
9210 Enclosing_Generic_Body (Opnd_Type);
9212 T_Gen : Node_Id;
9214 begin
9215 T_Gen := Enclosing_Generic_Body (Target_Type);
9216 while Present (T_Gen) and then T_Gen /= O_Gen loop
9217 T_Gen := Enclosing_Generic_Body (T_Gen);
9218 end loop;
9220 if T_Gen /= O_Gen then
9221 Error_Msg_N
9222 ("target type must be declared in same generic body"
9223 & " as operand type", N);
9224 end if;
9225 end;
9226 end if;
9228 return True;
9230 -- Remote subprogram access types
9232 elsif Is_Remote_Access_To_Subprogram_Type (Target_Type)
9233 and then Is_Remote_Access_To_Subprogram_Type (Opnd_Type)
9234 then
9235 -- It is valid to convert from one RAS type to another provided
9236 -- that their specification statically match.
9238 Check_Subtype_Conformant
9239 (New_Id =>
9240 Designated_Type (Corresponding_Remote_Type (Target_Type)),
9241 Old_Id =>
9242 Designated_Type (Corresponding_Remote_Type (Opnd_Type)),
9243 Err_Loc =>
9245 return True;
9247 -- If both are tagged types, check legality of view conversions
9249 elsif Is_Tagged_Type (Target_Type)
9250 and then Is_Tagged_Type (Opnd_Type)
9251 then
9252 return Valid_Tagged_Conversion (Target_Type, Opnd_Type);
9254 -- Types derived from the same root type are convertible
9256 elsif Root_Type (Target_Type) = Root_Type (Opnd_Type) then
9257 return True;
9259 -- In an instance or an inlined body, there may be inconsistent
9260 -- views of the same type, or of types derived from a common root.
9262 elsif (In_Instance or In_Inlined_Body)
9263 and then
9264 Root_Type (Underlying_Type (Target_Type)) =
9265 Root_Type (Underlying_Type (Opnd_Type))
9266 then
9267 return True;
9269 -- Special check for common access type error case
9271 elsif Ekind (Target_Type) = E_Access_Type
9272 and then Is_Access_Type (Opnd_Type)
9273 then
9274 Error_Msg_N ("target type must be general access type!", N);
9275 Error_Msg_NE ("add ALL to }!", N, Target_Type);
9277 return False;
9279 else
9280 Error_Msg_NE ("invalid conversion, not compatible with }",
9281 N, Opnd_Type);
9283 return False;
9284 end if;
9285 end Valid_Conversion;
9287 end Sem_Res;