Merge -r 127928:132243 from trunk
[official-gcc.git] / gcc / ada / sem_ch4.adb
blobebfdccf86ad97c7613f99c3a2cc100c2e3ace429
1 ------------------------------------------------------------------------------
2 -- --
3 -- GNAT COMPILER COMPONENTS --
4 -- --
5 -- S E M _ C H 4 --
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 Debug; use Debug;
28 with Einfo; use Einfo;
29 with Elists; use Elists;
30 with Errout; use Errout;
31 with Exp_Util; use Exp_Util;
32 with Fname; use Fname;
33 with Itypes; use Itypes;
34 with Lib; use Lib;
35 with Lib.Xref; use Lib.Xref;
36 with Namet; use Namet;
37 with Namet.Sp; use Namet.Sp;
38 with Nlists; use Nlists;
39 with Nmake; use Nmake;
40 with Opt; use Opt;
41 with Output; use Output;
42 with Restrict; use Restrict;
43 with Rident; use Rident;
44 with Sem; use Sem;
45 with Sem_Cat; use Sem_Cat;
46 with Sem_Ch3; use Sem_Ch3;
47 with Sem_Ch6; use Sem_Ch6;
48 with Sem_Ch8; use Sem_Ch8;
49 with Sem_Disp; use Sem_Disp;
50 with Sem_Dist; use Sem_Dist;
51 with Sem_Eval; use Sem_Eval;
52 with Sem_Res; use Sem_Res;
53 with Sem_Util; use Sem_Util;
54 with Sem_Type; use Sem_Type;
55 with Stand; use Stand;
56 with Sinfo; use Sinfo;
57 with Snames; use Snames;
58 with Tbuild; use Tbuild;
60 package body Sem_Ch4 is
62 -----------------------
63 -- Local Subprograms --
64 -----------------------
66 procedure Analyze_Concatenation_Rest (N : Node_Id);
67 -- Does the "rest" of the work of Analyze_Concatenation, after the left
68 -- operand has been analyzed. See Analyze_Concatenation for details.
70 procedure Analyze_Expression (N : Node_Id);
71 -- For expressions that are not names, this is just a call to analyze.
72 -- If the expression is a name, it may be a call to a parameterless
73 -- function, and if so must be converted into an explicit call node
74 -- and analyzed as such. This deproceduring must be done during the first
75 -- pass of overload resolution, because otherwise a procedure call with
76 -- overloaded actuals may fail to resolve. See 4327-001 for an example.
78 procedure Analyze_Operator_Call (N : Node_Id; Op_Id : Entity_Id);
79 -- Analyze a call of the form "+"(x, y), etc. The prefix of the call
80 -- is an operator name or an expanded name whose selector is an operator
81 -- name, and one possible interpretation is as a predefined operator.
83 procedure Analyze_Overloaded_Selected_Component (N : Node_Id);
84 -- If the prefix of a selected_component is overloaded, the proper
85 -- interpretation that yields a record type with the proper selector
86 -- name must be selected.
88 procedure Analyze_User_Defined_Binary_Op (N : Node_Id; Op_Id : Entity_Id);
89 -- Procedure to analyze a user defined binary operator, which is resolved
90 -- like a function, but instead of a list of actuals it is presented
91 -- with the left and right operands of an operator node.
93 procedure Analyze_User_Defined_Unary_Op (N : Node_Id; Op_Id : Entity_Id);
94 -- Procedure to analyze a user defined unary operator, which is resolved
95 -- like a function, but instead of a list of actuals, it is presented with
96 -- the operand of the operator node.
98 procedure Ambiguous_Operands (N : Node_Id);
99 -- for equality, membership, and comparison operators with overloaded
100 -- arguments, list possible interpretations.
102 procedure Analyze_One_Call
103 (N : Node_Id;
104 Nam : Entity_Id;
105 Report : Boolean;
106 Success : out Boolean;
107 Skip_First : Boolean := False);
108 -- Check one interpretation of an overloaded subprogram name for
109 -- compatibility with the types of the actuals in a call. If there is a
110 -- single interpretation which does not match, post error if Report is
111 -- set to True.
113 -- Nam is the entity that provides the formals against which the actuals
114 -- are checked. Nam is either the name of a subprogram, or the internal
115 -- subprogram type constructed for an access_to_subprogram. If the actuals
116 -- are compatible with Nam, then Nam is added to the list of candidate
117 -- interpretations for N, and Success is set to True.
119 -- The flag Skip_First is used when analyzing a call that was rewritten
120 -- from object notation. In this case the first actual may have to receive
121 -- an explicit dereference, depending on the first formal of the operation
122 -- being called. The caller will have verified that the object is legal
123 -- for the call. If the remaining parameters match, the first parameter
124 -- will rewritten as a dereference if needed, prior to completing analysis.
126 procedure Check_Misspelled_Selector
127 (Prefix : Entity_Id;
128 Sel : Node_Id);
129 -- Give possible misspelling diagnostic if Sel is likely to be
130 -- a misspelling of one of the selectors of the Prefix.
131 -- This is called by Analyze_Selected_Component after producing
132 -- an invalid selector error message.
134 function Defined_In_Scope (T : Entity_Id; S : Entity_Id) return Boolean;
135 -- Verify that type T is declared in scope S. Used to find intepretations
136 -- for operators given by expanded names. This is abstracted as a separate
137 -- function to handle extensions to System, where S is System, but T is
138 -- declared in the extension.
140 procedure Find_Arithmetic_Types
141 (L, R : Node_Id;
142 Op_Id : Entity_Id;
143 N : Node_Id);
144 -- L and R are the operands of an arithmetic operator. Find
145 -- consistent pairs of interpretations for L and R that have a
146 -- numeric type consistent with the semantics of the operator.
148 procedure Find_Comparison_Types
149 (L, R : Node_Id;
150 Op_Id : Entity_Id;
151 N : Node_Id);
152 -- L and R are operands of a comparison operator. Find consistent
153 -- pairs of interpretations for L and R.
155 procedure Find_Concatenation_Types
156 (L, R : Node_Id;
157 Op_Id : Entity_Id;
158 N : Node_Id);
159 -- For the four varieties of concatenation
161 procedure Find_Equality_Types
162 (L, R : Node_Id;
163 Op_Id : Entity_Id;
164 N : Node_Id);
165 -- Ditto for equality operators
167 procedure Find_Boolean_Types
168 (L, R : Node_Id;
169 Op_Id : Entity_Id;
170 N : Node_Id);
171 -- Ditto for binary logical operations
173 procedure Find_Negation_Types
174 (R : Node_Id;
175 Op_Id : Entity_Id;
176 N : Node_Id);
177 -- Find consistent interpretation for operand of negation operator
179 procedure Find_Non_Universal_Interpretations
180 (N : Node_Id;
181 R : Node_Id;
182 Op_Id : Entity_Id;
183 T1 : Entity_Id);
184 -- For equality and comparison operators, the result is always boolean,
185 -- and the legality of the operation is determined from the visibility
186 -- of the operand types. If one of the operands has a universal interpre-
187 -- tation, the legality check uses some compatible non-universal
188 -- interpretation of the other operand. N can be an operator node, or
189 -- a function call whose name is an operator designator.
191 function Find_Primitive_Operation (N : Node_Id) return Boolean;
192 -- Find candidate interpretations for the name Obj.Proc when it appears
193 -- in a subprogram renaming declaration.
195 procedure Find_Unary_Types
196 (R : Node_Id;
197 Op_Id : Entity_Id;
198 N : Node_Id);
199 -- Unary arithmetic types: plus, minus, abs
201 procedure Check_Arithmetic_Pair
202 (T1, T2 : Entity_Id;
203 Op_Id : Entity_Id;
204 N : Node_Id);
205 -- Subsidiary procedure to Find_Arithmetic_Types. T1 and T2 are valid
206 -- types for left and right operand. Determine whether they constitute
207 -- a valid pair for the given operator, and record the corresponding
208 -- interpretation of the operator node. The node N may be an operator
209 -- node (the usual case) or a function call whose prefix is an operator
210 -- designator. In both cases Op_Id is the operator name itself.
212 procedure Diagnose_Call (N : Node_Id; Nam : Node_Id);
213 -- Give detailed information on overloaded call where none of the
214 -- interpretations match. N is the call node, Nam the designator for
215 -- the overloaded entity being called.
217 function Junk_Operand (N : Node_Id) return Boolean;
218 -- Test for an operand that is an inappropriate entity (e.g. a package
219 -- name or a label). If so, issue an error message and return True. If
220 -- the operand is not an inappropriate entity kind, return False.
222 procedure Operator_Check (N : Node_Id);
223 -- Verify that an operator has received some valid interpretation. If none
224 -- was found, determine whether a use clause would make the operation
225 -- legal. The variable Candidate_Type (defined in Sem_Type) is set for
226 -- every type compatible with the operator, even if the operator for the
227 -- type is not directly visible. The routine uses this type to emit a more
228 -- informative message.
230 function Process_Implicit_Dereference_Prefix
231 (E : Entity_Id;
232 P : Node_Id) return Entity_Id;
233 -- Called when P is the prefix of an implicit dereference, denoting an
234 -- object E. The function returns the designated type of the prefix, taking
235 -- into account that the designated type of an anonymous access type may be
236 -- a limited view, when the non-limited view is visible.
237 -- If in semantics only mode (-gnatc or generic), the function also records
238 -- that the prefix is a reference to E, if any. Normally, such a reference
239 -- is generated only when the implicit dereference is expanded into an
240 -- explicit one, but for consistency we must generate the reference when
241 -- expansion is disabled as well.
243 procedure Remove_Abstract_Operations (N : Node_Id);
244 -- Ada 2005: implementation of AI-310. An abstract non-dispatching
245 -- operation is not a candidate interpretation.
247 function Try_Indexed_Call
248 (N : Node_Id;
249 Nam : Entity_Id;
250 Typ : Entity_Id;
251 Skip_First : Boolean) return Boolean;
252 -- If a function has defaults for all its actuals, a call to it may in fact
253 -- be an indexing on the result of the call. Try_Indexed_Call attempts the
254 -- interpretation as an indexing, prior to analysis as a call. If both are
255 -- possible, the node is overloaded with both interpretations (same symbol
256 -- but two different types). If the call is written in prefix form, the
257 -- prefix becomes the first parameter in the call, and only the remaining
258 -- actuals must be checked for the presence of defaults.
260 function Try_Indirect_Call
261 (N : Node_Id;
262 Nam : Entity_Id;
263 Typ : Entity_Id) return Boolean;
264 -- Similarly, a function F that needs no actuals can return an access to a
265 -- subprogram, and the call F (X) interpreted as F.all (X). In this case
266 -- the call may be overloaded with both interpretations.
268 function Try_Object_Operation (N : Node_Id) return Boolean;
269 -- Ada 2005 (AI-252): Support the object.operation notation
271 ------------------------
272 -- Ambiguous_Operands --
273 ------------------------
275 procedure Ambiguous_Operands (N : Node_Id) is
276 procedure List_Operand_Interps (Opnd : Node_Id);
278 --------------------------
279 -- List_Operand_Interps --
280 --------------------------
282 procedure List_Operand_Interps (Opnd : Node_Id) is
283 Nam : Node_Id;
284 Err : Node_Id := N;
286 begin
287 if Is_Overloaded (Opnd) then
288 if Nkind (Opnd) in N_Op then
289 Nam := Opnd;
290 elsif Nkind (Opnd) = N_Function_Call then
291 Nam := Name (Opnd);
292 else
293 return;
294 end if;
296 else
297 return;
298 end if;
300 if Opnd = Left_Opnd (N) then
301 Error_Msg_N
302 ("\left operand has the following interpretations", N);
303 else
304 Error_Msg_N
305 ("\right operand has the following interpretations", N);
306 Err := Opnd;
307 end if;
309 List_Interps (Nam, Err);
310 end List_Operand_Interps;
312 -- Start of processing for Ambiguous_Operands
314 begin
315 if Nkind (N) in N_Membership_Test then
316 Error_Msg_N ("ambiguous operands for membership", N);
318 elsif Nkind_In (N, N_Op_Eq, N_Op_Ne) then
319 Error_Msg_N ("ambiguous operands for equality", N);
321 else
322 Error_Msg_N ("ambiguous operands for comparison", N);
323 end if;
325 if All_Errors_Mode then
326 List_Operand_Interps (Left_Opnd (N));
327 List_Operand_Interps (Right_Opnd (N));
328 else
329 Error_Msg_N ("\use -gnatf switch for details", N);
330 end if;
331 end Ambiguous_Operands;
333 -----------------------
334 -- Analyze_Aggregate --
335 -----------------------
337 -- Most of the analysis of Aggregates requires that the type be known,
338 -- and is therefore put off until resolution.
340 procedure Analyze_Aggregate (N : Node_Id) is
341 begin
342 if No (Etype (N)) then
343 Set_Etype (N, Any_Composite);
344 end if;
345 end Analyze_Aggregate;
347 -----------------------
348 -- Analyze_Allocator --
349 -----------------------
351 procedure Analyze_Allocator (N : Node_Id) is
352 Loc : constant Source_Ptr := Sloc (N);
353 Sav_Errs : constant Nat := Serious_Errors_Detected;
354 E : Node_Id := Expression (N);
355 Acc_Type : Entity_Id;
356 Type_Id : Entity_Id;
358 begin
359 Check_Restriction (No_Allocators, N);
361 if Nkind (E) = N_Qualified_Expression then
362 Acc_Type := Create_Itype (E_Allocator_Type, N);
363 Set_Etype (Acc_Type, Acc_Type);
364 Init_Size_Align (Acc_Type);
365 Find_Type (Subtype_Mark (E));
367 -- Analyze the qualified expression, and apply the name resolution
368 -- rule given in 4.7 (3).
370 Analyze (E);
371 Type_Id := Etype (E);
372 Set_Directly_Designated_Type (Acc_Type, Type_Id);
374 Resolve (Expression (E), Type_Id);
376 if Is_Limited_Type (Type_Id)
377 and then Comes_From_Source (N)
378 and then not In_Instance_Body
379 then
380 if not OK_For_Limited_Init (Expression (E)) then
381 Error_Msg_N ("initialization not allowed for limited types", N);
382 Explain_Limited_Type (Type_Id, N);
383 end if;
384 end if;
386 -- A qualified expression requires an exact match of the type,
387 -- class-wide matching is not allowed.
389 -- if Is_Class_Wide_Type (Type_Id)
390 -- and then Base_Type
391 -- (Etype (Expression (E))) /= Base_Type (Type_Id)
392 -- then
393 -- Wrong_Type (Expression (E), Type_Id);
394 -- end if;
396 Check_Non_Static_Context (Expression (E));
398 -- We don't analyze the qualified expression itself because it's
399 -- part of the allocator
401 Set_Etype (E, Type_Id);
403 -- Case where allocator has a subtype indication
405 else
406 declare
407 Def_Id : Entity_Id;
408 Base_Typ : Entity_Id;
410 begin
411 -- If the allocator includes a N_Subtype_Indication then a
412 -- constraint is present, otherwise the node is a subtype mark.
413 -- Introduce an explicit subtype declaration into the tree
414 -- defining some anonymous subtype and rewrite the allocator to
415 -- use this subtype rather than the subtype indication.
417 -- It is important to introduce the explicit subtype declaration
418 -- so that the bounds of the subtype indication are attached to
419 -- the tree in case the allocator is inside a generic unit.
421 if Nkind (E) = N_Subtype_Indication then
423 -- A constraint is only allowed for a composite type in Ada
424 -- 95. In Ada 83, a constraint is also allowed for an
425 -- access-to-composite type, but the constraint is ignored.
427 Find_Type (Subtype_Mark (E));
428 Base_Typ := Entity (Subtype_Mark (E));
430 if Is_Elementary_Type (Base_Typ) then
431 if not (Ada_Version = Ada_83
432 and then Is_Access_Type (Base_Typ))
433 then
434 Error_Msg_N ("constraint not allowed here", E);
436 if Nkind (Constraint (E)) =
437 N_Index_Or_Discriminant_Constraint
438 then
439 Error_Msg_N
440 ("\if qualified expression was meant, " &
441 "use apostrophe", Constraint (E));
442 end if;
443 end if;
445 -- Get rid of the bogus constraint:
447 Rewrite (E, New_Copy_Tree (Subtype_Mark (E)));
448 Analyze_Allocator (N);
449 return;
451 -- Ada 2005, AI-363: if the designated type has a constrained
452 -- partial view, it cannot receive a discriminant constraint,
453 -- and the allocated object is unconstrained.
455 elsif Ada_Version >= Ada_05
456 and then Has_Constrained_Partial_View (Base_Typ)
457 then
458 Error_Msg_N
459 ("constraint no allowed when type " &
460 "has a constrained partial view", Constraint (E));
461 end if;
463 if Expander_Active then
464 Def_Id :=
465 Make_Defining_Identifier (Loc, New_Internal_Name ('S'));
467 Insert_Action (E,
468 Make_Subtype_Declaration (Loc,
469 Defining_Identifier => Def_Id,
470 Subtype_Indication => Relocate_Node (E)));
472 if Sav_Errs /= Serious_Errors_Detected
473 and then Nkind (Constraint (E)) =
474 N_Index_Or_Discriminant_Constraint
475 then
476 Error_Msg_N
477 ("if qualified expression was meant, " &
478 "use apostrophe!", Constraint (E));
479 end if;
481 E := New_Occurrence_Of (Def_Id, Loc);
482 Rewrite (Expression (N), E);
483 end if;
484 end if;
486 Type_Id := Process_Subtype (E, N);
487 Acc_Type := Create_Itype (E_Allocator_Type, N);
488 Set_Etype (Acc_Type, Acc_Type);
489 Init_Size_Align (Acc_Type);
490 Set_Directly_Designated_Type (Acc_Type, Type_Id);
491 Check_Fully_Declared (Type_Id, N);
493 -- Ada 2005 (AI-231)
495 if Can_Never_Be_Null (Type_Id) then
496 Error_Msg_N ("(Ada 2005) qualified expression required",
497 Expression (N));
498 end if;
500 -- Check restriction against dynamically allocated protected
501 -- objects. Note that when limited aggregates are supported,
502 -- a similar test should be applied to an allocator with a
503 -- qualified expression ???
505 if Is_Protected_Type (Type_Id) then
506 Check_Restriction (No_Protected_Type_Allocators, N);
507 end if;
509 -- Check for missing initialization. Skip this check if we already
510 -- had errors on analyzing the allocator, since in that case these
511 -- are probably cascaded errors.
513 if Is_Indefinite_Subtype (Type_Id)
514 and then Serious_Errors_Detected = Sav_Errs
515 then
516 if Is_Class_Wide_Type (Type_Id) then
517 Error_Msg_N
518 ("initialization required in class-wide allocation", N);
519 else
520 if Ada_Version < Ada_05
521 and then Is_Limited_Type (Type_Id)
522 then
523 Error_Msg_N ("unconstrained allocation not allowed", N);
525 if Is_Array_Type (Type_Id) then
526 Error_Msg_N
527 ("\constraint with array bounds required", N);
529 elsif Has_Unknown_Discriminants (Type_Id) then
530 null;
532 else pragma Assert (Has_Discriminants (Type_Id));
533 Error_Msg_N
534 ("\constraint with discriminant values required", N);
535 end if;
537 -- Limited Ada 2005 and general non-limited case
539 else
540 Error_Msg_N
541 ("uninitialized unconstrained allocation not allowed",
544 if Is_Array_Type (Type_Id) then
545 Error_Msg_N
546 ("\qualified expression or constraint with " &
547 "array bounds required", N);
549 elsif Has_Unknown_Discriminants (Type_Id) then
550 Error_Msg_N ("\qualified expression required", N);
552 else pragma Assert (Has_Discriminants (Type_Id));
553 Error_Msg_N
554 ("\qualified expression or constraint with " &
555 "discriminant values required", N);
556 end if;
557 end if;
558 end if;
559 end if;
560 end;
561 end if;
563 if Is_Abstract_Type (Type_Id) then
564 Error_Msg_N ("cannot allocate abstract object", E);
565 end if;
567 if Has_Task (Designated_Type (Acc_Type)) then
568 Check_Restriction (No_Tasking, N);
569 Check_Restriction (Max_Tasks, N);
570 Check_Restriction (No_Task_Allocators, N);
571 end if;
573 -- If the No_Streams restriction is set, check that the type of the
574 -- object is not, and does not contain, any subtype derived from
575 -- Ada.Streams.Root_Stream_Type. Note that we guard the call to
576 -- Has_Stream just for efficiency reasons. There is no point in
577 -- spending time on a Has_Stream check if the restriction is not set.
579 if Restrictions.Set (No_Streams) then
580 if Has_Stream (Designated_Type (Acc_Type)) then
581 Check_Restriction (No_Streams, N);
582 end if;
583 end if;
585 Set_Etype (N, Acc_Type);
587 if not Is_Library_Level_Entity (Acc_Type) then
588 Check_Restriction (No_Local_Allocators, N);
589 end if;
591 if Serious_Errors_Detected > Sav_Errs then
592 Set_Error_Posted (N);
593 Set_Etype (N, Any_Type);
594 end if;
595 end Analyze_Allocator;
597 ---------------------------
598 -- Analyze_Arithmetic_Op --
599 ---------------------------
601 procedure Analyze_Arithmetic_Op (N : Node_Id) is
602 L : constant Node_Id := Left_Opnd (N);
603 R : constant Node_Id := Right_Opnd (N);
604 Op_Id : Entity_Id;
606 begin
607 Candidate_Type := Empty;
608 Analyze_Expression (L);
609 Analyze_Expression (R);
611 -- If the entity is already set, the node is the instantiation of a
612 -- generic node with a non-local reference, or was manufactured by a
613 -- call to Make_Op_xxx. In either case the entity is known to be valid,
614 -- and we do not need to collect interpretations, instead we just get
615 -- the single possible interpretation.
617 Op_Id := Entity (N);
619 if Present (Op_Id) then
620 if Ekind (Op_Id) = E_Operator then
622 if Nkind_In (N, N_Op_Divide, N_Op_Mod, N_Op_Multiply, N_Op_Rem)
623 and then Treat_Fixed_As_Integer (N)
624 then
625 null;
626 else
627 Set_Etype (N, Any_Type);
628 Find_Arithmetic_Types (L, R, Op_Id, N);
629 end if;
631 else
632 Set_Etype (N, Any_Type);
633 Add_One_Interp (N, Op_Id, Etype (Op_Id));
634 end if;
636 -- Entity is not already set, so we do need to collect interpretations
638 else
639 Op_Id := Get_Name_Entity_Id (Chars (N));
640 Set_Etype (N, Any_Type);
642 while Present (Op_Id) loop
643 if Ekind (Op_Id) = E_Operator
644 and then Present (Next_Entity (First_Entity (Op_Id)))
645 then
646 Find_Arithmetic_Types (L, R, Op_Id, N);
648 -- The following may seem superfluous, because an operator cannot
649 -- be generic, but this ignores the cleverness of the author of
650 -- ACVC bc1013a.
652 elsif Is_Overloadable (Op_Id) then
653 Analyze_User_Defined_Binary_Op (N, Op_Id);
654 end if;
656 Op_Id := Homonym (Op_Id);
657 end loop;
658 end if;
660 Operator_Check (N);
661 end Analyze_Arithmetic_Op;
663 ------------------
664 -- Analyze_Call --
665 ------------------
667 -- Function, procedure, and entry calls are checked here. The Name in
668 -- the call may be overloaded. The actuals have been analyzed and may
669 -- themselves be overloaded. On exit from this procedure, the node N
670 -- may have zero, one or more interpretations. In the first case an
671 -- error message is produced. In the last case, the node is flagged
672 -- as overloaded and the interpretations are collected in All_Interp.
674 -- If the name is an Access_To_Subprogram, it cannot be overloaded, but
675 -- the type-checking is similar to that of other calls.
677 procedure Analyze_Call (N : Node_Id) is
678 Actuals : constant List_Id := Parameter_Associations (N);
679 Nam : Node_Id := Name (N);
680 X : Interp_Index;
681 It : Interp;
682 Nam_Ent : Entity_Id;
683 Success : Boolean := False;
685 function Name_Denotes_Function return Boolean;
686 -- If the type of the name is an access to subprogram, this may be
687 -- the type of a name, or the return type of the function being called.
688 -- If the name is not an entity then it can denote a protected function.
689 -- Until we distinguish Etype from Return_Type, we must use this
690 -- routine to resolve the meaning of the name in the call.
692 ---------------------------
693 -- Name_Denotes_Function --
694 ---------------------------
696 function Name_Denotes_Function return Boolean is
697 begin
698 if Is_Entity_Name (Nam) then
699 return Ekind (Entity (Nam)) = E_Function;
701 elsif Nkind (Nam) = N_Selected_Component then
702 return Ekind (Entity (Selector_Name (Nam))) = E_Function;
704 else
705 return False;
706 end if;
707 end Name_Denotes_Function;
709 -- Start of processing for Analyze_Call
711 begin
712 -- Initialize the type of the result of the call to the error type,
713 -- which will be reset if the type is successfully resolved.
715 Set_Etype (N, Any_Type);
717 if not Is_Overloaded (Nam) then
719 -- Only one interpretation to check
721 if Ekind (Etype (Nam)) = E_Subprogram_Type then
722 Nam_Ent := Etype (Nam);
724 -- If the prefix is an access_to_subprogram, this may be an indirect
725 -- call. This is the case if the name in the call is not an entity
726 -- name, or if it is a function name in the context of a procedure
727 -- call. In this latter case, we have a call to a parameterless
728 -- function that returns a pointer_to_procedure which is the entity
729 -- being called.
731 elsif Is_Access_Type (Etype (Nam))
732 and then Ekind (Designated_Type (Etype (Nam))) = E_Subprogram_Type
733 and then
734 (not Name_Denotes_Function
735 or else Nkind (N) = N_Procedure_Call_Statement)
736 then
737 Nam_Ent := Designated_Type (Etype (Nam));
738 Insert_Explicit_Dereference (Nam);
740 -- Selected component case. Simple entry or protected operation,
741 -- where the entry name is given by the selector name.
743 elsif Nkind (Nam) = N_Selected_Component then
744 Nam_Ent := Entity (Selector_Name (Nam));
746 if Ekind (Nam_Ent) /= E_Entry
747 and then Ekind (Nam_Ent) /= E_Entry_Family
748 and then Ekind (Nam_Ent) /= E_Function
749 and then Ekind (Nam_Ent) /= E_Procedure
750 then
751 Error_Msg_N ("name in call is not a callable entity", Nam);
752 Set_Etype (N, Any_Type);
753 return;
754 end if;
756 -- If the name is an Indexed component, it can be a call to a member
757 -- of an entry family. The prefix must be a selected component whose
758 -- selector is the entry. Analyze_Procedure_Call normalizes several
759 -- kinds of call into this form.
761 elsif Nkind (Nam) = N_Indexed_Component then
762 if Nkind (Prefix (Nam)) = N_Selected_Component then
763 Nam_Ent := Entity (Selector_Name (Prefix (Nam)));
764 else
765 Error_Msg_N ("name in call is not a callable entity", Nam);
766 Set_Etype (N, Any_Type);
767 return;
768 end if;
770 elsif not Is_Entity_Name (Nam) then
771 Error_Msg_N ("name in call is not a callable entity", Nam);
772 Set_Etype (N, Any_Type);
773 return;
775 else
776 Nam_Ent := Entity (Nam);
778 -- If no interpretations, give error message
780 if not Is_Overloadable (Nam_Ent) then
781 declare
782 L : constant Boolean := Is_List_Member (N);
783 K : constant Node_Kind := Nkind (Parent (N));
785 begin
786 -- If the node is in a list whose parent is not an
787 -- expression then it must be an attempted procedure call.
789 if L and then K not in N_Subexpr then
790 if Ekind (Entity (Nam)) = E_Generic_Procedure then
791 Error_Msg_NE
792 ("must instantiate generic procedure& before call",
793 Nam, Entity (Nam));
794 else
795 Error_Msg_N
796 ("procedure or entry name expected", Nam);
797 end if;
799 -- Check for tasking cases where only an entry call will do
801 elsif not L
802 and then Nkind_In (K, N_Entry_Call_Alternative,
803 N_Triggering_Alternative)
804 then
805 Error_Msg_N ("entry name expected", Nam);
807 -- Otherwise give general error message
809 else
810 Error_Msg_N ("invalid prefix in call", Nam);
811 end if;
813 return;
814 end;
815 end if;
816 end if;
818 Analyze_One_Call (N, Nam_Ent, True, Success);
820 -- If this is an indirect call, the return type of the access_to
821 -- subprogram may be an incomplete type. At the point of the call,
822 -- use the full type if available, and at the same time update
823 -- the return type of the access_to_subprogram.
825 if Success
826 and then Nkind (Nam) = N_Explicit_Dereference
827 and then Ekind (Etype (N)) = E_Incomplete_Type
828 and then Present (Full_View (Etype (N)))
829 then
830 Set_Etype (N, Full_View (Etype (N)));
831 Set_Etype (Nam_Ent, Etype (N));
832 end if;
834 else
835 -- An overloaded selected component must denote overloaded
836 -- operations of a concurrent type. The interpretations are
837 -- attached to the simple name of those operations.
839 if Nkind (Nam) = N_Selected_Component then
840 Nam := Selector_Name (Nam);
841 end if;
843 Get_First_Interp (Nam, X, It);
845 while Present (It.Nam) loop
846 Nam_Ent := It.Nam;
848 -- Name may be call that returns an access to subprogram, or more
849 -- generally an overloaded expression one of whose interpretations
850 -- yields an access to subprogram. If the name is an entity, we
851 -- do not dereference, because the node is a call that returns
852 -- the access type: note difference between f(x), where the call
853 -- may return an access subprogram type, and f(x)(y), where the
854 -- type returned by the call to f is implicitly dereferenced to
855 -- analyze the outer call.
857 if Is_Access_Type (Nam_Ent) then
858 Nam_Ent := Designated_Type (Nam_Ent);
860 elsif Is_Access_Type (Etype (Nam_Ent))
861 and then not Is_Entity_Name (Nam)
862 and then Ekind (Designated_Type (Etype (Nam_Ent)))
863 = E_Subprogram_Type
864 then
865 Nam_Ent := Designated_Type (Etype (Nam_Ent));
866 end if;
868 Analyze_One_Call (N, Nam_Ent, False, Success);
870 -- If the interpretation succeeds, mark the proper type of the
871 -- prefix (any valid candidate will do). If not, remove the
872 -- candidate interpretation. This only needs to be done for
873 -- overloaded protected operations, for other entities disambi-
874 -- guation is done directly in Resolve.
876 if Success then
877 Set_Etype (Nam, It.Typ);
879 elsif Nkind_In (Name (N), N_Selected_Component,
880 N_Function_Call)
881 then
882 Remove_Interp (X);
883 end if;
885 Get_Next_Interp (X, It);
886 end loop;
888 -- If the name is the result of a function call, it can only
889 -- be a call to a function returning an access to subprogram.
890 -- Insert explicit dereference.
892 if Nkind (Nam) = N_Function_Call then
893 Insert_Explicit_Dereference (Nam);
894 end if;
896 if Etype (N) = Any_Type then
898 -- None of the interpretations is compatible with the actuals
900 Diagnose_Call (N, Nam);
902 -- Special checks for uninstantiated put routines
904 if Nkind (N) = N_Procedure_Call_Statement
905 and then Is_Entity_Name (Nam)
906 and then Chars (Nam) = Name_Put
907 and then List_Length (Actuals) = 1
908 then
909 declare
910 Arg : constant Node_Id := First (Actuals);
911 Typ : Entity_Id;
913 begin
914 if Nkind (Arg) = N_Parameter_Association then
915 Typ := Etype (Explicit_Actual_Parameter (Arg));
916 else
917 Typ := Etype (Arg);
918 end if;
920 if Is_Signed_Integer_Type (Typ) then
921 Error_Msg_N
922 ("possible missing instantiation of " &
923 "'Text_'I'O.'Integer_'I'O!", Nam);
925 elsif Is_Modular_Integer_Type (Typ) then
926 Error_Msg_N
927 ("possible missing instantiation of " &
928 "'Text_'I'O.'Modular_'I'O!", Nam);
930 elsif Is_Floating_Point_Type (Typ) then
931 Error_Msg_N
932 ("possible missing instantiation of " &
933 "'Text_'I'O.'Float_'I'O!", Nam);
935 elsif Is_Ordinary_Fixed_Point_Type (Typ) then
936 Error_Msg_N
937 ("possible missing instantiation of " &
938 "'Text_'I'O.'Fixed_'I'O!", Nam);
940 elsif Is_Decimal_Fixed_Point_Type (Typ) then
941 Error_Msg_N
942 ("possible missing instantiation of " &
943 "'Text_'I'O.'Decimal_'I'O!", Nam);
945 elsif Is_Enumeration_Type (Typ) then
946 Error_Msg_N
947 ("possible missing instantiation of " &
948 "'Text_'I'O.'Enumeration_'I'O!", Nam);
949 end if;
950 end;
951 end if;
953 elsif not Is_Overloaded (N)
954 and then Is_Entity_Name (Nam)
955 then
956 -- Resolution yields a single interpretation. Verify that the
957 -- reference has capitalization consistent with the declaration.
959 Set_Entity_With_Style_Check (Nam, Entity (Nam));
960 Generate_Reference (Entity (Nam), Nam);
962 Set_Etype (Nam, Etype (Entity (Nam)));
963 else
964 Remove_Abstract_Operations (N);
965 end if;
967 End_Interp_List;
968 end if;
970 -- Check for not-yet-implemented cases of AI-318. We only need to check
971 -- for inherently limited types, because other limited types will be
972 -- returned by copy, which works just fine.
973 -- If the context is an attribute reference 'Class, this is really a
974 -- type conversion, which is illegal, and will be caught elsewhere.
976 if Ada_Version >= Ada_05
977 and then not Debug_Flag_Dot_L
978 and then Is_Inherently_Limited_Type (Etype (N))
979 and then (Nkind_In (Parent (N), N_Selected_Component,
980 N_Indexed_Component,
981 N_Slice)
982 or else
983 (Nkind (Parent (N)) = N_Attribute_Reference
984 and then Attribute_Name (Parent (N)) /= Name_Class))
985 then
986 Error_Msg_N ("(Ada 2005) limited function call in this context" &
987 " is not yet implemented", N);
988 end if;
989 end Analyze_Call;
991 ---------------------------
992 -- Analyze_Comparison_Op --
993 ---------------------------
995 procedure Analyze_Comparison_Op (N : Node_Id) is
996 L : constant Node_Id := Left_Opnd (N);
997 R : constant Node_Id := Right_Opnd (N);
998 Op_Id : Entity_Id := Entity (N);
1000 begin
1001 Set_Etype (N, Any_Type);
1002 Candidate_Type := Empty;
1004 Analyze_Expression (L);
1005 Analyze_Expression (R);
1007 if Present (Op_Id) then
1008 if Ekind (Op_Id) = E_Operator then
1009 Find_Comparison_Types (L, R, Op_Id, N);
1010 else
1011 Add_One_Interp (N, Op_Id, Etype (Op_Id));
1012 end if;
1014 if Is_Overloaded (L) then
1015 Set_Etype (L, Intersect_Types (L, R));
1016 end if;
1018 else
1019 Op_Id := Get_Name_Entity_Id (Chars (N));
1020 while Present (Op_Id) loop
1021 if Ekind (Op_Id) = E_Operator then
1022 Find_Comparison_Types (L, R, Op_Id, N);
1023 else
1024 Analyze_User_Defined_Binary_Op (N, Op_Id);
1025 end if;
1027 Op_Id := Homonym (Op_Id);
1028 end loop;
1029 end if;
1031 Operator_Check (N);
1032 end Analyze_Comparison_Op;
1034 ---------------------------
1035 -- Analyze_Concatenation --
1036 ---------------------------
1038 procedure Analyze_Concatenation (N : Node_Id) is
1040 -- We wish to avoid deep recursion, because concatenations are often
1041 -- deeply nested, as in A&B&...&Z. Therefore, we walk down the left
1042 -- operands nonrecursively until we find something that is not a
1043 -- concatenation (A in this case), or has already been analyzed. We
1044 -- analyze that, and then walk back up the tree following Parent
1045 -- pointers, calling Analyze_Concatenation_Rest to do the rest of the
1046 -- work at each level. The Parent pointers allow us to avoid recursion,
1047 -- and thus avoid running out of memory.
1049 NN : Node_Id := N;
1050 L : Node_Id;
1052 begin
1053 Candidate_Type := Empty;
1055 -- The following code is equivalent to:
1057 -- Set_Etype (N, Any_Type);
1058 -- Analyze_Expression (Left_Opnd (N));
1059 -- Analyze_Concatenation_Rest (N);
1061 -- where the Analyze_Expression call recurses back here if the left
1062 -- operand is a concatenation.
1064 -- Walk down left operands
1066 loop
1067 Set_Etype (NN, Any_Type);
1068 L := Left_Opnd (NN);
1069 exit when Nkind (L) /= N_Op_Concat or else Analyzed (L);
1070 NN := L;
1071 end loop;
1073 -- Now (given the above example) NN is A&B and L is A
1075 -- First analyze L ...
1077 Analyze_Expression (L);
1079 -- ... then walk NN back up until we reach N (where we started), calling
1080 -- Analyze_Concatenation_Rest along the way.
1082 loop
1083 Analyze_Concatenation_Rest (NN);
1084 exit when NN = N;
1085 NN := Parent (NN);
1086 end loop;
1087 end Analyze_Concatenation;
1089 --------------------------------
1090 -- Analyze_Concatenation_Rest --
1091 --------------------------------
1093 -- If the only one-dimensional array type in scope is String,
1094 -- this is the resulting type of the operation. Otherwise there
1095 -- will be a concatenation operation defined for each user-defined
1096 -- one-dimensional array.
1098 procedure Analyze_Concatenation_Rest (N : Node_Id) is
1099 L : constant Node_Id := Left_Opnd (N);
1100 R : constant Node_Id := Right_Opnd (N);
1101 Op_Id : Entity_Id := Entity (N);
1102 LT : Entity_Id;
1103 RT : Entity_Id;
1105 begin
1106 Analyze_Expression (R);
1108 -- If the entity is present, the node appears in an instance, and
1109 -- denotes a predefined concatenation operation. The resulting type is
1110 -- obtained from the arguments when possible. If the arguments are
1111 -- aggregates, the array type and the concatenation type must be
1112 -- visible.
1114 if Present (Op_Id) then
1115 if Ekind (Op_Id) = E_Operator then
1117 LT := Base_Type (Etype (L));
1118 RT := Base_Type (Etype (R));
1120 if Is_Array_Type (LT)
1121 and then (RT = LT or else RT = Base_Type (Component_Type (LT)))
1122 then
1123 Add_One_Interp (N, Op_Id, LT);
1125 elsif Is_Array_Type (RT)
1126 and then LT = Base_Type (Component_Type (RT))
1127 then
1128 Add_One_Interp (N, Op_Id, RT);
1130 -- If one operand is a string type or a user-defined array type,
1131 -- and the other is a literal, result is of the specific type.
1133 elsif
1134 (Root_Type (LT) = Standard_String
1135 or else Scope (LT) /= Standard_Standard)
1136 and then Etype (R) = Any_String
1137 then
1138 Add_One_Interp (N, Op_Id, LT);
1140 elsif
1141 (Root_Type (RT) = Standard_String
1142 or else Scope (RT) /= Standard_Standard)
1143 and then Etype (L) = Any_String
1144 then
1145 Add_One_Interp (N, Op_Id, RT);
1147 elsif not Is_Generic_Type (Etype (Op_Id)) then
1148 Add_One_Interp (N, Op_Id, Etype (Op_Id));
1150 else
1151 -- Type and its operations must be visible
1153 Set_Entity (N, Empty);
1154 Analyze_Concatenation (N);
1155 end if;
1157 else
1158 Add_One_Interp (N, Op_Id, Etype (Op_Id));
1159 end if;
1161 else
1162 Op_Id := Get_Name_Entity_Id (Name_Op_Concat);
1163 while Present (Op_Id) loop
1164 if Ekind (Op_Id) = E_Operator then
1166 -- Do not consider operators declared in dead code, they can
1167 -- not be part of the resolution.
1169 if Is_Eliminated (Op_Id) then
1170 null;
1171 else
1172 Find_Concatenation_Types (L, R, Op_Id, N);
1173 end if;
1175 else
1176 Analyze_User_Defined_Binary_Op (N, Op_Id);
1177 end if;
1179 Op_Id := Homonym (Op_Id);
1180 end loop;
1181 end if;
1183 Operator_Check (N);
1184 end Analyze_Concatenation_Rest;
1186 ------------------------------------
1187 -- Analyze_Conditional_Expression --
1188 ------------------------------------
1190 procedure Analyze_Conditional_Expression (N : Node_Id) is
1191 Condition : constant Node_Id := First (Expressions (N));
1192 Then_Expr : constant Node_Id := Next (Condition);
1193 Else_Expr : constant Node_Id := Next (Then_Expr);
1194 begin
1195 Analyze_Expression (Condition);
1196 Analyze_Expression (Then_Expr);
1197 Analyze_Expression (Else_Expr);
1198 Set_Etype (N, Etype (Then_Expr));
1199 end Analyze_Conditional_Expression;
1201 -------------------------
1202 -- Analyze_Equality_Op --
1203 -------------------------
1205 procedure Analyze_Equality_Op (N : Node_Id) is
1206 Loc : constant Source_Ptr := Sloc (N);
1207 L : constant Node_Id := Left_Opnd (N);
1208 R : constant Node_Id := Right_Opnd (N);
1209 Op_Id : Entity_Id;
1211 begin
1212 Set_Etype (N, Any_Type);
1213 Candidate_Type := Empty;
1215 Analyze_Expression (L);
1216 Analyze_Expression (R);
1218 -- If the entity is set, the node is a generic instance with a non-local
1219 -- reference to the predefined operator or to a user-defined function.
1220 -- It can also be an inequality that is expanded into the negation of a
1221 -- call to a user-defined equality operator.
1223 -- For the predefined case, the result is Boolean, regardless of the
1224 -- type of the operands. The operands may even be limited, if they are
1225 -- generic actuals. If they are overloaded, label the left argument with
1226 -- the common type that must be present, or with the type of the formal
1227 -- of the user-defined function.
1229 if Present (Entity (N)) then
1230 Op_Id := Entity (N);
1232 if Ekind (Op_Id) = E_Operator then
1233 Add_One_Interp (N, Op_Id, Standard_Boolean);
1234 else
1235 Add_One_Interp (N, Op_Id, Etype (Op_Id));
1236 end if;
1238 if Is_Overloaded (L) then
1239 if Ekind (Op_Id) = E_Operator then
1240 Set_Etype (L, Intersect_Types (L, R));
1241 else
1242 Set_Etype (L, Etype (First_Formal (Op_Id)));
1243 end if;
1244 end if;
1246 else
1247 Op_Id := Get_Name_Entity_Id (Chars (N));
1248 while Present (Op_Id) loop
1249 if Ekind (Op_Id) = E_Operator then
1250 Find_Equality_Types (L, R, Op_Id, N);
1251 else
1252 Analyze_User_Defined_Binary_Op (N, Op_Id);
1253 end if;
1255 Op_Id := Homonym (Op_Id);
1256 end loop;
1257 end if;
1259 -- If there was no match, and the operator is inequality, this may
1260 -- be a case where inequality has not been made explicit, as for
1261 -- tagged types. Analyze the node as the negation of an equality
1262 -- operation. This cannot be done earlier, because before analysis
1263 -- we cannot rule out the presence of an explicit inequality.
1265 if Etype (N) = Any_Type
1266 and then Nkind (N) = N_Op_Ne
1267 then
1268 Op_Id := Get_Name_Entity_Id (Name_Op_Eq);
1269 while Present (Op_Id) loop
1270 if Ekind (Op_Id) = E_Operator then
1271 Find_Equality_Types (L, R, Op_Id, N);
1272 else
1273 Analyze_User_Defined_Binary_Op (N, Op_Id);
1274 end if;
1276 Op_Id := Homonym (Op_Id);
1277 end loop;
1279 if Etype (N) /= Any_Type then
1280 Op_Id := Entity (N);
1282 Rewrite (N,
1283 Make_Op_Not (Loc,
1284 Right_Opnd =>
1285 Make_Op_Eq (Loc,
1286 Left_Opnd => Left_Opnd (N),
1287 Right_Opnd => Right_Opnd (N))));
1289 Set_Entity (Right_Opnd (N), Op_Id);
1290 Analyze (N);
1291 end if;
1292 end if;
1294 Operator_Check (N);
1295 end Analyze_Equality_Op;
1297 ----------------------------------
1298 -- Analyze_Explicit_Dereference --
1299 ----------------------------------
1301 procedure Analyze_Explicit_Dereference (N : Node_Id) is
1302 Loc : constant Source_Ptr := Sloc (N);
1303 P : constant Node_Id := Prefix (N);
1304 T : Entity_Id;
1305 I : Interp_Index;
1306 It : Interp;
1307 New_N : Node_Id;
1309 function Is_Function_Type return Boolean;
1310 -- Check whether node may be interpreted as an implicit function call
1312 ----------------------
1313 -- Is_Function_Type --
1314 ----------------------
1316 function Is_Function_Type return Boolean is
1317 I : Interp_Index;
1318 It : Interp;
1320 begin
1321 if not Is_Overloaded (N) then
1322 return Ekind (Base_Type (Etype (N))) = E_Subprogram_Type
1323 and then Etype (Base_Type (Etype (N))) /= Standard_Void_Type;
1325 else
1326 Get_First_Interp (N, I, It);
1327 while Present (It.Nam) loop
1328 if Ekind (Base_Type (It.Typ)) /= E_Subprogram_Type
1329 or else Etype (Base_Type (It.Typ)) = Standard_Void_Type
1330 then
1331 return False;
1332 end if;
1334 Get_Next_Interp (I, It);
1335 end loop;
1337 return True;
1338 end if;
1339 end Is_Function_Type;
1341 -- Start of processing for Analyze_Explicit_Dereference
1343 begin
1344 Analyze (P);
1345 Set_Etype (N, Any_Type);
1347 -- Test for remote access to subprogram type, and if so return
1348 -- after rewriting the original tree.
1350 if Remote_AST_E_Dereference (P) then
1351 return;
1352 end if;
1354 -- Normal processing for other than remote access to subprogram type
1356 if not Is_Overloaded (P) then
1357 if Is_Access_Type (Etype (P)) then
1359 -- Set the Etype. We need to go thru Is_For_Access_Subtypes to
1360 -- avoid other problems caused by the Private_Subtype and it is
1361 -- safe to go to the Base_Type because this is the same as
1362 -- converting the access value to its Base_Type.
1364 declare
1365 DT : Entity_Id := Designated_Type (Etype (P));
1367 begin
1368 if Ekind (DT) = E_Private_Subtype
1369 and then Is_For_Access_Subtype (DT)
1370 then
1371 DT := Base_Type (DT);
1372 end if;
1374 -- An explicit dereference is a legal occurrence of an
1375 -- incomplete type imported through a limited_with clause,
1376 -- if the full view is visible.
1378 if From_With_Type (DT)
1379 and then not From_With_Type (Scope (DT))
1380 and then
1381 (Is_Immediately_Visible (Scope (DT))
1382 or else
1383 (Is_Child_Unit (Scope (DT))
1384 and then Is_Visible_Child_Unit (Scope (DT))))
1385 then
1386 Set_Etype (N, Available_View (DT));
1388 else
1389 Set_Etype (N, DT);
1390 end if;
1391 end;
1393 elsif Etype (P) /= Any_Type then
1394 Error_Msg_N ("prefix of dereference must be an access type", N);
1395 return;
1396 end if;
1398 else
1399 Get_First_Interp (P, I, It);
1400 while Present (It.Nam) loop
1401 T := It.Typ;
1403 if Is_Access_Type (T) then
1404 Add_One_Interp (N, Designated_Type (T), Designated_Type (T));
1405 end if;
1407 Get_Next_Interp (I, It);
1408 end loop;
1410 -- Error if no interpretation of the prefix has an access type
1412 if Etype (N) = Any_Type then
1413 Error_Msg_N
1414 ("access type required in prefix of explicit dereference", P);
1415 Set_Etype (N, Any_Type);
1416 return;
1417 end if;
1418 end if;
1420 if Is_Function_Type
1421 and then Nkind (Parent (N)) /= N_Indexed_Component
1423 and then (Nkind (Parent (N)) /= N_Function_Call
1424 or else N /= Name (Parent (N)))
1426 and then (Nkind (Parent (N)) /= N_Procedure_Call_Statement
1427 or else N /= Name (Parent (N)))
1429 and then Nkind (Parent (N)) /= N_Subprogram_Renaming_Declaration
1430 and then (Nkind (Parent (N)) /= N_Attribute_Reference
1431 or else
1432 (Attribute_Name (Parent (N)) /= Name_Address
1433 and then
1434 Attribute_Name (Parent (N)) /= Name_Access))
1435 then
1436 -- Name is a function call with no actuals, in a context that
1437 -- requires deproceduring (including as an actual in an enclosing
1438 -- function or procedure call). There are some pathological cases
1439 -- where the prefix might include functions that return access to
1440 -- subprograms and others that return a regular type. Disambiguation
1441 -- of those has to take place in Resolve.
1442 -- See e.g. 7117-014 and E317-001.
1444 New_N :=
1445 Make_Function_Call (Loc,
1446 Name => Make_Explicit_Dereference (Loc, P),
1447 Parameter_Associations => New_List);
1449 -- If the prefix is overloaded, remove operations that have formals,
1450 -- we know that this is a parameterless call.
1452 if Is_Overloaded (P) then
1453 Get_First_Interp (P, I, It);
1454 while Present (It.Nam) loop
1455 T := It.Typ;
1457 if No (First_Formal (Base_Type (Designated_Type (T)))) then
1458 Set_Etype (P, T);
1459 else
1460 Remove_Interp (I);
1461 end if;
1463 Get_Next_Interp (I, It);
1464 end loop;
1465 end if;
1467 Rewrite (N, New_N);
1468 Analyze (N);
1470 elsif not Is_Function_Type
1471 and then Is_Overloaded (N)
1472 then
1473 -- The prefix may include access to subprograms and other access
1474 -- types. If the context selects the interpretation that is a call,
1475 -- we cannot rewrite the node yet, but we include the result of
1476 -- the call interpretation.
1478 Get_First_Interp (N, I, It);
1479 while Present (It.Nam) loop
1480 if Ekind (Base_Type (It.Typ)) = E_Subprogram_Type
1481 and then Etype (Base_Type (It.Typ)) /= Standard_Void_Type
1482 then
1483 Add_One_Interp (N, Etype (It.Typ), Etype (It.Typ));
1484 end if;
1486 Get_Next_Interp (I, It);
1487 end loop;
1488 end if;
1490 -- A value of remote access-to-class-wide must not be dereferenced
1491 -- (RM E.2.2(16)).
1493 Validate_Remote_Access_To_Class_Wide_Type (N);
1494 end Analyze_Explicit_Dereference;
1496 ------------------------
1497 -- Analyze_Expression --
1498 ------------------------
1500 procedure Analyze_Expression (N : Node_Id) is
1501 begin
1502 Analyze (N);
1503 Check_Parameterless_Call (N);
1504 end Analyze_Expression;
1506 ------------------------------------
1507 -- Analyze_Indexed_Component_Form --
1508 ------------------------------------
1510 procedure Analyze_Indexed_Component_Form (N : Node_Id) is
1511 P : constant Node_Id := Prefix (N);
1512 Exprs : constant List_Id := Expressions (N);
1513 Exp : Node_Id;
1514 P_T : Entity_Id;
1515 E : Node_Id;
1516 U_N : Entity_Id;
1518 procedure Process_Function_Call;
1519 -- Prefix in indexed component form is an overloadable entity,
1520 -- so the node is a function call. Reformat it as such.
1522 procedure Process_Indexed_Component;
1523 -- Prefix in indexed component form is actually an indexed component.
1524 -- This routine processes it, knowing that the prefix is already
1525 -- resolved.
1527 procedure Process_Indexed_Component_Or_Slice;
1528 -- An indexed component with a single index may designate a slice if
1529 -- the index is a subtype mark. This routine disambiguates these two
1530 -- cases by resolving the prefix to see if it is a subtype mark.
1532 procedure Process_Overloaded_Indexed_Component;
1533 -- If the prefix of an indexed component is overloaded, the proper
1534 -- interpretation is selected by the index types and the context.
1536 ---------------------------
1537 -- Process_Function_Call --
1538 ---------------------------
1540 procedure Process_Function_Call is
1541 Actual : Node_Id;
1543 begin
1544 Change_Node (N, N_Function_Call);
1545 Set_Name (N, P);
1546 Set_Parameter_Associations (N, Exprs);
1548 -- Analyze actuals prior to analyzing the call itself
1550 Actual := First (Parameter_Associations (N));
1551 while Present (Actual) loop
1552 Analyze (Actual);
1553 Check_Parameterless_Call (Actual);
1555 -- Move to next actual. Note that we use Next, not Next_Actual
1556 -- here. The reason for this is a bit subtle. If a function call
1557 -- includes named associations, the parser recognizes the node as
1558 -- a call, and it is analyzed as such. If all associations are
1559 -- positional, the parser builds an indexed_component node, and
1560 -- it is only after analysis of the prefix that the construct
1561 -- is recognized as a call, in which case Process_Function_Call
1562 -- rewrites the node and analyzes the actuals. If the list of
1563 -- actuals is malformed, the parser may leave the node as an
1564 -- indexed component (despite the presence of named associations).
1565 -- The iterator Next_Actual is equivalent to Next if the list is
1566 -- positional, but follows the normalized chain of actuals when
1567 -- named associations are present. In this case normalization has
1568 -- not taken place, and actuals remain unanalyzed, which leads to
1569 -- subsequent crashes or loops if there is an attempt to continue
1570 -- analysis of the program.
1572 Next (Actual);
1573 end loop;
1575 Analyze_Call (N);
1576 end Process_Function_Call;
1578 -------------------------------
1579 -- Process_Indexed_Component --
1580 -------------------------------
1582 procedure Process_Indexed_Component is
1583 Exp : Node_Id;
1584 Array_Type : Entity_Id;
1585 Index : Node_Id;
1586 Pent : Entity_Id := Empty;
1588 begin
1589 Exp := First (Exprs);
1591 if Is_Overloaded (P) then
1592 Process_Overloaded_Indexed_Component;
1594 else
1595 Array_Type := Etype (P);
1597 if Is_Entity_Name (P) then
1598 Pent := Entity (P);
1599 elsif Nkind (P) = N_Selected_Component
1600 and then Is_Entity_Name (Selector_Name (P))
1601 then
1602 Pent := Entity (Selector_Name (P));
1603 end if;
1605 -- Prefix must be appropriate for an array type, taking into
1606 -- account a possible implicit dereference.
1608 if Is_Access_Type (Array_Type) then
1609 Error_Msg_NW (Warn_On_Dereference, "?implicit dereference", N);
1610 Array_Type := Process_Implicit_Dereference_Prefix (Pent, P);
1611 end if;
1613 if Is_Array_Type (Array_Type) then
1614 null;
1616 elsif Present (Pent) and then Ekind (Pent) = E_Entry_Family then
1617 Analyze (Exp);
1618 Set_Etype (N, Any_Type);
1620 if not Has_Compatible_Type
1621 (Exp, Entry_Index_Type (Pent))
1622 then
1623 Error_Msg_N ("invalid index type in entry name", N);
1625 elsif Present (Next (Exp)) then
1626 Error_Msg_N ("too many subscripts in entry reference", N);
1628 else
1629 Set_Etype (N, Etype (P));
1630 end if;
1632 return;
1634 elsif Is_Record_Type (Array_Type)
1635 and then Remote_AST_I_Dereference (P)
1636 then
1637 return;
1639 elsif Array_Type = Any_Type then
1640 Set_Etype (N, Any_Type);
1641 return;
1643 -- Here we definitely have a bad indexing
1645 else
1646 if Nkind (Parent (N)) = N_Requeue_Statement
1647 and then Present (Pent) and then Ekind (Pent) = E_Entry
1648 then
1649 Error_Msg_N
1650 ("REQUEUE does not permit parameters", First (Exprs));
1652 elsif Is_Entity_Name (P)
1653 and then Etype (P) = Standard_Void_Type
1654 then
1655 Error_Msg_NE ("incorrect use of&", P, Entity (P));
1657 else
1658 Error_Msg_N ("array type required in indexed component", P);
1659 end if;
1661 Set_Etype (N, Any_Type);
1662 return;
1663 end if;
1665 Index := First_Index (Array_Type);
1666 while Present (Index) and then Present (Exp) loop
1667 if not Has_Compatible_Type (Exp, Etype (Index)) then
1668 Wrong_Type (Exp, Etype (Index));
1669 Set_Etype (N, Any_Type);
1670 return;
1671 end if;
1673 Next_Index (Index);
1674 Next (Exp);
1675 end loop;
1677 Set_Etype (N, Component_Type (Array_Type));
1679 if Present (Index) then
1680 Error_Msg_N
1681 ("too few subscripts in array reference", First (Exprs));
1683 elsif Present (Exp) then
1684 Error_Msg_N ("too many subscripts in array reference", Exp);
1685 end if;
1686 end if;
1687 end Process_Indexed_Component;
1689 ----------------------------------------
1690 -- Process_Indexed_Component_Or_Slice --
1691 ----------------------------------------
1693 procedure Process_Indexed_Component_Or_Slice is
1694 begin
1695 Exp := First (Exprs);
1696 while Present (Exp) loop
1697 Analyze_Expression (Exp);
1698 Next (Exp);
1699 end loop;
1701 Exp := First (Exprs);
1703 -- If one index is present, and it is a subtype name, then the
1704 -- node denotes a slice (note that the case of an explicit range
1705 -- for a slice was already built as an N_Slice node in the first
1706 -- place, so that case is not handled here).
1708 -- We use a replace rather than a rewrite here because this is one
1709 -- of the cases in which the tree built by the parser is plain wrong.
1711 if No (Next (Exp))
1712 and then Is_Entity_Name (Exp)
1713 and then Is_Type (Entity (Exp))
1714 then
1715 Replace (N,
1716 Make_Slice (Sloc (N),
1717 Prefix => P,
1718 Discrete_Range => New_Copy (Exp)));
1719 Analyze (N);
1721 -- Otherwise (more than one index present, or single index is not
1722 -- a subtype name), then we have the indexed component case.
1724 else
1725 Process_Indexed_Component;
1726 end if;
1727 end Process_Indexed_Component_Or_Slice;
1729 ------------------------------------------
1730 -- Process_Overloaded_Indexed_Component --
1731 ------------------------------------------
1733 procedure Process_Overloaded_Indexed_Component is
1734 Exp : Node_Id;
1735 I : Interp_Index;
1736 It : Interp;
1737 Typ : Entity_Id;
1738 Index : Node_Id;
1739 Found : Boolean;
1741 begin
1742 Set_Etype (N, Any_Type);
1744 Get_First_Interp (P, I, It);
1745 while Present (It.Nam) loop
1746 Typ := It.Typ;
1748 if Is_Access_Type (Typ) then
1749 Typ := Designated_Type (Typ);
1750 Error_Msg_NW (Warn_On_Dereference, "?implicit dereference", N);
1751 end if;
1753 if Is_Array_Type (Typ) then
1755 -- Got a candidate: verify that index types are compatible
1757 Index := First_Index (Typ);
1758 Found := True;
1759 Exp := First (Exprs);
1760 while Present (Index) and then Present (Exp) loop
1761 if Has_Compatible_Type (Exp, Etype (Index)) then
1762 null;
1763 else
1764 Found := False;
1765 Remove_Interp (I);
1766 exit;
1767 end if;
1769 Next_Index (Index);
1770 Next (Exp);
1771 end loop;
1773 if Found and then No (Index) and then No (Exp) then
1774 Add_One_Interp (N,
1775 Etype (Component_Type (Typ)),
1776 Etype (Component_Type (Typ)));
1777 end if;
1778 end if;
1780 Get_Next_Interp (I, It);
1781 end loop;
1783 if Etype (N) = Any_Type then
1784 Error_Msg_N ("no legal interpetation for indexed component", N);
1785 Set_Is_Overloaded (N, False);
1786 end if;
1788 End_Interp_List;
1789 end Process_Overloaded_Indexed_Component;
1791 -- Start of processing for Analyze_Indexed_Component_Form
1793 begin
1794 -- Get name of array, function or type
1796 Analyze (P);
1798 if Nkind_In (N, N_Function_Call, N_Procedure_Call_Statement) then
1800 -- If P is an explicit dereference whose prefix is of a
1801 -- remote access-to-subprogram type, then N has already
1802 -- been rewritten as a subprogram call and analyzed.
1804 return;
1805 end if;
1807 pragma Assert (Nkind (N) = N_Indexed_Component);
1809 P_T := Base_Type (Etype (P));
1811 if Is_Entity_Name (P)
1812 or else Nkind (P) = N_Operator_Symbol
1813 then
1814 U_N := Entity (P);
1816 if Is_Type (U_N) then
1818 -- Reformat node as a type conversion
1820 E := Remove_Head (Exprs);
1822 if Present (First (Exprs)) then
1823 Error_Msg_N
1824 ("argument of type conversion must be single expression", N);
1825 end if;
1827 Change_Node (N, N_Type_Conversion);
1828 Set_Subtype_Mark (N, P);
1829 Set_Etype (N, U_N);
1830 Set_Expression (N, E);
1832 -- After changing the node, call for the specific Analysis
1833 -- routine directly, to avoid a double call to the expander.
1835 Analyze_Type_Conversion (N);
1836 return;
1837 end if;
1839 if Is_Overloadable (U_N) then
1840 Process_Function_Call;
1842 elsif Ekind (Etype (P)) = E_Subprogram_Type
1843 or else (Is_Access_Type (Etype (P))
1844 and then
1845 Ekind (Designated_Type (Etype (P))) = E_Subprogram_Type)
1846 then
1847 -- Call to access_to-subprogram with possible implicit dereference
1849 Process_Function_Call;
1851 elsif Is_Generic_Subprogram (U_N) then
1853 -- A common beginner's (or C++ templates fan) error
1855 Error_Msg_N ("generic subprogram cannot be called", N);
1856 Set_Etype (N, Any_Type);
1857 return;
1859 else
1860 Process_Indexed_Component_Or_Slice;
1861 end if;
1863 -- If not an entity name, prefix is an expression that may denote
1864 -- an array or an access-to-subprogram.
1866 else
1867 if Ekind (P_T) = E_Subprogram_Type
1868 or else (Is_Access_Type (P_T)
1869 and then
1870 Ekind (Designated_Type (P_T)) = E_Subprogram_Type)
1871 then
1872 Process_Function_Call;
1874 elsif Nkind (P) = N_Selected_Component
1875 and then Is_Overloadable (Entity (Selector_Name (P)))
1876 then
1877 Process_Function_Call;
1879 else
1880 -- Indexed component, slice, or a call to a member of a family
1881 -- entry, which will be converted to an entry call later.
1883 Process_Indexed_Component_Or_Slice;
1884 end if;
1885 end if;
1886 end Analyze_Indexed_Component_Form;
1888 ------------------------
1889 -- Analyze_Logical_Op --
1890 ------------------------
1892 procedure Analyze_Logical_Op (N : Node_Id) is
1893 L : constant Node_Id := Left_Opnd (N);
1894 R : constant Node_Id := Right_Opnd (N);
1895 Op_Id : Entity_Id := Entity (N);
1897 begin
1898 Set_Etype (N, Any_Type);
1899 Candidate_Type := Empty;
1901 Analyze_Expression (L);
1902 Analyze_Expression (R);
1904 if Present (Op_Id) then
1906 if Ekind (Op_Id) = E_Operator then
1907 Find_Boolean_Types (L, R, Op_Id, N);
1908 else
1909 Add_One_Interp (N, Op_Id, Etype (Op_Id));
1910 end if;
1912 else
1913 Op_Id := Get_Name_Entity_Id (Chars (N));
1914 while Present (Op_Id) loop
1915 if Ekind (Op_Id) = E_Operator then
1916 Find_Boolean_Types (L, R, Op_Id, N);
1917 else
1918 Analyze_User_Defined_Binary_Op (N, Op_Id);
1919 end if;
1921 Op_Id := Homonym (Op_Id);
1922 end loop;
1923 end if;
1925 Operator_Check (N);
1926 end Analyze_Logical_Op;
1928 ---------------------------
1929 -- Analyze_Membership_Op --
1930 ---------------------------
1932 procedure Analyze_Membership_Op (N : Node_Id) is
1933 L : constant Node_Id := Left_Opnd (N);
1934 R : constant Node_Id := Right_Opnd (N);
1936 Index : Interp_Index;
1937 It : Interp;
1938 Found : Boolean := False;
1939 I_F : Interp_Index;
1940 T_F : Entity_Id;
1942 procedure Try_One_Interp (T1 : Entity_Id);
1943 -- Routine to try one proposed interpretation. Note that the context
1944 -- of the operation plays no role in resolving the arguments, so that
1945 -- if there is more than one interpretation of the operands that is
1946 -- compatible with a membership test, the operation is ambiguous.
1948 --------------------
1949 -- Try_One_Interp --
1950 --------------------
1952 procedure Try_One_Interp (T1 : Entity_Id) is
1953 begin
1954 if Has_Compatible_Type (R, T1) then
1955 if Found
1956 and then Base_Type (T1) /= Base_Type (T_F)
1957 then
1958 It := Disambiguate (L, I_F, Index, Any_Type);
1960 if It = No_Interp then
1961 Ambiguous_Operands (N);
1962 Set_Etype (L, Any_Type);
1963 return;
1965 else
1966 T_F := It.Typ;
1967 end if;
1969 else
1970 Found := True;
1971 T_F := T1;
1972 I_F := Index;
1973 end if;
1975 Set_Etype (L, T_F);
1976 end if;
1978 end Try_One_Interp;
1980 -- Start of processing for Analyze_Membership_Op
1982 begin
1983 Analyze_Expression (L);
1985 if Nkind (R) = N_Range
1986 or else (Nkind (R) = N_Attribute_Reference
1987 and then Attribute_Name (R) = Name_Range)
1988 then
1989 Analyze (R);
1991 if not Is_Overloaded (L) then
1992 Try_One_Interp (Etype (L));
1994 else
1995 Get_First_Interp (L, Index, It);
1996 while Present (It.Typ) loop
1997 Try_One_Interp (It.Typ);
1998 Get_Next_Interp (Index, It);
1999 end loop;
2000 end if;
2002 -- If not a range, it can only be a subtype mark, or else there
2003 -- is a more basic error, to be diagnosed in Find_Type.
2005 else
2006 Find_Type (R);
2008 if Is_Entity_Name (R) then
2009 Check_Fully_Declared (Entity (R), R);
2010 end if;
2011 end if;
2013 -- Compatibility between expression and subtype mark or range is
2014 -- checked during resolution. The result of the operation is Boolean
2015 -- in any case.
2017 Set_Etype (N, Standard_Boolean);
2019 if Comes_From_Source (N)
2020 and then Is_CPP_Class (Etype (Etype (Right_Opnd (N))))
2021 then
2022 Error_Msg_N ("membership test not applicable to cpp-class types", N);
2023 end if;
2024 end Analyze_Membership_Op;
2026 ----------------------
2027 -- Analyze_Negation --
2028 ----------------------
2030 procedure Analyze_Negation (N : Node_Id) is
2031 R : constant Node_Id := Right_Opnd (N);
2032 Op_Id : Entity_Id := Entity (N);
2034 begin
2035 Set_Etype (N, Any_Type);
2036 Candidate_Type := Empty;
2038 Analyze_Expression (R);
2040 if Present (Op_Id) then
2041 if Ekind (Op_Id) = E_Operator then
2042 Find_Negation_Types (R, Op_Id, N);
2043 else
2044 Add_One_Interp (N, Op_Id, Etype (Op_Id));
2045 end if;
2047 else
2048 Op_Id := Get_Name_Entity_Id (Chars (N));
2049 while Present (Op_Id) loop
2050 if Ekind (Op_Id) = E_Operator then
2051 Find_Negation_Types (R, Op_Id, N);
2052 else
2053 Analyze_User_Defined_Unary_Op (N, Op_Id);
2054 end if;
2056 Op_Id := Homonym (Op_Id);
2057 end loop;
2058 end if;
2060 Operator_Check (N);
2061 end Analyze_Negation;
2063 ------------------
2064 -- Analyze_Null --
2065 ------------------
2067 procedure Analyze_Null (N : Node_Id) is
2068 begin
2069 Set_Etype (N, Any_Access);
2070 end Analyze_Null;
2072 ----------------------
2073 -- Analyze_One_Call --
2074 ----------------------
2076 procedure Analyze_One_Call
2077 (N : Node_Id;
2078 Nam : Entity_Id;
2079 Report : Boolean;
2080 Success : out Boolean;
2081 Skip_First : Boolean := False)
2083 Actuals : constant List_Id := Parameter_Associations (N);
2084 Prev_T : constant Entity_Id := Etype (N);
2086 Must_Skip : constant Boolean := Skip_First
2087 or else Nkind (Original_Node (N)) = N_Selected_Component
2088 or else
2089 (Nkind (Original_Node (N)) = N_Indexed_Component
2090 and then Nkind (Prefix (Original_Node (N)))
2091 = N_Selected_Component);
2092 -- The first formal must be omitted from the match when trying to find
2093 -- a primitive operation that is a possible interpretation, and also
2094 -- after the call has been rewritten, because the corresponding actual
2095 -- is already known to be compatible, and because this may be an
2096 -- indexing of a call with default parameters.
2098 Formal : Entity_Id;
2099 Actual : Node_Id;
2100 Is_Indexed : Boolean := False;
2101 Subp_Type : constant Entity_Id := Etype (Nam);
2102 Norm_OK : Boolean;
2104 function Operator_Hidden_By (Fun : Entity_Id) return Boolean;
2105 -- There may be a user-defined operator that hides the current
2106 -- interpretation. We must check for this independently of the
2107 -- analysis of the call with the user-defined operation, because
2108 -- the parameter names may be wrong and yet the hiding takes place.
2109 -- This fixes a problem with ACATS test B34014O.
2111 -- When the type Address is a visible integer type, and the DEC
2112 -- system extension is visible, the predefined operator may be
2113 -- hidden as well, by one of the address operations in auxdec.
2114 -- Finally, The abstract operations on address do not hide the
2115 -- predefined operator (this is the purpose of making them abstract).
2117 procedure Indicate_Name_And_Type;
2118 -- If candidate interpretation matches, indicate name and type of
2119 -- result on call node.
2121 ----------------------------
2122 -- Indicate_Name_And_Type --
2123 ----------------------------
2125 procedure Indicate_Name_And_Type is
2126 begin
2127 Add_One_Interp (N, Nam, Etype (Nam));
2128 Success := True;
2130 -- If the prefix of the call is a name, indicate the entity
2131 -- being called. If it is not a name, it is an expression that
2132 -- denotes an access to subprogram or else an entry or family. In
2133 -- the latter case, the name is a selected component, and the entity
2134 -- being called is noted on the selector.
2136 if not Is_Type (Nam) then
2137 if Is_Entity_Name (Name (N))
2138 or else Nkind (Name (N)) = N_Operator_Symbol
2139 then
2140 Set_Entity (Name (N), Nam);
2142 elsif Nkind (Name (N)) = N_Selected_Component then
2143 Set_Entity (Selector_Name (Name (N)), Nam);
2144 end if;
2145 end if;
2147 if Debug_Flag_E and not Report then
2148 Write_Str (" Overloaded call ");
2149 Write_Int (Int (N));
2150 Write_Str (" compatible with ");
2151 Write_Int (Int (Nam));
2152 Write_Eol;
2153 end if;
2154 end Indicate_Name_And_Type;
2156 ------------------------
2157 -- Operator_Hidden_By --
2158 ------------------------
2160 function Operator_Hidden_By (Fun : Entity_Id) return Boolean is
2161 Act1 : constant Node_Id := First_Actual (N);
2162 Act2 : constant Node_Id := Next_Actual (Act1);
2163 Form1 : constant Entity_Id := First_Formal (Fun);
2164 Form2 : constant Entity_Id := Next_Formal (Form1);
2166 begin
2167 if Ekind (Fun) /= E_Function
2168 or else Is_Abstract_Subprogram (Fun)
2169 then
2170 return False;
2172 elsif not Has_Compatible_Type (Act1, Etype (Form1)) then
2173 return False;
2175 elsif Present (Form2) then
2177 No (Act2) or else not Has_Compatible_Type (Act2, Etype (Form2))
2178 then
2179 return False;
2180 end if;
2182 elsif Present (Act2) then
2183 return False;
2184 end if;
2186 -- Now we know that the arity of the operator matches the function,
2187 -- and the function call is a valid interpretation. The function
2188 -- hides the operator if it has the right signature, or if one of
2189 -- its operands is a non-abstract operation on Address when this is
2190 -- a visible integer type.
2192 return Hides_Op (Fun, Nam)
2193 or else Is_Descendent_Of_Address (Etype (Form1))
2194 or else
2195 (Present (Form2)
2196 and then Is_Descendent_Of_Address (Etype (Form2)));
2197 end Operator_Hidden_By;
2199 -- Start of processing for Analyze_One_Call
2201 begin
2202 Success := False;
2204 -- If the subprogram has no formals or if all the formals have defaults,
2205 -- and the return type is an array type, the node may denote an indexing
2206 -- of the result of a parameterless call. In Ada 2005, the subprogram
2207 -- may have one non-defaulted formal, and the call may have been written
2208 -- in prefix notation, so that the rebuilt parameter list has more than
2209 -- one actual.
2211 if Present (Actuals)
2212 and then
2213 (Needs_No_Actuals (Nam)
2214 or else
2215 (Needs_One_Actual (Nam)
2216 and then Present (Next_Actual (First (Actuals)))))
2217 then
2218 if Is_Array_Type (Subp_Type) then
2219 Is_Indexed := Try_Indexed_Call (N, Nam, Subp_Type, Must_Skip);
2221 elsif Is_Access_Type (Subp_Type)
2222 and then Is_Array_Type (Designated_Type (Subp_Type))
2223 then
2224 Is_Indexed :=
2225 Try_Indexed_Call
2226 (N, Nam, Designated_Type (Subp_Type), Must_Skip);
2228 -- The prefix can also be a parameterless function that returns an
2229 -- access to subprogram. in which case this is an indirect call.
2231 elsif Is_Access_Type (Subp_Type)
2232 and then Ekind (Designated_Type (Subp_Type)) = E_Subprogram_Type
2233 then
2234 Is_Indexed := Try_Indirect_Call (N, Nam, Subp_Type);
2235 end if;
2237 end if;
2239 Normalize_Actuals (N, Nam, (Report and not Is_Indexed), Norm_OK);
2241 if not Norm_OK then
2243 -- Mismatch in number or names of parameters
2245 if Debug_Flag_E then
2246 Write_Str (" normalization fails in call ");
2247 Write_Int (Int (N));
2248 Write_Str (" with subprogram ");
2249 Write_Int (Int (Nam));
2250 Write_Eol;
2251 end if;
2253 -- If the context expects a function call, discard any interpretation
2254 -- that is a procedure. If the node is not overloaded, leave as is for
2255 -- better error reporting when type mismatch is found.
2257 elsif Nkind (N) = N_Function_Call
2258 and then Is_Overloaded (Name (N))
2259 and then Ekind (Nam) = E_Procedure
2260 then
2261 return;
2263 -- Ditto for function calls in a procedure context
2265 elsif Nkind (N) = N_Procedure_Call_Statement
2266 and then Is_Overloaded (Name (N))
2267 and then Etype (Nam) /= Standard_Void_Type
2268 then
2269 return;
2271 elsif No (Actuals) then
2273 -- If Normalize succeeds, then there are default parameters for
2274 -- all formals.
2276 Indicate_Name_And_Type;
2278 elsif Ekind (Nam) = E_Operator then
2279 if Nkind (N) = N_Procedure_Call_Statement then
2280 return;
2281 end if;
2283 -- This can occur when the prefix of the call is an operator
2284 -- name or an expanded name whose selector is an operator name.
2286 Analyze_Operator_Call (N, Nam);
2288 if Etype (N) /= Prev_T then
2290 -- Check that operator is not hidden by a function interpretation
2292 if Is_Overloaded (Name (N)) then
2293 declare
2294 I : Interp_Index;
2295 It : Interp;
2297 begin
2298 Get_First_Interp (Name (N), I, It);
2299 while Present (It.Nam) loop
2300 if Operator_Hidden_By (It.Nam) then
2301 Set_Etype (N, Prev_T);
2302 return;
2303 end if;
2305 Get_Next_Interp (I, It);
2306 end loop;
2307 end;
2308 end if;
2310 -- If operator matches formals, record its name on the call.
2311 -- If the operator is overloaded, Resolve will select the
2312 -- correct one from the list of interpretations. The call
2313 -- node itself carries the first candidate.
2315 Set_Entity (Name (N), Nam);
2316 Success := True;
2318 elsif Report and then Etype (N) = Any_Type then
2319 Error_Msg_N ("incompatible arguments for operator", N);
2320 end if;
2322 else
2323 -- Normalize_Actuals has chained the named associations in the
2324 -- correct order of the formals.
2326 Actual := First_Actual (N);
2327 Formal := First_Formal (Nam);
2329 -- If we are analyzing a call rewritten from object notation,
2330 -- skip first actual, which may be rewritten later as an
2331 -- explicit dereference.
2333 if Must_Skip then
2334 Next_Actual (Actual);
2335 Next_Formal (Formal);
2336 end if;
2338 while Present (Actual) and then Present (Formal) loop
2339 if Nkind (Parent (Actual)) /= N_Parameter_Association
2340 or else Chars (Selector_Name (Parent (Actual))) = Chars (Formal)
2341 then
2342 -- The actual can be compatible with the formal, but we must
2343 -- also check that the context is not an address type that is
2344 -- visibly an integer type, as is the case in VMS_64. In this
2345 -- case the use of literals is illegal, except in the body of
2346 -- descendents of system, where arithmetic operations on
2347 -- address are of course used.
2349 if Has_Compatible_Type (Actual, Etype (Formal))
2350 and then
2351 (Etype (Actual) /= Universal_Integer
2352 or else not Is_Descendent_Of_Address (Etype (Formal))
2353 or else
2354 Is_Predefined_File_Name
2355 (Unit_File_Name (Get_Source_Unit (N))))
2356 then
2357 Next_Actual (Actual);
2358 Next_Formal (Formal);
2360 else
2361 if Debug_Flag_E then
2362 Write_Str (" type checking fails in call ");
2363 Write_Int (Int (N));
2364 Write_Str (" with formal ");
2365 Write_Int (Int (Formal));
2366 Write_Str (" in subprogram ");
2367 Write_Int (Int (Nam));
2368 Write_Eol;
2369 end if;
2371 if Report and not Is_Indexed then
2373 -- Ada 2005 (AI-251): Complete the error notification
2374 -- to help new Ada 2005 users
2376 if Is_Class_Wide_Type (Etype (Formal))
2377 and then Is_Interface (Etype (Etype (Formal)))
2378 and then not Interface_Present_In_Ancestor
2379 (Typ => Etype (Actual),
2380 Iface => Etype (Etype (Formal)))
2381 then
2382 Error_Msg_NE
2383 ("(Ada 2005) does not implement interface }",
2384 Actual, Etype (Etype (Formal)));
2385 end if;
2387 Wrong_Type (Actual, Etype (Formal));
2389 if Nkind (Actual) = N_Op_Eq
2390 and then Nkind (Left_Opnd (Actual)) = N_Identifier
2391 then
2392 Formal := First_Formal (Nam);
2393 while Present (Formal) loop
2394 if Chars (Left_Opnd (Actual)) = Chars (Formal) then
2395 Error_Msg_N
2396 ("possible misspelling of `='>`!", Actual);
2397 exit;
2398 end if;
2400 Next_Formal (Formal);
2401 end loop;
2402 end if;
2404 if All_Errors_Mode then
2405 Error_Msg_Sloc := Sloc (Nam);
2407 if Is_Overloadable (Nam)
2408 and then Present (Alias (Nam))
2409 and then not Comes_From_Source (Nam)
2410 then
2411 Error_Msg_NE
2412 ("\\ =='> in call to inherited operation & #!",
2413 Actual, Nam);
2415 elsif Ekind (Nam) = E_Subprogram_Type then
2416 declare
2417 Access_To_Subprogram_Typ :
2418 constant Entity_Id :=
2419 Defining_Identifier
2420 (Associated_Node_For_Itype (Nam));
2421 begin
2422 Error_Msg_NE (
2423 "\\ =='> in call to dereference of &#!",
2424 Actual, Access_To_Subprogram_Typ);
2425 end;
2427 else
2428 Error_Msg_NE
2429 ("\\ =='> in call to &#!", Actual, Nam);
2431 end if;
2432 end if;
2433 end if;
2435 return;
2436 end if;
2438 else
2439 -- Normalize_Actuals has verified that a default value exists
2440 -- for this formal. Current actual names a subsequent formal.
2442 Next_Formal (Formal);
2443 end if;
2444 end loop;
2446 -- On exit, all actuals match
2448 Indicate_Name_And_Type;
2449 end if;
2450 end Analyze_One_Call;
2452 ---------------------------
2453 -- Analyze_Operator_Call --
2454 ---------------------------
2456 procedure Analyze_Operator_Call (N : Node_Id; Op_Id : Entity_Id) is
2457 Op_Name : constant Name_Id := Chars (Op_Id);
2458 Act1 : constant Node_Id := First_Actual (N);
2459 Act2 : constant Node_Id := Next_Actual (Act1);
2461 begin
2462 -- Binary operator case
2464 if Present (Act2) then
2466 -- If more than two operands, then not binary operator after all
2468 if Present (Next_Actual (Act2)) then
2469 return;
2471 elsif Op_Name = Name_Op_Add
2472 or else Op_Name = Name_Op_Subtract
2473 or else Op_Name = Name_Op_Multiply
2474 or else Op_Name = Name_Op_Divide
2475 or else Op_Name = Name_Op_Mod
2476 or else Op_Name = Name_Op_Rem
2477 or else Op_Name = Name_Op_Expon
2478 then
2479 Find_Arithmetic_Types (Act1, Act2, Op_Id, N);
2481 elsif Op_Name = Name_Op_And
2482 or else Op_Name = Name_Op_Or
2483 or else Op_Name = Name_Op_Xor
2484 then
2485 Find_Boolean_Types (Act1, Act2, Op_Id, N);
2487 elsif Op_Name = Name_Op_Lt
2488 or else Op_Name = Name_Op_Le
2489 or else Op_Name = Name_Op_Gt
2490 or else Op_Name = Name_Op_Ge
2491 then
2492 Find_Comparison_Types (Act1, Act2, Op_Id, N);
2494 elsif Op_Name = Name_Op_Eq
2495 or else Op_Name = Name_Op_Ne
2496 then
2497 Find_Equality_Types (Act1, Act2, Op_Id, N);
2499 elsif Op_Name = Name_Op_Concat then
2500 Find_Concatenation_Types (Act1, Act2, Op_Id, N);
2502 -- Is this else null correct, or should it be an abort???
2504 else
2505 null;
2506 end if;
2508 -- Unary operator case
2510 else
2511 if Op_Name = Name_Op_Subtract or else
2512 Op_Name = Name_Op_Add or else
2513 Op_Name = Name_Op_Abs
2514 then
2515 Find_Unary_Types (Act1, Op_Id, N);
2517 elsif
2518 Op_Name = Name_Op_Not
2519 then
2520 Find_Negation_Types (Act1, Op_Id, N);
2522 -- Is this else null correct, or should it be an abort???
2524 else
2525 null;
2526 end if;
2527 end if;
2528 end Analyze_Operator_Call;
2530 -------------------------------------------
2531 -- Analyze_Overloaded_Selected_Component --
2532 -------------------------------------------
2534 procedure Analyze_Overloaded_Selected_Component (N : Node_Id) is
2535 Nam : constant Node_Id := Prefix (N);
2536 Sel : constant Node_Id := Selector_Name (N);
2537 Comp : Entity_Id;
2538 I : Interp_Index;
2539 It : Interp;
2540 T : Entity_Id;
2542 begin
2543 Set_Etype (Sel, Any_Type);
2545 Get_First_Interp (Nam, I, It);
2546 while Present (It.Typ) loop
2547 if Is_Access_Type (It.Typ) then
2548 T := Designated_Type (It.Typ);
2549 Error_Msg_NW (Warn_On_Dereference, "?implicit dereference", N);
2550 else
2551 T := It.Typ;
2552 end if;
2554 if Is_Record_Type (T) then
2556 -- If the prefix is a class-wide type, the visible components are
2557 -- those of the base type.
2559 if Is_Class_Wide_Type (T) then
2560 T := Etype (T);
2561 end if;
2563 Comp := First_Entity (T);
2564 while Present (Comp) loop
2565 if Chars (Comp) = Chars (Sel)
2566 and then Is_Visible_Component (Comp)
2567 then
2568 Set_Entity (Sel, Comp);
2569 Set_Etype (Sel, Etype (Comp));
2570 Add_One_Interp (N, Etype (Comp), Etype (Comp));
2572 -- This also specifies a candidate to resolve the name.
2573 -- Further overloading will be resolved from context.
2575 Set_Etype (Nam, It.Typ);
2576 end if;
2578 Next_Entity (Comp);
2579 end loop;
2581 elsif Is_Concurrent_Type (T) then
2582 Comp := First_Entity (T);
2583 while Present (Comp)
2584 and then Comp /= First_Private_Entity (T)
2585 loop
2586 if Chars (Comp) = Chars (Sel) then
2587 if Is_Overloadable (Comp) then
2588 Add_One_Interp (Sel, Comp, Etype (Comp));
2589 else
2590 Set_Entity_With_Style_Check (Sel, Comp);
2591 Generate_Reference (Comp, Sel);
2592 end if;
2594 Set_Etype (Sel, Etype (Comp));
2595 Set_Etype (N, Etype (Comp));
2596 Set_Etype (Nam, It.Typ);
2598 -- For access type case, introduce explicit deference for
2599 -- more uniform treatment of entry calls. Do this only
2600 -- once if several interpretations yield an access type.
2602 if Is_Access_Type (Etype (Nam))
2603 and then Nkind (Nam) /= N_Explicit_Dereference
2604 then
2605 Insert_Explicit_Dereference (Nam);
2606 Error_Msg_NW
2607 (Warn_On_Dereference, "?implicit dereference", N);
2608 end if;
2609 end if;
2611 Next_Entity (Comp);
2612 end loop;
2614 Set_Is_Overloaded (N, Is_Overloaded (Sel));
2615 end if;
2617 Get_Next_Interp (I, It);
2618 end loop;
2620 if Etype (N) = Any_Type
2621 and then not Try_Object_Operation (N)
2622 then
2623 Error_Msg_NE ("undefined selector& for overloaded prefix", N, Sel);
2624 Set_Entity (Sel, Any_Id);
2625 Set_Etype (Sel, Any_Type);
2626 end if;
2627 end Analyze_Overloaded_Selected_Component;
2629 ----------------------------------
2630 -- Analyze_Qualified_Expression --
2631 ----------------------------------
2633 procedure Analyze_Qualified_Expression (N : Node_Id) is
2634 Mark : constant Entity_Id := Subtype_Mark (N);
2635 Expr : constant Node_Id := Expression (N);
2636 I : Interp_Index;
2637 It : Interp;
2638 T : Entity_Id;
2640 begin
2641 Analyze_Expression (Expr);
2643 Set_Etype (N, Any_Type);
2644 Find_Type (Mark);
2645 T := Entity (Mark);
2646 Set_Etype (N, T);
2648 if T = Any_Type then
2649 return;
2650 end if;
2652 Check_Fully_Declared (T, N);
2654 -- If expected type is class-wide, check for exact match before
2655 -- expansion, because if the expression is a dispatching call it
2656 -- may be rewritten as explicit dereference with class-wide result.
2657 -- If expression is overloaded, retain only interpretations that
2658 -- will yield exact matches.
2660 if Is_Class_Wide_Type (T) then
2661 if not Is_Overloaded (Expr) then
2662 if Base_Type (Etype (Expr)) /= Base_Type (T) then
2663 if Nkind (Expr) = N_Aggregate then
2664 Error_Msg_N ("type of aggregate cannot be class-wide", Expr);
2665 else
2666 Wrong_Type (Expr, T);
2667 end if;
2668 end if;
2670 else
2671 Get_First_Interp (Expr, I, It);
2673 while Present (It.Nam) loop
2674 if Base_Type (It.Typ) /= Base_Type (T) then
2675 Remove_Interp (I);
2676 end if;
2678 Get_Next_Interp (I, It);
2679 end loop;
2680 end if;
2681 end if;
2683 Set_Etype (N, T);
2684 end Analyze_Qualified_Expression;
2686 -------------------
2687 -- Analyze_Range --
2688 -------------------
2690 procedure Analyze_Range (N : Node_Id) is
2691 L : constant Node_Id := Low_Bound (N);
2692 H : constant Node_Id := High_Bound (N);
2693 I1, I2 : Interp_Index;
2694 It1, It2 : Interp;
2696 procedure Check_Common_Type (T1, T2 : Entity_Id);
2697 -- Verify the compatibility of two types, and choose the
2698 -- non universal one if the other is universal.
2700 procedure Check_High_Bound (T : Entity_Id);
2701 -- Test one interpretation of the low bound against all those
2702 -- of the high bound.
2704 procedure Check_Universal_Expression (N : Node_Id);
2705 -- In Ada83, reject bounds of a universal range that are not
2706 -- literals or entity names.
2708 -----------------------
2709 -- Check_Common_Type --
2710 -----------------------
2712 procedure Check_Common_Type (T1, T2 : Entity_Id) is
2713 begin
2714 if Covers (T1, T2) or else Covers (T2, T1) then
2715 if T1 = Universal_Integer
2716 or else T1 = Universal_Real
2717 or else T1 = Any_Character
2718 then
2719 Add_One_Interp (N, Base_Type (T2), Base_Type (T2));
2721 elsif T1 = T2 then
2722 Add_One_Interp (N, T1, T1);
2724 else
2725 Add_One_Interp (N, Base_Type (T1), Base_Type (T1));
2726 end if;
2727 end if;
2728 end Check_Common_Type;
2730 ----------------------
2731 -- Check_High_Bound --
2732 ----------------------
2734 procedure Check_High_Bound (T : Entity_Id) is
2735 begin
2736 if not Is_Overloaded (H) then
2737 Check_Common_Type (T, Etype (H));
2738 else
2739 Get_First_Interp (H, I2, It2);
2740 while Present (It2.Typ) loop
2741 Check_Common_Type (T, It2.Typ);
2742 Get_Next_Interp (I2, It2);
2743 end loop;
2744 end if;
2745 end Check_High_Bound;
2747 -----------------------------
2748 -- Is_Universal_Expression --
2749 -----------------------------
2751 procedure Check_Universal_Expression (N : Node_Id) is
2752 begin
2753 if Etype (N) = Universal_Integer
2754 and then Nkind (N) /= N_Integer_Literal
2755 and then not Is_Entity_Name (N)
2756 and then Nkind (N) /= N_Attribute_Reference
2757 then
2758 Error_Msg_N ("illegal bound in discrete range", N);
2759 end if;
2760 end Check_Universal_Expression;
2762 -- Start of processing for Analyze_Range
2764 begin
2765 Set_Etype (N, Any_Type);
2766 Analyze_Expression (L);
2767 Analyze_Expression (H);
2769 if Etype (L) = Any_Type or else Etype (H) = Any_Type then
2770 return;
2772 else
2773 if not Is_Overloaded (L) then
2774 Check_High_Bound (Etype (L));
2775 else
2776 Get_First_Interp (L, I1, It1);
2777 while Present (It1.Typ) loop
2778 Check_High_Bound (It1.Typ);
2779 Get_Next_Interp (I1, It1);
2780 end loop;
2781 end if;
2783 -- If result is Any_Type, then we did not find a compatible pair
2785 if Etype (N) = Any_Type then
2786 Error_Msg_N ("incompatible types in range ", N);
2787 end if;
2788 end if;
2790 if Ada_Version = Ada_83
2791 and then
2792 (Nkind (Parent (N)) = N_Loop_Parameter_Specification
2793 or else Nkind (Parent (N)) = N_Constrained_Array_Definition)
2794 then
2795 Check_Universal_Expression (L);
2796 Check_Universal_Expression (H);
2797 end if;
2798 end Analyze_Range;
2800 -----------------------
2801 -- Analyze_Reference --
2802 -----------------------
2804 procedure Analyze_Reference (N : Node_Id) is
2805 P : constant Node_Id := Prefix (N);
2806 Acc_Type : Entity_Id;
2807 begin
2808 Analyze (P);
2809 Acc_Type := Create_Itype (E_Allocator_Type, N);
2810 Set_Etype (Acc_Type, Acc_Type);
2811 Init_Size_Align (Acc_Type);
2812 Set_Directly_Designated_Type (Acc_Type, Etype (P));
2813 Set_Etype (N, Acc_Type);
2814 end Analyze_Reference;
2816 --------------------------------
2817 -- Analyze_Selected_Component --
2818 --------------------------------
2820 -- Prefix is a record type or a task or protected type. In the
2821 -- later case, the selector must denote a visible entry.
2823 procedure Analyze_Selected_Component (N : Node_Id) is
2824 Name : constant Node_Id := Prefix (N);
2825 Sel : constant Node_Id := Selector_Name (N);
2826 Act_Decl : Node_Id;
2827 Comp : Entity_Id;
2828 Has_Candidate : Boolean := False;
2829 In_Scope : Boolean;
2830 Parent_N : Node_Id;
2831 Pent : Entity_Id := Empty;
2832 Prefix_Type : Entity_Id;
2834 Type_To_Use : Entity_Id;
2835 -- In most cases this is the Prefix_Type, but if the Prefix_Type is
2836 -- a class-wide type, we use its root type, whose components are
2837 -- present in the class-wide type.
2839 function Has_Mode_Conformant_Spec (Comp : Entity_Id) return Boolean;
2840 -- It is known that the parent of N denotes a subprogram call. Comp
2841 -- is an overloadable component of the concurrent type of the prefix.
2842 -- Determine whether all formals of the parent of N and Comp are mode
2843 -- conformant.
2845 ------------------------------
2846 -- Has_Mode_Conformant_Spec --
2847 ------------------------------
2849 function Has_Mode_Conformant_Spec (Comp : Entity_Id) return Boolean is
2850 Comp_Param : Entity_Id;
2851 Param : Node_Id;
2852 Param_Typ : Entity_Id;
2854 begin
2855 Comp_Param := First_Formal (Comp);
2856 Param := First (Parameter_Associations (Parent (N)));
2857 while Present (Comp_Param)
2858 and then Present (Param)
2859 loop
2860 Param_Typ := Find_Parameter_Type (Param);
2862 if Present (Param_Typ)
2863 and then
2864 not Conforming_Types
2865 (Etype (Comp_Param), Param_Typ, Mode_Conformant)
2866 then
2867 return False;
2868 end if;
2870 Next_Formal (Comp_Param);
2871 Next (Param);
2872 end loop;
2874 -- One of the specs has additional formals
2876 if Present (Comp_Param) or else Present (Param) then
2877 return False;
2878 end if;
2880 return True;
2881 end Has_Mode_Conformant_Spec;
2883 -- Start of processing for Analyze_Selected_Component
2885 begin
2886 Set_Etype (N, Any_Type);
2888 if Is_Overloaded (Name) then
2889 Analyze_Overloaded_Selected_Component (N);
2890 return;
2892 elsif Etype (Name) = Any_Type then
2893 Set_Entity (Sel, Any_Id);
2894 Set_Etype (Sel, Any_Type);
2895 return;
2897 else
2898 Prefix_Type := Etype (Name);
2899 end if;
2901 if Is_Access_Type (Prefix_Type) then
2903 -- A RACW object can never be used as prefix of a selected
2904 -- component since that means it is dereferenced without
2905 -- being a controlling operand of a dispatching operation
2906 -- (RM E.2.2(15)).
2908 if Is_Remote_Access_To_Class_Wide_Type (Prefix_Type)
2909 and then Comes_From_Source (N)
2910 then
2911 Error_Msg_N
2912 ("invalid dereference of a remote access to class-wide value",
2915 -- Normal case of selected component applied to access type
2917 else
2918 Error_Msg_NW (Warn_On_Dereference, "?implicit dereference", N);
2920 if Is_Entity_Name (Name) then
2921 Pent := Entity (Name);
2922 elsif Nkind (Name) = N_Selected_Component
2923 and then Is_Entity_Name (Selector_Name (Name))
2924 then
2925 Pent := Entity (Selector_Name (Name));
2926 end if;
2928 Prefix_Type := Process_Implicit_Dereference_Prefix (Pent, Name);
2929 end if;
2930 end if;
2932 -- (Ada 2005): if the prefix is the limited view of a type, and
2933 -- the context already includes the full view, use the full view
2934 -- in what follows, either to retrieve a component of to find
2935 -- a primitive operation. If the prefix is an explicit dereference,
2936 -- set the type of the prefix to reflect this transformation.
2937 -- If the non-limited view is itself an incomplete type, get the
2938 -- full view if available.
2940 if Is_Incomplete_Type (Prefix_Type)
2941 and then From_With_Type (Prefix_Type)
2942 and then Present (Non_Limited_View (Prefix_Type))
2943 then
2944 Prefix_Type := Get_Full_View (Non_Limited_View (Prefix_Type));
2946 if Nkind (N) = N_Explicit_Dereference then
2947 Set_Etype (Prefix (N), Prefix_Type);
2948 end if;
2950 elsif Ekind (Prefix_Type) = E_Class_Wide_Type
2951 and then From_With_Type (Prefix_Type)
2952 and then Present (Non_Limited_View (Etype (Prefix_Type)))
2953 then
2954 Prefix_Type :=
2955 Class_Wide_Type (Non_Limited_View (Etype (Prefix_Type)));
2957 if Nkind (N) = N_Explicit_Dereference then
2958 Set_Etype (Prefix (N), Prefix_Type);
2959 end if;
2960 end if;
2962 if Ekind (Prefix_Type) = E_Private_Subtype then
2963 Prefix_Type := Base_Type (Prefix_Type);
2964 end if;
2966 Type_To_Use := Prefix_Type;
2968 -- For class-wide types, use the entity list of the root type. This
2969 -- indirection is specially important for private extensions because
2970 -- only the root type get switched (not the class-wide type).
2972 if Is_Class_Wide_Type (Prefix_Type) then
2973 Type_To_Use := Root_Type (Prefix_Type);
2974 end if;
2976 Comp := First_Entity (Type_To_Use);
2978 -- If the selector has an original discriminant, the node appears in
2979 -- an instance. Replace the discriminant with the corresponding one
2980 -- in the current discriminated type. For nested generics, this must
2981 -- be done transitively, so note the new original discriminant.
2983 if Nkind (Sel) = N_Identifier
2984 and then Present (Original_Discriminant (Sel))
2985 then
2986 Comp := Find_Corresponding_Discriminant (Sel, Prefix_Type);
2988 -- Mark entity before rewriting, for completeness and because
2989 -- subsequent semantic checks might examine the original node.
2991 Set_Entity (Sel, Comp);
2992 Rewrite (Selector_Name (N),
2993 New_Occurrence_Of (Comp, Sloc (N)));
2994 Set_Original_Discriminant (Selector_Name (N), Comp);
2995 Set_Etype (N, Etype (Comp));
2997 if Is_Access_Type (Etype (Name)) then
2998 Insert_Explicit_Dereference (Name);
2999 Error_Msg_NW (Warn_On_Dereference, "?implicit dereference", N);
3000 end if;
3002 elsif Is_Record_Type (Prefix_Type) then
3004 -- Find component with given name
3006 while Present (Comp) loop
3007 if Chars (Comp) = Chars (Sel)
3008 and then Is_Visible_Component (Comp)
3009 then
3010 Set_Entity_With_Style_Check (Sel, Comp);
3011 Set_Etype (Sel, Etype (Comp));
3013 if Ekind (Comp) = E_Discriminant then
3014 if Is_Unchecked_Union (Base_Type (Prefix_Type)) then
3015 Error_Msg_N
3016 ("cannot reference discriminant of Unchecked_Union",
3017 Sel);
3018 end if;
3020 if Is_Generic_Type (Prefix_Type)
3021 or else
3022 Is_Generic_Type (Root_Type (Prefix_Type))
3023 then
3024 Set_Original_Discriminant (Sel, Comp);
3025 end if;
3026 end if;
3028 -- Resolve the prefix early otherwise it is not possible to
3029 -- build the actual subtype of the component: it may need
3030 -- to duplicate this prefix and duplication is only allowed
3031 -- on fully resolved expressions.
3033 Resolve (Name);
3035 -- Ada 2005 (AI-50217): Check wrong use of incomplete types or
3036 -- subtypes in a package specification.
3037 -- Example:
3039 -- limited with Pkg;
3040 -- package Pkg is
3041 -- type Acc_Inc is access Pkg.T;
3042 -- X : Acc_Inc;
3043 -- N : Natural := X.all.Comp; -- ERROR, limited view
3044 -- end Pkg; -- Comp is not visible
3046 if Nkind (Name) = N_Explicit_Dereference
3047 and then From_With_Type (Etype (Prefix (Name)))
3048 and then not Is_Potentially_Use_Visible (Etype (Name))
3049 and then Nkind (Parent (Cunit_Entity (Current_Sem_Unit))) =
3050 N_Package_Specification
3051 then
3052 Error_Msg_NE
3053 ("premature usage of incomplete}", Prefix (Name),
3054 Etype (Prefix (Name)));
3055 end if;
3057 -- We never need an actual subtype for the case of a selection
3058 -- for a indexed component of a non-packed array, since in
3059 -- this case gigi generates all the checks and can find the
3060 -- necessary bounds information.
3062 -- We also do not need an actual subtype for the case of
3063 -- a first, last, length, or range attribute applied to a
3064 -- non-packed array, since gigi can again get the bounds in
3065 -- these cases (gigi cannot handle the packed case, since it
3066 -- has the bounds of the packed array type, not the original
3067 -- bounds of the type). However, if the prefix is itself a
3068 -- selected component, as in a.b.c (i), gigi may regard a.b.c
3069 -- as a dynamic-sized temporary, so we do generate an actual
3070 -- subtype for this case.
3072 Parent_N := Parent (N);
3074 if not Is_Packed (Etype (Comp))
3075 and then
3076 ((Nkind (Parent_N) = N_Indexed_Component
3077 and then Nkind (Name) /= N_Selected_Component)
3078 or else
3079 (Nkind (Parent_N) = N_Attribute_Reference
3080 and then (Attribute_Name (Parent_N) = Name_First
3081 or else
3082 Attribute_Name (Parent_N) = Name_Last
3083 or else
3084 Attribute_Name (Parent_N) = Name_Length
3085 or else
3086 Attribute_Name (Parent_N) = Name_Range)))
3087 then
3088 Set_Etype (N, Etype (Comp));
3090 -- If full analysis is not enabled, we do not generate an
3091 -- actual subtype, because in the absence of expansion
3092 -- reference to a formal of a protected type, for example,
3093 -- will not be properly transformed, and will lead to
3094 -- out-of-scope references in gigi.
3096 -- In all other cases, we currently build an actual subtype.
3097 -- It seems likely that many of these cases can be avoided,
3098 -- but right now, the front end makes direct references to the
3099 -- bounds (e.g. in generating a length check), and if we do
3100 -- not make an actual subtype, we end up getting a direct
3101 -- reference to a discriminant, which will not do.
3103 elsif Full_Analysis then
3104 Act_Decl :=
3105 Build_Actual_Subtype_Of_Component (Etype (Comp), N);
3106 Insert_Action (N, Act_Decl);
3108 if No (Act_Decl) then
3109 Set_Etype (N, Etype (Comp));
3111 else
3112 -- Component type depends on discriminants. Enter the
3113 -- main attributes of the subtype.
3115 declare
3116 Subt : constant Entity_Id :=
3117 Defining_Identifier (Act_Decl);
3119 begin
3120 Set_Etype (Subt, Base_Type (Etype (Comp)));
3121 Set_Ekind (Subt, Ekind (Etype (Comp)));
3122 Set_Etype (N, Subt);
3123 end;
3124 end if;
3126 -- If Full_Analysis not enabled, just set the Etype
3128 else
3129 Set_Etype (N, Etype (Comp));
3130 end if;
3132 return;
3133 end if;
3135 -- If the prefix is a private extension, check only the visible
3136 -- components of the partial view. This must include the tag,
3137 -- wich can appear in expanded code in a tag check.
3139 if Ekind (Type_To_Use) = E_Record_Type_With_Private
3140 and then Chars (Selector_Name (N)) /= Name_uTag
3141 then
3142 exit when Comp = Last_Entity (Type_To_Use);
3143 end if;
3145 Next_Entity (Comp);
3146 end loop;
3148 -- Ada 2005 (AI-252): The selected component can be interpreted as
3149 -- a prefixed view of a subprogram. Depending on the context, this is
3150 -- either a name that can appear in a renaming declaration, or part
3151 -- of an enclosing call given in prefix form.
3153 -- Ada 2005 (AI05-0030): In the case of dispatching requeue, the
3154 -- selected component should resolve to a name.
3156 if Ada_Version >= Ada_05
3157 and then Is_Tagged_Type (Prefix_Type)
3158 and then not Is_Concurrent_Type (Prefix_Type)
3159 then
3160 if Nkind (Parent (N)) = N_Generic_Association
3161 or else Nkind (Parent (N)) = N_Requeue_Statement
3162 or else Nkind (Parent (N)) = N_Subprogram_Renaming_Declaration
3163 then
3164 if Find_Primitive_Operation (N) then
3165 return;
3166 end if;
3168 elsif Try_Object_Operation (N) then
3169 return;
3170 end if;
3172 -- If the transformation fails, it will be necessary to redo the
3173 -- analysis with all errors enabled, to indicate candidate
3174 -- interpretations and reasons for each failure ???
3176 end if;
3178 elsif Is_Private_Type (Prefix_Type) then
3180 -- Allow access only to discriminants of the type. If the type has
3181 -- no full view, gigi uses the parent type for the components, so we
3182 -- do the same here.
3184 if No (Full_View (Prefix_Type)) then
3185 Type_To_Use := Root_Type (Base_Type (Prefix_Type));
3186 Comp := First_Entity (Type_To_Use);
3187 end if;
3189 while Present (Comp) loop
3190 if Chars (Comp) = Chars (Sel) then
3191 if Ekind (Comp) = E_Discriminant then
3192 Set_Entity_With_Style_Check (Sel, Comp);
3193 Generate_Reference (Comp, Sel);
3195 Set_Etype (Sel, Etype (Comp));
3196 Set_Etype (N, Etype (Comp));
3198 if Is_Generic_Type (Prefix_Type)
3199 or else Is_Generic_Type (Root_Type (Prefix_Type))
3200 then
3201 Set_Original_Discriminant (Sel, Comp);
3202 end if;
3204 -- Before declararing an error, check whether this is tagged
3205 -- private type and a call to a primitive operation.
3207 elsif Ada_Version >= Ada_05
3208 and then Is_Tagged_Type (Prefix_Type)
3209 and then Try_Object_Operation (N)
3210 then
3211 return;
3213 else
3214 Error_Msg_NE
3215 ("invisible selector for }",
3216 N, First_Subtype (Prefix_Type));
3217 Set_Entity (Sel, Any_Id);
3218 Set_Etype (N, Any_Type);
3219 end if;
3221 return;
3222 end if;
3224 Next_Entity (Comp);
3225 end loop;
3227 elsif Is_Concurrent_Type (Prefix_Type) then
3229 -- Find visible operation with given name. For a protected type,
3230 -- the possible candidates are discriminants, entries or protected
3231 -- procedures. For a task type, the set can only include entries or
3232 -- discriminants if the task type is not an enclosing scope. If it
3233 -- is an enclosing scope (e.g. in an inner task) then all entities
3234 -- are visible, but the prefix must denote the enclosing scope, i.e.
3235 -- can only be a direct name or an expanded name.
3237 Set_Etype (Sel, Any_Type);
3238 In_Scope := In_Open_Scopes (Prefix_Type);
3240 while Present (Comp) loop
3241 if Chars (Comp) = Chars (Sel) then
3242 if Is_Overloadable (Comp) then
3243 Add_One_Interp (Sel, Comp, Etype (Comp));
3245 -- If the prefix is tagged, the correct interpretation may
3246 -- lie in the primitive or class-wide operations of the
3247 -- type. Perform a simple conformance check to determine
3248 -- whether Try_Object_Operation should be invoked even if
3249 -- a visible entity is found.
3251 if Is_Tagged_Type (Prefix_Type)
3252 and then
3253 Nkind_In (Parent (N), N_Procedure_Call_Statement,
3254 N_Function_Call)
3255 and then Has_Mode_Conformant_Spec (Comp)
3256 then
3257 Has_Candidate := True;
3258 end if;
3260 elsif Ekind (Comp) = E_Discriminant
3261 or else Ekind (Comp) = E_Entry_Family
3262 or else (In_Scope
3263 and then Is_Entity_Name (Name))
3264 then
3265 Set_Entity_With_Style_Check (Sel, Comp);
3266 Generate_Reference (Comp, Sel);
3268 else
3269 goto Next_Comp;
3270 end if;
3272 Set_Etype (Sel, Etype (Comp));
3273 Set_Etype (N, Etype (Comp));
3275 if Ekind (Comp) = E_Discriminant then
3276 Set_Original_Discriminant (Sel, Comp);
3277 end if;
3279 -- For access type case, introduce explicit deference for more
3280 -- uniform treatment of entry calls.
3282 if Is_Access_Type (Etype (Name)) then
3283 Insert_Explicit_Dereference (Name);
3284 Error_Msg_NW
3285 (Warn_On_Dereference, "?implicit dereference", N);
3286 end if;
3287 end if;
3289 <<Next_Comp>>
3290 Next_Entity (Comp);
3291 exit when not In_Scope
3292 and then
3293 Comp = First_Private_Entity (Base_Type (Prefix_Type));
3294 end loop;
3296 -- If there is no visible entity with the given name or none of the
3297 -- visible entities are plausible interpretations, check whether
3298 -- there is some other primitive operation with that name.
3300 if Ada_Version >= Ada_05
3301 and then Is_Tagged_Type (Prefix_Type)
3302 then
3303 if (Etype (N) = Any_Type
3304 or else not Has_Candidate)
3305 and then Try_Object_Operation (N)
3306 then
3307 return;
3309 -- If the context is not syntactically a procedure call, it
3310 -- may be a call to a primitive function declared outside of
3311 -- the synchronized type.
3313 -- If the context is a procedure call, there might still be
3314 -- an overloading between an entry and a primitive procedure
3315 -- declared outside of the synchronized type, called in prefix
3316 -- notation. This is harder to disambiguate because in one case
3317 -- the controlling formal is implicit ???
3319 elsif Nkind (Parent (N)) /= N_Procedure_Call_Statement
3320 and then Try_Object_Operation (N)
3321 then
3322 return;
3323 end if;
3324 end if;
3326 Set_Is_Overloaded (N, Is_Overloaded (Sel));
3328 else
3329 -- Invalid prefix
3331 Error_Msg_NE ("invalid prefix in selected component&", N, Sel);
3332 end if;
3334 -- If N still has no type, the component is not defined in the prefix
3336 if Etype (N) = Any_Type then
3338 -- If the prefix is a single concurrent object, use its name in the
3339 -- error message, rather than that of its anonymous type.
3341 if Is_Concurrent_Type (Prefix_Type)
3342 and then Is_Internal_Name (Chars (Prefix_Type))
3343 and then not Is_Derived_Type (Prefix_Type)
3344 and then Is_Entity_Name (Name)
3345 then
3347 Error_Msg_Node_2 := Entity (Name);
3348 Error_Msg_NE ("no selector& for&", N, Sel);
3350 Check_Misspelled_Selector (Type_To_Use, Sel);
3352 elsif Is_Generic_Type (Prefix_Type)
3353 and then Ekind (Prefix_Type) = E_Record_Type_With_Private
3354 and then Prefix_Type /= Etype (Prefix_Type)
3355 and then Is_Record_Type (Etype (Prefix_Type))
3356 then
3357 -- If this is a derived formal type, the parent may have
3358 -- different visibility at this point. Try for an inherited
3359 -- component before reporting an error.
3361 Set_Etype (Prefix (N), Etype (Prefix_Type));
3362 Analyze_Selected_Component (N);
3363 return;
3365 elsif Ekind (Prefix_Type) = E_Record_Subtype_With_Private
3366 and then Is_Generic_Actual_Type (Prefix_Type)
3367 and then Present (Full_View (Prefix_Type))
3368 then
3369 -- Similarly, if this the actual for a formal derived type, the
3370 -- component inherited from the generic parent may not be visible
3371 -- in the actual, but the selected component is legal.
3373 declare
3374 Comp : Entity_Id;
3376 begin
3377 Comp :=
3378 First_Component (Generic_Parent_Type (Parent (Prefix_Type)));
3379 while Present (Comp) loop
3380 if Chars (Comp) = Chars (Sel) then
3381 Set_Entity_With_Style_Check (Sel, Comp);
3382 Set_Etype (Sel, Etype (Comp));
3383 Set_Etype (N, Etype (Comp));
3384 return;
3385 end if;
3387 Next_Component (Comp);
3388 end loop;
3390 pragma Assert (Etype (N) /= Any_Type);
3391 end;
3393 else
3394 if Ekind (Prefix_Type) = E_Record_Subtype then
3396 -- Check whether this is a component of the base type
3397 -- which is absent from a statically constrained subtype.
3398 -- This will raise constraint error at run-time, but is
3399 -- not a compile-time error. When the selector is illegal
3400 -- for base type as well fall through and generate a
3401 -- compilation error anyway.
3403 Comp := First_Component (Base_Type (Prefix_Type));
3404 while Present (Comp) loop
3405 if Chars (Comp) = Chars (Sel)
3406 and then Is_Visible_Component (Comp)
3407 then
3408 Set_Entity_With_Style_Check (Sel, Comp);
3409 Generate_Reference (Comp, Sel);
3410 Set_Etype (Sel, Etype (Comp));
3411 Set_Etype (N, Etype (Comp));
3413 -- Emit appropriate message. Gigi will replace the
3414 -- node subsequently with the appropriate Raise.
3416 Apply_Compile_Time_Constraint_Error
3417 (N, "component not present in }?",
3418 CE_Discriminant_Check_Failed,
3419 Ent => Prefix_Type, Rep => False);
3420 Set_Raises_Constraint_Error (N);
3421 return;
3422 end if;
3424 Next_Component (Comp);
3425 end loop;
3427 end if;
3429 Error_Msg_Node_2 := First_Subtype (Prefix_Type);
3430 Error_Msg_NE ("no selector& for}", N, Sel);
3432 Check_Misspelled_Selector (Type_To_Use, Sel);
3434 end if;
3436 Set_Entity (Sel, Any_Id);
3437 Set_Etype (Sel, Any_Type);
3438 end if;
3439 end Analyze_Selected_Component;
3441 ---------------------------
3442 -- Analyze_Short_Circuit --
3443 ---------------------------
3445 procedure Analyze_Short_Circuit (N : Node_Id) is
3446 L : constant Node_Id := Left_Opnd (N);
3447 R : constant Node_Id := Right_Opnd (N);
3448 Ind : Interp_Index;
3449 It : Interp;
3451 begin
3452 Analyze_Expression (L);
3453 Analyze_Expression (R);
3454 Set_Etype (N, Any_Type);
3456 if not Is_Overloaded (L) then
3457 if Root_Type (Etype (L)) = Standard_Boolean
3458 and then Has_Compatible_Type (R, Etype (L))
3459 then
3460 Add_One_Interp (N, Etype (L), Etype (L));
3461 end if;
3463 else
3464 Get_First_Interp (L, Ind, It);
3465 while Present (It.Typ) loop
3466 if Root_Type (It.Typ) = Standard_Boolean
3467 and then Has_Compatible_Type (R, It.Typ)
3468 then
3469 Add_One_Interp (N, It.Typ, It.Typ);
3470 end if;
3472 Get_Next_Interp (Ind, It);
3473 end loop;
3474 end if;
3476 -- Here we have failed to find an interpretation. Clearly we know that
3477 -- it is not the case that both operands can have an interpretation of
3478 -- Boolean, but this is by far the most likely intended interpretation.
3479 -- So we simply resolve both operands as Booleans, and at least one of
3480 -- these resolutions will generate an error message, and we do not need
3481 -- to give another error message on the short circuit operation itself.
3483 if Etype (N) = Any_Type then
3484 Resolve (L, Standard_Boolean);
3485 Resolve (R, Standard_Boolean);
3486 Set_Etype (N, Standard_Boolean);
3487 end if;
3488 end Analyze_Short_Circuit;
3490 -------------------
3491 -- Analyze_Slice --
3492 -------------------
3494 procedure Analyze_Slice (N : Node_Id) is
3495 P : constant Node_Id := Prefix (N);
3496 D : constant Node_Id := Discrete_Range (N);
3497 Array_Type : Entity_Id;
3499 procedure Analyze_Overloaded_Slice;
3500 -- If the prefix is overloaded, select those interpretations that
3501 -- yield a one-dimensional array type.
3503 ------------------------------
3504 -- Analyze_Overloaded_Slice --
3505 ------------------------------
3507 procedure Analyze_Overloaded_Slice is
3508 I : Interp_Index;
3509 It : Interp;
3510 Typ : Entity_Id;
3512 begin
3513 Set_Etype (N, Any_Type);
3515 Get_First_Interp (P, I, It);
3516 while Present (It.Nam) loop
3517 Typ := It.Typ;
3519 if Is_Access_Type (Typ) then
3520 Typ := Designated_Type (Typ);
3521 Error_Msg_NW (Warn_On_Dereference, "?implicit dereference", N);
3522 end if;
3524 if Is_Array_Type (Typ)
3525 and then Number_Dimensions (Typ) = 1
3526 and then Has_Compatible_Type (D, Etype (First_Index (Typ)))
3527 then
3528 Add_One_Interp (N, Typ, Typ);
3529 end if;
3531 Get_Next_Interp (I, It);
3532 end loop;
3534 if Etype (N) = Any_Type then
3535 Error_Msg_N ("expect array type in prefix of slice", N);
3536 end if;
3537 end Analyze_Overloaded_Slice;
3539 -- Start of processing for Analyze_Slice
3541 begin
3542 Analyze (P);
3543 Analyze (D);
3545 if Is_Overloaded (P) then
3546 Analyze_Overloaded_Slice;
3548 else
3549 Array_Type := Etype (P);
3550 Set_Etype (N, Any_Type);
3552 if Is_Access_Type (Array_Type) then
3553 Array_Type := Designated_Type (Array_Type);
3554 Error_Msg_NW (Warn_On_Dereference, "?implicit dereference", N);
3555 end if;
3557 if not Is_Array_Type (Array_Type) then
3558 Wrong_Type (P, Any_Array);
3560 elsif Number_Dimensions (Array_Type) > 1 then
3561 Error_Msg_N
3562 ("type is not one-dimensional array in slice prefix", N);
3564 elsif not
3565 Has_Compatible_Type (D, Etype (First_Index (Array_Type)))
3566 then
3567 Wrong_Type (D, Etype (First_Index (Array_Type)));
3569 else
3570 Set_Etype (N, Array_Type);
3571 end if;
3572 end if;
3573 end Analyze_Slice;
3575 -----------------------------
3576 -- Analyze_Type_Conversion --
3577 -----------------------------
3579 procedure Analyze_Type_Conversion (N : Node_Id) is
3580 Expr : constant Node_Id := Expression (N);
3581 T : Entity_Id;
3583 begin
3584 -- If Conversion_OK is set, then the Etype is already set, and the
3585 -- only processing required is to analyze the expression. This is
3586 -- used to construct certain "illegal" conversions which are not
3587 -- allowed by Ada semantics, but can be handled OK by Gigi, see
3588 -- Sinfo for further details.
3590 if Conversion_OK (N) then
3591 Analyze (Expr);
3592 return;
3593 end if;
3595 -- Otherwise full type analysis is required, as well as some semantic
3596 -- checks to make sure the argument of the conversion is appropriate.
3598 Find_Type (Subtype_Mark (N));
3599 T := Entity (Subtype_Mark (N));
3600 Set_Etype (N, T);
3601 Check_Fully_Declared (T, N);
3602 Analyze_Expression (Expr);
3603 Validate_Remote_Type_Type_Conversion (N);
3605 -- Only remaining step is validity checks on the argument. These
3606 -- are skipped if the conversion does not come from the source.
3608 if not Comes_From_Source (N) then
3609 return;
3611 -- If there was an error in a generic unit, no need to replicate the
3612 -- error message. Conversely, constant-folding in the generic may
3613 -- transform the argument of a conversion into a string literal, which
3614 -- is legal. Therefore the following tests are not performed in an
3615 -- instance.
3617 elsif In_Instance then
3618 return;
3620 elsif Nkind (Expr) = N_Null then
3621 Error_Msg_N ("argument of conversion cannot be null", N);
3622 Error_Msg_N ("\use qualified expression instead", N);
3623 Set_Etype (N, Any_Type);
3625 elsif Nkind (Expr) = N_Aggregate then
3626 Error_Msg_N ("argument of conversion cannot be aggregate", N);
3627 Error_Msg_N ("\use qualified expression instead", N);
3629 elsif Nkind (Expr) = N_Allocator then
3630 Error_Msg_N ("argument of conversion cannot be an allocator", N);
3631 Error_Msg_N ("\use qualified expression instead", N);
3633 elsif Nkind (Expr) = N_String_Literal then
3634 Error_Msg_N ("argument of conversion cannot be string literal", N);
3635 Error_Msg_N ("\use qualified expression instead", N);
3637 elsif Nkind (Expr) = N_Character_Literal then
3638 if Ada_Version = Ada_83 then
3639 Resolve (Expr, T);
3640 else
3641 Error_Msg_N ("argument of conversion cannot be character literal",
3643 Error_Msg_N ("\use qualified expression instead", N);
3644 end if;
3646 elsif Nkind (Expr) = N_Attribute_Reference
3647 and then
3648 (Attribute_Name (Expr) = Name_Access or else
3649 Attribute_Name (Expr) = Name_Unchecked_Access or else
3650 Attribute_Name (Expr) = Name_Unrestricted_Access)
3651 then
3652 Error_Msg_N ("argument of conversion cannot be access", N);
3653 Error_Msg_N ("\use qualified expression instead", N);
3654 end if;
3655 end Analyze_Type_Conversion;
3657 ----------------------
3658 -- Analyze_Unary_Op --
3659 ----------------------
3661 procedure Analyze_Unary_Op (N : Node_Id) is
3662 R : constant Node_Id := Right_Opnd (N);
3663 Op_Id : Entity_Id := Entity (N);
3665 begin
3666 Set_Etype (N, Any_Type);
3667 Candidate_Type := Empty;
3669 Analyze_Expression (R);
3671 if Present (Op_Id) then
3672 if Ekind (Op_Id) = E_Operator then
3673 Find_Unary_Types (R, Op_Id, N);
3674 else
3675 Add_One_Interp (N, Op_Id, Etype (Op_Id));
3676 end if;
3678 else
3679 Op_Id := Get_Name_Entity_Id (Chars (N));
3680 while Present (Op_Id) loop
3681 if Ekind (Op_Id) = E_Operator then
3682 if No (Next_Entity (First_Entity (Op_Id))) then
3683 Find_Unary_Types (R, Op_Id, N);
3684 end if;
3686 elsif Is_Overloadable (Op_Id) then
3687 Analyze_User_Defined_Unary_Op (N, Op_Id);
3688 end if;
3690 Op_Id := Homonym (Op_Id);
3691 end loop;
3692 end if;
3694 Operator_Check (N);
3695 end Analyze_Unary_Op;
3697 ----------------------------------
3698 -- Analyze_Unchecked_Expression --
3699 ----------------------------------
3701 procedure Analyze_Unchecked_Expression (N : Node_Id) is
3702 begin
3703 Analyze (Expression (N), Suppress => All_Checks);
3704 Set_Etype (N, Etype (Expression (N)));
3705 Save_Interps (Expression (N), N);
3706 end Analyze_Unchecked_Expression;
3708 ---------------------------------------
3709 -- Analyze_Unchecked_Type_Conversion --
3710 ---------------------------------------
3712 procedure Analyze_Unchecked_Type_Conversion (N : Node_Id) is
3713 begin
3714 Find_Type (Subtype_Mark (N));
3715 Analyze_Expression (Expression (N));
3716 Set_Etype (N, Entity (Subtype_Mark (N)));
3717 end Analyze_Unchecked_Type_Conversion;
3719 ------------------------------------
3720 -- Analyze_User_Defined_Binary_Op --
3721 ------------------------------------
3723 procedure Analyze_User_Defined_Binary_Op
3724 (N : Node_Id;
3725 Op_Id : Entity_Id)
3727 begin
3728 -- Only do analysis if the operator Comes_From_Source, since otherwise
3729 -- the operator was generated by the expander, and all such operators
3730 -- always refer to the operators in package Standard.
3732 if Comes_From_Source (N) then
3733 declare
3734 F1 : constant Entity_Id := First_Formal (Op_Id);
3735 F2 : constant Entity_Id := Next_Formal (F1);
3737 begin
3738 -- Verify that Op_Id is a visible binary function. Note that since
3739 -- we know Op_Id is overloaded, potentially use visible means use
3740 -- visible for sure (RM 9.4(11)).
3742 if Ekind (Op_Id) = E_Function
3743 and then Present (F2)
3744 and then (Is_Immediately_Visible (Op_Id)
3745 or else Is_Potentially_Use_Visible (Op_Id))
3746 and then Has_Compatible_Type (Left_Opnd (N), Etype (F1))
3747 and then Has_Compatible_Type (Right_Opnd (N), Etype (F2))
3748 then
3749 Add_One_Interp (N, Op_Id, Etype (Op_Id));
3751 if Debug_Flag_E then
3752 Write_Str ("user defined operator ");
3753 Write_Name (Chars (Op_Id));
3754 Write_Str (" on node ");
3755 Write_Int (Int (N));
3756 Write_Eol;
3757 end if;
3758 end if;
3759 end;
3760 end if;
3761 end Analyze_User_Defined_Binary_Op;
3763 -----------------------------------
3764 -- Analyze_User_Defined_Unary_Op --
3765 -----------------------------------
3767 procedure Analyze_User_Defined_Unary_Op
3768 (N : Node_Id;
3769 Op_Id : Entity_Id)
3771 begin
3772 -- Only do analysis if the operator Comes_From_Source, since otherwise
3773 -- the operator was generated by the expander, and all such operators
3774 -- always refer to the operators in package Standard.
3776 if Comes_From_Source (N) then
3777 declare
3778 F : constant Entity_Id := First_Formal (Op_Id);
3780 begin
3781 -- Verify that Op_Id is a visible unary function. Note that since
3782 -- we know Op_Id is overloaded, potentially use visible means use
3783 -- visible for sure (RM 9.4(11)).
3785 if Ekind (Op_Id) = E_Function
3786 and then No (Next_Formal (F))
3787 and then (Is_Immediately_Visible (Op_Id)
3788 or else Is_Potentially_Use_Visible (Op_Id))
3789 and then Has_Compatible_Type (Right_Opnd (N), Etype (F))
3790 then
3791 Add_One_Interp (N, Op_Id, Etype (Op_Id));
3792 end if;
3793 end;
3794 end if;
3795 end Analyze_User_Defined_Unary_Op;
3797 ---------------------------
3798 -- Check_Arithmetic_Pair --
3799 ---------------------------
3801 procedure Check_Arithmetic_Pair
3802 (T1, T2 : Entity_Id;
3803 Op_Id : Entity_Id;
3804 N : Node_Id)
3806 Op_Name : constant Name_Id := Chars (Op_Id);
3808 function Has_Fixed_Op (Typ : Entity_Id; Op : Entity_Id) return Boolean;
3809 -- Check whether the fixed-point type Typ has a user-defined operator
3810 -- (multiplication or division) that should hide the corresponding
3811 -- predefined operator. Used to implement Ada 2005 AI-264, to make
3812 -- such operators more visible and therefore useful.
3814 function Specific_Type (T1, T2 : Entity_Id) return Entity_Id;
3815 -- Get specific type (i.e. non-universal type if there is one)
3817 ------------------
3818 -- Has_Fixed_Op --
3819 ------------------
3821 function Has_Fixed_Op (Typ : Entity_Id; Op : Entity_Id) return Boolean is
3822 Bas : constant Entity_Id := Base_Type (Typ);
3823 Ent : Entity_Id;
3824 F1 : Entity_Id;
3825 F2 : Entity_Id;
3827 begin
3828 -- The operation is treated as primitive if it is declared in the
3829 -- same scope as the type, and therefore on the same entity chain.
3831 Ent := Next_Entity (Typ);
3832 while Present (Ent) loop
3833 if Chars (Ent) = Chars (Op) then
3834 F1 := First_Formal (Ent);
3835 F2 := Next_Formal (F1);
3837 -- The operation counts as primitive if either operand or
3838 -- result are of the given base type, and both operands are
3839 -- fixed point types.
3841 if (Base_Type (Etype (F1)) = Bas
3842 and then Is_Fixed_Point_Type (Etype (F2)))
3844 or else
3845 (Base_Type (Etype (F2)) = Bas
3846 and then Is_Fixed_Point_Type (Etype (F1)))
3848 or else
3849 (Base_Type (Etype (Ent)) = Bas
3850 and then Is_Fixed_Point_Type (Etype (F1))
3851 and then Is_Fixed_Point_Type (Etype (F2)))
3852 then
3853 return True;
3854 end if;
3855 end if;
3857 Next_Entity (Ent);
3858 end loop;
3860 return False;
3861 end Has_Fixed_Op;
3863 -------------------
3864 -- Specific_Type --
3865 -------------------
3867 function Specific_Type (T1, T2 : Entity_Id) return Entity_Id is
3868 begin
3869 if T1 = Universal_Integer or else T1 = Universal_Real then
3870 return Base_Type (T2);
3871 else
3872 return Base_Type (T1);
3873 end if;
3874 end Specific_Type;
3876 -- Start of processing for Check_Arithmetic_Pair
3878 begin
3879 if Op_Name = Name_Op_Add or else Op_Name = Name_Op_Subtract then
3881 if Is_Numeric_Type (T1)
3882 and then Is_Numeric_Type (T2)
3883 and then (Covers (T1, T2) or else Covers (T2, T1))
3884 then
3885 Add_One_Interp (N, Op_Id, Specific_Type (T1, T2));
3886 end if;
3888 elsif Op_Name = Name_Op_Multiply or else Op_Name = Name_Op_Divide then
3890 if Is_Fixed_Point_Type (T1)
3891 and then (Is_Fixed_Point_Type (T2)
3892 or else T2 = Universal_Real)
3893 then
3894 -- If Treat_Fixed_As_Integer is set then the Etype is already set
3895 -- and no further processing is required (this is the case of an
3896 -- operator constructed by Exp_Fixd for a fixed point operation)
3897 -- Otherwise add one interpretation with universal fixed result
3898 -- If the operator is given in functional notation, it comes
3899 -- from source and Fixed_As_Integer cannot apply.
3901 if (Nkind (N) not in N_Op
3902 or else not Treat_Fixed_As_Integer (N))
3903 and then
3904 (not Has_Fixed_Op (T1, Op_Id)
3905 or else Nkind (Parent (N)) = N_Type_Conversion)
3906 then
3907 Add_One_Interp (N, Op_Id, Universal_Fixed);
3908 end if;
3910 elsif Is_Fixed_Point_Type (T2)
3911 and then (Nkind (N) not in N_Op
3912 or else not Treat_Fixed_As_Integer (N))
3913 and then T1 = Universal_Real
3914 and then
3915 (not Has_Fixed_Op (T1, Op_Id)
3916 or else Nkind (Parent (N)) = N_Type_Conversion)
3917 then
3918 Add_One_Interp (N, Op_Id, Universal_Fixed);
3920 elsif Is_Numeric_Type (T1)
3921 and then Is_Numeric_Type (T2)
3922 and then (Covers (T1, T2) or else Covers (T2, T1))
3923 then
3924 Add_One_Interp (N, Op_Id, Specific_Type (T1, T2));
3926 elsif Is_Fixed_Point_Type (T1)
3927 and then (Base_Type (T2) = Base_Type (Standard_Integer)
3928 or else T2 = Universal_Integer)
3929 then
3930 Add_One_Interp (N, Op_Id, T1);
3932 elsif T2 = Universal_Real
3933 and then Base_Type (T1) = Base_Type (Standard_Integer)
3934 and then Op_Name = Name_Op_Multiply
3935 then
3936 Add_One_Interp (N, Op_Id, Any_Fixed);
3938 elsif T1 = Universal_Real
3939 and then Base_Type (T2) = Base_Type (Standard_Integer)
3940 then
3941 Add_One_Interp (N, Op_Id, Any_Fixed);
3943 elsif Is_Fixed_Point_Type (T2)
3944 and then (Base_Type (T1) = Base_Type (Standard_Integer)
3945 or else T1 = Universal_Integer)
3946 and then Op_Name = Name_Op_Multiply
3947 then
3948 Add_One_Interp (N, Op_Id, T2);
3950 elsif T1 = Universal_Real and then T2 = Universal_Integer then
3951 Add_One_Interp (N, Op_Id, T1);
3953 elsif T2 = Universal_Real
3954 and then T1 = Universal_Integer
3955 and then Op_Name = Name_Op_Multiply
3956 then
3957 Add_One_Interp (N, Op_Id, T2);
3958 end if;
3960 elsif Op_Name = Name_Op_Mod or else Op_Name = Name_Op_Rem then
3962 -- Note: The fixed-point operands case with Treat_Fixed_As_Integer
3963 -- set does not require any special processing, since the Etype is
3964 -- already set (case of operation constructed by Exp_Fixed).
3966 if Is_Integer_Type (T1)
3967 and then (Covers (T1, T2) or else Covers (T2, T1))
3968 then
3969 Add_One_Interp (N, Op_Id, Specific_Type (T1, T2));
3970 end if;
3972 elsif Op_Name = Name_Op_Expon then
3973 if Is_Numeric_Type (T1)
3974 and then not Is_Fixed_Point_Type (T1)
3975 and then (Base_Type (T2) = Base_Type (Standard_Integer)
3976 or else T2 = Universal_Integer)
3977 then
3978 Add_One_Interp (N, Op_Id, Base_Type (T1));
3979 end if;
3981 else pragma Assert (Nkind (N) in N_Op_Shift);
3983 -- If not one of the predefined operators, the node may be one
3984 -- of the intrinsic functions. Its kind is always specific, and
3985 -- we can use it directly, rather than the name of the operation.
3987 if Is_Integer_Type (T1)
3988 and then (Base_Type (T2) = Base_Type (Standard_Integer)
3989 or else T2 = Universal_Integer)
3990 then
3991 Add_One_Interp (N, Op_Id, Base_Type (T1));
3992 end if;
3993 end if;
3994 end Check_Arithmetic_Pair;
3996 -------------------------------
3997 -- Check_Misspelled_Selector --
3998 -------------------------------
4000 procedure Check_Misspelled_Selector
4001 (Prefix : Entity_Id;
4002 Sel : Node_Id)
4004 Max_Suggestions : constant := 2;
4005 Nr_Of_Suggestions : Natural := 0;
4007 Suggestion_1 : Entity_Id := Empty;
4008 Suggestion_2 : Entity_Id := Empty;
4010 Comp : Entity_Id;
4012 begin
4013 -- All the components of the prefix of selector Sel are matched
4014 -- against Sel and a count is maintained of possible misspellings.
4015 -- When at the end of the analysis there are one or two (not more!)
4016 -- possible misspellings, these misspellings will be suggested as
4017 -- possible correction.
4019 if not (Is_Private_Type (Prefix) or else Is_Record_Type (Prefix)) then
4021 -- Concurrent types should be handled as well ???
4023 return;
4024 end if;
4026 Comp := First_Entity (Prefix);
4027 while Nr_Of_Suggestions <= Max_Suggestions and then Present (Comp) loop
4028 if Is_Visible_Component (Comp) then
4029 if Is_Bad_Spelling_Of (Chars (Comp), Chars (Sel)) then
4030 Nr_Of_Suggestions := Nr_Of_Suggestions + 1;
4032 case Nr_Of_Suggestions is
4033 when 1 => Suggestion_1 := Comp;
4034 when 2 => Suggestion_2 := Comp;
4035 when others => exit;
4036 end case;
4037 end if;
4038 end if;
4040 Comp := Next_Entity (Comp);
4041 end loop;
4043 -- Report at most two suggestions
4045 if Nr_Of_Suggestions = 1 then
4046 Error_Msg_NE
4047 ("\possible misspelling of&", Sel, Suggestion_1);
4049 elsif Nr_Of_Suggestions = 2 then
4050 Error_Msg_Node_2 := Suggestion_2;
4051 Error_Msg_NE
4052 ("\possible misspelling of& or&", Sel, Suggestion_1);
4053 end if;
4054 end Check_Misspelled_Selector;
4056 ----------------------
4057 -- Defined_In_Scope --
4058 ----------------------
4060 function Defined_In_Scope (T : Entity_Id; S : Entity_Id) return Boolean
4062 S1 : constant Entity_Id := Scope (Base_Type (T));
4063 begin
4064 return S1 = S
4065 or else (S1 = System_Aux_Id and then S = Scope (S1));
4066 end Defined_In_Scope;
4068 -------------------
4069 -- Diagnose_Call --
4070 -------------------
4072 procedure Diagnose_Call (N : Node_Id; Nam : Node_Id) is
4073 Actual : Node_Id;
4074 X : Interp_Index;
4075 It : Interp;
4076 Err_Mode : Boolean;
4077 New_Nam : Node_Id;
4078 Void_Interp_Seen : Boolean := False;
4080 Success : Boolean;
4081 pragma Warnings (Off, Boolean);
4083 begin
4084 if Ada_Version >= Ada_05 then
4085 Actual := First_Actual (N);
4086 while Present (Actual) loop
4088 -- Ada 2005 (AI-50217): Post an error in case of premature
4089 -- usage of an entity from the limited view.
4091 if not Analyzed (Etype (Actual))
4092 and then From_With_Type (Etype (Actual))
4093 then
4094 Error_Msg_Qual_Level := 1;
4095 Error_Msg_NE
4096 ("missing with_clause for scope of imported type&",
4097 Actual, Etype (Actual));
4098 Error_Msg_Qual_Level := 0;
4099 end if;
4101 Next_Actual (Actual);
4102 end loop;
4103 end if;
4105 -- Analyze each candidate call again, with full error reporting
4106 -- for each.
4108 Error_Msg_N
4109 ("no candidate interpretations match the actuals:!", Nam);
4110 Err_Mode := All_Errors_Mode;
4111 All_Errors_Mode := True;
4113 -- If this is a call to an operation of a concurrent type,
4114 -- the failed interpretations have been removed from the
4115 -- name. Recover them to provide full diagnostics.
4117 if Nkind (Parent (Nam)) = N_Selected_Component then
4118 Set_Entity (Nam, Empty);
4119 New_Nam := New_Copy_Tree (Parent (Nam));
4120 Set_Is_Overloaded (New_Nam, False);
4121 Set_Is_Overloaded (Selector_Name (New_Nam), False);
4122 Set_Parent (New_Nam, Parent (Parent (Nam)));
4123 Analyze_Selected_Component (New_Nam);
4124 Get_First_Interp (Selector_Name (New_Nam), X, It);
4125 else
4126 Get_First_Interp (Nam, X, It);
4127 end if;
4129 while Present (It.Nam) loop
4130 if Etype (It.Nam) = Standard_Void_Type then
4131 Void_Interp_Seen := True;
4132 end if;
4134 Analyze_One_Call (N, It.Nam, True, Success);
4135 Get_Next_Interp (X, It);
4136 end loop;
4138 if Nkind (N) = N_Function_Call then
4139 Get_First_Interp (Nam, X, It);
4140 while Present (It.Nam) loop
4141 if Ekind (It.Nam) = E_Function
4142 or else Ekind (It.Nam) = E_Operator
4143 then
4144 return;
4145 else
4146 Get_Next_Interp (X, It);
4147 end if;
4148 end loop;
4150 -- If all interpretations are procedures, this deserves a
4151 -- more precise message. Ditto if this appears as the prefix
4152 -- of a selected component, which may be a lexical error.
4154 Error_Msg_N
4155 ("\context requires function call, found procedure name", Nam);
4157 if Nkind (Parent (N)) = N_Selected_Component
4158 and then N = Prefix (Parent (N))
4159 then
4160 Error_Msg_N (
4161 "\period should probably be semicolon", Parent (N));
4162 end if;
4164 elsif Nkind (N) = N_Procedure_Call_Statement
4165 and then not Void_Interp_Seen
4166 then
4167 Error_Msg_N (
4168 "\function name found in procedure call", Nam);
4169 end if;
4171 All_Errors_Mode := Err_Mode;
4172 end Diagnose_Call;
4174 ---------------------------
4175 -- Find_Arithmetic_Types --
4176 ---------------------------
4178 procedure Find_Arithmetic_Types
4179 (L, R : Node_Id;
4180 Op_Id : Entity_Id;
4181 N : Node_Id)
4183 Index1 : Interp_Index;
4184 Index2 : Interp_Index;
4185 It1 : Interp;
4186 It2 : Interp;
4188 procedure Check_Right_Argument (T : Entity_Id);
4189 -- Check right operand of operator
4191 --------------------------
4192 -- Check_Right_Argument --
4193 --------------------------
4195 procedure Check_Right_Argument (T : Entity_Id) is
4196 begin
4197 if not Is_Overloaded (R) then
4198 Check_Arithmetic_Pair (T, Etype (R), Op_Id, N);
4199 else
4200 Get_First_Interp (R, Index2, It2);
4201 while Present (It2.Typ) loop
4202 Check_Arithmetic_Pair (T, It2.Typ, Op_Id, N);
4203 Get_Next_Interp (Index2, It2);
4204 end loop;
4205 end if;
4206 end Check_Right_Argument;
4208 -- Start processing for Find_Arithmetic_Types
4210 begin
4211 if not Is_Overloaded (L) then
4212 Check_Right_Argument (Etype (L));
4214 else
4215 Get_First_Interp (L, Index1, It1);
4216 while Present (It1.Typ) loop
4217 Check_Right_Argument (It1.Typ);
4218 Get_Next_Interp (Index1, It1);
4219 end loop;
4220 end if;
4222 end Find_Arithmetic_Types;
4224 ------------------------
4225 -- Find_Boolean_Types --
4226 ------------------------
4228 procedure Find_Boolean_Types
4229 (L, R : Node_Id;
4230 Op_Id : Entity_Id;
4231 N : Node_Id)
4233 Index : Interp_Index;
4234 It : Interp;
4236 procedure Check_Numeric_Argument (T : Entity_Id);
4237 -- Special case for logical operations one of whose operands is an
4238 -- integer literal. If both are literal the result is any modular type.
4240 ----------------------------
4241 -- Check_Numeric_Argument --
4242 ----------------------------
4244 procedure Check_Numeric_Argument (T : Entity_Id) is
4245 begin
4246 if T = Universal_Integer then
4247 Add_One_Interp (N, Op_Id, Any_Modular);
4249 elsif Is_Modular_Integer_Type (T) then
4250 Add_One_Interp (N, Op_Id, T);
4251 end if;
4252 end Check_Numeric_Argument;
4254 -- Start of processing for Find_Boolean_Types
4256 begin
4257 if not Is_Overloaded (L) then
4258 if Etype (L) = Universal_Integer
4259 or else Etype (L) = Any_Modular
4260 then
4261 if not Is_Overloaded (R) then
4262 Check_Numeric_Argument (Etype (R));
4264 else
4265 Get_First_Interp (R, Index, It);
4266 while Present (It.Typ) loop
4267 Check_Numeric_Argument (It.Typ);
4268 Get_Next_Interp (Index, It);
4269 end loop;
4270 end if;
4272 -- If operands are aggregates, we must assume that they may be
4273 -- boolean arrays, and leave disambiguation for the second pass.
4274 -- If only one is an aggregate, verify that the other one has an
4275 -- interpretation as a boolean array
4277 elsif Nkind (L) = N_Aggregate then
4278 if Nkind (R) = N_Aggregate then
4279 Add_One_Interp (N, Op_Id, Etype (L));
4281 elsif not Is_Overloaded (R) then
4282 if Valid_Boolean_Arg (Etype (R)) then
4283 Add_One_Interp (N, Op_Id, Etype (R));
4284 end if;
4286 else
4287 Get_First_Interp (R, Index, It);
4288 while Present (It.Typ) loop
4289 if Valid_Boolean_Arg (It.Typ) then
4290 Add_One_Interp (N, Op_Id, It.Typ);
4291 end if;
4293 Get_Next_Interp (Index, It);
4294 end loop;
4295 end if;
4297 elsif Valid_Boolean_Arg (Etype (L))
4298 and then Has_Compatible_Type (R, Etype (L))
4299 then
4300 Add_One_Interp (N, Op_Id, Etype (L));
4301 end if;
4303 else
4304 Get_First_Interp (L, Index, It);
4305 while Present (It.Typ) loop
4306 if Valid_Boolean_Arg (It.Typ)
4307 and then Has_Compatible_Type (R, It.Typ)
4308 then
4309 Add_One_Interp (N, Op_Id, It.Typ);
4310 end if;
4312 Get_Next_Interp (Index, It);
4313 end loop;
4314 end if;
4315 end Find_Boolean_Types;
4317 ---------------------------
4318 -- Find_Comparison_Types --
4319 ---------------------------
4321 procedure Find_Comparison_Types
4322 (L, R : Node_Id;
4323 Op_Id : Entity_Id;
4324 N : Node_Id)
4326 Index : Interp_Index;
4327 It : Interp;
4328 Found : Boolean := False;
4329 I_F : Interp_Index;
4330 T_F : Entity_Id;
4331 Scop : Entity_Id := Empty;
4333 procedure Try_One_Interp (T1 : Entity_Id);
4334 -- Routine to try one proposed interpretation. Note that the context
4335 -- of the operator plays no role in resolving the arguments, so that
4336 -- if there is more than one interpretation of the operands that is
4337 -- compatible with comparison, the operation is ambiguous.
4339 --------------------
4340 -- Try_One_Interp --
4341 --------------------
4343 procedure Try_One_Interp (T1 : Entity_Id) is
4344 begin
4346 -- If the operator is an expanded name, then the type of the operand
4347 -- must be defined in the corresponding scope. If the type is
4348 -- universal, the context will impose the correct type.
4350 if Present (Scop)
4351 and then not Defined_In_Scope (T1, Scop)
4352 and then T1 /= Universal_Integer
4353 and then T1 /= Universal_Real
4354 and then T1 /= Any_String
4355 and then T1 /= Any_Composite
4356 then
4357 return;
4358 end if;
4360 if Valid_Comparison_Arg (T1)
4361 and then Has_Compatible_Type (R, T1)
4362 then
4363 if Found
4364 and then Base_Type (T1) /= Base_Type (T_F)
4365 then
4366 It := Disambiguate (L, I_F, Index, Any_Type);
4368 if It = No_Interp then
4369 Ambiguous_Operands (N);
4370 Set_Etype (L, Any_Type);
4371 return;
4373 else
4374 T_F := It.Typ;
4375 end if;
4377 else
4378 Found := True;
4379 T_F := T1;
4380 I_F := Index;
4381 end if;
4383 Set_Etype (L, T_F);
4384 Find_Non_Universal_Interpretations (N, R, Op_Id, T1);
4386 end if;
4387 end Try_One_Interp;
4389 -- Start processing for Find_Comparison_Types
4391 begin
4392 -- If left operand is aggregate, the right operand has to
4393 -- provide a usable type for it.
4395 if Nkind (L) = N_Aggregate
4396 and then Nkind (R) /= N_Aggregate
4397 then
4398 Find_Comparison_Types (R, L, Op_Id, N);
4399 return;
4400 end if;
4402 if Nkind (N) = N_Function_Call
4403 and then Nkind (Name (N)) = N_Expanded_Name
4404 then
4405 Scop := Entity (Prefix (Name (N)));
4407 -- The prefix may be a package renaming, and the subsequent test
4408 -- requires the original package.
4410 if Ekind (Scop) = E_Package
4411 and then Present (Renamed_Entity (Scop))
4412 then
4413 Scop := Renamed_Entity (Scop);
4414 Set_Entity (Prefix (Name (N)), Scop);
4415 end if;
4416 end if;
4418 if not Is_Overloaded (L) then
4419 Try_One_Interp (Etype (L));
4421 else
4422 Get_First_Interp (L, Index, It);
4423 while Present (It.Typ) loop
4424 Try_One_Interp (It.Typ);
4425 Get_Next_Interp (Index, It);
4426 end loop;
4427 end if;
4428 end Find_Comparison_Types;
4430 ----------------------------------------
4431 -- Find_Non_Universal_Interpretations --
4432 ----------------------------------------
4434 procedure Find_Non_Universal_Interpretations
4435 (N : Node_Id;
4436 R : Node_Id;
4437 Op_Id : Entity_Id;
4438 T1 : Entity_Id)
4440 Index : Interp_Index;
4441 It : Interp;
4443 begin
4444 if T1 = Universal_Integer
4445 or else T1 = Universal_Real
4446 then
4447 if not Is_Overloaded (R) then
4448 Add_One_Interp
4449 (N, Op_Id, Standard_Boolean, Base_Type (Etype (R)));
4450 else
4451 Get_First_Interp (R, Index, It);
4452 while Present (It.Typ) loop
4453 if Covers (It.Typ, T1) then
4454 Add_One_Interp
4455 (N, Op_Id, Standard_Boolean, Base_Type (It.Typ));
4456 end if;
4458 Get_Next_Interp (Index, It);
4459 end loop;
4460 end if;
4461 else
4462 Add_One_Interp (N, Op_Id, Standard_Boolean, Base_Type (T1));
4463 end if;
4464 end Find_Non_Universal_Interpretations;
4466 ------------------------------
4467 -- Find_Concatenation_Types --
4468 ------------------------------
4470 procedure Find_Concatenation_Types
4471 (L, R : Node_Id;
4472 Op_Id : Entity_Id;
4473 N : Node_Id)
4475 Op_Type : constant Entity_Id := Etype (Op_Id);
4477 begin
4478 if Is_Array_Type (Op_Type)
4479 and then not Is_Limited_Type (Op_Type)
4481 and then (Has_Compatible_Type (L, Op_Type)
4482 or else
4483 Has_Compatible_Type (L, Component_Type (Op_Type)))
4485 and then (Has_Compatible_Type (R, Op_Type)
4486 or else
4487 Has_Compatible_Type (R, Component_Type (Op_Type)))
4488 then
4489 Add_One_Interp (N, Op_Id, Op_Type);
4490 end if;
4491 end Find_Concatenation_Types;
4493 -------------------------
4494 -- Find_Equality_Types --
4495 -------------------------
4497 procedure Find_Equality_Types
4498 (L, R : Node_Id;
4499 Op_Id : Entity_Id;
4500 N : Node_Id)
4502 Index : Interp_Index;
4503 It : Interp;
4504 Found : Boolean := False;
4505 I_F : Interp_Index;
4506 T_F : Entity_Id;
4507 Scop : Entity_Id := Empty;
4509 procedure Try_One_Interp (T1 : Entity_Id);
4510 -- The context of the operator plays no role in resolving the
4511 -- arguments, so that if there is more than one interpretation
4512 -- of the operands that is compatible with equality, the construct
4513 -- is ambiguous and an error can be emitted now, after trying to
4514 -- disambiguate, i.e. applying preference rules.
4516 --------------------
4517 -- Try_One_Interp --
4518 --------------------
4520 procedure Try_One_Interp (T1 : Entity_Id) is
4521 begin
4522 -- If the operator is an expanded name, then the type of the operand
4523 -- must be defined in the corresponding scope. If the type is
4524 -- universal, the context will impose the correct type. An anonymous
4525 -- type for a 'Access reference is also universal in this sense, as
4526 -- the actual type is obtained from context.
4527 -- In Ada 2005, the equality operator for anonymous access types
4528 -- is declared in Standard, and preference rules apply to it.
4530 if Present (Scop) then
4531 if Defined_In_Scope (T1, Scop)
4532 or else T1 = Universal_Integer
4533 or else T1 = Universal_Real
4534 or else T1 = Any_Access
4535 or else T1 = Any_String
4536 or else T1 = Any_Composite
4537 or else (Ekind (T1) = E_Access_Subprogram_Type
4538 and then not Comes_From_Source (T1))
4539 then
4540 null;
4542 elsif Ekind (T1) = E_Anonymous_Access_Type
4543 and then Scop = Standard_Standard
4544 then
4545 null;
4547 else
4548 -- The scope does not contain an operator for the type
4550 return;
4551 end if;
4552 end if;
4554 -- Ada 2005 (AI-230): Keep restriction imposed by Ada 83 and 95:
4555 -- Do not allow anonymous access types in equality operators.
4557 if Ada_Version < Ada_05
4558 and then Ekind (T1) = E_Anonymous_Access_Type
4559 then
4560 return;
4561 end if;
4563 if T1 /= Standard_Void_Type
4564 and then not Is_Limited_Type (T1)
4565 and then not Is_Limited_Composite (T1)
4566 and then Has_Compatible_Type (R, T1)
4567 then
4568 if Found
4569 and then Base_Type (T1) /= Base_Type (T_F)
4570 then
4571 It := Disambiguate (L, I_F, Index, Any_Type);
4573 if It = No_Interp then
4574 Ambiguous_Operands (N);
4575 Set_Etype (L, Any_Type);
4576 return;
4578 else
4579 T_F := It.Typ;
4580 end if;
4582 else
4583 Found := True;
4584 T_F := T1;
4585 I_F := Index;
4586 end if;
4588 if not Analyzed (L) then
4589 Set_Etype (L, T_F);
4590 end if;
4592 Find_Non_Universal_Interpretations (N, R, Op_Id, T1);
4594 -- Case of operator was not visible, Etype still set to Any_Type
4596 if Etype (N) = Any_Type then
4597 Found := False;
4598 end if;
4600 elsif Scop = Standard_Standard
4601 and then Ekind (T1) = E_Anonymous_Access_Type
4602 then
4603 Found := True;
4604 end if;
4605 end Try_One_Interp;
4607 -- Start of processing for Find_Equality_Types
4609 begin
4610 -- If left operand is aggregate, the right operand has to
4611 -- provide a usable type for it.
4613 if Nkind (L) = N_Aggregate
4614 and then Nkind (R) /= N_Aggregate
4615 then
4616 Find_Equality_Types (R, L, Op_Id, N);
4617 return;
4618 end if;
4620 if Nkind (N) = N_Function_Call
4621 and then Nkind (Name (N)) = N_Expanded_Name
4622 then
4623 Scop := Entity (Prefix (Name (N)));
4625 -- The prefix may be a package renaming, and the subsequent test
4626 -- requires the original package.
4628 if Ekind (Scop) = E_Package
4629 and then Present (Renamed_Entity (Scop))
4630 then
4631 Scop := Renamed_Entity (Scop);
4632 Set_Entity (Prefix (Name (N)), Scop);
4633 end if;
4634 end if;
4636 if not Is_Overloaded (L) then
4637 Try_One_Interp (Etype (L));
4639 else
4640 Get_First_Interp (L, Index, It);
4641 while Present (It.Typ) loop
4642 Try_One_Interp (It.Typ);
4643 Get_Next_Interp (Index, It);
4644 end loop;
4645 end if;
4646 end Find_Equality_Types;
4648 -------------------------
4649 -- Find_Negation_Types --
4650 -------------------------
4652 procedure Find_Negation_Types
4653 (R : Node_Id;
4654 Op_Id : Entity_Id;
4655 N : Node_Id)
4657 Index : Interp_Index;
4658 It : Interp;
4660 begin
4661 if not Is_Overloaded (R) then
4662 if Etype (R) = Universal_Integer then
4663 Add_One_Interp (N, Op_Id, Any_Modular);
4664 elsif Valid_Boolean_Arg (Etype (R)) then
4665 Add_One_Interp (N, Op_Id, Etype (R));
4666 end if;
4668 else
4669 Get_First_Interp (R, Index, It);
4670 while Present (It.Typ) loop
4671 if Valid_Boolean_Arg (It.Typ) then
4672 Add_One_Interp (N, Op_Id, It.Typ);
4673 end if;
4675 Get_Next_Interp (Index, It);
4676 end loop;
4677 end if;
4678 end Find_Negation_Types;
4680 ------------------------------
4681 -- Find_Primitive_Operation --
4682 ------------------------------
4684 function Find_Primitive_Operation (N : Node_Id) return Boolean is
4685 Obj : constant Node_Id := Prefix (N);
4686 Op : constant Node_Id := Selector_Name (N);
4688 Prim : Elmt_Id;
4689 Prims : Elist_Id;
4690 Typ : Entity_Id;
4692 begin
4693 Set_Etype (Op, Any_Type);
4695 if Is_Access_Type (Etype (Obj)) then
4696 Typ := Designated_Type (Etype (Obj));
4697 else
4698 Typ := Etype (Obj);
4699 end if;
4701 if Is_Class_Wide_Type (Typ) then
4702 Typ := Root_Type (Typ);
4703 end if;
4705 Prims := Primitive_Operations (Typ);
4707 Prim := First_Elmt (Prims);
4708 while Present (Prim) loop
4709 if Chars (Node (Prim)) = Chars (Op) then
4710 Add_One_Interp (Op, Node (Prim), Etype (Node (Prim)));
4711 Set_Etype (N, Etype (Node (Prim)));
4712 end if;
4714 Next_Elmt (Prim);
4715 end loop;
4717 -- Now look for class-wide operations of the type or any of its
4718 -- ancestors by iterating over the homonyms of the selector.
4720 declare
4721 Cls_Type : constant Entity_Id := Class_Wide_Type (Typ);
4722 Hom : Entity_Id;
4724 begin
4725 Hom := Current_Entity (Op);
4726 while Present (Hom) loop
4727 if (Ekind (Hom) = E_Procedure
4728 or else
4729 Ekind (Hom) = E_Function)
4730 and then Scope (Hom) = Scope (Typ)
4731 and then Present (First_Formal (Hom))
4732 and then
4733 (Base_Type (Etype (First_Formal (Hom))) = Cls_Type
4734 or else
4735 (Is_Access_Type (Etype (First_Formal (Hom)))
4736 and then
4737 Ekind (Etype (First_Formal (Hom))) =
4738 E_Anonymous_Access_Type
4739 and then
4740 Base_Type
4741 (Designated_Type (Etype (First_Formal (Hom)))) =
4742 Cls_Type))
4743 then
4744 Add_One_Interp (Op, Hom, Etype (Hom));
4745 Set_Etype (N, Etype (Hom));
4746 end if;
4748 Hom := Homonym (Hom);
4749 end loop;
4750 end;
4752 return Etype (Op) /= Any_Type;
4753 end Find_Primitive_Operation;
4755 ----------------------
4756 -- Find_Unary_Types --
4757 ----------------------
4759 procedure Find_Unary_Types
4760 (R : Node_Id;
4761 Op_Id : Entity_Id;
4762 N : Node_Id)
4764 Index : Interp_Index;
4765 It : Interp;
4767 begin
4768 if not Is_Overloaded (R) then
4769 if Is_Numeric_Type (Etype (R)) then
4770 Add_One_Interp (N, Op_Id, Base_Type (Etype (R)));
4771 end if;
4773 else
4774 Get_First_Interp (R, Index, It);
4775 while Present (It.Typ) loop
4776 if Is_Numeric_Type (It.Typ) then
4777 Add_One_Interp (N, Op_Id, Base_Type (It.Typ));
4778 end if;
4780 Get_Next_Interp (Index, It);
4781 end loop;
4782 end if;
4783 end Find_Unary_Types;
4785 ------------------
4786 -- Junk_Operand --
4787 ------------------
4789 function Junk_Operand (N : Node_Id) return Boolean is
4790 Enode : Node_Id;
4792 begin
4793 if Error_Posted (N) then
4794 return False;
4795 end if;
4797 -- Get entity to be tested
4799 if Is_Entity_Name (N)
4800 and then Present (Entity (N))
4801 then
4802 Enode := N;
4804 -- An odd case, a procedure name gets converted to a very peculiar
4805 -- function call, and here is where we detect this happening.
4807 elsif Nkind (N) = N_Function_Call
4808 and then Is_Entity_Name (Name (N))
4809 and then Present (Entity (Name (N)))
4810 then
4811 Enode := Name (N);
4813 -- Another odd case, there are at least some cases of selected
4814 -- components where the selected component is not marked as having
4815 -- an entity, even though the selector does have an entity
4817 elsif Nkind (N) = N_Selected_Component
4818 and then Present (Entity (Selector_Name (N)))
4819 then
4820 Enode := Selector_Name (N);
4822 else
4823 return False;
4824 end if;
4826 -- Now test the entity we got to see if it is a bad case
4828 case Ekind (Entity (Enode)) is
4830 when E_Package =>
4831 Error_Msg_N
4832 ("package name cannot be used as operand", Enode);
4834 when Generic_Unit_Kind =>
4835 Error_Msg_N
4836 ("generic unit name cannot be used as operand", Enode);
4838 when Type_Kind =>
4839 Error_Msg_N
4840 ("subtype name cannot be used as operand", Enode);
4842 when Entry_Kind =>
4843 Error_Msg_N
4844 ("entry name cannot be used as operand", Enode);
4846 when E_Procedure =>
4847 Error_Msg_N
4848 ("procedure name cannot be used as operand", Enode);
4850 when E_Exception =>
4851 Error_Msg_N
4852 ("exception name cannot be used as operand", Enode);
4854 when E_Block | E_Label | E_Loop =>
4855 Error_Msg_N
4856 ("label name cannot be used as operand", Enode);
4858 when others =>
4859 return False;
4861 end case;
4863 return True;
4864 end Junk_Operand;
4866 --------------------
4867 -- Operator_Check --
4868 --------------------
4870 procedure Operator_Check (N : Node_Id) is
4871 begin
4872 Remove_Abstract_Operations (N);
4874 -- Test for case of no interpretation found for operator
4876 if Etype (N) = Any_Type then
4877 declare
4878 L : Node_Id;
4879 R : Node_Id;
4880 Op_Id : Entity_Id := Empty;
4882 begin
4883 R := Right_Opnd (N);
4885 if Nkind (N) in N_Binary_Op then
4886 L := Left_Opnd (N);
4887 else
4888 L := Empty;
4889 end if;
4891 -- If either operand has no type, then don't complain further,
4892 -- since this simply means that we have a propagated error.
4894 if R = Error
4895 or else Etype (R) = Any_Type
4896 or else (Nkind (N) in N_Binary_Op and then Etype (L) = Any_Type)
4897 then
4898 return;
4900 -- We explicitly check for the case of concatenation of component
4901 -- with component to avoid reporting spurious matching array types
4902 -- that might happen to be lurking in distant packages (such as
4903 -- run-time packages). This also prevents inconsistencies in the
4904 -- messages for certain ACVC B tests, which can vary depending on
4905 -- types declared in run-time interfaces. Another improvement when
4906 -- aggregates are present is to look for a well-typed operand.
4908 elsif Present (Candidate_Type)
4909 and then (Nkind (N) /= N_Op_Concat
4910 or else Is_Array_Type (Etype (L))
4911 or else Is_Array_Type (Etype (R)))
4912 then
4914 if Nkind (N) = N_Op_Concat then
4915 if Etype (L) /= Any_Composite
4916 and then Is_Array_Type (Etype (L))
4917 then
4918 Candidate_Type := Etype (L);
4920 elsif Etype (R) /= Any_Composite
4921 and then Is_Array_Type (Etype (R))
4922 then
4923 Candidate_Type := Etype (R);
4924 end if;
4925 end if;
4927 Error_Msg_NE
4928 ("operator for} is not directly visible!",
4929 N, First_Subtype (Candidate_Type));
4930 Error_Msg_N ("use clause would make operation legal!", N);
4931 return;
4933 -- If either operand is a junk operand (e.g. package name), then
4934 -- post appropriate error messages, but do not complain further.
4936 -- Note that the use of OR in this test instead of OR ELSE is
4937 -- quite deliberate, we may as well check both operands in the
4938 -- binary operator case.
4940 elsif Junk_Operand (R)
4941 or (Nkind (N) in N_Binary_Op and then Junk_Operand (L))
4942 then
4943 return;
4945 -- If we have a logical operator, one of whose operands is
4946 -- Boolean, then we know that the other operand cannot resolve to
4947 -- Boolean (since we got no interpretations), but in that case we
4948 -- pretty much know that the other operand should be Boolean, so
4949 -- resolve it that way (generating an error)
4951 elsif Nkind_In (N, N_Op_And, N_Op_Or, N_Op_Xor) then
4952 if Etype (L) = Standard_Boolean then
4953 Resolve (R, Standard_Boolean);
4954 return;
4955 elsif Etype (R) = Standard_Boolean then
4956 Resolve (L, Standard_Boolean);
4957 return;
4958 end if;
4960 -- For an arithmetic operator or comparison operator, if one
4961 -- of the operands is numeric, then we know the other operand
4962 -- is not the same numeric type. If it is a non-numeric type,
4963 -- then probably it is intended to match the other operand.
4965 elsif Nkind_In (N, N_Op_Add,
4966 N_Op_Divide,
4967 N_Op_Ge,
4968 N_Op_Gt,
4969 N_Op_Le)
4970 or else
4971 Nkind_In (N, N_Op_Lt,
4972 N_Op_Mod,
4973 N_Op_Multiply,
4974 N_Op_Rem,
4975 N_Op_Subtract)
4976 then
4977 if Is_Numeric_Type (Etype (L))
4978 and then not Is_Numeric_Type (Etype (R))
4979 then
4980 Resolve (R, Etype (L));
4981 return;
4983 elsif Is_Numeric_Type (Etype (R))
4984 and then not Is_Numeric_Type (Etype (L))
4985 then
4986 Resolve (L, Etype (R));
4987 return;
4988 end if;
4990 -- Comparisons on A'Access are common enough to deserve a
4991 -- special message.
4993 elsif Nkind_In (N, N_Op_Eq, N_Op_Ne)
4994 and then Ekind (Etype (L)) = E_Access_Attribute_Type
4995 and then Ekind (Etype (R)) = E_Access_Attribute_Type
4996 then
4997 Error_Msg_N
4998 ("two access attributes cannot be compared directly", N);
4999 Error_Msg_N
5000 ("\use qualified expression for one of the operands",
5002 return;
5004 -- Another one for C programmers
5006 elsif Nkind (N) = N_Op_Concat
5007 and then Valid_Boolean_Arg (Etype (L))
5008 and then Valid_Boolean_Arg (Etype (R))
5009 then
5010 Error_Msg_N ("invalid operands for concatenation", N);
5011 Error_Msg_N ("\maybe AND was meant", N);
5012 return;
5014 -- A special case for comparison of access parameter with null
5016 elsif Nkind (N) = N_Op_Eq
5017 and then Is_Entity_Name (L)
5018 and then Nkind (Parent (Entity (L))) = N_Parameter_Specification
5019 and then Nkind (Parameter_Type (Parent (Entity (L)))) =
5020 N_Access_Definition
5021 and then Nkind (R) = N_Null
5022 then
5023 Error_Msg_N ("access parameter is not allowed to be null", L);
5024 Error_Msg_N ("\(call would raise Constraint_Error)", L);
5025 return;
5026 end if;
5028 -- If we fall through then just give general message. Note that in
5029 -- the following messages, if the operand is overloaded we choose
5030 -- an arbitrary type to complain about, but that is probably more
5031 -- useful than not giving a type at all.
5033 if Nkind (N) in N_Unary_Op then
5034 Error_Msg_Node_2 := Etype (R);
5035 Error_Msg_N ("operator& not defined for}", N);
5036 return;
5038 else
5039 if Nkind (N) in N_Binary_Op then
5040 if not Is_Overloaded (L)
5041 and then not Is_Overloaded (R)
5042 and then Base_Type (Etype (L)) = Base_Type (Etype (R))
5043 then
5044 Error_Msg_Node_2 := First_Subtype (Etype (R));
5045 Error_Msg_N ("there is no applicable operator& for}", N);
5047 else
5048 -- Another attempt to find a fix: one of the candidate
5049 -- interpretations may not be use-visible. This has
5050 -- already been checked for predefined operators, so
5051 -- we examine only user-defined functions.
5053 Op_Id := Get_Name_Entity_Id (Chars (N));
5055 while Present (Op_Id) loop
5056 if Ekind (Op_Id) /= E_Operator
5057 and then Is_Overloadable (Op_Id)
5058 then
5059 if not Is_Immediately_Visible (Op_Id)
5060 and then not In_Use (Scope (Op_Id))
5061 and then not Is_Abstract_Subprogram (Op_Id)
5062 and then not Is_Hidden (Op_Id)
5063 and then Ekind (Scope (Op_Id)) = E_Package
5064 and then
5065 Has_Compatible_Type
5066 (L, Etype (First_Formal (Op_Id)))
5067 and then Present
5068 (Next_Formal (First_Formal (Op_Id)))
5069 and then
5070 Has_Compatible_Type
5072 Etype (Next_Formal (First_Formal (Op_Id))))
5073 then
5074 Error_Msg_N
5075 ("No legal interpretation for operator&", N);
5076 Error_Msg_NE
5077 ("\use clause on& would make operation legal",
5078 N, Scope (Op_Id));
5079 exit;
5080 end if;
5081 end if;
5083 Op_Id := Homonym (Op_Id);
5084 end loop;
5086 if No (Op_Id) then
5087 Error_Msg_N ("invalid operand types for operator&", N);
5089 if Nkind (N) /= N_Op_Concat then
5090 Error_Msg_NE ("\left operand has}!", N, Etype (L));
5091 Error_Msg_NE ("\right operand has}!", N, Etype (R));
5092 end if;
5093 end if;
5094 end if;
5095 end if;
5096 end if;
5097 end;
5098 end if;
5099 end Operator_Check;
5101 -----------------------------------------
5102 -- Process_Implicit_Dereference_Prefix --
5103 -----------------------------------------
5105 function Process_Implicit_Dereference_Prefix
5106 (E : Entity_Id;
5107 P : Entity_Id) return Entity_Id
5109 Ref : Node_Id;
5110 Typ : constant Entity_Id := Designated_Type (Etype (P));
5112 begin
5113 if Present (E)
5114 and then (Operating_Mode = Check_Semantics or else not Expander_Active)
5115 then
5116 -- We create a dummy reference to E to ensure that the reference
5117 -- is not considered as part of an assignment (an implicit
5118 -- dereference can never assign to its prefix). The Comes_From_Source
5119 -- attribute needs to be propagated for accurate warnings.
5121 Ref := New_Reference_To (E, Sloc (P));
5122 Set_Comes_From_Source (Ref, Comes_From_Source (P));
5123 Generate_Reference (E, Ref);
5124 end if;
5126 -- An implicit dereference is a legal occurrence of an
5127 -- incomplete type imported through a limited_with clause,
5128 -- if the full view is visible.
5130 if From_With_Type (Typ)
5131 and then not From_With_Type (Scope (Typ))
5132 and then
5133 (Is_Immediately_Visible (Scope (Typ))
5134 or else
5135 (Is_Child_Unit (Scope (Typ))
5136 and then Is_Visible_Child_Unit (Scope (Typ))))
5137 then
5138 return Available_View (Typ);
5139 else
5140 return Typ;
5141 end if;
5143 end Process_Implicit_Dereference_Prefix;
5145 --------------------------------
5146 -- Remove_Abstract_Operations --
5147 --------------------------------
5149 procedure Remove_Abstract_Operations (N : Node_Id) is
5150 Abstract_Op : Entity_Id := Empty;
5151 Address_Kludge : Boolean := False;
5152 I : Interp_Index;
5153 It : Interp;
5155 -- AI-310: If overloaded, remove abstract non-dispatching operations. We
5156 -- activate this if either extensions are enabled, or if the abstract
5157 -- operation in question comes from a predefined file. This latter test
5158 -- allows us to use abstract to make operations invisible to users. In
5159 -- particular, if type Address is non-private and abstract subprograms
5160 -- are used to hide its operators, they will be truly hidden.
5162 type Operand_Position is (First_Op, Second_Op);
5163 Univ_Type : constant Entity_Id := Universal_Interpretation (N);
5165 procedure Remove_Address_Interpretations (Op : Operand_Position);
5166 -- Ambiguities may arise when the operands are literal and the address
5167 -- operations in s-auxdec are visible. In that case, remove the
5168 -- interpretation of a literal as Address, to retain the semantics of
5169 -- Address as a private type.
5171 ------------------------------------
5172 -- Remove_Address_Interpretations --
5173 ------------------------------------
5175 procedure Remove_Address_Interpretations (Op : Operand_Position) is
5176 Formal : Entity_Id;
5178 begin
5179 if Is_Overloaded (N) then
5180 Get_First_Interp (N, I, It);
5181 while Present (It.Nam) loop
5182 Formal := First_Entity (It.Nam);
5184 if Op = Second_Op then
5185 Formal := Next_Entity (Formal);
5186 end if;
5188 if Is_Descendent_Of_Address (Etype (Formal)) then
5189 Address_Kludge := True;
5190 Remove_Interp (I);
5191 end if;
5193 Get_Next_Interp (I, It);
5194 end loop;
5195 end if;
5196 end Remove_Address_Interpretations;
5198 -- Start of processing for Remove_Abstract_Operations
5200 begin
5201 if Is_Overloaded (N) then
5202 Get_First_Interp (N, I, It);
5204 while Present (It.Nam) loop
5205 if Is_Overloadable (It.Nam)
5206 and then Is_Abstract_Subprogram (It.Nam)
5207 and then not Is_Dispatching_Operation (It.Nam)
5208 then
5209 Abstract_Op := It.Nam;
5211 if Is_Descendent_Of_Address (It.Typ) then
5212 Address_Kludge := True;
5213 Remove_Interp (I);
5214 exit;
5216 -- In Ada 2005, this operation does not participate in Overload
5217 -- resolution. If the operation is defined in a predefined
5218 -- unit, it is one of the operations declared abstract in some
5219 -- variants of System, and it must be removed as well.
5221 elsif Ada_Version >= Ada_05
5222 or else Is_Predefined_File_Name
5223 (Unit_File_Name (Get_Source_Unit (It.Nam)))
5224 then
5225 Remove_Interp (I);
5226 exit;
5227 end if;
5228 end if;
5230 Get_Next_Interp (I, It);
5231 end loop;
5233 if No (Abstract_Op) then
5235 -- If some interpretation yields an integer type, it is still
5236 -- possible that there are address interpretations. Remove them
5237 -- if one operand is a literal, to avoid spurious ambiguities
5238 -- on systems where Address is a visible integer type.
5240 if Is_Overloaded (N)
5241 and then Nkind (N) in N_Op
5242 and then Is_Integer_Type (Etype (N))
5243 then
5244 if Nkind (N) in N_Binary_Op then
5245 if Nkind (Right_Opnd (N)) = N_Integer_Literal then
5246 Remove_Address_Interpretations (Second_Op);
5248 elsif Nkind (Right_Opnd (N)) = N_Integer_Literal then
5249 Remove_Address_Interpretations (First_Op);
5250 end if;
5251 end if;
5252 end if;
5254 elsif Nkind (N) in N_Op then
5256 -- Remove interpretations that treat literals as addresses. This
5257 -- is never appropriate, even when Address is defined as a visible
5258 -- Integer type. The reason is that we would really prefer Address
5259 -- to behave as a private type, even in this case, which is there
5260 -- only to accomodate oddities of VMS address sizes. If Address is
5261 -- a visible integer type, we get lots of overload ambiguities.
5263 if Nkind (N) in N_Binary_Op then
5264 declare
5265 U1 : constant Boolean :=
5266 Present (Universal_Interpretation (Right_Opnd (N)));
5267 U2 : constant Boolean :=
5268 Present (Universal_Interpretation (Left_Opnd (N)));
5270 begin
5271 if U1 then
5272 Remove_Address_Interpretations (Second_Op);
5273 end if;
5275 if U2 then
5276 Remove_Address_Interpretations (First_Op);
5277 end if;
5279 if not (U1 and U2) then
5281 -- Remove corresponding predefined operator, which is
5282 -- always added to the overload set.
5284 Get_First_Interp (N, I, It);
5285 while Present (It.Nam) loop
5286 if Scope (It.Nam) = Standard_Standard
5287 and then Base_Type (It.Typ) =
5288 Base_Type (Etype (Abstract_Op))
5289 then
5290 Remove_Interp (I);
5291 end if;
5293 Get_Next_Interp (I, It);
5294 end loop;
5296 elsif Is_Overloaded (N)
5297 and then Present (Univ_Type)
5298 then
5299 -- If both operands have a universal interpretation,
5300 -- it is still necessary to remove interpretations that
5301 -- yield Address. Any remaining ambiguities will be
5302 -- removed in Disambiguate.
5304 Get_First_Interp (N, I, It);
5305 while Present (It.Nam) loop
5306 if Is_Descendent_Of_Address (It.Typ) then
5307 Remove_Interp (I);
5309 elsif not Is_Type (It.Nam) then
5310 Set_Entity (N, It.Nam);
5311 end if;
5313 Get_Next_Interp (I, It);
5314 end loop;
5315 end if;
5316 end;
5317 end if;
5319 elsif Nkind (N) = N_Function_Call
5320 and then
5321 (Nkind (Name (N)) = N_Operator_Symbol
5322 or else
5323 (Nkind (Name (N)) = N_Expanded_Name
5324 and then
5325 Nkind (Selector_Name (Name (N))) = N_Operator_Symbol))
5326 then
5328 declare
5329 Arg1 : constant Node_Id := First (Parameter_Associations (N));
5330 U1 : constant Boolean :=
5331 Present (Universal_Interpretation (Arg1));
5332 U2 : constant Boolean :=
5333 Present (Next (Arg1)) and then
5334 Present (Universal_Interpretation (Next (Arg1)));
5336 begin
5337 if U1 then
5338 Remove_Address_Interpretations (First_Op);
5339 end if;
5341 if U2 then
5342 Remove_Address_Interpretations (Second_Op);
5343 end if;
5345 if not (U1 and U2) then
5346 Get_First_Interp (N, I, It);
5347 while Present (It.Nam) loop
5348 if Scope (It.Nam) = Standard_Standard
5349 and then It.Typ = Base_Type (Etype (Abstract_Op))
5350 then
5351 Remove_Interp (I);
5352 end if;
5354 Get_Next_Interp (I, It);
5355 end loop;
5356 end if;
5357 end;
5358 end if;
5360 -- If the removal has left no valid interpretations, emit an error
5361 -- message now and label node as illegal.
5363 if Present (Abstract_Op) then
5364 Get_First_Interp (N, I, It);
5366 if No (It.Nam) then
5368 -- Removal of abstract operation left no viable candidate
5370 Set_Etype (N, Any_Type);
5371 Error_Msg_Sloc := Sloc (Abstract_Op);
5372 Error_Msg_NE
5373 ("cannot call abstract operation& declared#", N, Abstract_Op);
5375 -- In Ada 2005, an abstract operation may disable predefined
5376 -- operators. Since the context is not yet known, we mark the
5377 -- predefined operators as potentially hidden. Do not include
5378 -- predefined operators when addresses are involved since this
5379 -- case is handled separately.
5381 elsif Ada_Version >= Ada_05
5382 and then not Address_Kludge
5383 then
5384 while Present (It.Nam) loop
5385 if Is_Numeric_Type (It.Typ)
5386 and then Scope (It.Typ) = Standard_Standard
5387 then
5388 Set_Abstract_Op (I, Abstract_Op);
5389 end if;
5391 Get_Next_Interp (I, It);
5392 end loop;
5393 end if;
5394 end if;
5395 end if;
5396 end Remove_Abstract_Operations;
5398 -----------------------
5399 -- Try_Indirect_Call --
5400 -----------------------
5402 function Try_Indirect_Call
5403 (N : Node_Id;
5404 Nam : Entity_Id;
5405 Typ : Entity_Id) return Boolean
5407 Actual : Node_Id;
5408 Formal : Entity_Id;
5410 Call_OK : Boolean;
5411 pragma Warnings (Off, Call_OK);
5413 begin
5414 Normalize_Actuals (N, Designated_Type (Typ), False, Call_OK);
5416 Actual := First_Actual (N);
5417 Formal := First_Formal (Designated_Type (Typ));
5418 while Present (Actual) and then Present (Formal) loop
5419 if not Has_Compatible_Type (Actual, Etype (Formal)) then
5420 return False;
5421 end if;
5423 Next (Actual);
5424 Next_Formal (Formal);
5425 end loop;
5427 if No (Actual) and then No (Formal) then
5428 Add_One_Interp (N, Nam, Etype (Designated_Type (Typ)));
5430 -- Nam is a candidate interpretation for the name in the call,
5431 -- if it is not an indirect call.
5433 if not Is_Type (Nam)
5434 and then Is_Entity_Name (Name (N))
5435 then
5436 Set_Entity (Name (N), Nam);
5437 end if;
5439 return True;
5440 else
5441 return False;
5442 end if;
5443 end Try_Indirect_Call;
5445 ----------------------
5446 -- Try_Indexed_Call --
5447 ----------------------
5449 function Try_Indexed_Call
5450 (N : Node_Id;
5451 Nam : Entity_Id;
5452 Typ : Entity_Id;
5453 Skip_First : Boolean) return Boolean
5455 Actuals : constant List_Id := Parameter_Associations (N);
5456 Actual : Node_Id;
5457 Index : Entity_Id;
5459 begin
5460 Actual := First (Actuals);
5462 -- If the call was originally written in prefix form, skip the first
5463 -- actual, which is obviously not defaulted.
5465 if Skip_First then
5466 Next (Actual);
5467 end if;
5469 Index := First_Index (Typ);
5470 while Present (Actual) and then Present (Index) loop
5472 -- If the parameter list has a named association, the expression
5473 -- is definitely a call and not an indexed component.
5475 if Nkind (Actual) = N_Parameter_Association then
5476 return False;
5477 end if;
5479 if not Has_Compatible_Type (Actual, Etype (Index)) then
5480 return False;
5481 end if;
5483 Next (Actual);
5484 Next_Index (Index);
5485 end loop;
5487 if No (Actual) and then No (Index) then
5488 Add_One_Interp (N, Nam, Component_Type (Typ));
5490 -- Nam is a candidate interpretation for the name in the call,
5491 -- if it is not an indirect call.
5493 if not Is_Type (Nam)
5494 and then Is_Entity_Name (Name (N))
5495 then
5496 Set_Entity (Name (N), Nam);
5497 end if;
5499 return True;
5500 else
5501 return False;
5502 end if;
5503 end Try_Indexed_Call;
5505 --------------------------
5506 -- Try_Object_Operation --
5507 --------------------------
5509 function Try_Object_Operation (N : Node_Id) return Boolean is
5510 K : constant Node_Kind := Nkind (Parent (N));
5511 Is_Subprg_Call : constant Boolean := Nkind_In
5512 (K, N_Procedure_Call_Statement,
5513 N_Function_Call);
5514 Loc : constant Source_Ptr := Sloc (N);
5515 Obj : constant Node_Id := Prefix (N);
5516 Subprog : constant Node_Id :=
5517 Make_Identifier (Sloc (Selector_Name (N)),
5518 Chars => Chars (Selector_Name (N)));
5519 -- Identifier on which possible interpretations will be collected
5521 Report_Error : Boolean := False;
5522 -- If no candidate interpretation matches the context, redo the
5523 -- analysis with error enabled to provide additional information.
5525 Actual : Node_Id;
5526 Candidate : Entity_Id := Empty;
5527 New_Call_Node : Node_Id := Empty;
5528 Node_To_Replace : Node_Id;
5529 Obj_Type : Entity_Id := Etype (Obj);
5530 Success : Boolean := False;
5532 function Valid_Candidate
5533 (Success : Boolean;
5534 Call : Node_Id;
5535 Subp : Entity_Id) return Entity_Id;
5536 -- If the subprogram is a valid interpretation, record it, and add
5537 -- to the list of interpretations of Subprog.
5539 procedure Complete_Object_Operation
5540 (Call_Node : Node_Id;
5541 Node_To_Replace : Node_Id);
5542 -- Make Subprog the name of Call_Node, replace Node_To_Replace with
5543 -- Call_Node, insert the object (or its dereference) as the first actual
5544 -- in the call, and complete the analysis of the call.
5546 procedure Report_Ambiguity (Op : Entity_Id);
5547 -- If a prefixed procedure call is ambiguous, indicate whether the
5548 -- call includes an implicit dereference or an implicit 'Access.
5550 procedure Transform_Object_Operation
5551 (Call_Node : out Node_Id;
5552 Node_To_Replace : out Node_Id);
5553 -- Transform Obj.Operation (X, Y,,) into Operation (Obj, X, Y ..)
5554 -- Call_Node is the resulting subprogram call, Node_To_Replace is
5555 -- either N or the parent of N, and Subprog is a reference to the
5556 -- subprogram we are trying to match.
5558 function Try_Class_Wide_Operation
5559 (Call_Node : Node_Id;
5560 Node_To_Replace : Node_Id) return Boolean;
5561 -- Traverse all ancestor types looking for a class-wide subprogram
5562 -- for which the current operation is a valid non-dispatching call.
5564 procedure Try_One_Prefix_Interpretation (T : Entity_Id);
5565 -- If prefix is overloaded, its interpretation may include different
5566 -- tagged types, and we must examine the primitive operations and
5567 -- the class-wide operations of each in order to find candidate
5568 -- interpretations for the call as a whole.
5570 function Try_Primitive_Operation
5571 (Call_Node : Node_Id;
5572 Node_To_Replace : Node_Id) return Boolean;
5573 -- Traverse the list of primitive subprograms looking for a dispatching
5574 -- operation for which the current node is a valid call .
5576 ---------------------
5577 -- Valid_Candidate --
5578 ---------------------
5580 function Valid_Candidate
5581 (Success : Boolean;
5582 Call : Node_Id;
5583 Subp : Entity_Id) return Entity_Id
5585 Comp_Type : Entity_Id;
5587 begin
5588 -- If the subprogram is a valid interpretation, record it in global
5589 -- variable Subprog, to collect all possible overloadings.
5591 if Success then
5592 if Subp /= Entity (Subprog) then
5593 Add_One_Interp (Subprog, Subp, Etype (Subp));
5594 end if;
5595 end if;
5597 -- If the call may be an indexed call, retrieve component type of
5598 -- resulting expression, and add possible interpretation.
5600 Comp_Type := Empty;
5602 if Nkind (Call) = N_Function_Call
5603 and then Nkind (Parent (N)) = N_Indexed_Component
5604 and then Needs_One_Actual (Subp)
5605 then
5606 if Is_Array_Type (Etype (Subp)) then
5607 Comp_Type := Component_Type (Etype (Subp));
5609 elsif Is_Access_Type (Etype (Subp))
5610 and then Is_Array_Type (Designated_Type (Etype (Subp)))
5611 then
5612 Comp_Type := Component_Type (Designated_Type (Etype (Subp)));
5613 end if;
5614 end if;
5616 if Present (Comp_Type)
5617 and then Etype (Subprog) /= Comp_Type
5618 then
5619 Add_One_Interp (Subprog, Subp, Comp_Type);
5620 end if;
5622 if Etype (Call) /= Any_Type then
5623 return Subp;
5624 else
5625 return Empty;
5626 end if;
5627 end Valid_Candidate;
5629 -------------------------------
5630 -- Complete_Object_Operation --
5631 -------------------------------
5633 procedure Complete_Object_Operation
5634 (Call_Node : Node_Id;
5635 Node_To_Replace : Node_Id)
5637 Formal_Type : constant Entity_Id :=
5638 Etype (First_Formal (Entity (Subprog)));
5639 First_Actual : Node_Id;
5641 begin
5642 -- Place the name of the operation, with its interpretations,
5643 -- on the rewritten call.
5645 Set_Name (Call_Node, Subprog);
5647 First_Actual := First (Parameter_Associations (Call_Node));
5649 -- For cross-reference purposes, treat the new node as being in
5650 -- the source if the original one is.
5652 Set_Comes_From_Source (Subprog, Comes_From_Source (N));
5653 Set_Comes_From_Source (Call_Node, Comes_From_Source (N));
5655 if Nkind (N) = N_Selected_Component
5656 and then not Inside_A_Generic
5657 then
5658 Set_Entity (Selector_Name (N), Entity (Subprog));
5659 end if;
5661 -- If need be, rewrite first actual as an explicit dereference
5662 -- If the call is overloaded, the rewriting can only be done
5663 -- once the primitive operation is identified.
5665 if Is_Overloaded (Subprog) then
5667 -- The prefix itself may be overloaded, and its interpretations
5668 -- must be propagated to the new actual in the call.
5670 if Is_Overloaded (Obj) then
5671 Save_Interps (Obj, First_Actual);
5672 end if;
5674 Rewrite (First_Actual, Obj);
5676 elsif not Is_Access_Type (Formal_Type)
5677 and then Is_Access_Type (Etype (Obj))
5678 then
5679 Rewrite (First_Actual,
5680 Make_Explicit_Dereference (Sloc (Obj), Obj));
5681 Analyze (First_Actual);
5683 -- If we need to introduce an explicit dereference, verify that
5684 -- the resulting actual is compatible with the mode of the formal.
5686 if Ekind (First_Formal (Entity (Subprog))) /= E_In_Parameter
5687 and then Is_Access_Constant (Etype (Obj))
5688 then
5689 Error_Msg_NE
5690 ("expect variable in call to&", Prefix (N), Entity (Subprog));
5691 end if;
5693 -- Conversely, if the formal is an access parameter and the object
5694 -- is not, replace the actual with a 'Access reference. Its analysis
5695 -- will check that the object is aliased.
5697 elsif Is_Access_Type (Formal_Type)
5698 and then not Is_Access_Type (Etype (Obj))
5699 then
5700 Rewrite (First_Actual,
5701 Make_Attribute_Reference (Loc,
5702 Attribute_Name => Name_Access,
5703 Prefix => Relocate_Node (Obj)));
5705 if not Is_Aliased_View (Obj) then
5706 Error_Msg_NE
5707 ("object in prefixed call to& must be aliased"
5708 & " (RM-2005 4.3.1 (13))",
5709 Prefix (First_Actual), Subprog);
5710 end if;
5712 Analyze (First_Actual);
5714 else
5715 if Is_Overloaded (Obj) then
5716 Save_Interps (Obj, First_Actual);
5717 end if;
5719 Rewrite (First_Actual, Obj);
5720 end if;
5722 Rewrite (Node_To_Replace, Call_Node);
5724 -- Propagate the interpretations collected in subprog to the new
5725 -- function call node, to be resolved from context.
5727 if Is_Overloaded (Subprog) then
5728 Save_Interps (Subprog, Node_To_Replace);
5729 else
5730 Analyze (Node_To_Replace);
5731 end if;
5732 end Complete_Object_Operation;
5734 ----------------------
5735 -- Report_Ambiguity --
5736 ----------------------
5738 procedure Report_Ambiguity (Op : Entity_Id) is
5739 Access_Formal : constant Boolean :=
5740 Is_Access_Type (Etype (First_Formal (Op)));
5741 Access_Actual : constant Boolean :=
5742 Is_Access_Type (Etype (Prefix (N)));
5744 begin
5745 Error_Msg_Sloc := Sloc (Op);
5747 if Access_Formal and then not Access_Actual then
5748 if Nkind (Parent (Op)) = N_Full_Type_Declaration then
5749 Error_Msg_N
5750 ("\possible interpretation"
5751 & " (inherited, with implicit 'Access) #", N);
5752 else
5753 Error_Msg_N
5754 ("\possible interpretation (with implicit 'Access) #", N);
5755 end if;
5757 elsif not Access_Formal and then Access_Actual then
5758 if Nkind (Parent (Op)) = N_Full_Type_Declaration then
5759 Error_Msg_N
5760 ("\possible interpretation"
5761 & " ( inherited, with implicit dereference) #", N);
5762 else
5763 Error_Msg_N
5764 ("\possible interpretation (with implicit dereference) #", N);
5765 end if;
5767 else
5768 if Nkind (Parent (Op)) = N_Full_Type_Declaration then
5769 Error_Msg_N ("\possible interpretation (inherited)#", N);
5770 else
5771 Error_Msg_N ("\possible interpretation#", N);
5772 end if;
5773 end if;
5774 end Report_Ambiguity;
5776 --------------------------------
5777 -- Transform_Object_Operation --
5778 --------------------------------
5780 procedure Transform_Object_Operation
5781 (Call_Node : out Node_Id;
5782 Node_To_Replace : out Node_Id)
5784 Dummy : constant Node_Id := New_Copy (Obj);
5785 -- Placeholder used as a first parameter in the call, replaced
5786 -- eventually by the proper object.
5788 Parent_Node : constant Node_Id := Parent (N);
5790 Actual : Node_Id;
5791 Actuals : List_Id;
5793 begin
5794 -- Common case covering 1) Call to a procedure and 2) Call to a
5795 -- function that has some additional actuals.
5797 if Nkind_In (Parent_Node, N_Function_Call,
5798 N_Procedure_Call_Statement)
5800 -- N is a selected component node containing the name of the
5801 -- subprogram. If N is not the name of the parent node we must
5802 -- not replace the parent node by the new construct. This case
5803 -- occurs when N is a parameterless call to a subprogram that
5804 -- is an actual parameter of a call to another subprogram. For
5805 -- example:
5806 -- Some_Subprogram (..., Obj.Operation, ...)
5808 and then Name (Parent_Node) = N
5809 then
5810 Node_To_Replace := Parent_Node;
5812 Actuals := Parameter_Associations (Parent_Node);
5814 if Present (Actuals) then
5815 Prepend (Dummy, Actuals);
5816 else
5817 Actuals := New_List (Dummy);
5818 end if;
5820 if Nkind (Parent_Node) = N_Procedure_Call_Statement then
5821 Call_Node :=
5822 Make_Procedure_Call_Statement (Loc,
5823 Name => New_Copy (Subprog),
5824 Parameter_Associations => Actuals);
5826 else
5827 Call_Node :=
5828 Make_Function_Call (Loc,
5829 Name => New_Copy (Subprog),
5830 Parameter_Associations => Actuals);
5832 end if;
5834 -- Before analysis, a function call appears as an indexed component
5835 -- if there are no named associations.
5837 elsif Nkind (Parent_Node) = N_Indexed_Component
5838 and then N = Prefix (Parent_Node)
5839 then
5840 Node_To_Replace := Parent_Node;
5842 Actuals := Expressions (Parent_Node);
5844 Actual := First (Actuals);
5845 while Present (Actual) loop
5846 Analyze (Actual);
5847 Next (Actual);
5848 end loop;
5850 Prepend (Dummy, Actuals);
5852 Call_Node :=
5853 Make_Function_Call (Loc,
5854 Name => New_Copy (Subprog),
5855 Parameter_Associations => Actuals);
5857 -- Parameterless call: Obj.F is rewritten as F (Obj)
5859 else
5860 Node_To_Replace := N;
5862 Call_Node :=
5863 Make_Function_Call (Loc,
5864 Name => New_Copy (Subprog),
5865 Parameter_Associations => New_List (Dummy));
5866 end if;
5867 end Transform_Object_Operation;
5869 ------------------------------
5870 -- Try_Class_Wide_Operation --
5871 ------------------------------
5873 function Try_Class_Wide_Operation
5874 (Call_Node : Node_Id;
5875 Node_To_Replace : Node_Id) return Boolean
5877 Anc_Type : Entity_Id;
5878 Matching_Op : Entity_Id := Empty;
5879 Error : Boolean;
5881 procedure Traverse_Homonyms
5882 (Anc_Type : Entity_Id;
5883 Error : out Boolean);
5884 -- Traverse the homonym chain of the subprogram searching for those
5885 -- homonyms whose first formal has the Anc_Type's class-wide type,
5886 -- or an anonymous access type designating the class-wide type. If
5887 -- an ambiguity is detected, then Error is set to True.
5889 procedure Traverse_Interfaces
5890 (Anc_Type : Entity_Id;
5891 Error : out Boolean);
5892 -- Traverse the list of interfaces, if any, associated with Anc_Type
5893 -- and search for acceptable class-wide homonyms associated with each
5894 -- interface. If an ambiguity is detected, then Error is set to True.
5896 -----------------------
5897 -- Traverse_Homonyms --
5898 -----------------------
5900 procedure Traverse_Homonyms
5901 (Anc_Type : Entity_Id;
5902 Error : out Boolean)
5904 Cls_Type : Entity_Id;
5905 Hom : Entity_Id;
5906 Hom_Ref : Node_Id;
5907 Success : Boolean;
5909 begin
5910 Error := False;
5912 Cls_Type := Class_Wide_Type (Anc_Type);
5914 Hom := Current_Entity (Subprog);
5916 -- Find operation whose first parameter is of the class-wide
5917 -- type, a subtype thereof, or an anonymous access to same.
5919 while Present (Hom) loop
5920 if (Ekind (Hom) = E_Procedure
5921 or else
5922 Ekind (Hom) = E_Function)
5923 and then Scope (Hom) = Scope (Anc_Type)
5924 and then Present (First_Formal (Hom))
5925 and then
5926 (Base_Type (Etype (First_Formal (Hom))) = Cls_Type
5927 or else
5928 (Is_Access_Type (Etype (First_Formal (Hom)))
5929 and then
5930 Ekind (Etype (First_Formal (Hom))) =
5931 E_Anonymous_Access_Type
5932 and then
5933 Base_Type
5934 (Designated_Type (Etype (First_Formal (Hom)))) =
5935 Cls_Type))
5936 then
5937 Set_Etype (Call_Node, Any_Type);
5938 Set_Is_Overloaded (Call_Node, False);
5939 Success := False;
5941 if No (Matching_Op) then
5942 Hom_Ref := New_Reference_To (Hom, Sloc (Subprog));
5943 Set_Etype (Call_Node, Any_Type);
5944 Set_Parent (Call_Node, Parent (Node_To_Replace));
5946 Set_Name (Call_Node, Hom_Ref);
5948 Analyze_One_Call
5949 (N => Call_Node,
5950 Nam => Hom,
5951 Report => Report_Error,
5952 Success => Success,
5953 Skip_First => True);
5955 Matching_Op :=
5956 Valid_Candidate (Success, Call_Node, Hom);
5958 else
5959 Analyze_One_Call
5960 (N => Call_Node,
5961 Nam => Hom,
5962 Report => Report_Error,
5963 Success => Success,
5964 Skip_First => True);
5966 if Present (Valid_Candidate (Success, Call_Node, Hom))
5967 and then Nkind (Call_Node) /= N_Function_Call
5968 then
5969 Error_Msg_NE ("ambiguous call to&", N, Hom);
5970 Report_Ambiguity (Matching_Op);
5971 Report_Ambiguity (Hom);
5972 Error := True;
5973 return;
5974 end if;
5975 end if;
5976 end if;
5978 Hom := Homonym (Hom);
5979 end loop;
5980 end Traverse_Homonyms;
5982 -------------------------
5983 -- Traverse_Interfaces --
5984 -------------------------
5986 procedure Traverse_Interfaces
5987 (Anc_Type : Entity_Id;
5988 Error : out Boolean)
5990 Intface_List : constant List_Id :=
5991 Abstract_Interface_List (Anc_Type);
5992 Intface : Node_Id;
5994 begin
5995 Error := False;
5997 if Is_Non_Empty_List (Intface_List) then
5998 Intface := First (Intface_List);
5999 while Present (Intface) loop
6001 -- Look for acceptable class-wide homonyms associated with
6002 -- the interface.
6004 Traverse_Homonyms (Etype (Intface), Error);
6006 if Error then
6007 return;
6008 end if;
6010 -- Continue the search by looking at each of the interface's
6011 -- associated interface ancestors.
6013 Traverse_Interfaces (Etype (Intface), Error);
6015 if Error then
6016 return;
6017 end if;
6019 Next (Intface);
6020 end loop;
6021 end if;
6022 end Traverse_Interfaces;
6024 -- Start of processing for Try_Class_Wide_Operation
6026 begin
6027 -- Loop through ancestor types (including interfaces), traversing
6028 -- the homonym chain of the subprogram, trying out those homonyms
6029 -- whose first formal has the class-wide type of the ancestor, or
6030 -- an anonymous access type designating the class-wide type.
6032 Anc_Type := Obj_Type;
6033 loop
6034 -- Look for a match among homonyms associated with the ancestor
6036 Traverse_Homonyms (Anc_Type, Error);
6038 if Error then
6039 return True;
6040 end if;
6042 -- Continue the search for matches among homonyms associated with
6043 -- any interfaces implemented by the ancestor.
6045 Traverse_Interfaces (Anc_Type, Error);
6047 if Error then
6048 return True;
6049 end if;
6051 exit when Etype (Anc_Type) = Anc_Type;
6052 Anc_Type := Etype (Anc_Type);
6053 end loop;
6055 if Present (Matching_Op) then
6056 Set_Etype (Call_Node, Etype (Matching_Op));
6057 end if;
6059 return Present (Matching_Op);
6060 end Try_Class_Wide_Operation;
6062 -----------------------------------
6063 -- Try_One_Prefix_Interpretation --
6064 -----------------------------------
6066 procedure Try_One_Prefix_Interpretation (T : Entity_Id) is
6067 begin
6068 Obj_Type := T;
6070 if Is_Access_Type (Obj_Type) then
6071 Obj_Type := Designated_Type (Obj_Type);
6072 end if;
6074 if Ekind (Obj_Type) = E_Private_Subtype then
6075 Obj_Type := Base_Type (Obj_Type);
6076 end if;
6078 if Is_Class_Wide_Type (Obj_Type) then
6079 Obj_Type := Etype (Class_Wide_Type (Obj_Type));
6080 end if;
6082 -- The type may have be obtained through a limited_with clause,
6083 -- in which case the primitive operations are available on its
6084 -- non-limited view. If still incomplete, retrieve full view.
6086 if Ekind (Obj_Type) = E_Incomplete_Type
6087 and then From_With_Type (Obj_Type)
6088 then
6089 Obj_Type := Get_Full_View (Non_Limited_View (Obj_Type));
6090 end if;
6092 -- If the object is not tagged, or the type is still an incomplete
6093 -- type, this is not a prefixed call.
6095 if not Is_Tagged_Type (Obj_Type)
6096 or else Is_Incomplete_Type (Obj_Type)
6097 then
6098 return;
6099 end if;
6101 if Try_Primitive_Operation
6102 (Call_Node => New_Call_Node,
6103 Node_To_Replace => Node_To_Replace)
6104 or else
6105 Try_Class_Wide_Operation
6106 (Call_Node => New_Call_Node,
6107 Node_To_Replace => Node_To_Replace)
6108 then
6109 null;
6110 end if;
6111 end Try_One_Prefix_Interpretation;
6113 -----------------------------
6114 -- Try_Primitive_Operation --
6115 -----------------------------
6117 function Try_Primitive_Operation
6118 (Call_Node : Node_Id;
6119 Node_To_Replace : Node_Id) return Boolean
6121 Elmt : Elmt_Id;
6122 Prim_Op : Entity_Id;
6123 Matching_Op : Entity_Id := Empty;
6124 Prim_Op_Ref : Node_Id := Empty;
6126 Corr_Type : Entity_Id := Empty;
6127 -- If the prefix is a synchronized type, the controlling type of
6128 -- the primitive operation is the corresponding record type, else
6129 -- this is the object type itself.
6131 Success : Boolean := False;
6133 function Collect_Generic_Type_Ops (T : Entity_Id) return Elist_Id;
6134 -- For tagged types the candidate interpretations are found in
6135 -- the list of primitive operations of the type and its ancestors.
6136 -- For formal tagged types we have to find the operations declared
6137 -- in the same scope as the type (including in the generic formal
6138 -- part) because the type itself carries no primitive operations,
6139 -- except for formal derived types that inherit the operations of
6140 -- the parent and progenitors.
6141 -- If the context is a generic subprogram body, the generic formals
6142 -- are visible by name, but are not in the entity list of the
6143 -- subprogram because that list starts with the subprogram formals.
6144 -- We retrieve the candidate operations from the generic declaration.
6146 function Valid_First_Argument_Of (Op : Entity_Id) return Boolean;
6147 -- Verify that the prefix, dereferenced if need be, is a valid
6148 -- controlling argument in a call to Op. The remaining actuals
6149 -- are checked in the subsequent call to Analyze_One_Call.
6151 ------------------------------
6152 -- Collect_Generic_Type_Ops --
6153 ------------------------------
6155 function Collect_Generic_Type_Ops (T : Entity_Id) return Elist_Id is
6156 Bas : constant Entity_Id := Base_Type (T);
6157 Candidates : constant Elist_Id := New_Elmt_List;
6158 Subp : Entity_Id;
6159 Formal : Entity_Id;
6161 procedure Check_Candidate;
6162 -- The operation is a candidate if its first parameter is a
6163 -- controlling operand of the desired type.
6165 -----------------------
6166 -- Check_Candidate; --
6167 -----------------------
6169 procedure Check_Candidate is
6170 begin
6171 Formal := First_Formal (Subp);
6173 if Present (Formal)
6174 and then Is_Controlling_Formal (Formal)
6175 and then
6176 (Base_Type (Etype (Formal)) = Bas
6177 or else
6178 (Is_Access_Type (Etype (Formal))
6179 and then Designated_Type (Etype (Formal)) = Bas))
6180 then
6181 Append_Elmt (Subp, Candidates);
6182 end if;
6183 end Check_Candidate;
6185 -- Start of processing for Collect_Generic_Type_Ops
6187 begin
6188 if Is_Derived_Type (T) then
6189 return Primitive_Operations (T);
6191 elsif Ekind (Scope (T)) = E_Procedure
6192 or else Ekind (Scope (T)) = E_Function
6193 then
6194 -- Scan the list of generic formals to find subprograms
6195 -- that may have a first controlling formal of the type.
6197 declare
6198 Decl : Node_Id;
6200 begin
6201 Decl :=
6202 First (Generic_Formal_Declarations
6203 (Unit_Declaration_Node (Scope (T))));
6204 while Present (Decl) loop
6205 if Nkind (Decl) in N_Formal_Subprogram_Declaration then
6206 Subp := Defining_Entity (Decl);
6207 Check_Candidate;
6208 end if;
6210 Next (Decl);
6211 end loop;
6212 end;
6214 return Candidates;
6216 else
6217 -- Scan the list of entities declared in the same scope as
6218 -- the type. In general this will be an open scope, given that
6219 -- the call we are analyzing can only appear within a generic
6220 -- declaration or body (either the one that declares T, or a
6221 -- child unit).
6223 Subp := First_Entity (Scope (T));
6224 while Present (Subp) loop
6225 if Is_Overloadable (Subp) then
6226 Check_Candidate;
6227 end if;
6229 Next_Entity (Subp);
6230 end loop;
6232 return Candidates;
6233 end if;
6234 end Collect_Generic_Type_Ops;
6236 -----------------------------
6237 -- Valid_First_Argument_Of --
6238 -----------------------------
6240 function Valid_First_Argument_Of (Op : Entity_Id) return Boolean is
6241 Typ : constant Entity_Id := Etype (First_Formal (Op));
6243 begin
6244 -- Simple case. Object may be a subtype of the tagged type or
6245 -- may be the corresponding record of a synchronized type.
6247 return Obj_Type = Typ
6248 or else Base_Type (Obj_Type) = Typ
6249 or else Corr_Type = Typ
6251 -- Prefix can be dereferenced
6253 or else
6254 (Is_Access_Type (Corr_Type)
6255 and then Designated_Type (Corr_Type) = Typ)
6257 -- Formal is an access parameter, for which the object
6258 -- can provide an access.
6260 or else
6261 (Ekind (Typ) = E_Anonymous_Access_Type
6262 and then Designated_Type (Typ) = Base_Type (Corr_Type));
6263 end Valid_First_Argument_Of;
6265 -- Start of processing for Try_Primitive_Operation
6267 begin
6268 -- Look for subprograms in the list of primitive operations. The name
6269 -- must be identical, and the kind of call indicates the expected
6270 -- kind of operation (function or procedure). If the type is a
6271 -- (tagged) synchronized type, the primitive ops are attached to the
6272 -- corresponding record type.
6274 if Is_Concurrent_Type (Obj_Type) then
6275 Corr_Type := Corresponding_Record_Type (Obj_Type);
6276 Elmt := First_Elmt (Primitive_Operations (Corr_Type));
6278 elsif not Is_Generic_Type (Obj_Type) then
6279 Corr_Type := Obj_Type;
6280 Elmt := First_Elmt (Primitive_Operations (Obj_Type));
6282 else
6283 Corr_Type := Obj_Type;
6284 Elmt := First_Elmt (Collect_Generic_Type_Ops (Obj_Type));
6285 end if;
6287 while Present (Elmt) loop
6288 Prim_Op := Node (Elmt);
6290 if Chars (Prim_Op) = Chars (Subprog)
6291 and then Present (First_Formal (Prim_Op))
6292 and then Valid_First_Argument_Of (Prim_Op)
6293 and then
6294 (Nkind (Call_Node) = N_Function_Call)
6295 = (Ekind (Prim_Op) = E_Function)
6296 then
6297 -- Ada 2005 (AI-251): If this primitive operation corresponds
6298 -- with an immediate ancestor interface there is no need to add
6299 -- it to the list of interpretations; the corresponding aliased
6300 -- primitive is also in this list of primitive operations and
6301 -- will be used instead.
6303 if (Present (Abstract_Interface_Alias (Prim_Op))
6304 and then Is_Ancestor (Find_Dispatching_Type
6305 (Alias (Prim_Op)), Corr_Type))
6306 or else
6308 -- Do not consider hidden primitives unless the type is in an
6309 -- open scope or we are within an instance, where visibility
6310 -- is known to be correct.
6312 (Is_Hidden (Prim_Op)
6313 and then not Is_Immediately_Visible (Obj_Type)
6314 and then not In_Instance)
6315 then
6316 goto Continue;
6317 end if;
6319 Set_Etype (Call_Node, Any_Type);
6320 Set_Is_Overloaded (Call_Node, False);
6322 if No (Matching_Op) then
6323 Prim_Op_Ref := New_Reference_To (Prim_Op, Sloc (Subprog));
6324 Candidate := Prim_Op;
6326 Set_Parent (Call_Node, Parent (Node_To_Replace));
6328 Set_Name (Call_Node, Prim_Op_Ref);
6329 Success := False;
6331 Analyze_One_Call
6332 (N => Call_Node,
6333 Nam => Prim_Op,
6334 Report => Report_Error,
6335 Success => Success,
6336 Skip_First => True);
6338 Matching_Op := Valid_Candidate (Success, Call_Node, Prim_Op);
6340 -- More than one interpretation, collect for subsequent
6341 -- disambiguation. If this is a procedure call and there
6342 -- is another match, report ambiguity now.
6344 else
6345 Analyze_One_Call
6346 (N => Call_Node,
6347 Nam => Prim_Op,
6348 Report => Report_Error,
6349 Success => Success,
6350 Skip_First => True);
6352 if Present (Valid_Candidate (Success, Call_Node, Prim_Op))
6353 and then Nkind (Call_Node) /= N_Function_Call
6354 then
6355 Error_Msg_NE ("ambiguous call to&", N, Prim_Op);
6356 Report_Ambiguity (Matching_Op);
6357 Report_Ambiguity (Prim_Op);
6358 return True;
6359 end if;
6360 end if;
6361 end if;
6363 <<Continue>>
6364 Next_Elmt (Elmt);
6365 end loop;
6367 if Present (Matching_Op) then
6368 Set_Etype (Call_Node, Etype (Matching_Op));
6369 end if;
6371 return Present (Matching_Op);
6372 end Try_Primitive_Operation;
6374 -- Start of processing for Try_Object_Operation
6376 begin
6377 Analyze_Expression (Obj);
6379 -- Analyze the actuals if node is known to be a subprogram call
6381 if Is_Subprg_Call and then N = Name (Parent (N)) then
6382 Actual := First (Parameter_Associations (Parent (N)));
6383 while Present (Actual) loop
6384 Analyze_Expression (Actual);
6385 Next (Actual);
6386 end loop;
6387 end if;
6389 -- Build a subprogram call node, using a copy of Obj as its first
6390 -- actual. This is a placeholder, to be replaced by an explicit
6391 -- dereference when needed.
6393 Transform_Object_Operation
6394 (Call_Node => New_Call_Node,
6395 Node_To_Replace => Node_To_Replace);
6397 Set_Etype (New_Call_Node, Any_Type);
6398 Set_Etype (Subprog, Any_Type);
6399 Set_Parent (New_Call_Node, Parent (Node_To_Replace));
6401 if not Is_Overloaded (Obj) then
6402 Try_One_Prefix_Interpretation (Obj_Type);
6404 else
6405 declare
6406 I : Interp_Index;
6407 It : Interp;
6408 begin
6409 Get_First_Interp (Obj, I, It);
6410 while Present (It.Nam) loop
6411 Try_One_Prefix_Interpretation (It.Typ);
6412 Get_Next_Interp (I, It);
6413 end loop;
6414 end;
6415 end if;
6417 if Etype (New_Call_Node) /= Any_Type then
6418 Complete_Object_Operation
6419 (Call_Node => New_Call_Node,
6420 Node_To_Replace => Node_To_Replace);
6421 return True;
6423 elsif Present (Candidate) then
6425 -- The argument list is not type correct. Re-analyze with error
6426 -- reporting enabled, and use one of the possible candidates.
6427 -- In All_Errors_Mode, re-analyze all failed interpretations.
6429 if All_Errors_Mode then
6430 Report_Error := True;
6431 if Try_Primitive_Operation
6432 (Call_Node => New_Call_Node,
6433 Node_To_Replace => Node_To_Replace)
6435 or else
6436 Try_Class_Wide_Operation
6437 (Call_Node => New_Call_Node,
6438 Node_To_Replace => Node_To_Replace)
6439 then
6440 null;
6441 end if;
6443 else
6444 Analyze_One_Call
6445 (N => New_Call_Node,
6446 Nam => Candidate,
6447 Report => True,
6448 Success => Success,
6449 Skip_First => True);
6450 end if;
6452 -- No need for further errors
6454 return True;
6456 else
6457 -- There was no candidate operation, so report it as an error
6458 -- in the caller: Analyze_Selected_Component.
6460 return False;
6461 end if;
6462 end Try_Object_Operation;
6464 end Sem_Ch4;