Daily bump.
[official-gcc.git] / gcc / ada / sem_ch4.adb
blobd2a12e6c5c631447222623432483205d744c4360
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 Nlists; use Nlists;
38 with Nmake; use Nmake;
39 with Opt; use Opt;
40 with Output; use Output;
41 with Restrict; use Restrict;
42 with Rident; use Rident;
43 with Sem; use Sem;
44 with Sem_Cat; use Sem_Cat;
45 with Sem_Ch3; use Sem_Ch3;
46 with Sem_Ch8; use Sem_Ch8;
47 with Sem_Disp; use Sem_Disp;
48 with Sem_Dist; use Sem_Dist;
49 with Sem_Eval; use Sem_Eval;
50 with Sem_Res; use Sem_Res;
51 with Sem_Util; use Sem_Util;
52 with Sem_Type; use Sem_Type;
53 with Stand; use Stand;
54 with Sinfo; use Sinfo;
55 with Snames; use Snames;
56 with Tbuild; use Tbuild;
58 with GNAT.Spelling_Checker; use GNAT.Spelling_Checker;
60 package body Sem_Ch4 is
62 -----------------------
63 -- Local Subprograms --
64 -----------------------
66 procedure Analyze_Expression (N : Node_Id);
67 -- For expressions that are not names, this is just a call to analyze.
68 -- If the expression is a name, it may be a call to a parameterless
69 -- function, and if so must be converted into an explicit call node
70 -- and analyzed as such. This deproceduring must be done during the first
71 -- pass of overload resolution, because otherwise a procedure call with
72 -- overloaded actuals may fail to resolve. See 4327-001 for an example.
74 procedure Analyze_Operator_Call (N : Node_Id; Op_Id : Entity_Id);
75 -- Analyze a call of the form "+"(x, y), etc. The prefix of the call
76 -- is an operator name or an expanded name whose selector is an operator
77 -- name, and one possible interpretation is as a predefined operator.
79 procedure Analyze_Overloaded_Selected_Component (N : Node_Id);
80 -- If the prefix of a selected_component is overloaded, the proper
81 -- interpretation that yields a record type with the proper selector
82 -- name must be selected.
84 procedure Analyze_User_Defined_Binary_Op (N : Node_Id; Op_Id : Entity_Id);
85 -- Procedure to analyze a user defined binary operator, which is resolved
86 -- like a function, but instead of a list of actuals it is presented
87 -- with the left and right operands of an operator node.
89 procedure Analyze_User_Defined_Unary_Op (N : Node_Id; Op_Id : Entity_Id);
90 -- Procedure to analyze a user defined unary operator, which is resolved
91 -- like a function, but instead of a list of actuals, it is presented with
92 -- the operand of the operator node.
94 procedure Ambiguous_Operands (N : Node_Id);
95 -- for equality, membership, and comparison operators with overloaded
96 -- arguments, list possible interpretations.
98 procedure Analyze_One_Call
99 (N : Node_Id;
100 Nam : Entity_Id;
101 Report : Boolean;
102 Success : out Boolean;
103 Skip_First : Boolean := False);
104 -- Check one interpretation of an overloaded subprogram name for
105 -- compatibility with the types of the actuals in a call. If there is a
106 -- single interpretation which does not match, post error if Report is
107 -- set to True.
109 -- Nam is the entity that provides the formals against which the actuals
110 -- are checked. Nam is either the name of a subprogram, or the internal
111 -- subprogram type constructed for an access_to_subprogram. If the actuals
112 -- are compatible with Nam, then Nam is added to the list of candidate
113 -- interpretations for N, and Success is set to True.
115 -- The flag Skip_First is used when analyzing a call that was rewritten
116 -- from object notation. In this case the first actual may have to receive
117 -- an explicit dereference, depending on the first formal of the operation
118 -- being called. The caller will have verified that the object is legal
119 -- for the call. If the remaining parameters match, the first parameter
120 -- will rewritten as a dereference if needed, prior to completing analysis.
122 procedure Check_Misspelled_Selector
123 (Prefix : Entity_Id;
124 Sel : Node_Id);
125 -- Give possible misspelling diagnostic if Sel is likely to be
126 -- a misspelling of one of the selectors of the Prefix.
127 -- This is called by Analyze_Selected_Component after producing
128 -- an invalid selector error message.
130 function Defined_In_Scope (T : Entity_Id; S : Entity_Id) return Boolean;
131 -- Verify that type T is declared in scope S. Used to find intepretations
132 -- for operators given by expanded names. This is abstracted as a separate
133 -- function to handle extensions to System, where S is System, but T is
134 -- declared in the extension.
136 procedure Find_Arithmetic_Types
137 (L, R : Node_Id;
138 Op_Id : Entity_Id;
139 N : Node_Id);
140 -- L and R are the operands of an arithmetic operator. Find
141 -- consistent pairs of interpretations for L and R that have a
142 -- numeric type consistent with the semantics of the operator.
144 procedure Find_Comparison_Types
145 (L, R : Node_Id;
146 Op_Id : Entity_Id;
147 N : Node_Id);
148 -- L and R are operands of a comparison operator. Find consistent
149 -- pairs of interpretations for L and R.
151 procedure Find_Concatenation_Types
152 (L, R : Node_Id;
153 Op_Id : Entity_Id;
154 N : Node_Id);
155 -- For the four varieties of concatenation
157 procedure Find_Equality_Types
158 (L, R : Node_Id;
159 Op_Id : Entity_Id;
160 N : Node_Id);
161 -- Ditto for equality operators
163 procedure Find_Boolean_Types
164 (L, R : Node_Id;
165 Op_Id : Entity_Id;
166 N : Node_Id);
167 -- Ditto for binary logical operations
169 procedure Find_Negation_Types
170 (R : Node_Id;
171 Op_Id : Entity_Id;
172 N : Node_Id);
173 -- Find consistent interpretation for operand of negation operator
175 procedure Find_Non_Universal_Interpretations
176 (N : Node_Id;
177 R : Node_Id;
178 Op_Id : Entity_Id;
179 T1 : Entity_Id);
180 -- For equality and comparison operators, the result is always boolean,
181 -- and the legality of the operation is determined from the visibility
182 -- of the operand types. If one of the operands has a universal interpre-
183 -- tation, the legality check uses some compatible non-universal
184 -- interpretation of the other operand. N can be an operator node, or
185 -- a function call whose name is an operator designator.
187 procedure Find_Unary_Types
188 (R : Node_Id;
189 Op_Id : Entity_Id;
190 N : Node_Id);
191 -- Unary arithmetic types: plus, minus, abs
193 procedure Check_Arithmetic_Pair
194 (T1, T2 : Entity_Id;
195 Op_Id : Entity_Id;
196 N : Node_Id);
197 -- Subsidiary procedure to Find_Arithmetic_Types. T1 and T2 are valid
198 -- types for left and right operand. Determine whether they constitute
199 -- a valid pair for the given operator, and record the corresponding
200 -- interpretation of the operator node. The node N may be an operator
201 -- node (the usual case) or a function call whose prefix is an operator
202 -- designator. In both cases Op_Id is the operator name itself.
204 procedure Diagnose_Call (N : Node_Id; Nam : Node_Id);
205 -- Give detailed information on overloaded call where none of the
206 -- interpretations match. N is the call node, Nam the designator for
207 -- the overloaded entity being called.
209 function Junk_Operand (N : Node_Id) return Boolean;
210 -- Test for an operand that is an inappropriate entity (e.g. a package
211 -- name or a label). If so, issue an error message and return True. If
212 -- the operand is not an inappropriate entity kind, return False.
214 procedure Operator_Check (N : Node_Id);
215 -- Verify that an operator has received some valid interpretation. If none
216 -- was found, determine whether a use clause would make the operation
217 -- legal. The variable Candidate_Type (defined in Sem_Type) is set for
218 -- every type compatible with the operator, even if the operator for the
219 -- type is not directly visible. The routine uses this type to emit a more
220 -- informative message.
222 procedure Process_Implicit_Dereference_Prefix
223 (E : Entity_Id;
224 P : Node_Id);
225 -- Called when P is the prefix of an implicit dereference, denoting an
226 -- object E. If in semantics only mode (-gnatc or generic), record that is
227 -- a reference to E. Normally, such a reference is generated only when the
228 -- implicit dereference is expanded into an explicit one. E may be empty,
229 -- in which case this procedure does nothing.
231 procedure Remove_Abstract_Operations (N : Node_Id);
232 -- Ada 2005: implementation of AI-310. An abstract non-dispatching
233 -- operation is not a candidate interpretation.
235 function Try_Indexed_Call
236 (N : Node_Id;
237 Nam : Entity_Id;
238 Typ : Entity_Id;
239 Skip_First : Boolean) return Boolean;
240 -- If a function has defaults for all its actuals, a call to it may in fact
241 -- be an indexing on the result of the call. Try_Indexed_Call attempts the
242 -- interpretation as an indexing, prior to analysis as a call. If both are
243 -- possible, the node is overloaded with both interpretations (same symbol
244 -- but two different types). If the call is written in prefix form, the
245 -- prefix becomes the first parameter in the call, and only the remaining
246 -- actuals must be checked for the presence of defaults.
248 function Try_Indirect_Call
249 (N : Node_Id;
250 Nam : Entity_Id;
251 Typ : Entity_Id) return Boolean;
252 -- Similarly, a function F that needs no actuals can return an access to a
253 -- subprogram, and the call F (X) interpreted as F.all (X). In this case
254 -- the call may be overloaded with both interpretations.
256 function Try_Object_Operation (N : Node_Id) return Boolean;
257 -- Ada 2005 (AI-252): Support the object.operation notation
259 ------------------------
260 -- Ambiguous_Operands --
261 ------------------------
263 procedure Ambiguous_Operands (N : Node_Id) is
264 procedure List_Operand_Interps (Opnd : Node_Id);
266 --------------------------
267 -- List_Operand_Interps --
268 --------------------------
270 procedure List_Operand_Interps (Opnd : Node_Id) is
271 Nam : Node_Id;
272 Err : Node_Id := N;
274 begin
275 if Is_Overloaded (Opnd) then
276 if Nkind (Opnd) in N_Op then
277 Nam := Opnd;
278 elsif Nkind (Opnd) = N_Function_Call then
279 Nam := Name (Opnd);
280 else
281 return;
282 end if;
284 else
285 return;
286 end if;
288 if Opnd = Left_Opnd (N) then
289 Error_Msg_N
290 ("\left operand has the following interpretations", N);
291 else
292 Error_Msg_N
293 ("\right operand has the following interpretations", N);
294 Err := Opnd;
295 end if;
297 List_Interps (Nam, Err);
298 end List_Operand_Interps;
300 -- Start of processing for Ambiguous_Operands
302 begin
303 if Nkind (N) in N_Membership_Test then
304 Error_Msg_N ("ambiguous operands for membership", N);
306 elsif Nkind (N) = N_Op_Eq
307 or else Nkind (N) = N_Op_Ne
308 then
309 Error_Msg_N ("ambiguous operands for equality", N);
311 else
312 Error_Msg_N ("ambiguous operands for comparison", N);
313 end if;
315 if All_Errors_Mode then
316 List_Operand_Interps (Left_Opnd (N));
317 List_Operand_Interps (Right_Opnd (N));
318 else
319 Error_Msg_N ("\use -gnatf switch for details", N);
320 end if;
321 end Ambiguous_Operands;
323 -----------------------
324 -- Analyze_Aggregate --
325 -----------------------
327 -- Most of the analysis of Aggregates requires that the type be known,
328 -- and is therefore put off until resolution.
330 procedure Analyze_Aggregate (N : Node_Id) is
331 begin
332 if No (Etype (N)) then
333 Set_Etype (N, Any_Composite);
334 end if;
335 end Analyze_Aggregate;
337 -----------------------
338 -- Analyze_Allocator --
339 -----------------------
341 procedure Analyze_Allocator (N : Node_Id) is
342 Loc : constant Source_Ptr := Sloc (N);
343 Sav_Errs : constant Nat := Serious_Errors_Detected;
344 E : Node_Id := Expression (N);
345 Acc_Type : Entity_Id;
346 Type_Id : Entity_Id;
348 begin
349 Check_Restriction (No_Allocators, N);
351 if Nkind (E) = N_Qualified_Expression then
353 Acc_Type := Create_Itype (E_Allocator_Type, N);
354 Set_Etype (Acc_Type, Acc_Type);
355 Init_Size_Align (Acc_Type);
356 Find_Type (Subtype_Mark (E));
358 -- Analyze the qualified expression, and apply the name resolution
359 -- rule given in 4.7 (3).
361 Analyze (E);
362 Type_Id := Etype (E);
363 Set_Directly_Designated_Type (Acc_Type, Type_Id);
365 Resolve (Expression (E), Type_Id);
367 if Is_Limited_Type (Type_Id)
368 and then Comes_From_Source (N)
369 and then not In_Instance_Body
370 then
371 if not OK_For_Limited_Init (Expression (E)) then
372 Error_Msg_N ("initialization not allowed for limited types", N);
373 Explain_Limited_Type (Type_Id, N);
374 end if;
375 end if;
377 -- A qualified expression requires an exact match of the type,
378 -- class-wide matching is not allowed.
380 -- if Is_Class_Wide_Type (Type_Id)
381 -- and then Base_Type
382 -- (Etype (Expression (E))) /= Base_Type (Type_Id)
383 -- then
384 -- Wrong_Type (Expression (E), Type_Id);
385 -- end if;
387 Check_Non_Static_Context (Expression (E));
389 -- We don't analyze the qualified expression itself because it's
390 -- part of the allocator
392 Set_Etype (E, Type_Id);
394 -- Case where allocator has a subtype indication
396 else
397 declare
398 Def_Id : Entity_Id;
399 Base_Typ : Entity_Id;
401 begin
402 -- If the allocator includes a N_Subtype_Indication then a
403 -- constraint is present, otherwise the node is a subtype mark.
404 -- Introduce an explicit subtype declaration into the tree
405 -- defining some anonymous subtype and rewrite the allocator to
406 -- use this subtype rather than the subtype indication.
408 -- It is important to introduce the explicit subtype declaration
409 -- so that the bounds of the subtype indication are attached to
410 -- the tree in case the allocator is inside a generic unit.
412 if Nkind (E) = N_Subtype_Indication then
414 -- A constraint is only allowed for a composite type in Ada
415 -- 95. In Ada 83, a constraint is also allowed for an
416 -- access-to-composite type, but the constraint is ignored.
418 Find_Type (Subtype_Mark (E));
419 Base_Typ := Entity (Subtype_Mark (E));
421 if Is_Elementary_Type (Base_Typ) then
422 if not (Ada_Version = Ada_83
423 and then Is_Access_Type (Base_Typ))
424 then
425 Error_Msg_N ("constraint not allowed here", E);
427 if Nkind (Constraint (E))
428 = N_Index_Or_Discriminant_Constraint
429 then
430 Error_Msg_N
431 ("\if qualified expression was meant, " &
432 "use apostrophe", Constraint (E));
433 end if;
434 end if;
436 -- Get rid of the bogus constraint:
438 Rewrite (E, New_Copy_Tree (Subtype_Mark (E)));
439 Analyze_Allocator (N);
440 return;
442 -- Ada 2005, AI-363: if the designated type has a constrained
443 -- partial view, it cannot receive a discriminant constraint,
444 -- and the allocated object is unconstrained.
446 elsif Ada_Version >= Ada_05
447 and then Has_Constrained_Partial_View (Base_Typ)
448 then
449 Error_Msg_N
450 ("constraint no allowed when type " &
451 "has a constrained partial view", Constraint (E));
452 end if;
454 if Expander_Active then
455 Def_Id :=
456 Make_Defining_Identifier (Loc, New_Internal_Name ('S'));
458 Insert_Action (E,
459 Make_Subtype_Declaration (Loc,
460 Defining_Identifier => Def_Id,
461 Subtype_Indication => Relocate_Node (E)));
463 if Sav_Errs /= Serious_Errors_Detected
464 and then Nkind (Constraint (E))
465 = N_Index_Or_Discriminant_Constraint
466 then
467 Error_Msg_N
468 ("if qualified expression was meant, " &
469 "use apostrophe!", Constraint (E));
470 end if;
472 E := New_Occurrence_Of (Def_Id, Loc);
473 Rewrite (Expression (N), E);
474 end if;
475 end if;
477 Type_Id := Process_Subtype (E, N);
478 Acc_Type := Create_Itype (E_Allocator_Type, N);
479 Set_Etype (Acc_Type, Acc_Type);
480 Init_Size_Align (Acc_Type);
481 Set_Directly_Designated_Type (Acc_Type, Type_Id);
482 Check_Fully_Declared (Type_Id, N);
484 -- Ada 2005 (AI-231)
486 if Can_Never_Be_Null (Type_Id) then
487 Error_Msg_N ("(Ada 2005) qualified expression required",
488 Expression (N));
489 end if;
491 -- Check restriction against dynamically allocated protected
492 -- objects. Note that when limited aggregates are supported,
493 -- a similar test should be applied to an allocator with a
494 -- qualified expression ???
496 if Is_Protected_Type (Type_Id) then
497 Check_Restriction (No_Protected_Type_Allocators, N);
498 end if;
500 -- Check for missing initialization. Skip this check if we already
501 -- had errors on analyzing the allocator, since in that case these
502 -- are probably cascaded errors
504 if Is_Indefinite_Subtype (Type_Id)
505 and then Serious_Errors_Detected = Sav_Errs
506 then
507 if Is_Class_Wide_Type (Type_Id) then
508 Error_Msg_N
509 ("initialization required in class-wide allocation", N);
510 else
511 Error_Msg_N
512 ("initialization required in unconstrained allocation", N);
513 end if;
514 end if;
515 end;
516 end if;
518 if Is_Abstract_Type (Type_Id) then
519 Error_Msg_N ("cannot allocate abstract object", E);
520 end if;
522 if Has_Task (Designated_Type (Acc_Type)) then
523 Check_Restriction (No_Tasking, N);
524 Check_Restriction (Max_Tasks, N);
525 Check_Restriction (No_Task_Allocators, N);
526 end if;
528 -- If the No_Streams restriction is set, check that the type of the
529 -- object is not, and does not contain, any subtype derived from
530 -- Ada.Streams.Root_Stream_Type. Note that we guard the call to
531 -- Has_Stream just for efficiency reasons. There is no point in
532 -- spending time on a Has_Stream check if the restriction is not set.
534 if Restrictions.Set (No_Streams) then
535 if Has_Stream (Designated_Type (Acc_Type)) then
536 Check_Restriction (No_Streams, N);
537 end if;
538 end if;
540 Set_Etype (N, Acc_Type);
542 if not Is_Library_Level_Entity (Acc_Type) then
543 Check_Restriction (No_Local_Allocators, N);
544 end if;
546 if Serious_Errors_Detected > Sav_Errs then
547 Set_Error_Posted (N);
548 Set_Etype (N, Any_Type);
549 end if;
550 end Analyze_Allocator;
552 ---------------------------
553 -- Analyze_Arithmetic_Op --
554 ---------------------------
556 procedure Analyze_Arithmetic_Op (N : Node_Id) is
557 L : constant Node_Id := Left_Opnd (N);
558 R : constant Node_Id := Right_Opnd (N);
559 Op_Id : Entity_Id;
561 begin
562 Candidate_Type := Empty;
563 Analyze_Expression (L);
564 Analyze_Expression (R);
566 -- If the entity is already set, the node is the instantiation of
567 -- a generic node with a non-local reference, or was manufactured
568 -- by a call to Make_Op_xxx. In either case the entity is known to
569 -- be valid, and we do not need to collect interpretations, instead
570 -- we just get the single possible interpretation.
572 Op_Id := Entity (N);
574 if Present (Op_Id) then
575 if Ekind (Op_Id) = E_Operator then
577 if (Nkind (N) = N_Op_Divide or else
578 Nkind (N) = N_Op_Mod or else
579 Nkind (N) = N_Op_Multiply or else
580 Nkind (N) = N_Op_Rem)
581 and then Treat_Fixed_As_Integer (N)
582 then
583 null;
584 else
585 Set_Etype (N, Any_Type);
586 Find_Arithmetic_Types (L, R, Op_Id, N);
587 end if;
589 else
590 Set_Etype (N, Any_Type);
591 Add_One_Interp (N, Op_Id, Etype (Op_Id));
592 end if;
594 -- Entity is not already set, so we do need to collect interpretations
596 else
597 Op_Id := Get_Name_Entity_Id (Chars (N));
598 Set_Etype (N, Any_Type);
600 while Present (Op_Id) loop
601 if Ekind (Op_Id) = E_Operator
602 and then Present (Next_Entity (First_Entity (Op_Id)))
603 then
604 Find_Arithmetic_Types (L, R, Op_Id, N);
606 -- The following may seem superfluous, because an operator cannot
607 -- be generic, but this ignores the cleverness of the author of
608 -- ACVC bc1013a.
610 elsif Is_Overloadable (Op_Id) then
611 Analyze_User_Defined_Binary_Op (N, Op_Id);
612 end if;
614 Op_Id := Homonym (Op_Id);
615 end loop;
616 end if;
618 Operator_Check (N);
619 end Analyze_Arithmetic_Op;
621 ------------------
622 -- Analyze_Call --
623 ------------------
625 -- Function, procedure, and entry calls are checked here. The Name in
626 -- the call may be overloaded. The actuals have been analyzed and may
627 -- themselves be overloaded. On exit from this procedure, the node N
628 -- may have zero, one or more interpretations. In the first case an
629 -- error message is produced. In the last case, the node is flagged
630 -- as overloaded and the interpretations are collected in All_Interp.
632 -- If the name is an Access_To_Subprogram, it cannot be overloaded, but
633 -- the type-checking is similar to that of other calls.
635 procedure Analyze_Call (N : Node_Id) is
636 Actuals : constant List_Id := Parameter_Associations (N);
637 Nam : Node_Id := Name (N);
638 X : Interp_Index;
639 It : Interp;
640 Nam_Ent : Entity_Id;
641 Success : Boolean := False;
643 function Name_Denotes_Function return Boolean;
644 -- If the type of the name is an access to subprogram, this may be
645 -- the type of a name, or the return type of the function being called.
646 -- If the name is not an entity then it can denote a protected function.
647 -- Until we distinguish Etype from Return_Type, we must use this
648 -- routine to resolve the meaning of the name in the call.
650 ---------------------------
651 -- Name_Denotes_Function --
652 ---------------------------
654 function Name_Denotes_Function return Boolean is
655 begin
656 if Is_Entity_Name (Nam) then
657 return Ekind (Entity (Nam)) = E_Function;
659 elsif Nkind (Nam) = N_Selected_Component then
660 return Ekind (Entity (Selector_Name (Nam))) = E_Function;
662 else
663 return False;
664 end if;
665 end Name_Denotes_Function;
667 -- Start of processing for Analyze_Call
669 begin
670 -- Initialize the type of the result of the call to the error type,
671 -- which will be reset if the type is successfully resolved.
673 Set_Etype (N, Any_Type);
675 if not Is_Overloaded (Nam) then
677 -- Only one interpretation to check
679 if Ekind (Etype (Nam)) = E_Subprogram_Type then
680 Nam_Ent := Etype (Nam);
682 -- If the prefix is an access_to_subprogram, this may be an indirect
683 -- call. This is the case if the name in the call is not an entity
684 -- name, or if it is a function name in the context of a procedure
685 -- call. In this latter case, we have a call to a parameterless
686 -- function that returns a pointer_to_procedure which is the entity
687 -- being called.
689 elsif Is_Access_Type (Etype (Nam))
690 and then Ekind (Designated_Type (Etype (Nam))) = E_Subprogram_Type
691 and then
692 (not Name_Denotes_Function
693 or else Nkind (N) = N_Procedure_Call_Statement)
694 then
695 Nam_Ent := Designated_Type (Etype (Nam));
696 Insert_Explicit_Dereference (Nam);
698 -- Selected component case. Simple entry or protected operation,
699 -- where the entry name is given by the selector name.
701 elsif Nkind (Nam) = N_Selected_Component then
702 Nam_Ent := Entity (Selector_Name (Nam));
704 if Ekind (Nam_Ent) /= E_Entry
705 and then Ekind (Nam_Ent) /= E_Entry_Family
706 and then Ekind (Nam_Ent) /= E_Function
707 and then Ekind (Nam_Ent) /= E_Procedure
708 then
709 Error_Msg_N ("name in call is not a callable entity", Nam);
710 Set_Etype (N, Any_Type);
711 return;
712 end if;
714 -- If the name is an Indexed component, it can be a call to a member
715 -- of an entry family. The prefix must be a selected component whose
716 -- selector is the entry. Analyze_Procedure_Call normalizes several
717 -- kinds of call into this form.
719 elsif Nkind (Nam) = N_Indexed_Component then
721 if Nkind (Prefix (Nam)) = N_Selected_Component then
722 Nam_Ent := Entity (Selector_Name (Prefix (Nam)));
723 else
724 Error_Msg_N ("name in call is not a callable entity", Nam);
725 Set_Etype (N, Any_Type);
726 return;
727 end if;
729 elsif not Is_Entity_Name (Nam) then
730 Error_Msg_N ("name in call is not a callable entity", Nam);
731 Set_Etype (N, Any_Type);
732 return;
734 else
735 Nam_Ent := Entity (Nam);
737 -- If no interpretations, give error message
739 if not Is_Overloadable (Nam_Ent) then
740 declare
741 L : constant Boolean := Is_List_Member (N);
742 K : constant Node_Kind := Nkind (Parent (N));
744 begin
745 -- If the node is in a list whose parent is not an
746 -- expression then it must be an attempted procedure call.
748 if L and then K not in N_Subexpr then
749 if Ekind (Entity (Nam)) = E_Generic_Procedure then
750 Error_Msg_NE
751 ("must instantiate generic procedure& before call",
752 Nam, Entity (Nam));
753 else
754 Error_Msg_N
755 ("procedure or entry name expected", Nam);
756 end if;
758 -- Check for tasking cases where only an entry call will do
760 elsif not L
761 and then (K = N_Entry_Call_Alternative
762 or else K = N_Triggering_Alternative)
763 then
764 Error_Msg_N ("entry name expected", Nam);
766 -- Otherwise give general error message
768 else
769 Error_Msg_N ("invalid prefix in call", Nam);
770 end if;
772 return;
773 end;
774 end if;
775 end if;
777 Analyze_One_Call (N, Nam_Ent, True, Success);
779 -- If this is an indirect call, the return type of the access_to
780 -- subprogram may be an incomplete type. At the point of the call,
781 -- use the full type if available, and at the same time update
782 -- the return type of the access_to_subprogram.
784 if Success
785 and then Nkind (Nam) = N_Explicit_Dereference
786 and then Ekind (Etype (N)) = E_Incomplete_Type
787 and then Present (Full_View (Etype (N)))
788 then
789 Set_Etype (N, Full_View (Etype (N)));
790 Set_Etype (Nam_Ent, Etype (N));
791 end if;
793 else
794 -- An overloaded selected component must denote overloaded
795 -- operations of a concurrent type. The interpretations are
796 -- attached to the simple name of those operations.
798 if Nkind (Nam) = N_Selected_Component then
799 Nam := Selector_Name (Nam);
800 end if;
802 Get_First_Interp (Nam, X, It);
804 while Present (It.Nam) loop
805 Nam_Ent := It.Nam;
807 -- Name may be call that returns an access to subprogram, or more
808 -- generally an overloaded expression one of whose interpretations
809 -- yields an access to subprogram. If the name is an entity, we
810 -- do not dereference, because the node is a call that returns
811 -- the access type: note difference between f(x), where the call
812 -- may return an access subprogram type, and f(x)(y), where the
813 -- type returned by the call to f is implicitly dereferenced to
814 -- analyze the outer call.
816 if Is_Access_Type (Nam_Ent) then
817 Nam_Ent := Designated_Type (Nam_Ent);
819 elsif Is_Access_Type (Etype (Nam_Ent))
820 and then not Is_Entity_Name (Nam)
821 and then Ekind (Designated_Type (Etype (Nam_Ent)))
822 = E_Subprogram_Type
823 then
824 Nam_Ent := Designated_Type (Etype (Nam_Ent));
825 end if;
827 Analyze_One_Call (N, Nam_Ent, False, Success);
829 -- If the interpretation succeeds, mark the proper type of the
830 -- prefix (any valid candidate will do). If not, remove the
831 -- candidate interpretation. This only needs to be done for
832 -- overloaded protected operations, for other entities disambi-
833 -- guation is done directly in Resolve.
835 if Success then
836 Set_Etype (Nam, It.Typ);
838 elsif Nkind (Name (N)) = N_Selected_Component
839 or else Nkind (Name (N)) = N_Function_Call
840 then
841 Remove_Interp (X);
842 end if;
844 Get_Next_Interp (X, It);
845 end loop;
847 -- If the name is the result of a function call, it can only
848 -- be a call to a function returning an access to subprogram.
849 -- Insert explicit dereference.
851 if Nkind (Nam) = N_Function_Call then
852 Insert_Explicit_Dereference (Nam);
853 end if;
855 if Etype (N) = Any_Type then
857 -- None of the interpretations is compatible with the actuals
859 Diagnose_Call (N, Nam);
861 -- Special checks for uninstantiated put routines
863 if Nkind (N) = N_Procedure_Call_Statement
864 and then Is_Entity_Name (Nam)
865 and then Chars (Nam) = Name_Put
866 and then List_Length (Actuals) = 1
867 then
868 declare
869 Arg : constant Node_Id := First (Actuals);
870 Typ : Entity_Id;
872 begin
873 if Nkind (Arg) = N_Parameter_Association then
874 Typ := Etype (Explicit_Actual_Parameter (Arg));
875 else
876 Typ := Etype (Arg);
877 end if;
879 if Is_Signed_Integer_Type (Typ) then
880 Error_Msg_N
881 ("possible missing instantiation of " &
882 "'Text_'I'O.'Integer_'I'O!", Nam);
884 elsif Is_Modular_Integer_Type (Typ) then
885 Error_Msg_N
886 ("possible missing instantiation of " &
887 "'Text_'I'O.'Modular_'I'O!", Nam);
889 elsif Is_Floating_Point_Type (Typ) then
890 Error_Msg_N
891 ("possible missing instantiation of " &
892 "'Text_'I'O.'Float_'I'O!", Nam);
894 elsif Is_Ordinary_Fixed_Point_Type (Typ) then
895 Error_Msg_N
896 ("possible missing instantiation of " &
897 "'Text_'I'O.'Fixed_'I'O!", Nam);
899 elsif Is_Decimal_Fixed_Point_Type (Typ) then
900 Error_Msg_N
901 ("possible missing instantiation of " &
902 "'Text_'I'O.'Decimal_'I'O!", Nam);
904 elsif Is_Enumeration_Type (Typ) then
905 Error_Msg_N
906 ("possible missing instantiation of " &
907 "'Text_'I'O.'Enumeration_'I'O!", Nam);
908 end if;
909 end;
910 end if;
912 elsif not Is_Overloaded (N)
913 and then Is_Entity_Name (Nam)
914 then
915 -- Resolution yields a single interpretation. Verify that the
916 -- reference has capitalization consistent with the declaration.
918 Set_Entity_With_Style_Check (Nam, Entity (Nam));
919 Generate_Reference (Entity (Nam), Nam);
921 Set_Etype (Nam, Etype (Entity (Nam)));
922 else
923 Remove_Abstract_Operations (N);
924 end if;
926 End_Interp_List;
927 end if;
929 -- Check for not-yet-implemented cases of AI-318. We only need to check
930 -- for inherently limited types, because other limited types will be
931 -- returned by copy, which works just fine.
932 -- If the context is an attribute reference 'Class, this is really a
933 -- type conversion, which is illegal, and will be caught elsewhere.
935 if Ada_Version >= Ada_05
936 and then not Debug_Flag_Dot_L
937 and then Is_Inherently_Limited_Type (Etype (N))
938 and then (Nkind (Parent (N)) = N_Selected_Component
939 or else Nkind (Parent (N)) = N_Indexed_Component
940 or else Nkind (Parent (N)) = N_Slice
941 or else
942 (Nkind (Parent (N)) = N_Attribute_Reference
943 and then Attribute_Name (Parent (N)) /= Name_Class))
944 then
945 Error_Msg_N ("(Ada 2005) limited function call in this context" &
946 " is not yet implemented", N);
947 end if;
948 end Analyze_Call;
950 ---------------------------
951 -- Analyze_Comparison_Op --
952 ---------------------------
954 procedure Analyze_Comparison_Op (N : Node_Id) is
955 L : constant Node_Id := Left_Opnd (N);
956 R : constant Node_Id := Right_Opnd (N);
957 Op_Id : Entity_Id := Entity (N);
959 begin
960 Set_Etype (N, Any_Type);
961 Candidate_Type := Empty;
963 Analyze_Expression (L);
964 Analyze_Expression (R);
966 if Present (Op_Id) then
967 if Ekind (Op_Id) = E_Operator then
968 Find_Comparison_Types (L, R, Op_Id, N);
969 else
970 Add_One_Interp (N, Op_Id, Etype (Op_Id));
971 end if;
973 if Is_Overloaded (L) then
974 Set_Etype (L, Intersect_Types (L, R));
975 end if;
977 else
978 Op_Id := Get_Name_Entity_Id (Chars (N));
979 while Present (Op_Id) loop
980 if Ekind (Op_Id) = E_Operator then
981 Find_Comparison_Types (L, R, Op_Id, N);
982 else
983 Analyze_User_Defined_Binary_Op (N, Op_Id);
984 end if;
986 Op_Id := Homonym (Op_Id);
987 end loop;
988 end if;
990 Operator_Check (N);
991 end Analyze_Comparison_Op;
993 ---------------------------
994 -- Analyze_Concatenation --
995 ---------------------------
997 -- If the only one-dimensional array type in scope is String,
998 -- this is the resulting type of the operation. Otherwise there
999 -- will be a concatenation operation defined for each user-defined
1000 -- one-dimensional array.
1002 procedure Analyze_Concatenation (N : Node_Id) is
1003 L : constant Node_Id := Left_Opnd (N);
1004 R : constant Node_Id := Right_Opnd (N);
1005 Op_Id : Entity_Id := Entity (N);
1006 LT : Entity_Id;
1007 RT : Entity_Id;
1009 begin
1010 Set_Etype (N, Any_Type);
1011 Candidate_Type := Empty;
1013 Analyze_Expression (L);
1014 Analyze_Expression (R);
1016 -- If the entity is present, the node appears in an instance, and
1017 -- denotes a predefined concatenation operation. The resulting type is
1018 -- obtained from the arguments when possible. If the arguments are
1019 -- aggregates, the array type and the concatenation type must be
1020 -- visible.
1022 if Present (Op_Id) then
1023 if Ekind (Op_Id) = E_Operator then
1025 LT := Base_Type (Etype (L));
1026 RT := Base_Type (Etype (R));
1028 if Is_Array_Type (LT)
1029 and then (RT = LT or else RT = Base_Type (Component_Type (LT)))
1030 then
1031 Add_One_Interp (N, Op_Id, LT);
1033 elsif Is_Array_Type (RT)
1034 and then LT = Base_Type (Component_Type (RT))
1035 then
1036 Add_One_Interp (N, Op_Id, RT);
1038 -- If one operand is a string type or a user-defined array type,
1039 -- and the other is a literal, result is of the specific type.
1041 elsif
1042 (Root_Type (LT) = Standard_String
1043 or else Scope (LT) /= Standard_Standard)
1044 and then Etype (R) = Any_String
1045 then
1046 Add_One_Interp (N, Op_Id, LT);
1048 elsif
1049 (Root_Type (RT) = Standard_String
1050 or else Scope (RT) /= Standard_Standard)
1051 and then Etype (L) = Any_String
1052 then
1053 Add_One_Interp (N, Op_Id, RT);
1055 elsif not Is_Generic_Type (Etype (Op_Id)) then
1056 Add_One_Interp (N, Op_Id, Etype (Op_Id));
1058 else
1059 -- Type and its operations must be visible
1061 Set_Entity (N, Empty);
1062 Analyze_Concatenation (N);
1063 end if;
1065 else
1066 Add_One_Interp (N, Op_Id, Etype (Op_Id));
1067 end if;
1069 else
1070 Op_Id := Get_Name_Entity_Id (Name_Op_Concat);
1071 while Present (Op_Id) loop
1072 if Ekind (Op_Id) = E_Operator then
1074 -- Do not consider operators declared in dead code, they can
1075 -- not be part of the resolution.
1077 if Is_Eliminated (Op_Id) then
1078 null;
1079 else
1080 Find_Concatenation_Types (L, R, Op_Id, N);
1081 end if;
1083 else
1084 Analyze_User_Defined_Binary_Op (N, Op_Id);
1085 end if;
1087 Op_Id := Homonym (Op_Id);
1088 end loop;
1089 end if;
1091 Operator_Check (N);
1092 end Analyze_Concatenation;
1094 ------------------------------------
1095 -- Analyze_Conditional_Expression --
1096 ------------------------------------
1098 procedure Analyze_Conditional_Expression (N : Node_Id) is
1099 Condition : constant Node_Id := First (Expressions (N));
1100 Then_Expr : constant Node_Id := Next (Condition);
1101 Else_Expr : constant Node_Id := Next (Then_Expr);
1102 begin
1103 Analyze_Expression (Condition);
1104 Analyze_Expression (Then_Expr);
1105 Analyze_Expression (Else_Expr);
1106 Set_Etype (N, Etype (Then_Expr));
1107 end Analyze_Conditional_Expression;
1109 -------------------------
1110 -- Analyze_Equality_Op --
1111 -------------------------
1113 procedure Analyze_Equality_Op (N : Node_Id) is
1114 Loc : constant Source_Ptr := Sloc (N);
1115 L : constant Node_Id := Left_Opnd (N);
1116 R : constant Node_Id := Right_Opnd (N);
1117 Op_Id : Entity_Id;
1119 begin
1120 Set_Etype (N, Any_Type);
1121 Candidate_Type := Empty;
1123 Analyze_Expression (L);
1124 Analyze_Expression (R);
1126 -- If the entity is set, the node is a generic instance with a non-local
1127 -- reference to the predefined operator or to a user-defined function.
1128 -- It can also be an inequality that is expanded into the negation of a
1129 -- call to a user-defined equality operator.
1131 -- For the predefined case, the result is Boolean, regardless of the
1132 -- type of the operands. The operands may even be limited, if they are
1133 -- generic actuals. If they are overloaded, label the left argument with
1134 -- the common type that must be present, or with the type of the formal
1135 -- of the user-defined function.
1137 if Present (Entity (N)) then
1138 Op_Id := Entity (N);
1140 if Ekind (Op_Id) = E_Operator then
1141 Add_One_Interp (N, Op_Id, Standard_Boolean);
1142 else
1143 Add_One_Interp (N, Op_Id, Etype (Op_Id));
1144 end if;
1146 if Is_Overloaded (L) then
1147 if Ekind (Op_Id) = E_Operator then
1148 Set_Etype (L, Intersect_Types (L, R));
1149 else
1150 Set_Etype (L, Etype (First_Formal (Op_Id)));
1151 end if;
1152 end if;
1154 else
1155 Op_Id := Get_Name_Entity_Id (Chars (N));
1156 while Present (Op_Id) loop
1157 if Ekind (Op_Id) = E_Operator then
1158 Find_Equality_Types (L, R, Op_Id, N);
1159 else
1160 Analyze_User_Defined_Binary_Op (N, Op_Id);
1161 end if;
1163 Op_Id := Homonym (Op_Id);
1164 end loop;
1165 end if;
1167 -- If there was no match, and the operator is inequality, this may
1168 -- be a case where inequality has not been made explicit, as for
1169 -- tagged types. Analyze the node as the negation of an equality
1170 -- operation. This cannot be done earlier, because before analysis
1171 -- we cannot rule out the presence of an explicit inequality.
1173 if Etype (N) = Any_Type
1174 and then Nkind (N) = N_Op_Ne
1175 then
1176 Op_Id := Get_Name_Entity_Id (Name_Op_Eq);
1177 while Present (Op_Id) loop
1178 if Ekind (Op_Id) = E_Operator then
1179 Find_Equality_Types (L, R, Op_Id, N);
1180 else
1181 Analyze_User_Defined_Binary_Op (N, Op_Id);
1182 end if;
1184 Op_Id := Homonym (Op_Id);
1185 end loop;
1187 if Etype (N) /= Any_Type then
1188 Op_Id := Entity (N);
1190 Rewrite (N,
1191 Make_Op_Not (Loc,
1192 Right_Opnd =>
1193 Make_Op_Eq (Loc,
1194 Left_Opnd => Left_Opnd (N),
1195 Right_Opnd => Right_Opnd (N))));
1197 Set_Entity (Right_Opnd (N), Op_Id);
1198 Analyze (N);
1199 end if;
1200 end if;
1202 Operator_Check (N);
1203 end Analyze_Equality_Op;
1205 ----------------------------------
1206 -- Analyze_Explicit_Dereference --
1207 ----------------------------------
1209 procedure Analyze_Explicit_Dereference (N : Node_Id) is
1210 Loc : constant Source_Ptr := Sloc (N);
1211 P : constant Node_Id := Prefix (N);
1212 T : Entity_Id;
1213 I : Interp_Index;
1214 It : Interp;
1215 New_N : Node_Id;
1217 function Is_Function_Type return Boolean;
1218 -- Check whether node may be interpreted as an implicit function call
1220 ----------------------
1221 -- Is_Function_Type --
1222 ----------------------
1224 function Is_Function_Type return Boolean is
1225 I : Interp_Index;
1226 It : Interp;
1228 begin
1229 if not Is_Overloaded (N) then
1230 return Ekind (Base_Type (Etype (N))) = E_Subprogram_Type
1231 and then Etype (Base_Type (Etype (N))) /= Standard_Void_Type;
1233 else
1234 Get_First_Interp (N, I, It);
1235 while Present (It.Nam) loop
1236 if Ekind (Base_Type (It.Typ)) /= E_Subprogram_Type
1237 or else Etype (Base_Type (It.Typ)) = Standard_Void_Type
1238 then
1239 return False;
1240 end if;
1242 Get_Next_Interp (I, It);
1243 end loop;
1245 return True;
1246 end if;
1247 end Is_Function_Type;
1249 -- Start of processing for Analyze_Explicit_Dereference
1251 begin
1252 Analyze (P);
1253 Set_Etype (N, Any_Type);
1255 -- Test for remote access to subprogram type, and if so return
1256 -- after rewriting the original tree.
1258 if Remote_AST_E_Dereference (P) then
1259 return;
1260 end if;
1262 -- Normal processing for other than remote access to subprogram type
1264 if not Is_Overloaded (P) then
1265 if Is_Access_Type (Etype (P)) then
1267 -- Set the Etype. We need to go thru Is_For_Access_Subtypes to
1268 -- avoid other problems caused by the Private_Subtype and it is
1269 -- safe to go to the Base_Type because this is the same as
1270 -- converting the access value to its Base_Type.
1272 declare
1273 DT : Entity_Id := Designated_Type (Etype (P));
1275 begin
1276 if Ekind (DT) = E_Private_Subtype
1277 and then Is_For_Access_Subtype (DT)
1278 then
1279 DT := Base_Type (DT);
1280 end if;
1282 -- An explicit dereference is a legal occurrence of an
1283 -- incomplete type imported through a limited_with clause,
1284 -- if the full view is visible.
1286 if From_With_Type (DT)
1287 and then not From_With_Type (Scope (DT))
1288 and then
1289 (Is_Immediately_Visible (Scope (DT))
1290 or else
1291 (Is_Child_Unit (Scope (DT))
1292 and then Is_Visible_Child_Unit (Scope (DT))))
1293 then
1294 Set_Etype (N, Available_View (DT));
1296 else
1297 Set_Etype (N, DT);
1298 end if;
1299 end;
1301 elsif Etype (P) /= Any_Type then
1302 Error_Msg_N ("prefix of dereference must be an access type", N);
1303 return;
1304 end if;
1306 else
1307 Get_First_Interp (P, I, It);
1308 while Present (It.Nam) loop
1309 T := It.Typ;
1311 if Is_Access_Type (T) then
1312 Add_One_Interp (N, Designated_Type (T), Designated_Type (T));
1313 end if;
1315 Get_Next_Interp (I, It);
1316 end loop;
1318 -- Error if no interpretation of the prefix has an access type
1320 if Etype (N) = Any_Type then
1321 Error_Msg_N
1322 ("access type required in prefix of explicit dereference", P);
1323 Set_Etype (N, Any_Type);
1324 return;
1325 end if;
1326 end if;
1328 if Is_Function_Type
1329 and then Nkind (Parent (N)) /= N_Indexed_Component
1331 and then (Nkind (Parent (N)) /= N_Function_Call
1332 or else N /= Name (Parent (N)))
1334 and then (Nkind (Parent (N)) /= N_Procedure_Call_Statement
1335 or else N /= Name (Parent (N)))
1337 and then Nkind (Parent (N)) /= N_Subprogram_Renaming_Declaration
1338 and then (Nkind (Parent (N)) /= N_Attribute_Reference
1339 or else
1340 (Attribute_Name (Parent (N)) /= Name_Address
1341 and then
1342 Attribute_Name (Parent (N)) /= Name_Access))
1343 then
1344 -- Name is a function call with no actuals, in a context that
1345 -- requires deproceduring (including as an actual in an enclosing
1346 -- function or procedure call). There are some pathological cases
1347 -- where the prefix might include functions that return access to
1348 -- subprograms and others that return a regular type. Disambiguation
1349 -- of those has to take place in Resolve.
1350 -- See e.g. 7117-014 and E317-001.
1352 New_N :=
1353 Make_Function_Call (Loc,
1354 Name => Make_Explicit_Dereference (Loc, P),
1355 Parameter_Associations => New_List);
1357 -- If the prefix is overloaded, remove operations that have formals,
1358 -- we know that this is a parameterless call.
1360 if Is_Overloaded (P) then
1361 Get_First_Interp (P, I, It);
1362 while Present (It.Nam) loop
1363 T := It.Typ;
1365 if No (First_Formal (Base_Type (Designated_Type (T)))) then
1366 Set_Etype (P, T);
1367 else
1368 Remove_Interp (I);
1369 end if;
1371 Get_Next_Interp (I, It);
1372 end loop;
1373 end if;
1375 Rewrite (N, New_N);
1376 Analyze (N);
1378 elsif not Is_Function_Type
1379 and then Is_Overloaded (N)
1380 then
1381 -- The prefix may include access to subprograms and other access
1382 -- types. If the context selects the interpretation that is a call,
1383 -- we cannot rewrite the node yet, but we include the result of
1384 -- the call interpretation.
1386 Get_First_Interp (N, I, It);
1387 while Present (It.Nam) loop
1388 if Ekind (Base_Type (It.Typ)) = E_Subprogram_Type
1389 and then Etype (Base_Type (It.Typ)) /= Standard_Void_Type
1390 then
1391 Add_One_Interp (N, Etype (It.Typ), Etype (It.Typ));
1392 end if;
1394 Get_Next_Interp (I, It);
1395 end loop;
1396 end if;
1398 -- A value of remote access-to-class-wide must not be dereferenced
1399 -- (RM E.2.2(16)).
1401 Validate_Remote_Access_To_Class_Wide_Type (N);
1402 end Analyze_Explicit_Dereference;
1404 ------------------------
1405 -- Analyze_Expression --
1406 ------------------------
1408 procedure Analyze_Expression (N : Node_Id) is
1409 begin
1410 Analyze (N);
1411 Check_Parameterless_Call (N);
1412 end Analyze_Expression;
1414 ------------------------------------
1415 -- Analyze_Indexed_Component_Form --
1416 ------------------------------------
1418 procedure Analyze_Indexed_Component_Form (N : Node_Id) is
1419 P : constant Node_Id := Prefix (N);
1420 Exprs : constant List_Id := Expressions (N);
1421 Exp : Node_Id;
1422 P_T : Entity_Id;
1423 E : Node_Id;
1424 U_N : Entity_Id;
1426 procedure Process_Function_Call;
1427 -- Prefix in indexed component form is an overloadable entity,
1428 -- so the node is a function call. Reformat it as such.
1430 procedure Process_Indexed_Component;
1431 -- Prefix in indexed component form is actually an indexed component.
1432 -- This routine processes it, knowing that the prefix is already
1433 -- resolved.
1435 procedure Process_Indexed_Component_Or_Slice;
1436 -- An indexed component with a single index may designate a slice if
1437 -- the index is a subtype mark. This routine disambiguates these two
1438 -- cases by resolving the prefix to see if it is a subtype mark.
1440 procedure Process_Overloaded_Indexed_Component;
1441 -- If the prefix of an indexed component is overloaded, the proper
1442 -- interpretation is selected by the index types and the context.
1444 ---------------------------
1445 -- Process_Function_Call --
1446 ---------------------------
1448 procedure Process_Function_Call is
1449 Actual : Node_Id;
1451 begin
1452 Change_Node (N, N_Function_Call);
1453 Set_Name (N, P);
1454 Set_Parameter_Associations (N, Exprs);
1456 -- Analyze actuals prior to analyzing the call itself
1458 Actual := First (Parameter_Associations (N));
1459 while Present (Actual) loop
1460 Analyze (Actual);
1461 Check_Parameterless_Call (Actual);
1463 -- Move to next actual. Note that we use Next, not Next_Actual
1464 -- here. The reason for this is a bit subtle. If a function call
1465 -- includes named associations, the parser recognizes the node as
1466 -- a call, and it is analyzed as such. If all associations are
1467 -- positional, the parser builds an indexed_component node, and
1468 -- it is only after analysis of the prefix that the construct
1469 -- is recognized as a call, in which case Process_Function_Call
1470 -- rewrites the node and analyzes the actuals. If the list of
1471 -- actuals is malformed, the parser may leave the node as an
1472 -- indexed component (despite the presence of named associations).
1473 -- The iterator Next_Actual is equivalent to Next if the list is
1474 -- positional, but follows the normalized chain of actuals when
1475 -- named associations are present. In this case normalization has
1476 -- not taken place, and actuals remain unanalyzed, which leads to
1477 -- subsequent crashes or loops if there is an attempt to continue
1478 -- analysis of the program.
1480 Next (Actual);
1481 end loop;
1483 Analyze_Call (N);
1484 end Process_Function_Call;
1486 -------------------------------
1487 -- Process_Indexed_Component --
1488 -------------------------------
1490 procedure Process_Indexed_Component is
1491 Exp : Node_Id;
1492 Array_Type : Entity_Id;
1493 Index : Node_Id;
1494 Pent : Entity_Id := Empty;
1496 begin
1497 Exp := First (Exprs);
1499 if Is_Overloaded (P) then
1500 Process_Overloaded_Indexed_Component;
1502 else
1503 Array_Type := Etype (P);
1505 if Is_Entity_Name (P) then
1506 Pent := Entity (P);
1507 elsif Nkind (P) = N_Selected_Component
1508 and then Is_Entity_Name (Selector_Name (P))
1509 then
1510 Pent := Entity (Selector_Name (P));
1511 end if;
1513 -- Prefix must be appropriate for an array type, taking into
1514 -- account a possible implicit dereference.
1516 if Is_Access_Type (Array_Type) then
1517 Array_Type := Designated_Type (Array_Type);
1518 Error_Msg_NW (Warn_On_Dereference, "?implicit dereference", N);
1519 Process_Implicit_Dereference_Prefix (Pent, P);
1520 end if;
1522 if Is_Array_Type (Array_Type) then
1523 null;
1525 elsif Present (Pent) and then Ekind (Pent) = E_Entry_Family then
1526 Analyze (Exp);
1527 Set_Etype (N, Any_Type);
1529 if not Has_Compatible_Type
1530 (Exp, Entry_Index_Type (Pent))
1531 then
1532 Error_Msg_N ("invalid index type in entry name", N);
1534 elsif Present (Next (Exp)) then
1535 Error_Msg_N ("too many subscripts in entry reference", N);
1537 else
1538 Set_Etype (N, Etype (P));
1539 end if;
1541 return;
1543 elsif Is_Record_Type (Array_Type)
1544 and then Remote_AST_I_Dereference (P)
1545 then
1546 return;
1548 elsif Array_Type = Any_Type then
1549 Set_Etype (N, Any_Type);
1550 return;
1552 -- Here we definitely have a bad indexing
1554 else
1555 if Nkind (Parent (N)) = N_Requeue_Statement
1556 and then Present (Pent) and then Ekind (Pent) = E_Entry
1557 then
1558 Error_Msg_N
1559 ("REQUEUE does not permit parameters", First (Exprs));
1561 elsif Is_Entity_Name (P)
1562 and then Etype (P) = Standard_Void_Type
1563 then
1564 Error_Msg_NE ("incorrect use of&", P, Entity (P));
1566 else
1567 Error_Msg_N ("array type required in indexed component", P);
1568 end if;
1570 Set_Etype (N, Any_Type);
1571 return;
1572 end if;
1574 Index := First_Index (Array_Type);
1575 while Present (Index) and then Present (Exp) loop
1576 if not Has_Compatible_Type (Exp, Etype (Index)) then
1577 Wrong_Type (Exp, Etype (Index));
1578 Set_Etype (N, Any_Type);
1579 return;
1580 end if;
1582 Next_Index (Index);
1583 Next (Exp);
1584 end loop;
1586 Set_Etype (N, Component_Type (Array_Type));
1588 if Present (Index) then
1589 Error_Msg_N
1590 ("too few subscripts in array reference", First (Exprs));
1592 elsif Present (Exp) then
1593 Error_Msg_N ("too many subscripts in array reference", Exp);
1594 end if;
1595 end if;
1596 end Process_Indexed_Component;
1598 ----------------------------------------
1599 -- Process_Indexed_Component_Or_Slice --
1600 ----------------------------------------
1602 procedure Process_Indexed_Component_Or_Slice is
1603 begin
1604 Exp := First (Exprs);
1605 while Present (Exp) loop
1606 Analyze_Expression (Exp);
1607 Next (Exp);
1608 end loop;
1610 Exp := First (Exprs);
1612 -- If one index is present, and it is a subtype name, then the
1613 -- node denotes a slice (note that the case of an explicit range
1614 -- for a slice was already built as an N_Slice node in the first
1615 -- place, so that case is not handled here).
1617 -- We use a replace rather than a rewrite here because this is one
1618 -- of the cases in which the tree built by the parser is plain wrong.
1620 if No (Next (Exp))
1621 and then Is_Entity_Name (Exp)
1622 and then Is_Type (Entity (Exp))
1623 then
1624 Replace (N,
1625 Make_Slice (Sloc (N),
1626 Prefix => P,
1627 Discrete_Range => New_Copy (Exp)));
1628 Analyze (N);
1630 -- Otherwise (more than one index present, or single index is not
1631 -- a subtype name), then we have the indexed component case.
1633 else
1634 Process_Indexed_Component;
1635 end if;
1636 end Process_Indexed_Component_Or_Slice;
1638 ------------------------------------------
1639 -- Process_Overloaded_Indexed_Component --
1640 ------------------------------------------
1642 procedure Process_Overloaded_Indexed_Component is
1643 Exp : Node_Id;
1644 I : Interp_Index;
1645 It : Interp;
1646 Typ : Entity_Id;
1647 Index : Node_Id;
1648 Found : Boolean;
1650 begin
1651 Set_Etype (N, Any_Type);
1653 Get_First_Interp (P, I, It);
1654 while Present (It.Nam) loop
1655 Typ := It.Typ;
1657 if Is_Access_Type (Typ) then
1658 Typ := Designated_Type (Typ);
1659 Error_Msg_NW (Warn_On_Dereference, "?implicit dereference", N);
1660 end if;
1662 if Is_Array_Type (Typ) then
1664 -- Got a candidate: verify that index types are compatible
1666 Index := First_Index (Typ);
1667 Found := True;
1668 Exp := First (Exprs);
1669 while Present (Index) and then Present (Exp) loop
1670 if Has_Compatible_Type (Exp, Etype (Index)) then
1671 null;
1672 else
1673 Found := False;
1674 Remove_Interp (I);
1675 exit;
1676 end if;
1678 Next_Index (Index);
1679 Next (Exp);
1680 end loop;
1682 if Found and then No (Index) and then No (Exp) then
1683 Add_One_Interp (N,
1684 Etype (Component_Type (Typ)),
1685 Etype (Component_Type (Typ)));
1686 end if;
1687 end if;
1689 Get_Next_Interp (I, It);
1690 end loop;
1692 if Etype (N) = Any_Type then
1693 Error_Msg_N ("no legal interpetation for indexed component", N);
1694 Set_Is_Overloaded (N, False);
1695 end if;
1697 End_Interp_List;
1698 end Process_Overloaded_Indexed_Component;
1700 -- Start of processing for Analyze_Indexed_Component_Form
1702 begin
1703 -- Get name of array, function or type
1705 Analyze (P);
1706 if Nkind (N) = N_Function_Call
1707 or else Nkind (N) = N_Procedure_Call_Statement
1708 then
1709 -- If P is an explicit dereference whose prefix is of a
1710 -- remote access-to-subprogram type, then N has already
1711 -- been rewritten as a subprogram call and analyzed.
1713 return;
1714 end if;
1716 pragma Assert (Nkind (N) = N_Indexed_Component);
1718 P_T := Base_Type (Etype (P));
1720 if Is_Entity_Name (P)
1721 or else Nkind (P) = N_Operator_Symbol
1722 then
1723 U_N := Entity (P);
1725 if Is_Type (U_N) then
1727 -- Reformat node as a type conversion
1729 E := Remove_Head (Exprs);
1731 if Present (First (Exprs)) then
1732 Error_Msg_N
1733 ("argument of type conversion must be single expression", N);
1734 end if;
1736 Change_Node (N, N_Type_Conversion);
1737 Set_Subtype_Mark (N, P);
1738 Set_Etype (N, U_N);
1739 Set_Expression (N, E);
1741 -- After changing the node, call for the specific Analysis
1742 -- routine directly, to avoid a double call to the expander.
1744 Analyze_Type_Conversion (N);
1745 return;
1746 end if;
1748 if Is_Overloadable (U_N) then
1749 Process_Function_Call;
1751 elsif Ekind (Etype (P)) = E_Subprogram_Type
1752 or else (Is_Access_Type (Etype (P))
1753 and then
1754 Ekind (Designated_Type (Etype (P))) = E_Subprogram_Type)
1755 then
1756 -- Call to access_to-subprogram with possible implicit dereference
1758 Process_Function_Call;
1760 elsif Is_Generic_Subprogram (U_N) then
1762 -- A common beginner's (or C++ templates fan) error
1764 Error_Msg_N ("generic subprogram cannot be called", N);
1765 Set_Etype (N, Any_Type);
1766 return;
1768 else
1769 Process_Indexed_Component_Or_Slice;
1770 end if;
1772 -- If not an entity name, prefix is an expression that may denote
1773 -- an array or an access-to-subprogram.
1775 else
1776 if Ekind (P_T) = E_Subprogram_Type
1777 or else (Is_Access_Type (P_T)
1778 and then
1779 Ekind (Designated_Type (P_T)) = E_Subprogram_Type)
1780 then
1781 Process_Function_Call;
1783 elsif Nkind (P) = N_Selected_Component
1784 and then Is_Overloadable (Entity (Selector_Name (P)))
1785 then
1786 Process_Function_Call;
1788 else
1789 -- Indexed component, slice, or a call to a member of a family
1790 -- entry, which will be converted to an entry call later.
1792 Process_Indexed_Component_Or_Slice;
1793 end if;
1794 end if;
1795 end Analyze_Indexed_Component_Form;
1797 ------------------------
1798 -- Analyze_Logical_Op --
1799 ------------------------
1801 procedure Analyze_Logical_Op (N : Node_Id) is
1802 L : constant Node_Id := Left_Opnd (N);
1803 R : constant Node_Id := Right_Opnd (N);
1804 Op_Id : Entity_Id := Entity (N);
1806 begin
1807 Set_Etype (N, Any_Type);
1808 Candidate_Type := Empty;
1810 Analyze_Expression (L);
1811 Analyze_Expression (R);
1813 if Present (Op_Id) then
1815 if Ekind (Op_Id) = E_Operator then
1816 Find_Boolean_Types (L, R, Op_Id, N);
1817 else
1818 Add_One_Interp (N, Op_Id, Etype (Op_Id));
1819 end if;
1821 else
1822 Op_Id := Get_Name_Entity_Id (Chars (N));
1823 while Present (Op_Id) loop
1824 if Ekind (Op_Id) = E_Operator then
1825 Find_Boolean_Types (L, R, Op_Id, N);
1826 else
1827 Analyze_User_Defined_Binary_Op (N, Op_Id);
1828 end if;
1830 Op_Id := Homonym (Op_Id);
1831 end loop;
1832 end if;
1834 Operator_Check (N);
1835 end Analyze_Logical_Op;
1837 ---------------------------
1838 -- Analyze_Membership_Op --
1839 ---------------------------
1841 procedure Analyze_Membership_Op (N : Node_Id) is
1842 L : constant Node_Id := Left_Opnd (N);
1843 R : constant Node_Id := Right_Opnd (N);
1845 Index : Interp_Index;
1846 It : Interp;
1847 Found : Boolean := False;
1848 I_F : Interp_Index;
1849 T_F : Entity_Id;
1851 procedure Try_One_Interp (T1 : Entity_Id);
1852 -- Routine to try one proposed interpretation. Note that the context
1853 -- of the operation plays no role in resolving the arguments, so that
1854 -- if there is more than one interpretation of the operands that is
1855 -- compatible with a membership test, the operation is ambiguous.
1857 --------------------
1858 -- Try_One_Interp --
1859 --------------------
1861 procedure Try_One_Interp (T1 : Entity_Id) is
1862 begin
1863 if Has_Compatible_Type (R, T1) then
1864 if Found
1865 and then Base_Type (T1) /= Base_Type (T_F)
1866 then
1867 It := Disambiguate (L, I_F, Index, Any_Type);
1869 if It = No_Interp then
1870 Ambiguous_Operands (N);
1871 Set_Etype (L, Any_Type);
1872 return;
1874 else
1875 T_F := It.Typ;
1876 end if;
1878 else
1879 Found := True;
1880 T_F := T1;
1881 I_F := Index;
1882 end if;
1884 Set_Etype (L, T_F);
1885 end if;
1887 end Try_One_Interp;
1889 -- Start of processing for Analyze_Membership_Op
1891 begin
1892 Analyze_Expression (L);
1894 if Nkind (R) = N_Range
1895 or else (Nkind (R) = N_Attribute_Reference
1896 and then Attribute_Name (R) = Name_Range)
1897 then
1898 Analyze (R);
1900 if not Is_Overloaded (L) then
1901 Try_One_Interp (Etype (L));
1903 else
1904 Get_First_Interp (L, Index, It);
1905 while Present (It.Typ) loop
1906 Try_One_Interp (It.Typ);
1907 Get_Next_Interp (Index, It);
1908 end loop;
1909 end if;
1911 -- If not a range, it can only be a subtype mark, or else there
1912 -- is a more basic error, to be diagnosed in Find_Type.
1914 else
1915 Find_Type (R);
1917 if Is_Entity_Name (R) then
1918 Check_Fully_Declared (Entity (R), R);
1919 end if;
1920 end if;
1922 -- Compatibility between expression and subtype mark or range is
1923 -- checked during resolution. The result of the operation is Boolean
1924 -- in any case.
1926 Set_Etype (N, Standard_Boolean);
1928 if Comes_From_Source (N)
1929 and then Is_CPP_Class (Etype (Etype (Right_Opnd (N))))
1930 then
1931 Error_Msg_N ("membership test not applicable to cpp-class types", N);
1932 end if;
1933 end Analyze_Membership_Op;
1935 ----------------------
1936 -- Analyze_Negation --
1937 ----------------------
1939 procedure Analyze_Negation (N : Node_Id) is
1940 R : constant Node_Id := Right_Opnd (N);
1941 Op_Id : Entity_Id := Entity (N);
1943 begin
1944 Set_Etype (N, Any_Type);
1945 Candidate_Type := Empty;
1947 Analyze_Expression (R);
1949 if Present (Op_Id) then
1950 if Ekind (Op_Id) = E_Operator then
1951 Find_Negation_Types (R, Op_Id, N);
1952 else
1953 Add_One_Interp (N, Op_Id, Etype (Op_Id));
1954 end if;
1956 else
1957 Op_Id := Get_Name_Entity_Id (Chars (N));
1958 while Present (Op_Id) loop
1959 if Ekind (Op_Id) = E_Operator then
1960 Find_Negation_Types (R, Op_Id, N);
1961 else
1962 Analyze_User_Defined_Unary_Op (N, Op_Id);
1963 end if;
1965 Op_Id := Homonym (Op_Id);
1966 end loop;
1967 end if;
1969 Operator_Check (N);
1970 end Analyze_Negation;
1972 ------------------
1973 -- Analyze_Null --
1974 ------------------
1976 procedure Analyze_Null (N : Node_Id) is
1977 begin
1978 Set_Etype (N, Any_Access);
1979 end Analyze_Null;
1981 ----------------------
1982 -- Analyze_One_Call --
1983 ----------------------
1985 procedure Analyze_One_Call
1986 (N : Node_Id;
1987 Nam : Entity_Id;
1988 Report : Boolean;
1989 Success : out Boolean;
1990 Skip_First : Boolean := False)
1992 Actuals : constant List_Id := Parameter_Associations (N);
1993 Prev_T : constant Entity_Id := Etype (N);
1994 Must_Skip : constant Boolean := Skip_First
1995 or else Nkind (Original_Node (N)) = N_Selected_Component
1996 or else
1997 (Nkind (Original_Node (N)) = N_Indexed_Component
1998 and then Nkind (Prefix (Original_Node (N)))
1999 = N_Selected_Component);
2000 -- The first formal must be omitted from the match when trying to find
2001 -- a primitive operation that is a possible interpretation, and also
2002 -- after the call has been rewritten, because the corresponding actual
2003 -- is already known to be compatible, and because this may be an
2004 -- indexing of a call with default parameters.
2006 Formal : Entity_Id;
2007 Actual : Node_Id;
2008 Is_Indexed : Boolean := False;
2009 Subp_Type : constant Entity_Id := Etype (Nam);
2010 Norm_OK : Boolean;
2012 function Operator_Hidden_By (Fun : Entity_Id) return Boolean;
2013 -- There may be a user-defined operator that hides the current
2014 -- interpretation. We must check for this independently of the
2015 -- analysis of the call with the user-defined operation, because
2016 -- the parameter names may be wrong and yet the hiding takes place.
2017 -- This fixes a problem with ACATS test B34014O.
2019 -- When the type Address is a visible integer type, and the DEC
2020 -- system extension is visible, the predefined operator may be
2021 -- hidden as well, by one of the address operations in auxdec.
2022 -- Finally, The abstract operations on address do not hide the
2023 -- predefined operator (this is the purpose of making them abstract).
2025 procedure Indicate_Name_And_Type;
2026 -- If candidate interpretation matches, indicate name and type of
2027 -- result on call node.
2029 ----------------------------
2030 -- Indicate_Name_And_Type --
2031 ----------------------------
2033 procedure Indicate_Name_And_Type is
2034 begin
2035 Add_One_Interp (N, Nam, Etype (Nam));
2036 Success := True;
2038 -- If the prefix of the call is a name, indicate the entity
2039 -- being called. If it is not a name, it is an expression that
2040 -- denotes an access to subprogram or else an entry or family. In
2041 -- the latter case, the name is a selected component, and the entity
2042 -- being called is noted on the selector.
2044 if not Is_Type (Nam) then
2045 if Is_Entity_Name (Name (N))
2046 or else Nkind (Name (N)) = N_Operator_Symbol
2047 then
2048 Set_Entity (Name (N), Nam);
2050 elsif Nkind (Name (N)) = N_Selected_Component then
2051 Set_Entity (Selector_Name (Name (N)), Nam);
2052 end if;
2053 end if;
2055 if Debug_Flag_E and not Report then
2056 Write_Str (" Overloaded call ");
2057 Write_Int (Int (N));
2058 Write_Str (" compatible with ");
2059 Write_Int (Int (Nam));
2060 Write_Eol;
2061 end if;
2062 end Indicate_Name_And_Type;
2064 ------------------------
2065 -- Operator_Hidden_By --
2066 ------------------------
2068 function Operator_Hidden_By (Fun : Entity_Id) return Boolean is
2069 Act1 : constant Node_Id := First_Actual (N);
2070 Act2 : constant Node_Id := Next_Actual (Act1);
2071 Form1 : constant Entity_Id := First_Formal (Fun);
2072 Form2 : constant Entity_Id := Next_Formal (Form1);
2074 begin
2075 if Ekind (Fun) /= E_Function
2076 or else Is_Abstract_Subprogram (Fun)
2077 then
2078 return False;
2080 elsif not Has_Compatible_Type (Act1, Etype (Form1)) then
2081 return False;
2083 elsif Present (Form2) then
2085 No (Act2) or else not Has_Compatible_Type (Act2, Etype (Form2))
2086 then
2087 return False;
2088 end if;
2090 elsif Present (Act2) then
2091 return False;
2092 end if;
2094 -- Now we know that the arity of the operator matches the function,
2095 -- and the function call is a valid interpretation. The function
2096 -- hides the operator if it has the right signature, or if one of
2097 -- its operands is a non-abstract operation on Address when this is
2098 -- a visible integer type.
2100 return Hides_Op (Fun, Nam)
2101 or else Is_Descendent_Of_Address (Etype (Form1))
2102 or else
2103 (Present (Form2)
2104 and then Is_Descendent_Of_Address (Etype (Form2)));
2105 end Operator_Hidden_By;
2107 -- Start of processing for Analyze_One_Call
2109 begin
2110 Success := False;
2112 -- If the subprogram has no formals or if all the formals have defaults,
2113 -- and the return type is an array type, the node may denote an indexing
2114 -- of the result of a parameterless call. In Ada 2005, the subprogram
2115 -- may have one non-defaulted formal, and the call may have been written
2116 -- in prefix notation, so that the rebuilt parameter list has more than
2117 -- one actual.
2119 if Present (Actuals)
2120 and then
2121 (Needs_No_Actuals (Nam)
2122 or else
2123 (Needs_One_Actual (Nam)
2124 and then Present (Next_Actual (First (Actuals)))))
2125 then
2126 if Is_Array_Type (Subp_Type) then
2127 Is_Indexed := Try_Indexed_Call (N, Nam, Subp_Type, Must_Skip);
2129 elsif Is_Access_Type (Subp_Type)
2130 and then Is_Array_Type (Designated_Type (Subp_Type))
2131 then
2132 Is_Indexed :=
2133 Try_Indexed_Call
2134 (N, Nam, Designated_Type (Subp_Type), Must_Skip);
2136 -- The prefix can also be a parameterless function that returns an
2137 -- access to subprogram. in which case this is an indirect call.
2139 elsif Is_Access_Type (Subp_Type)
2140 and then Ekind (Designated_Type (Subp_Type)) = E_Subprogram_Type
2141 then
2142 Is_Indexed := Try_Indirect_Call (N, Nam, Subp_Type);
2143 end if;
2145 end if;
2147 Normalize_Actuals (N, Nam, (Report and not Is_Indexed), Norm_OK);
2149 if not Norm_OK then
2151 -- Mismatch in number or names of parameters
2153 if Debug_Flag_E then
2154 Write_Str (" normalization fails in call ");
2155 Write_Int (Int (N));
2156 Write_Str (" with subprogram ");
2157 Write_Int (Int (Nam));
2158 Write_Eol;
2159 end if;
2161 -- If the context expects a function call, discard any interpretation
2162 -- that is a procedure. If the node is not overloaded, leave as is for
2163 -- better error reporting when type mismatch is found.
2165 elsif Nkind (N) = N_Function_Call
2166 and then Is_Overloaded (Name (N))
2167 and then Ekind (Nam) = E_Procedure
2168 then
2169 return;
2171 -- Ditto for function calls in a procedure context
2173 elsif Nkind (N) = N_Procedure_Call_Statement
2174 and then Is_Overloaded (Name (N))
2175 and then Etype (Nam) /= Standard_Void_Type
2176 then
2177 return;
2179 elsif No (Actuals) then
2181 -- If Normalize succeeds, then there are default parameters for
2182 -- all formals.
2184 Indicate_Name_And_Type;
2186 elsif Ekind (Nam) = E_Operator then
2187 if Nkind (N) = N_Procedure_Call_Statement then
2188 return;
2189 end if;
2191 -- This can occur when the prefix of the call is an operator
2192 -- name or an expanded name whose selector is an operator name.
2194 Analyze_Operator_Call (N, Nam);
2196 if Etype (N) /= Prev_T then
2198 -- Check that operator is not hidden by a function interpretation
2200 if Is_Overloaded (Name (N)) then
2201 declare
2202 I : Interp_Index;
2203 It : Interp;
2205 begin
2206 Get_First_Interp (Name (N), I, It);
2207 while Present (It.Nam) loop
2208 if Operator_Hidden_By (It.Nam) then
2209 Set_Etype (N, Prev_T);
2210 return;
2211 end if;
2213 Get_Next_Interp (I, It);
2214 end loop;
2215 end;
2216 end if;
2218 -- If operator matches formals, record its name on the call.
2219 -- If the operator is overloaded, Resolve will select the
2220 -- correct one from the list of interpretations. The call
2221 -- node itself carries the first candidate.
2223 Set_Entity (Name (N), Nam);
2224 Success := True;
2226 elsif Report and then Etype (N) = Any_Type then
2227 Error_Msg_N ("incompatible arguments for operator", N);
2228 end if;
2230 else
2231 -- Normalize_Actuals has chained the named associations in the
2232 -- correct order of the formals.
2234 Actual := First_Actual (N);
2235 Formal := First_Formal (Nam);
2237 -- If we are analyzing a call rewritten from object notation,
2238 -- skip first actual, which may be rewritten later as an
2239 -- explicit dereference.
2241 if Must_Skip then
2242 Next_Actual (Actual);
2243 Next_Formal (Formal);
2244 end if;
2246 while Present (Actual) and then Present (Formal) loop
2247 if Nkind (Parent (Actual)) /= N_Parameter_Association
2248 or else Chars (Selector_Name (Parent (Actual))) = Chars (Formal)
2249 then
2250 -- The actual can be compatible with the formal, but we must
2251 -- also check that the context is not an address type that is
2252 -- visibly an integer type, as is the case in VMS_64. In this
2253 -- case the use of literals is illegal, except in the body of
2254 -- descendents of system, where arithmetic operations on
2255 -- address are of course used.
2257 if Has_Compatible_Type (Actual, Etype (Formal))
2258 and then
2259 (Etype (Actual) /= Universal_Integer
2260 or else not Is_Descendent_Of_Address (Etype (Formal))
2261 or else
2262 Is_Predefined_File_Name
2263 (Unit_File_Name (Get_Source_Unit (N))))
2264 then
2265 Next_Actual (Actual);
2266 Next_Formal (Formal);
2268 else
2269 if Debug_Flag_E then
2270 Write_Str (" type checking fails in call ");
2271 Write_Int (Int (N));
2272 Write_Str (" with formal ");
2273 Write_Int (Int (Formal));
2274 Write_Str (" in subprogram ");
2275 Write_Int (Int (Nam));
2276 Write_Eol;
2277 end if;
2279 if Report and not Is_Indexed then
2281 -- Ada 2005 (AI-251): Complete the error notification
2282 -- to help new Ada 2005 users
2284 if Is_Class_Wide_Type (Etype (Formal))
2285 and then Is_Interface (Etype (Etype (Formal)))
2286 and then not Interface_Present_In_Ancestor
2287 (Typ => Etype (Actual),
2288 Iface => Etype (Etype (Formal)))
2289 then
2290 Error_Msg_NE
2291 ("(Ada 2005) does not implement interface }",
2292 Actual, Etype (Etype (Formal)));
2293 end if;
2295 Wrong_Type (Actual, Etype (Formal));
2297 if Nkind (Actual) = N_Op_Eq
2298 and then Nkind (Left_Opnd (Actual)) = N_Identifier
2299 then
2300 Formal := First_Formal (Nam);
2301 while Present (Formal) loop
2302 if Chars (Left_Opnd (Actual)) = Chars (Formal) then
2303 Error_Msg_N
2304 ("possible misspelling of `='>`!", Actual);
2305 exit;
2306 end if;
2308 Next_Formal (Formal);
2309 end loop;
2310 end if;
2312 if All_Errors_Mode then
2313 Error_Msg_Sloc := Sloc (Nam);
2315 if Is_Overloadable (Nam)
2316 and then Present (Alias (Nam))
2317 and then not Comes_From_Source (Nam)
2318 then
2319 Error_Msg_NE
2320 ("\\ =='> in call to inherited operation & #!",
2321 Actual, Nam);
2323 elsif Ekind (Nam) = E_Subprogram_Type then
2324 declare
2325 Access_To_Subprogram_Typ :
2326 constant Entity_Id :=
2327 Defining_Identifier
2328 (Associated_Node_For_Itype (Nam));
2329 begin
2330 Error_Msg_NE (
2331 "\\ =='> in call to dereference of &#!",
2332 Actual, Access_To_Subprogram_Typ);
2333 end;
2335 else
2336 Error_Msg_NE
2337 ("\\ =='> in call to &#!", Actual, Nam);
2339 end if;
2340 end if;
2341 end if;
2343 return;
2344 end if;
2346 else
2347 -- Normalize_Actuals has verified that a default value exists
2348 -- for this formal. Current actual names a subsequent formal.
2350 Next_Formal (Formal);
2351 end if;
2352 end loop;
2354 -- On exit, all actuals match
2356 Indicate_Name_And_Type;
2357 end if;
2358 end Analyze_One_Call;
2360 ---------------------------
2361 -- Analyze_Operator_Call --
2362 ---------------------------
2364 procedure Analyze_Operator_Call (N : Node_Id; Op_Id : Entity_Id) is
2365 Op_Name : constant Name_Id := Chars (Op_Id);
2366 Act1 : constant Node_Id := First_Actual (N);
2367 Act2 : constant Node_Id := Next_Actual (Act1);
2369 begin
2370 -- Binary operator case
2372 if Present (Act2) then
2374 -- If more than two operands, then not binary operator after all
2376 if Present (Next_Actual (Act2)) then
2377 return;
2379 elsif Op_Name = Name_Op_Add
2380 or else Op_Name = Name_Op_Subtract
2381 or else Op_Name = Name_Op_Multiply
2382 or else Op_Name = Name_Op_Divide
2383 or else Op_Name = Name_Op_Mod
2384 or else Op_Name = Name_Op_Rem
2385 or else Op_Name = Name_Op_Expon
2386 then
2387 Find_Arithmetic_Types (Act1, Act2, Op_Id, N);
2389 elsif Op_Name = Name_Op_And
2390 or else Op_Name = Name_Op_Or
2391 or else Op_Name = Name_Op_Xor
2392 then
2393 Find_Boolean_Types (Act1, Act2, Op_Id, N);
2395 elsif Op_Name = Name_Op_Lt
2396 or else Op_Name = Name_Op_Le
2397 or else Op_Name = Name_Op_Gt
2398 or else Op_Name = Name_Op_Ge
2399 then
2400 Find_Comparison_Types (Act1, Act2, Op_Id, N);
2402 elsif Op_Name = Name_Op_Eq
2403 or else Op_Name = Name_Op_Ne
2404 then
2405 Find_Equality_Types (Act1, Act2, Op_Id, N);
2407 elsif Op_Name = Name_Op_Concat then
2408 Find_Concatenation_Types (Act1, Act2, Op_Id, N);
2410 -- Is this else null correct, or should it be an abort???
2412 else
2413 null;
2414 end if;
2416 -- Unary operator case
2418 else
2419 if Op_Name = Name_Op_Subtract or else
2420 Op_Name = Name_Op_Add or else
2421 Op_Name = Name_Op_Abs
2422 then
2423 Find_Unary_Types (Act1, Op_Id, N);
2425 elsif
2426 Op_Name = Name_Op_Not
2427 then
2428 Find_Negation_Types (Act1, Op_Id, N);
2430 -- Is this else null correct, or should it be an abort???
2432 else
2433 null;
2434 end if;
2435 end if;
2436 end Analyze_Operator_Call;
2438 -------------------------------------------
2439 -- Analyze_Overloaded_Selected_Component --
2440 -------------------------------------------
2442 procedure Analyze_Overloaded_Selected_Component (N : Node_Id) is
2443 Nam : constant Node_Id := Prefix (N);
2444 Sel : constant Node_Id := Selector_Name (N);
2445 Comp : Entity_Id;
2446 I : Interp_Index;
2447 It : Interp;
2448 T : Entity_Id;
2450 begin
2451 Set_Etype (Sel, Any_Type);
2453 Get_First_Interp (Nam, I, It);
2454 while Present (It.Typ) loop
2455 if Is_Access_Type (It.Typ) then
2456 T := Designated_Type (It.Typ);
2457 Error_Msg_NW (Warn_On_Dereference, "?implicit dereference", N);
2458 else
2459 T := It.Typ;
2460 end if;
2462 if Is_Record_Type (T) then
2463 Comp := First_Entity (T);
2464 while Present (Comp) loop
2465 if Chars (Comp) = Chars (Sel)
2466 and then Is_Visible_Component (Comp)
2467 then
2468 Set_Entity (Sel, Comp);
2469 Set_Etype (Sel, Etype (Comp));
2470 Add_One_Interp (N, Etype (Comp), Etype (Comp));
2472 -- This also specifies a candidate to resolve the name.
2473 -- Further overloading will be resolved from context.
2475 Set_Etype (Nam, It.Typ);
2476 end if;
2478 Next_Entity (Comp);
2479 end loop;
2481 elsif Is_Concurrent_Type (T) then
2482 Comp := First_Entity (T);
2483 while Present (Comp)
2484 and then Comp /= First_Private_Entity (T)
2485 loop
2486 if Chars (Comp) = Chars (Sel) then
2487 if Is_Overloadable (Comp) then
2488 Add_One_Interp (Sel, Comp, Etype (Comp));
2489 else
2490 Set_Entity_With_Style_Check (Sel, Comp);
2491 Generate_Reference (Comp, Sel);
2492 end if;
2494 Set_Etype (Sel, Etype (Comp));
2495 Set_Etype (N, Etype (Comp));
2496 Set_Etype (Nam, It.Typ);
2498 -- For access type case, introduce explicit deference for
2499 -- more uniform treatment of entry calls.
2501 if Is_Access_Type (Etype (Nam)) then
2502 Insert_Explicit_Dereference (Nam);
2503 Error_Msg_NW
2504 (Warn_On_Dereference, "?implicit dereference", N);
2505 end if;
2506 end if;
2508 Next_Entity (Comp);
2509 end loop;
2511 Set_Is_Overloaded (N, Is_Overloaded (Sel));
2512 end if;
2514 Get_Next_Interp (I, It);
2515 end loop;
2517 if Etype (N) = Any_Type
2518 and then not Try_Object_Operation (N)
2519 then
2520 Error_Msg_NE ("undefined selector& for overloaded prefix", N, Sel);
2521 Set_Entity (Sel, Any_Id);
2522 Set_Etype (Sel, Any_Type);
2523 end if;
2524 end Analyze_Overloaded_Selected_Component;
2526 ----------------------------------
2527 -- Analyze_Qualified_Expression --
2528 ----------------------------------
2530 procedure Analyze_Qualified_Expression (N : Node_Id) is
2531 Mark : constant Entity_Id := Subtype_Mark (N);
2532 Expr : constant Node_Id := Expression (N);
2533 I : Interp_Index;
2534 It : Interp;
2535 T : Entity_Id;
2537 begin
2538 Analyze_Expression (Expr);
2540 Set_Etype (N, Any_Type);
2541 Find_Type (Mark);
2542 T := Entity (Mark);
2543 Set_Etype (N, T);
2545 if T = Any_Type then
2546 return;
2547 end if;
2549 Check_Fully_Declared (T, N);
2551 -- If expected type is class-wide, check for exact match before
2552 -- expansion, because if the expression is a dispatching call it
2553 -- may be rewritten as explicit dereference with class-wide result.
2554 -- If expression is overloaded, retain only interpretations that
2555 -- will yield exact matches.
2557 if Is_Class_Wide_Type (T) then
2558 if not Is_Overloaded (Expr) then
2559 if Base_Type (Etype (Expr)) /= Base_Type (T) then
2560 if Nkind (Expr) = N_Aggregate then
2561 Error_Msg_N ("type of aggregate cannot be class-wide", Expr);
2562 else
2563 Wrong_Type (Expr, T);
2564 end if;
2565 end if;
2567 else
2568 Get_First_Interp (Expr, I, It);
2570 while Present (It.Nam) loop
2571 if Base_Type (It.Typ) /= Base_Type (T) then
2572 Remove_Interp (I);
2573 end if;
2575 Get_Next_Interp (I, It);
2576 end loop;
2577 end if;
2578 end if;
2580 Set_Etype (N, T);
2581 end Analyze_Qualified_Expression;
2583 -------------------
2584 -- Analyze_Range --
2585 -------------------
2587 procedure Analyze_Range (N : Node_Id) is
2588 L : constant Node_Id := Low_Bound (N);
2589 H : constant Node_Id := High_Bound (N);
2590 I1, I2 : Interp_Index;
2591 It1, It2 : Interp;
2593 procedure Check_Common_Type (T1, T2 : Entity_Id);
2594 -- Verify the compatibility of two types, and choose the
2595 -- non universal one if the other is universal.
2597 procedure Check_High_Bound (T : Entity_Id);
2598 -- Test one interpretation of the low bound against all those
2599 -- of the high bound.
2601 procedure Check_Universal_Expression (N : Node_Id);
2602 -- In Ada83, reject bounds of a universal range that are not
2603 -- literals or entity names.
2605 -----------------------
2606 -- Check_Common_Type --
2607 -----------------------
2609 procedure Check_Common_Type (T1, T2 : Entity_Id) is
2610 begin
2611 if Covers (T1, T2) or else Covers (T2, T1) then
2612 if T1 = Universal_Integer
2613 or else T1 = Universal_Real
2614 or else T1 = Any_Character
2615 then
2616 Add_One_Interp (N, Base_Type (T2), Base_Type (T2));
2618 elsif T1 = T2 then
2619 Add_One_Interp (N, T1, T1);
2621 else
2622 Add_One_Interp (N, Base_Type (T1), Base_Type (T1));
2623 end if;
2624 end if;
2625 end Check_Common_Type;
2627 ----------------------
2628 -- Check_High_Bound --
2629 ----------------------
2631 procedure Check_High_Bound (T : Entity_Id) is
2632 begin
2633 if not Is_Overloaded (H) then
2634 Check_Common_Type (T, Etype (H));
2635 else
2636 Get_First_Interp (H, I2, It2);
2637 while Present (It2.Typ) loop
2638 Check_Common_Type (T, It2.Typ);
2639 Get_Next_Interp (I2, It2);
2640 end loop;
2641 end if;
2642 end Check_High_Bound;
2644 -----------------------------
2645 -- Is_Universal_Expression --
2646 -----------------------------
2648 procedure Check_Universal_Expression (N : Node_Id) is
2649 begin
2650 if Etype (N) = Universal_Integer
2651 and then Nkind (N) /= N_Integer_Literal
2652 and then not Is_Entity_Name (N)
2653 and then Nkind (N) /= N_Attribute_Reference
2654 then
2655 Error_Msg_N ("illegal bound in discrete range", N);
2656 end if;
2657 end Check_Universal_Expression;
2659 -- Start of processing for Analyze_Range
2661 begin
2662 Set_Etype (N, Any_Type);
2663 Analyze_Expression (L);
2664 Analyze_Expression (H);
2666 if Etype (L) = Any_Type or else Etype (H) = Any_Type then
2667 return;
2669 else
2670 if not Is_Overloaded (L) then
2671 Check_High_Bound (Etype (L));
2672 else
2673 Get_First_Interp (L, I1, It1);
2674 while Present (It1.Typ) loop
2675 Check_High_Bound (It1.Typ);
2676 Get_Next_Interp (I1, It1);
2677 end loop;
2678 end if;
2680 -- If result is Any_Type, then we did not find a compatible pair
2682 if Etype (N) = Any_Type then
2683 Error_Msg_N ("incompatible types in range ", N);
2684 end if;
2685 end if;
2687 if Ada_Version = Ada_83
2688 and then
2689 (Nkind (Parent (N)) = N_Loop_Parameter_Specification
2690 or else Nkind (Parent (N)) = N_Constrained_Array_Definition)
2691 then
2692 Check_Universal_Expression (L);
2693 Check_Universal_Expression (H);
2694 end if;
2695 end Analyze_Range;
2697 -----------------------
2698 -- Analyze_Reference --
2699 -----------------------
2701 procedure Analyze_Reference (N : Node_Id) is
2702 P : constant Node_Id := Prefix (N);
2703 Acc_Type : Entity_Id;
2704 begin
2705 Analyze (P);
2706 Acc_Type := Create_Itype (E_Allocator_Type, N);
2707 Set_Etype (Acc_Type, Acc_Type);
2708 Init_Size_Align (Acc_Type);
2709 Set_Directly_Designated_Type (Acc_Type, Etype (P));
2710 Set_Etype (N, Acc_Type);
2711 end Analyze_Reference;
2713 --------------------------------
2714 -- Analyze_Selected_Component --
2715 --------------------------------
2717 -- Prefix is a record type or a task or protected type. In the
2718 -- later case, the selector must denote a visible entry.
2720 procedure Analyze_Selected_Component (N : Node_Id) is
2721 Name : constant Node_Id := Prefix (N);
2722 Sel : constant Node_Id := Selector_Name (N);
2723 Comp : Entity_Id;
2724 Prefix_Type : Entity_Id;
2726 Type_To_Use : Entity_Id;
2727 -- In most cases this is the Prefix_Type, but if the Prefix_Type is
2728 -- a class-wide type, we use its root type, whose components are
2729 -- present in the class-wide type.
2731 Pent : Entity_Id := Empty;
2732 Act_Decl : Node_Id;
2733 In_Scope : Boolean;
2734 Parent_N : Node_Id;
2736 -- Start of processing for Analyze_Selected_Component
2738 begin
2739 Set_Etype (N, Any_Type);
2741 if Is_Overloaded (Name) then
2742 Analyze_Overloaded_Selected_Component (N);
2743 return;
2745 elsif Etype (Name) = Any_Type then
2746 Set_Entity (Sel, Any_Id);
2747 Set_Etype (Sel, Any_Type);
2748 return;
2750 else
2751 Prefix_Type := Etype (Name);
2752 end if;
2754 if Is_Access_Type (Prefix_Type) then
2756 -- A RACW object can never be used as prefix of a selected
2757 -- component since that means it is dereferenced without
2758 -- being a controlling operand of a dispatching operation
2759 -- (RM E.2.2(15)).
2761 if Is_Remote_Access_To_Class_Wide_Type (Prefix_Type)
2762 and then Comes_From_Source (N)
2763 then
2764 Error_Msg_N
2765 ("invalid dereference of a remote access to class-wide value",
2768 -- Normal case of selected component applied to access type
2770 else
2771 Error_Msg_NW (Warn_On_Dereference, "?implicit dereference", N);
2773 if Is_Entity_Name (Name) then
2774 Pent := Entity (Name);
2775 elsif Nkind (Name) = N_Selected_Component
2776 and then Is_Entity_Name (Selector_Name (Name))
2777 then
2778 Pent := Entity (Selector_Name (Name));
2779 end if;
2781 Process_Implicit_Dereference_Prefix (Pent, Name);
2782 end if;
2784 Prefix_Type := Designated_Type (Prefix_Type);
2786 end if;
2788 -- (Ada 2005): if the prefix is the limited view of a type, and
2789 -- the context already includes the full view, use the full view
2790 -- in what follows, either to retrieve a component of to find
2791 -- a primitive operation. If the prefix is an explicit dereference,
2792 -- set the type of the prefix to reflect this transformation.
2793 -- If the non-limited view is itself an incomplete type, get the
2794 -- full view if available.
2796 if Is_Incomplete_Type (Prefix_Type)
2797 and then From_With_Type (Prefix_Type)
2798 and then Present (Non_Limited_View (Prefix_Type))
2799 then
2800 Prefix_Type := Get_Full_View (Non_Limited_View (Prefix_Type));
2802 if Nkind (N) = N_Explicit_Dereference then
2803 Set_Etype (Prefix (N), Prefix_Type);
2804 end if;
2806 elsif Ekind (Prefix_Type) = E_Class_Wide_Type
2807 and then From_With_Type (Prefix_Type)
2808 and then Present (Non_Limited_View (Etype (Prefix_Type)))
2809 then
2810 Prefix_Type :=
2811 Class_Wide_Type (Non_Limited_View (Etype (Prefix_Type)));
2813 if Nkind (N) = N_Explicit_Dereference then
2814 Set_Etype (Prefix (N), Prefix_Type);
2815 end if;
2816 end if;
2818 if Ekind (Prefix_Type) = E_Private_Subtype then
2819 Prefix_Type := Base_Type (Prefix_Type);
2820 end if;
2822 Type_To_Use := Prefix_Type;
2824 -- For class-wide types, use the entity list of the root type. This
2825 -- indirection is specially important for private extensions because
2826 -- only the root type get switched (not the class-wide type).
2828 if Is_Class_Wide_Type (Prefix_Type) then
2829 Type_To_Use := Root_Type (Prefix_Type);
2830 end if;
2832 Comp := First_Entity (Type_To_Use);
2834 -- If the selector has an original discriminant, the node appears in
2835 -- an instance. Replace the discriminant with the corresponding one
2836 -- in the current discriminated type. For nested generics, this must
2837 -- be done transitively, so note the new original discriminant.
2839 if Nkind (Sel) = N_Identifier
2840 and then Present (Original_Discriminant (Sel))
2841 then
2842 Comp := Find_Corresponding_Discriminant (Sel, Prefix_Type);
2844 -- Mark entity before rewriting, for completeness and because
2845 -- subsequent semantic checks might examine the original node.
2847 Set_Entity (Sel, Comp);
2848 Rewrite (Selector_Name (N),
2849 New_Occurrence_Of (Comp, Sloc (N)));
2850 Set_Original_Discriminant (Selector_Name (N), Comp);
2851 Set_Etype (N, Etype (Comp));
2853 if Is_Access_Type (Etype (Name)) then
2854 Insert_Explicit_Dereference (Name);
2855 Error_Msg_NW (Warn_On_Dereference, "?implicit dereference", N);
2856 end if;
2858 elsif Is_Record_Type (Prefix_Type) then
2860 -- Find component with given name
2862 while Present (Comp) loop
2863 if Chars (Comp) = Chars (Sel)
2864 and then Is_Visible_Component (Comp)
2865 then
2866 Set_Entity_With_Style_Check (Sel, Comp);
2867 Set_Etype (Sel, Etype (Comp));
2869 if Ekind (Comp) = E_Discriminant then
2870 if Is_Unchecked_Union (Base_Type (Prefix_Type)) then
2871 Error_Msg_N
2872 ("cannot reference discriminant of Unchecked_Union",
2873 Sel);
2874 end if;
2876 if Is_Generic_Type (Prefix_Type)
2877 or else
2878 Is_Generic_Type (Root_Type (Prefix_Type))
2879 then
2880 Set_Original_Discriminant (Sel, Comp);
2881 end if;
2882 end if;
2884 -- Resolve the prefix early otherwise it is not possible to
2885 -- build the actual subtype of the component: it may need
2886 -- to duplicate this prefix and duplication is only allowed
2887 -- on fully resolved expressions.
2889 Resolve (Name);
2891 -- Ada 2005 (AI-50217): Check wrong use of incomplete types or
2892 -- subtypes in a package specification.
2893 -- Example:
2895 -- limited with Pkg;
2896 -- package Pkg is
2897 -- type Acc_Inc is access Pkg.T;
2898 -- X : Acc_Inc;
2899 -- N : Natural := X.all.Comp; -- ERROR, limited view
2900 -- end Pkg; -- Comp is not visible
2902 if Nkind (Name) = N_Explicit_Dereference
2903 and then From_With_Type (Etype (Prefix (Name)))
2904 and then not Is_Potentially_Use_Visible (Etype (Name))
2905 and then Nkind (Parent (Cunit_Entity (Current_Sem_Unit))) =
2906 N_Package_Specification
2907 then
2908 Error_Msg_NE
2909 ("premature usage of incomplete}", Prefix (Name),
2910 Etype (Prefix (Name)));
2911 end if;
2913 -- We never need an actual subtype for the case of a selection
2914 -- for a indexed component of a non-packed array, since in
2915 -- this case gigi generates all the checks and can find the
2916 -- necessary bounds information.
2918 -- We also do not need an actual subtype for the case of
2919 -- a first, last, length, or range attribute applied to a
2920 -- non-packed array, since gigi can again get the bounds in
2921 -- these cases (gigi cannot handle the packed case, since it
2922 -- has the bounds of the packed array type, not the original
2923 -- bounds of the type). However, if the prefix is itself a
2924 -- selected component, as in a.b.c (i), gigi may regard a.b.c
2925 -- as a dynamic-sized temporary, so we do generate an actual
2926 -- subtype for this case.
2928 Parent_N := Parent (N);
2930 if not Is_Packed (Etype (Comp))
2931 and then
2932 ((Nkind (Parent_N) = N_Indexed_Component
2933 and then Nkind (Name) /= N_Selected_Component)
2934 or else
2935 (Nkind (Parent_N) = N_Attribute_Reference
2936 and then (Attribute_Name (Parent_N) = Name_First
2937 or else
2938 Attribute_Name (Parent_N) = Name_Last
2939 or else
2940 Attribute_Name (Parent_N) = Name_Length
2941 or else
2942 Attribute_Name (Parent_N) = Name_Range)))
2943 then
2944 Set_Etype (N, Etype (Comp));
2946 -- If full analysis is not enabled, we do not generate an
2947 -- actual subtype, because in the absence of expansion
2948 -- reference to a formal of a protected type, for example,
2949 -- will not be properly transformed, and will lead to
2950 -- out-of-scope references in gigi.
2952 -- In all other cases, we currently build an actual subtype.
2953 -- It seems likely that many of these cases can be avoided,
2954 -- but right now, the front end makes direct references to the
2955 -- bounds (e.g. in generating a length check), and if we do
2956 -- not make an actual subtype, we end up getting a direct
2957 -- reference to a discriminant, which will not do.
2959 elsif Full_Analysis then
2960 Act_Decl :=
2961 Build_Actual_Subtype_Of_Component (Etype (Comp), N);
2962 Insert_Action (N, Act_Decl);
2964 if No (Act_Decl) then
2965 Set_Etype (N, Etype (Comp));
2967 else
2968 -- Component type depends on discriminants. Enter the
2969 -- main attributes of the subtype.
2971 declare
2972 Subt : constant Entity_Id :=
2973 Defining_Identifier (Act_Decl);
2975 begin
2976 Set_Etype (Subt, Base_Type (Etype (Comp)));
2977 Set_Ekind (Subt, Ekind (Etype (Comp)));
2978 Set_Etype (N, Subt);
2979 end;
2980 end if;
2982 -- If Full_Analysis not enabled, just set the Etype
2984 else
2985 Set_Etype (N, Etype (Comp));
2986 end if;
2988 return;
2989 end if;
2991 -- If the prefix is a private extension, check only the visible
2992 -- components of the partial view. This must include the tag,
2993 -- wich can appear in expanded code in a tag check.
2995 if Ekind (Type_To_Use) = E_Record_Type_With_Private
2996 and then Chars (Selector_Name (N)) /= Name_uTag
2997 then
2998 exit when Comp = Last_Entity (Type_To_Use);
2999 end if;
3001 Next_Entity (Comp);
3002 end loop;
3004 -- Ada 2005 (AI-252)
3006 if Ada_Version >= Ada_05
3007 and then Is_Tagged_Type (Prefix_Type)
3008 and then Try_Object_Operation (N)
3009 then
3010 return;
3012 -- If the transformation fails, it will be necessary to redo the
3013 -- analysis with all errors enabled, to indicate candidate
3014 -- interpretations and reasons for each failure ???
3016 end if;
3018 elsif Is_Private_Type (Prefix_Type) then
3019 -- Allow access only to discriminants of the type. If the type has
3020 -- no full view, gigi uses the parent type for the components, so we
3021 -- do the same here.
3023 if No (Full_View (Prefix_Type)) then
3024 Type_To_Use := Root_Type (Base_Type (Prefix_Type));
3025 Comp := First_Entity (Type_To_Use);
3026 end if;
3028 while Present (Comp) loop
3029 if Chars (Comp) = Chars (Sel) then
3030 if Ekind (Comp) = E_Discriminant then
3031 Set_Entity_With_Style_Check (Sel, Comp);
3032 Generate_Reference (Comp, Sel);
3034 Set_Etype (Sel, Etype (Comp));
3035 Set_Etype (N, Etype (Comp));
3037 if Is_Generic_Type (Prefix_Type)
3038 or else
3039 Is_Generic_Type (Root_Type (Prefix_Type))
3040 then
3041 Set_Original_Discriminant (Sel, Comp);
3042 end if;
3044 -- Before declararing an error, check whether this is tagged
3045 -- private type and a call to a primitive operation.
3047 elsif Ada_Version >= Ada_05
3048 and then Is_Tagged_Type (Prefix_Type)
3049 and then Try_Object_Operation (N)
3050 then
3051 return;
3053 else
3054 Error_Msg_NE
3055 ("invisible selector for }",
3056 N, First_Subtype (Prefix_Type));
3057 Set_Entity (Sel, Any_Id);
3058 Set_Etype (N, Any_Type);
3059 end if;
3061 return;
3062 end if;
3064 Next_Entity (Comp);
3065 end loop;
3067 elsif Is_Concurrent_Type (Prefix_Type) then
3069 -- Prefix is concurrent type. Find visible operation with given name
3070 -- For a task, this can only include entries or discriminants if the
3071 -- task type is not an enclosing scope. If it is an enclosing scope
3072 -- (e.g. in an inner task) then all entities are visible, but the
3073 -- prefix must denote the enclosing scope, i.e. can only be a direct
3074 -- name or an expanded name.
3076 Set_Etype (Sel, Any_Type);
3077 In_Scope := In_Open_Scopes (Prefix_Type);
3079 while Present (Comp) loop
3080 if Chars (Comp) = Chars (Sel) then
3081 if Is_Overloadable (Comp) then
3082 Add_One_Interp (Sel, Comp, Etype (Comp));
3084 elsif Ekind (Comp) = E_Discriminant
3085 or else Ekind (Comp) = E_Entry_Family
3086 or else (In_Scope
3087 and then Is_Entity_Name (Name))
3088 then
3089 Set_Entity_With_Style_Check (Sel, Comp);
3090 Generate_Reference (Comp, Sel);
3092 else
3093 goto Next_Comp;
3094 end if;
3096 Set_Etype (Sel, Etype (Comp));
3097 Set_Etype (N, Etype (Comp));
3099 if Ekind (Comp) = E_Discriminant then
3100 Set_Original_Discriminant (Sel, Comp);
3101 end if;
3103 -- For access type case, introduce explicit deference for more
3104 -- uniform treatment of entry calls.
3106 if Is_Access_Type (Etype (Name)) then
3107 Insert_Explicit_Dereference (Name);
3108 Error_Msg_NW
3109 (Warn_On_Dereference, "?implicit dereference", N);
3110 end if;
3111 end if;
3113 <<Next_Comp>>
3114 Next_Entity (Comp);
3115 exit when not In_Scope
3116 and then
3117 Comp = First_Private_Entity (Base_Type (Prefix_Type));
3118 end loop;
3120 -- If there is no visible entry with the given name, and the task
3121 -- implements an interface, check whether there is some other
3122 -- primitive operation with that name.
3124 if Ada_Version >= Ada_05
3125 and then Is_Tagged_Type (Prefix_Type)
3126 then
3127 if Etype (N) = Any_Type
3128 and then Try_Object_Operation (N)
3129 then
3130 return;
3132 -- If the context is not syntactically a procedure call, it
3133 -- may be a call to a primitive function declared outside of
3134 -- the synchronized type.
3136 -- If the context is a procedure call, there might still be
3137 -- an overloading between an entry and a primitive procedure
3138 -- declared outside of the synchronized type, called in prefix
3139 -- notation. This is harder to disambiguate because in one case
3140 -- the controlling formal is implicit ???
3142 elsif Nkind (Parent (N)) /= N_Procedure_Call_Statement
3143 and then Try_Object_Operation (N)
3144 then
3145 return;
3146 end if;
3147 end if;
3149 Set_Is_Overloaded (N, Is_Overloaded (Sel));
3151 else
3152 -- Invalid prefix
3154 Error_Msg_NE ("invalid prefix in selected component&", N, Sel);
3155 end if;
3157 -- If N still has no type, the component is not defined in the prefix
3159 if Etype (N) = Any_Type then
3161 -- If the prefix is a single concurrent object, use its name in the
3162 -- error message, rather than that of its anonymous type.
3164 if Is_Concurrent_Type (Prefix_Type)
3165 and then Is_Internal_Name (Chars (Prefix_Type))
3166 and then not Is_Derived_Type (Prefix_Type)
3167 and then Is_Entity_Name (Name)
3168 then
3170 Error_Msg_Node_2 := Entity (Name);
3171 Error_Msg_NE ("no selector& for&", N, Sel);
3173 Check_Misspelled_Selector (Type_To_Use, Sel);
3175 elsif Is_Generic_Type (Prefix_Type)
3176 and then Ekind (Prefix_Type) = E_Record_Type_With_Private
3177 and then Prefix_Type /= Etype (Prefix_Type)
3178 and then Is_Record_Type (Etype (Prefix_Type))
3179 then
3180 -- If this is a derived formal type, the parent may have
3181 -- different visibility at this point. Try for an inherited
3182 -- component before reporting an error.
3184 Set_Etype (Prefix (N), Etype (Prefix_Type));
3185 Analyze_Selected_Component (N);
3186 return;
3188 elsif Ekind (Prefix_Type) = E_Record_Subtype_With_Private
3189 and then Is_Generic_Actual_Type (Prefix_Type)
3190 and then Present (Full_View (Prefix_Type))
3191 then
3192 -- Similarly, if this the actual for a formal derived type, the
3193 -- component inherited from the generic parent may not be visible
3194 -- in the actual, but the selected component is legal.
3196 declare
3197 Comp : Entity_Id;
3199 begin
3200 Comp :=
3201 First_Component (Generic_Parent_Type (Parent (Prefix_Type)));
3202 while Present (Comp) loop
3203 if Chars (Comp) = Chars (Sel) then
3204 Set_Entity_With_Style_Check (Sel, Comp);
3205 Set_Etype (Sel, Etype (Comp));
3206 Set_Etype (N, Etype (Comp));
3207 return;
3208 end if;
3210 Next_Component (Comp);
3211 end loop;
3213 pragma Assert (Etype (N) /= Any_Type);
3214 end;
3216 else
3217 if Ekind (Prefix_Type) = E_Record_Subtype then
3219 -- Check whether this is a component of the base type
3220 -- which is absent from a statically constrained subtype.
3221 -- This will raise constraint error at run-time, but is
3222 -- not a compile-time error. When the selector is illegal
3223 -- for base type as well fall through and generate a
3224 -- compilation error anyway.
3226 Comp := First_Component (Base_Type (Prefix_Type));
3227 while Present (Comp) loop
3228 if Chars (Comp) = Chars (Sel)
3229 and then Is_Visible_Component (Comp)
3230 then
3231 Set_Entity_With_Style_Check (Sel, Comp);
3232 Generate_Reference (Comp, Sel);
3233 Set_Etype (Sel, Etype (Comp));
3234 Set_Etype (N, Etype (Comp));
3236 -- Emit appropriate message. Gigi will replace the
3237 -- node subsequently with the appropriate Raise.
3239 Apply_Compile_Time_Constraint_Error
3240 (N, "component not present in }?",
3241 CE_Discriminant_Check_Failed,
3242 Ent => Prefix_Type, Rep => False);
3243 Set_Raises_Constraint_Error (N);
3244 return;
3245 end if;
3247 Next_Component (Comp);
3248 end loop;
3250 end if;
3252 Error_Msg_Node_2 := First_Subtype (Prefix_Type);
3253 Error_Msg_NE ("no selector& for}", N, Sel);
3255 Check_Misspelled_Selector (Type_To_Use, Sel);
3257 end if;
3259 Set_Entity (Sel, Any_Id);
3260 Set_Etype (Sel, Any_Type);
3261 end if;
3262 end Analyze_Selected_Component;
3264 ---------------------------
3265 -- Analyze_Short_Circuit --
3266 ---------------------------
3268 procedure Analyze_Short_Circuit (N : Node_Id) is
3269 L : constant Node_Id := Left_Opnd (N);
3270 R : constant Node_Id := Right_Opnd (N);
3271 Ind : Interp_Index;
3272 It : Interp;
3274 begin
3275 Analyze_Expression (L);
3276 Analyze_Expression (R);
3277 Set_Etype (N, Any_Type);
3279 if not Is_Overloaded (L) then
3281 if Root_Type (Etype (L)) = Standard_Boolean
3282 and then Has_Compatible_Type (R, Etype (L))
3283 then
3284 Add_One_Interp (N, Etype (L), Etype (L));
3285 end if;
3287 else
3288 Get_First_Interp (L, Ind, It);
3289 while Present (It.Typ) loop
3290 if Root_Type (It.Typ) = Standard_Boolean
3291 and then Has_Compatible_Type (R, It.Typ)
3292 then
3293 Add_One_Interp (N, It.Typ, It.Typ);
3294 end if;
3296 Get_Next_Interp (Ind, It);
3297 end loop;
3298 end if;
3300 -- Here we have failed to find an interpretation. Clearly we
3301 -- know that it is not the case that both operands can have
3302 -- an interpretation of Boolean, but this is by far the most
3303 -- likely intended interpretation. So we simply resolve both
3304 -- operands as Booleans, and at least one of these resolutions
3305 -- will generate an error message, and we do not need to give
3306 -- a further error message on the short circuit operation itself.
3308 if Etype (N) = Any_Type then
3309 Resolve (L, Standard_Boolean);
3310 Resolve (R, Standard_Boolean);
3311 Set_Etype (N, Standard_Boolean);
3312 end if;
3313 end Analyze_Short_Circuit;
3315 -------------------
3316 -- Analyze_Slice --
3317 -------------------
3319 procedure Analyze_Slice (N : Node_Id) is
3320 P : constant Node_Id := Prefix (N);
3321 D : constant Node_Id := Discrete_Range (N);
3322 Array_Type : Entity_Id;
3324 procedure Analyze_Overloaded_Slice;
3325 -- If the prefix is overloaded, select those interpretations that
3326 -- yield a one-dimensional array type.
3328 ------------------------------
3329 -- Analyze_Overloaded_Slice --
3330 ------------------------------
3332 procedure Analyze_Overloaded_Slice is
3333 I : Interp_Index;
3334 It : Interp;
3335 Typ : Entity_Id;
3337 begin
3338 Set_Etype (N, Any_Type);
3340 Get_First_Interp (P, I, It);
3341 while Present (It.Nam) loop
3342 Typ := It.Typ;
3344 if Is_Access_Type (Typ) then
3345 Typ := Designated_Type (Typ);
3346 Error_Msg_NW (Warn_On_Dereference, "?implicit dereference", N);
3347 end if;
3349 if Is_Array_Type (Typ)
3350 and then Number_Dimensions (Typ) = 1
3351 and then Has_Compatible_Type (D, Etype (First_Index (Typ)))
3352 then
3353 Add_One_Interp (N, Typ, Typ);
3354 end if;
3356 Get_Next_Interp (I, It);
3357 end loop;
3359 if Etype (N) = Any_Type then
3360 Error_Msg_N ("expect array type in prefix of slice", N);
3361 end if;
3362 end Analyze_Overloaded_Slice;
3364 -- Start of processing for Analyze_Slice
3366 begin
3367 Analyze (P);
3368 Analyze (D);
3370 if Is_Overloaded (P) then
3371 Analyze_Overloaded_Slice;
3373 else
3374 Array_Type := Etype (P);
3375 Set_Etype (N, Any_Type);
3377 if Is_Access_Type (Array_Type) then
3378 Array_Type := Designated_Type (Array_Type);
3379 Error_Msg_NW (Warn_On_Dereference, "?implicit dereference", N);
3380 end if;
3382 if not Is_Array_Type (Array_Type) then
3383 Wrong_Type (P, Any_Array);
3385 elsif Number_Dimensions (Array_Type) > 1 then
3386 Error_Msg_N
3387 ("type is not one-dimensional array in slice prefix", N);
3389 elsif not
3390 Has_Compatible_Type (D, Etype (First_Index (Array_Type)))
3391 then
3392 Wrong_Type (D, Etype (First_Index (Array_Type)));
3394 else
3395 Set_Etype (N, Array_Type);
3396 end if;
3397 end if;
3398 end Analyze_Slice;
3400 -----------------------------
3401 -- Analyze_Type_Conversion --
3402 -----------------------------
3404 procedure Analyze_Type_Conversion (N : Node_Id) is
3405 Expr : constant Node_Id := Expression (N);
3406 T : Entity_Id;
3408 begin
3409 -- If Conversion_OK is set, then the Etype is already set, and the
3410 -- only processing required is to analyze the expression. This is
3411 -- used to construct certain "illegal" conversions which are not
3412 -- allowed by Ada semantics, but can be handled OK by Gigi, see
3413 -- Sinfo for further details.
3415 if Conversion_OK (N) then
3416 Analyze (Expr);
3417 return;
3418 end if;
3420 -- Otherwise full type analysis is required, as well as some semantic
3421 -- checks to make sure the argument of the conversion is appropriate.
3423 Find_Type (Subtype_Mark (N));
3424 T := Entity (Subtype_Mark (N));
3425 Set_Etype (N, T);
3426 Check_Fully_Declared (T, N);
3427 Analyze_Expression (Expr);
3428 Validate_Remote_Type_Type_Conversion (N);
3430 -- Only remaining step is validity checks on the argument. These
3431 -- are skipped if the conversion does not come from the source.
3433 if not Comes_From_Source (N) then
3434 return;
3436 -- If there was an error in a generic unit, no need to replicate the
3437 -- error message. Conversely, constant-folding in the generic may
3438 -- transform the argument of a conversion into a string literal, which
3439 -- is legal. Therefore the following tests are not performed in an
3440 -- instance.
3442 elsif In_Instance then
3443 return;
3445 elsif Nkind (Expr) = N_Null then
3446 Error_Msg_N ("argument of conversion cannot be null", N);
3447 Error_Msg_N ("\use qualified expression instead", N);
3448 Set_Etype (N, Any_Type);
3450 elsif Nkind (Expr) = N_Aggregate then
3451 Error_Msg_N ("argument of conversion cannot be aggregate", N);
3452 Error_Msg_N ("\use qualified expression instead", N);
3454 elsif Nkind (Expr) = N_Allocator then
3455 Error_Msg_N ("argument of conversion cannot be an allocator", N);
3456 Error_Msg_N ("\use qualified expression instead", N);
3458 elsif Nkind (Expr) = N_String_Literal then
3459 Error_Msg_N ("argument of conversion cannot be string literal", N);
3460 Error_Msg_N ("\use qualified expression instead", N);
3462 elsif Nkind (Expr) = N_Character_Literal then
3463 if Ada_Version = Ada_83 then
3464 Resolve (Expr, T);
3465 else
3466 Error_Msg_N ("argument of conversion cannot be character literal",
3468 Error_Msg_N ("\use qualified expression instead", N);
3469 end if;
3471 elsif Nkind (Expr) = N_Attribute_Reference
3472 and then
3473 (Attribute_Name (Expr) = Name_Access or else
3474 Attribute_Name (Expr) = Name_Unchecked_Access or else
3475 Attribute_Name (Expr) = Name_Unrestricted_Access)
3476 then
3477 Error_Msg_N ("argument of conversion cannot be access", N);
3478 Error_Msg_N ("\use qualified expression instead", N);
3479 end if;
3480 end Analyze_Type_Conversion;
3482 ----------------------
3483 -- Analyze_Unary_Op --
3484 ----------------------
3486 procedure Analyze_Unary_Op (N : Node_Id) is
3487 R : constant Node_Id := Right_Opnd (N);
3488 Op_Id : Entity_Id := Entity (N);
3490 begin
3491 Set_Etype (N, Any_Type);
3492 Candidate_Type := Empty;
3494 Analyze_Expression (R);
3496 if Present (Op_Id) then
3497 if Ekind (Op_Id) = E_Operator then
3498 Find_Unary_Types (R, Op_Id, N);
3499 else
3500 Add_One_Interp (N, Op_Id, Etype (Op_Id));
3501 end if;
3503 else
3504 Op_Id := Get_Name_Entity_Id (Chars (N));
3505 while Present (Op_Id) loop
3506 if Ekind (Op_Id) = E_Operator then
3507 if No (Next_Entity (First_Entity (Op_Id))) then
3508 Find_Unary_Types (R, Op_Id, N);
3509 end if;
3511 elsif Is_Overloadable (Op_Id) then
3512 Analyze_User_Defined_Unary_Op (N, Op_Id);
3513 end if;
3515 Op_Id := Homonym (Op_Id);
3516 end loop;
3517 end if;
3519 Operator_Check (N);
3520 end Analyze_Unary_Op;
3522 ----------------------------------
3523 -- Analyze_Unchecked_Expression --
3524 ----------------------------------
3526 procedure Analyze_Unchecked_Expression (N : Node_Id) is
3527 begin
3528 Analyze (Expression (N), Suppress => All_Checks);
3529 Set_Etype (N, Etype (Expression (N)));
3530 Save_Interps (Expression (N), N);
3531 end Analyze_Unchecked_Expression;
3533 ---------------------------------------
3534 -- Analyze_Unchecked_Type_Conversion --
3535 ---------------------------------------
3537 procedure Analyze_Unchecked_Type_Conversion (N : Node_Id) is
3538 begin
3539 Find_Type (Subtype_Mark (N));
3540 Analyze_Expression (Expression (N));
3541 Set_Etype (N, Entity (Subtype_Mark (N)));
3542 end Analyze_Unchecked_Type_Conversion;
3544 ------------------------------------
3545 -- Analyze_User_Defined_Binary_Op --
3546 ------------------------------------
3548 procedure Analyze_User_Defined_Binary_Op
3549 (N : Node_Id;
3550 Op_Id : Entity_Id)
3552 begin
3553 -- Only do analysis if the operator Comes_From_Source, since otherwise
3554 -- the operator was generated by the expander, and all such operators
3555 -- always refer to the operators in package Standard.
3557 if Comes_From_Source (N) then
3558 declare
3559 F1 : constant Entity_Id := First_Formal (Op_Id);
3560 F2 : constant Entity_Id := Next_Formal (F1);
3562 begin
3563 -- Verify that Op_Id is a visible binary function. Note that since
3564 -- we know Op_Id is overloaded, potentially use visible means use
3565 -- visible for sure (RM 9.4(11)).
3567 if Ekind (Op_Id) = E_Function
3568 and then Present (F2)
3569 and then (Is_Immediately_Visible (Op_Id)
3570 or else Is_Potentially_Use_Visible (Op_Id))
3571 and then Has_Compatible_Type (Left_Opnd (N), Etype (F1))
3572 and then Has_Compatible_Type (Right_Opnd (N), Etype (F2))
3573 then
3574 Add_One_Interp (N, Op_Id, Etype (Op_Id));
3576 if Debug_Flag_E then
3577 Write_Str ("user defined operator ");
3578 Write_Name (Chars (Op_Id));
3579 Write_Str (" on node ");
3580 Write_Int (Int (N));
3581 Write_Eol;
3582 end if;
3583 end if;
3584 end;
3585 end if;
3586 end Analyze_User_Defined_Binary_Op;
3588 -----------------------------------
3589 -- Analyze_User_Defined_Unary_Op --
3590 -----------------------------------
3592 procedure Analyze_User_Defined_Unary_Op
3593 (N : Node_Id;
3594 Op_Id : Entity_Id)
3596 begin
3597 -- Only do analysis if the operator Comes_From_Source, since otherwise
3598 -- the operator was generated by the expander, and all such operators
3599 -- always refer to the operators in package Standard.
3601 if Comes_From_Source (N) then
3602 declare
3603 F : constant Entity_Id := First_Formal (Op_Id);
3605 begin
3606 -- Verify that Op_Id is a visible unary function. Note that since
3607 -- we know Op_Id is overloaded, potentially use visible means use
3608 -- visible for sure (RM 9.4(11)).
3610 if Ekind (Op_Id) = E_Function
3611 and then No (Next_Formal (F))
3612 and then (Is_Immediately_Visible (Op_Id)
3613 or else Is_Potentially_Use_Visible (Op_Id))
3614 and then Has_Compatible_Type (Right_Opnd (N), Etype (F))
3615 then
3616 Add_One_Interp (N, Op_Id, Etype (Op_Id));
3617 end if;
3618 end;
3619 end if;
3620 end Analyze_User_Defined_Unary_Op;
3622 ---------------------------
3623 -- Check_Arithmetic_Pair --
3624 ---------------------------
3626 procedure Check_Arithmetic_Pair
3627 (T1, T2 : Entity_Id;
3628 Op_Id : Entity_Id;
3629 N : Node_Id)
3631 Op_Name : constant Name_Id := Chars (Op_Id);
3633 function Has_Fixed_Op (Typ : Entity_Id; Op : Entity_Id) return Boolean;
3634 -- Check whether the fixed-point type Typ has a user-defined operator
3635 -- (multiplication or division) that should hide the corresponding
3636 -- predefined operator. Used to implement Ada 2005 AI-264, to make
3637 -- such operators more visible and therefore useful.
3639 function Specific_Type (T1, T2 : Entity_Id) return Entity_Id;
3640 -- Get specific type (i.e. non-universal type if there is one)
3642 ------------------
3643 -- Has_Fixed_Op --
3644 ------------------
3646 function Has_Fixed_Op (Typ : Entity_Id; Op : Entity_Id) return Boolean is
3647 Bas : constant Entity_Id := Base_Type (Typ);
3648 Ent : Entity_Id;
3649 F1 : Entity_Id;
3650 F2 : Entity_Id;
3652 begin
3653 -- The operation is treated as primitive if it is declared in the
3654 -- same scope as the type, and therefore on the same entity chain.
3656 Ent := Next_Entity (Typ);
3657 while Present (Ent) loop
3658 if Chars (Ent) = Chars (Op) then
3659 F1 := First_Formal (Ent);
3660 F2 := Next_Formal (F1);
3662 -- The operation counts as primitive if either operand or
3663 -- result are of the given base type, and both operands are
3664 -- fixed point types.
3666 if (Base_Type (Etype (F1)) = Bas
3667 and then Is_Fixed_Point_Type (Etype (F2)))
3669 or else
3670 (Base_Type (Etype (F2)) = Bas
3671 and then Is_Fixed_Point_Type (Etype (F1)))
3673 or else
3674 (Base_Type (Etype (Ent)) = Bas
3675 and then Is_Fixed_Point_Type (Etype (F1))
3676 and then Is_Fixed_Point_Type (Etype (F2)))
3677 then
3678 return True;
3679 end if;
3680 end if;
3682 Next_Entity (Ent);
3683 end loop;
3685 return False;
3686 end Has_Fixed_Op;
3688 -------------------
3689 -- Specific_Type --
3690 -------------------
3692 function Specific_Type (T1, T2 : Entity_Id) return Entity_Id is
3693 begin
3694 if T1 = Universal_Integer or else T1 = Universal_Real then
3695 return Base_Type (T2);
3696 else
3697 return Base_Type (T1);
3698 end if;
3699 end Specific_Type;
3701 -- Start of processing for Check_Arithmetic_Pair
3703 begin
3704 if Op_Name = Name_Op_Add or else Op_Name = Name_Op_Subtract then
3706 if Is_Numeric_Type (T1)
3707 and then Is_Numeric_Type (T2)
3708 and then (Covers (T1, T2) or else Covers (T2, T1))
3709 then
3710 Add_One_Interp (N, Op_Id, Specific_Type (T1, T2));
3711 end if;
3713 elsif Op_Name = Name_Op_Multiply or else Op_Name = Name_Op_Divide then
3715 if Is_Fixed_Point_Type (T1)
3716 and then (Is_Fixed_Point_Type (T2)
3717 or else T2 = Universal_Real)
3718 then
3719 -- If Treat_Fixed_As_Integer is set then the Etype is already set
3720 -- and no further processing is required (this is the case of an
3721 -- operator constructed by Exp_Fixd for a fixed point operation)
3722 -- Otherwise add one interpretation with universal fixed result
3723 -- If the operator is given in functional notation, it comes
3724 -- from source and Fixed_As_Integer cannot apply.
3726 if (Nkind (N) not in N_Op
3727 or else not Treat_Fixed_As_Integer (N))
3728 and then
3729 (not Has_Fixed_Op (T1, Op_Id)
3730 or else Nkind (Parent (N)) = N_Type_Conversion)
3731 then
3732 Add_One_Interp (N, Op_Id, Universal_Fixed);
3733 end if;
3735 elsif Is_Fixed_Point_Type (T2)
3736 and then (Nkind (N) not in N_Op
3737 or else not Treat_Fixed_As_Integer (N))
3738 and then T1 = Universal_Real
3739 and then
3740 (not Has_Fixed_Op (T1, Op_Id)
3741 or else Nkind (Parent (N)) = N_Type_Conversion)
3742 then
3743 Add_One_Interp (N, Op_Id, Universal_Fixed);
3745 elsif Is_Numeric_Type (T1)
3746 and then Is_Numeric_Type (T2)
3747 and then (Covers (T1, T2) or else Covers (T2, T1))
3748 then
3749 Add_One_Interp (N, Op_Id, Specific_Type (T1, T2));
3751 elsif Is_Fixed_Point_Type (T1)
3752 and then (Base_Type (T2) = Base_Type (Standard_Integer)
3753 or else T2 = Universal_Integer)
3754 then
3755 Add_One_Interp (N, Op_Id, T1);
3757 elsif T2 = Universal_Real
3758 and then Base_Type (T1) = Base_Type (Standard_Integer)
3759 and then Op_Name = Name_Op_Multiply
3760 then
3761 Add_One_Interp (N, Op_Id, Any_Fixed);
3763 elsif T1 = Universal_Real
3764 and then Base_Type (T2) = Base_Type (Standard_Integer)
3765 then
3766 Add_One_Interp (N, Op_Id, Any_Fixed);
3768 elsif Is_Fixed_Point_Type (T2)
3769 and then (Base_Type (T1) = Base_Type (Standard_Integer)
3770 or else T1 = Universal_Integer)
3771 and then Op_Name = Name_Op_Multiply
3772 then
3773 Add_One_Interp (N, Op_Id, T2);
3775 elsif T1 = Universal_Real and then T2 = Universal_Integer then
3776 Add_One_Interp (N, Op_Id, T1);
3778 elsif T2 = Universal_Real
3779 and then T1 = Universal_Integer
3780 and then Op_Name = Name_Op_Multiply
3781 then
3782 Add_One_Interp (N, Op_Id, T2);
3783 end if;
3785 elsif Op_Name = Name_Op_Mod or else Op_Name = Name_Op_Rem then
3787 -- Note: The fixed-point operands case with Treat_Fixed_As_Integer
3788 -- set does not require any special processing, since the Etype is
3789 -- already set (case of operation constructed by Exp_Fixed).
3791 if Is_Integer_Type (T1)
3792 and then (Covers (T1, T2) or else Covers (T2, T1))
3793 then
3794 Add_One_Interp (N, Op_Id, Specific_Type (T1, T2));
3795 end if;
3797 elsif Op_Name = Name_Op_Expon then
3798 if Is_Numeric_Type (T1)
3799 and then not Is_Fixed_Point_Type (T1)
3800 and then (Base_Type (T2) = Base_Type (Standard_Integer)
3801 or else T2 = Universal_Integer)
3802 then
3803 Add_One_Interp (N, Op_Id, Base_Type (T1));
3804 end if;
3806 else pragma Assert (Nkind (N) in N_Op_Shift);
3808 -- If not one of the predefined operators, the node may be one
3809 -- of the intrinsic functions. Its kind is always specific, and
3810 -- we can use it directly, rather than the name of the operation.
3812 if Is_Integer_Type (T1)
3813 and then (Base_Type (T2) = Base_Type (Standard_Integer)
3814 or else T2 = Universal_Integer)
3815 then
3816 Add_One_Interp (N, Op_Id, Base_Type (T1));
3817 end if;
3818 end if;
3819 end Check_Arithmetic_Pair;
3821 -------------------------------
3822 -- Check_Misspelled_Selector --
3823 -------------------------------
3825 procedure Check_Misspelled_Selector
3826 (Prefix : Entity_Id;
3827 Sel : Node_Id)
3829 Max_Suggestions : constant := 2;
3830 Nr_Of_Suggestions : Natural := 0;
3832 Suggestion_1 : Entity_Id := Empty;
3833 Suggestion_2 : Entity_Id := Empty;
3835 Comp : Entity_Id;
3837 begin
3838 -- All the components of the prefix of selector Sel are matched
3839 -- against Sel and a count is maintained of possible misspellings.
3840 -- When at the end of the analysis there are one or two (not more!)
3841 -- possible misspellings, these misspellings will be suggested as
3842 -- possible correction.
3844 if not (Is_Private_Type (Prefix) or else Is_Record_Type (Prefix)) then
3846 -- Concurrent types should be handled as well ???
3848 return;
3849 end if;
3851 Get_Name_String (Chars (Sel));
3853 declare
3854 S : constant String (1 .. Name_Len) := Name_Buffer (1 .. Name_Len);
3856 begin
3857 Comp := First_Entity (Prefix);
3858 while Nr_Of_Suggestions <= Max_Suggestions
3859 and then Present (Comp)
3860 loop
3861 if Is_Visible_Component (Comp) then
3862 Get_Name_String (Chars (Comp));
3864 if Is_Bad_Spelling_Of (Name_Buffer (1 .. Name_Len), S) then
3865 Nr_Of_Suggestions := Nr_Of_Suggestions + 1;
3867 case Nr_Of_Suggestions is
3868 when 1 => Suggestion_1 := Comp;
3869 when 2 => Suggestion_2 := Comp;
3870 when others => exit;
3871 end case;
3872 end if;
3873 end if;
3875 Comp := Next_Entity (Comp);
3876 end loop;
3878 -- Report at most two suggestions
3880 if Nr_Of_Suggestions = 1 then
3881 Error_Msg_NE ("\possible misspelling of&", Sel, Suggestion_1);
3883 elsif Nr_Of_Suggestions = 2 then
3884 Error_Msg_Node_2 := Suggestion_2;
3885 Error_Msg_NE ("\possible misspelling of& or&",
3886 Sel, Suggestion_1);
3887 end if;
3888 end;
3889 end Check_Misspelled_Selector;
3891 ----------------------
3892 -- Defined_In_Scope --
3893 ----------------------
3895 function Defined_In_Scope (T : Entity_Id; S : Entity_Id) return Boolean
3897 S1 : constant Entity_Id := Scope (Base_Type (T));
3898 begin
3899 return S1 = S
3900 or else (S1 = System_Aux_Id and then S = Scope (S1));
3901 end Defined_In_Scope;
3903 -------------------
3904 -- Diagnose_Call --
3905 -------------------
3907 procedure Diagnose_Call (N : Node_Id; Nam : Node_Id) is
3908 Actual : Node_Id;
3909 X : Interp_Index;
3910 It : Interp;
3911 Success : Boolean;
3912 Err_Mode : Boolean;
3913 New_Nam : Node_Id;
3914 Void_Interp_Seen : Boolean := False;
3916 begin
3917 if Ada_Version >= Ada_05 then
3918 Actual := First_Actual (N);
3919 while Present (Actual) loop
3921 -- Ada 2005 (AI-50217): Post an error in case of premature
3922 -- usage of an entity from the limited view.
3924 if not Analyzed (Etype (Actual))
3925 and then From_With_Type (Etype (Actual))
3926 then
3927 Error_Msg_Qual_Level := 1;
3928 Error_Msg_NE
3929 ("missing with_clause for scope of imported type&",
3930 Actual, Etype (Actual));
3931 Error_Msg_Qual_Level := 0;
3932 end if;
3934 Next_Actual (Actual);
3935 end loop;
3936 end if;
3938 -- Analyze each candidate call again, with full error reporting
3939 -- for each.
3941 Error_Msg_N
3942 ("no candidate interpretations match the actuals:!", Nam);
3943 Err_Mode := All_Errors_Mode;
3944 All_Errors_Mode := True;
3946 -- If this is a call to an operation of a concurrent type,
3947 -- the failed interpretations have been removed from the
3948 -- name. Recover them to provide full diagnostics.
3950 if Nkind (Parent (Nam)) = N_Selected_Component then
3951 Set_Entity (Nam, Empty);
3952 New_Nam := New_Copy_Tree (Parent (Nam));
3953 Set_Is_Overloaded (New_Nam, False);
3954 Set_Is_Overloaded (Selector_Name (New_Nam), False);
3955 Set_Parent (New_Nam, Parent (Parent (Nam)));
3956 Analyze_Selected_Component (New_Nam);
3957 Get_First_Interp (Selector_Name (New_Nam), X, It);
3958 else
3959 Get_First_Interp (Nam, X, It);
3960 end if;
3962 while Present (It.Nam) loop
3963 if Etype (It.Nam) = Standard_Void_Type then
3964 Void_Interp_Seen := True;
3965 end if;
3967 Analyze_One_Call (N, It.Nam, True, Success);
3968 Get_Next_Interp (X, It);
3969 end loop;
3971 if Nkind (N) = N_Function_Call then
3972 Get_First_Interp (Nam, X, It);
3973 while Present (It.Nam) loop
3974 if Ekind (It.Nam) = E_Function
3975 or else Ekind (It.Nam) = E_Operator
3976 then
3977 return;
3978 else
3979 Get_Next_Interp (X, It);
3980 end if;
3981 end loop;
3983 -- If all interpretations are procedures, this deserves a
3984 -- more precise message. Ditto if this appears as the prefix
3985 -- of a selected component, which may be a lexical error.
3987 Error_Msg_N
3988 ("\context requires function call, found procedure name", Nam);
3990 if Nkind (Parent (N)) = N_Selected_Component
3991 and then N = Prefix (Parent (N))
3992 then
3993 Error_Msg_N (
3994 "\period should probably be semicolon", Parent (N));
3995 end if;
3997 elsif Nkind (N) = N_Procedure_Call_Statement
3998 and then not Void_Interp_Seen
3999 then
4000 Error_Msg_N (
4001 "\function name found in procedure call", Nam);
4002 end if;
4004 All_Errors_Mode := Err_Mode;
4005 end Diagnose_Call;
4007 ---------------------------
4008 -- Find_Arithmetic_Types --
4009 ---------------------------
4011 procedure Find_Arithmetic_Types
4012 (L, R : Node_Id;
4013 Op_Id : Entity_Id;
4014 N : Node_Id)
4016 Index1 : Interp_Index;
4017 Index2 : Interp_Index;
4018 It1 : Interp;
4019 It2 : Interp;
4021 procedure Check_Right_Argument (T : Entity_Id);
4022 -- Check right operand of operator
4024 --------------------------
4025 -- Check_Right_Argument --
4026 --------------------------
4028 procedure Check_Right_Argument (T : Entity_Id) is
4029 begin
4030 if not Is_Overloaded (R) then
4031 Check_Arithmetic_Pair (T, Etype (R), Op_Id, N);
4032 else
4033 Get_First_Interp (R, Index2, It2);
4034 while Present (It2.Typ) loop
4035 Check_Arithmetic_Pair (T, It2.Typ, Op_Id, N);
4036 Get_Next_Interp (Index2, It2);
4037 end loop;
4038 end if;
4039 end Check_Right_Argument;
4041 -- Start processing for Find_Arithmetic_Types
4043 begin
4044 if not Is_Overloaded (L) then
4045 Check_Right_Argument (Etype (L));
4047 else
4048 Get_First_Interp (L, Index1, It1);
4049 while Present (It1.Typ) loop
4050 Check_Right_Argument (It1.Typ);
4051 Get_Next_Interp (Index1, It1);
4052 end loop;
4053 end if;
4055 end Find_Arithmetic_Types;
4057 ------------------------
4058 -- Find_Boolean_Types --
4059 ------------------------
4061 procedure Find_Boolean_Types
4062 (L, R : Node_Id;
4063 Op_Id : Entity_Id;
4064 N : Node_Id)
4066 Index : Interp_Index;
4067 It : Interp;
4069 procedure Check_Numeric_Argument (T : Entity_Id);
4070 -- Special case for logical operations one of whose operands is an
4071 -- integer literal. If both are literal the result is any modular type.
4073 ----------------------------
4074 -- Check_Numeric_Argument --
4075 ----------------------------
4077 procedure Check_Numeric_Argument (T : Entity_Id) is
4078 begin
4079 if T = Universal_Integer then
4080 Add_One_Interp (N, Op_Id, Any_Modular);
4082 elsif Is_Modular_Integer_Type (T) then
4083 Add_One_Interp (N, Op_Id, T);
4084 end if;
4085 end Check_Numeric_Argument;
4087 -- Start of processing for Find_Boolean_Types
4089 begin
4090 if not Is_Overloaded (L) then
4091 if Etype (L) = Universal_Integer
4092 or else Etype (L) = Any_Modular
4093 then
4094 if not Is_Overloaded (R) then
4095 Check_Numeric_Argument (Etype (R));
4097 else
4098 Get_First_Interp (R, Index, It);
4099 while Present (It.Typ) loop
4100 Check_Numeric_Argument (It.Typ);
4101 Get_Next_Interp (Index, It);
4102 end loop;
4103 end if;
4105 -- If operands are aggregates, we must assume that they may be
4106 -- boolean arrays, and leave disambiguation for the second pass.
4107 -- If only one is an aggregate, verify that the other one has an
4108 -- interpretation as a boolean array
4110 elsif Nkind (L) = N_Aggregate then
4111 if Nkind (R) = N_Aggregate then
4112 Add_One_Interp (N, Op_Id, Etype (L));
4114 elsif not Is_Overloaded (R) then
4115 if Valid_Boolean_Arg (Etype (R)) then
4116 Add_One_Interp (N, Op_Id, Etype (R));
4117 end if;
4119 else
4120 Get_First_Interp (R, Index, It);
4121 while Present (It.Typ) loop
4122 if Valid_Boolean_Arg (It.Typ) then
4123 Add_One_Interp (N, Op_Id, It.Typ);
4124 end if;
4126 Get_Next_Interp (Index, It);
4127 end loop;
4128 end if;
4130 elsif Valid_Boolean_Arg (Etype (L))
4131 and then Has_Compatible_Type (R, Etype (L))
4132 then
4133 Add_One_Interp (N, Op_Id, Etype (L));
4134 end if;
4136 else
4137 Get_First_Interp (L, Index, It);
4138 while Present (It.Typ) loop
4139 if Valid_Boolean_Arg (It.Typ)
4140 and then Has_Compatible_Type (R, It.Typ)
4141 then
4142 Add_One_Interp (N, Op_Id, It.Typ);
4143 end if;
4145 Get_Next_Interp (Index, It);
4146 end loop;
4147 end if;
4148 end Find_Boolean_Types;
4150 ---------------------------
4151 -- Find_Comparison_Types --
4152 ---------------------------
4154 procedure Find_Comparison_Types
4155 (L, R : Node_Id;
4156 Op_Id : Entity_Id;
4157 N : Node_Id)
4159 Index : Interp_Index;
4160 It : Interp;
4161 Found : Boolean := False;
4162 I_F : Interp_Index;
4163 T_F : Entity_Id;
4164 Scop : Entity_Id := Empty;
4166 procedure Try_One_Interp (T1 : Entity_Id);
4167 -- Routine to try one proposed interpretation. Note that the context
4168 -- of the operator plays no role in resolving the arguments, so that
4169 -- if there is more than one interpretation of the operands that is
4170 -- compatible with comparison, the operation is ambiguous.
4172 --------------------
4173 -- Try_One_Interp --
4174 --------------------
4176 procedure Try_One_Interp (T1 : Entity_Id) is
4177 begin
4179 -- If the operator is an expanded name, then the type of the operand
4180 -- must be defined in the corresponding scope. If the type is
4181 -- universal, the context will impose the correct type.
4183 if Present (Scop)
4184 and then not Defined_In_Scope (T1, Scop)
4185 and then T1 /= Universal_Integer
4186 and then T1 /= Universal_Real
4187 and then T1 /= Any_String
4188 and then T1 /= Any_Composite
4189 then
4190 return;
4191 end if;
4193 if Valid_Comparison_Arg (T1)
4194 and then Has_Compatible_Type (R, T1)
4195 then
4196 if Found
4197 and then Base_Type (T1) /= Base_Type (T_F)
4198 then
4199 It := Disambiguate (L, I_F, Index, Any_Type);
4201 if It = No_Interp then
4202 Ambiguous_Operands (N);
4203 Set_Etype (L, Any_Type);
4204 return;
4206 else
4207 T_F := It.Typ;
4208 end if;
4210 else
4211 Found := True;
4212 T_F := T1;
4213 I_F := Index;
4214 end if;
4216 Set_Etype (L, T_F);
4217 Find_Non_Universal_Interpretations (N, R, Op_Id, T1);
4219 end if;
4220 end Try_One_Interp;
4222 -- Start processing for Find_Comparison_Types
4224 begin
4225 -- If left operand is aggregate, the right operand has to
4226 -- provide a usable type for it.
4228 if Nkind (L) = N_Aggregate
4229 and then Nkind (R) /= N_Aggregate
4230 then
4231 Find_Comparison_Types (R, L, Op_Id, N);
4232 return;
4233 end if;
4235 if Nkind (N) = N_Function_Call
4236 and then Nkind (Name (N)) = N_Expanded_Name
4237 then
4238 Scop := Entity (Prefix (Name (N)));
4240 -- The prefix may be a package renaming, and the subsequent test
4241 -- requires the original package.
4243 if Ekind (Scop) = E_Package
4244 and then Present (Renamed_Entity (Scop))
4245 then
4246 Scop := Renamed_Entity (Scop);
4247 Set_Entity (Prefix (Name (N)), Scop);
4248 end if;
4249 end if;
4251 if not Is_Overloaded (L) then
4252 Try_One_Interp (Etype (L));
4254 else
4255 Get_First_Interp (L, Index, It);
4256 while Present (It.Typ) loop
4257 Try_One_Interp (It.Typ);
4258 Get_Next_Interp (Index, It);
4259 end loop;
4260 end if;
4261 end Find_Comparison_Types;
4263 ----------------------------------------
4264 -- Find_Non_Universal_Interpretations --
4265 ----------------------------------------
4267 procedure Find_Non_Universal_Interpretations
4268 (N : Node_Id;
4269 R : Node_Id;
4270 Op_Id : Entity_Id;
4271 T1 : Entity_Id)
4273 Index : Interp_Index;
4274 It : Interp;
4276 begin
4277 if T1 = Universal_Integer
4278 or else T1 = Universal_Real
4279 then
4280 if not Is_Overloaded (R) then
4281 Add_One_Interp
4282 (N, Op_Id, Standard_Boolean, Base_Type (Etype (R)));
4283 else
4284 Get_First_Interp (R, Index, It);
4285 while Present (It.Typ) loop
4286 if Covers (It.Typ, T1) then
4287 Add_One_Interp
4288 (N, Op_Id, Standard_Boolean, Base_Type (It.Typ));
4289 end if;
4291 Get_Next_Interp (Index, It);
4292 end loop;
4293 end if;
4294 else
4295 Add_One_Interp (N, Op_Id, Standard_Boolean, Base_Type (T1));
4296 end if;
4297 end Find_Non_Universal_Interpretations;
4299 ------------------------------
4300 -- Find_Concatenation_Types --
4301 ------------------------------
4303 procedure Find_Concatenation_Types
4304 (L, R : Node_Id;
4305 Op_Id : Entity_Id;
4306 N : Node_Id)
4308 Op_Type : constant Entity_Id := Etype (Op_Id);
4310 begin
4311 if Is_Array_Type (Op_Type)
4312 and then not Is_Limited_Type (Op_Type)
4314 and then (Has_Compatible_Type (L, Op_Type)
4315 or else
4316 Has_Compatible_Type (L, Component_Type (Op_Type)))
4318 and then (Has_Compatible_Type (R, Op_Type)
4319 or else
4320 Has_Compatible_Type (R, Component_Type (Op_Type)))
4321 then
4322 Add_One_Interp (N, Op_Id, Op_Type);
4323 end if;
4324 end Find_Concatenation_Types;
4326 -------------------------
4327 -- Find_Equality_Types --
4328 -------------------------
4330 procedure Find_Equality_Types
4331 (L, R : Node_Id;
4332 Op_Id : Entity_Id;
4333 N : Node_Id)
4335 Index : Interp_Index;
4336 It : Interp;
4337 Found : Boolean := False;
4338 I_F : Interp_Index;
4339 T_F : Entity_Id;
4340 Scop : Entity_Id := Empty;
4342 procedure Try_One_Interp (T1 : Entity_Id);
4343 -- The context of the operator plays no role in resolving the
4344 -- arguments, so that if there is more than one interpretation
4345 -- of the operands that is compatible with equality, the construct
4346 -- is ambiguous and an error can be emitted now, after trying to
4347 -- disambiguate, i.e. applying preference rules.
4349 --------------------
4350 -- Try_One_Interp --
4351 --------------------
4353 procedure Try_One_Interp (T1 : Entity_Id) is
4354 begin
4355 -- If the operator is an expanded name, then the type of the operand
4356 -- must be defined in the corresponding scope. If the type is
4357 -- universal, the context will impose the correct type. An anonymous
4358 -- type for a 'Access reference is also universal in this sense, as
4359 -- the actual type is obtained from context.
4360 -- In Ada 2005, the equality operator for anonymous access types
4361 -- is declared in Standard, and preference rules apply to it.
4363 if Present (Scop) then
4364 if Defined_In_Scope (T1, Scop)
4365 or else T1 = Universal_Integer
4366 or else T1 = Universal_Real
4367 or else T1 = Any_Access
4368 or else T1 = Any_String
4369 or else T1 = Any_Composite
4370 or else (Ekind (T1) = E_Access_Subprogram_Type
4371 and then not Comes_From_Source (T1))
4372 then
4373 null;
4375 elsif Ekind (T1) = E_Anonymous_Access_Type
4376 and then Scop = Standard_Standard
4377 then
4378 null;
4380 else
4381 -- The scope does not contain an operator for the type
4383 return;
4384 end if;
4385 end if;
4387 -- Ada 2005 (AI-230): Keep restriction imposed by Ada 83 and 95:
4388 -- Do not allow anonymous access types in equality operators.
4390 if Ada_Version < Ada_05
4391 and then Ekind (T1) = E_Anonymous_Access_Type
4392 then
4393 return;
4394 end if;
4396 if T1 /= Standard_Void_Type
4397 and then not Is_Limited_Type (T1)
4398 and then not Is_Limited_Composite (T1)
4399 and then Has_Compatible_Type (R, T1)
4400 then
4401 if Found
4402 and then Base_Type (T1) /= Base_Type (T_F)
4403 then
4404 It := Disambiguate (L, I_F, Index, Any_Type);
4406 if It = No_Interp then
4407 Ambiguous_Operands (N);
4408 Set_Etype (L, Any_Type);
4409 return;
4411 else
4412 T_F := It.Typ;
4413 end if;
4415 else
4416 Found := True;
4417 T_F := T1;
4418 I_F := Index;
4419 end if;
4421 if not Analyzed (L) then
4422 Set_Etype (L, T_F);
4423 end if;
4425 Find_Non_Universal_Interpretations (N, R, Op_Id, T1);
4427 -- Case of operator was not visible, Etype still set to Any_Type
4429 if Etype (N) = Any_Type then
4430 Found := False;
4431 end if;
4433 elsif Scop = Standard_Standard
4434 and then Ekind (T1) = E_Anonymous_Access_Type
4435 then
4436 Found := True;
4437 end if;
4438 end Try_One_Interp;
4440 -- Start of processing for Find_Equality_Types
4442 begin
4443 -- If left operand is aggregate, the right operand has to
4444 -- provide a usable type for it.
4446 if Nkind (L) = N_Aggregate
4447 and then Nkind (R) /= N_Aggregate
4448 then
4449 Find_Equality_Types (R, L, Op_Id, N);
4450 return;
4451 end if;
4453 if Nkind (N) = N_Function_Call
4454 and then Nkind (Name (N)) = N_Expanded_Name
4455 then
4456 Scop := Entity (Prefix (Name (N)));
4458 -- The prefix may be a package renaming, and the subsequent test
4459 -- requires the original package.
4461 if Ekind (Scop) = E_Package
4462 and then Present (Renamed_Entity (Scop))
4463 then
4464 Scop := Renamed_Entity (Scop);
4465 Set_Entity (Prefix (Name (N)), Scop);
4466 end if;
4467 end if;
4469 if not Is_Overloaded (L) then
4470 Try_One_Interp (Etype (L));
4472 else
4473 Get_First_Interp (L, Index, It);
4474 while Present (It.Typ) loop
4475 Try_One_Interp (It.Typ);
4476 Get_Next_Interp (Index, It);
4477 end loop;
4478 end if;
4479 end Find_Equality_Types;
4481 -------------------------
4482 -- Find_Negation_Types --
4483 -------------------------
4485 procedure Find_Negation_Types
4486 (R : Node_Id;
4487 Op_Id : Entity_Id;
4488 N : Node_Id)
4490 Index : Interp_Index;
4491 It : Interp;
4493 begin
4494 if not Is_Overloaded (R) then
4495 if Etype (R) = Universal_Integer then
4496 Add_One_Interp (N, Op_Id, Any_Modular);
4497 elsif Valid_Boolean_Arg (Etype (R)) then
4498 Add_One_Interp (N, Op_Id, Etype (R));
4499 end if;
4501 else
4502 Get_First_Interp (R, Index, It);
4503 while Present (It.Typ) loop
4504 if Valid_Boolean_Arg (It.Typ) then
4505 Add_One_Interp (N, Op_Id, It.Typ);
4506 end if;
4508 Get_Next_Interp (Index, It);
4509 end loop;
4510 end if;
4511 end Find_Negation_Types;
4513 ----------------------
4514 -- Find_Unary_Types --
4515 ----------------------
4517 procedure Find_Unary_Types
4518 (R : Node_Id;
4519 Op_Id : Entity_Id;
4520 N : Node_Id)
4522 Index : Interp_Index;
4523 It : Interp;
4525 begin
4526 if not Is_Overloaded (R) then
4527 if Is_Numeric_Type (Etype (R)) then
4528 Add_One_Interp (N, Op_Id, Base_Type (Etype (R)));
4529 end if;
4531 else
4532 Get_First_Interp (R, Index, It);
4533 while Present (It.Typ) loop
4534 if Is_Numeric_Type (It.Typ) then
4535 Add_One_Interp (N, Op_Id, Base_Type (It.Typ));
4536 end if;
4538 Get_Next_Interp (Index, It);
4539 end loop;
4540 end if;
4541 end Find_Unary_Types;
4543 ------------------
4544 -- Junk_Operand --
4545 ------------------
4547 function Junk_Operand (N : Node_Id) return Boolean is
4548 Enode : Node_Id;
4550 begin
4551 if Error_Posted (N) then
4552 return False;
4553 end if;
4555 -- Get entity to be tested
4557 if Is_Entity_Name (N)
4558 and then Present (Entity (N))
4559 then
4560 Enode := N;
4562 -- An odd case, a procedure name gets converted to a very peculiar
4563 -- function call, and here is where we detect this happening.
4565 elsif Nkind (N) = N_Function_Call
4566 and then Is_Entity_Name (Name (N))
4567 and then Present (Entity (Name (N)))
4568 then
4569 Enode := Name (N);
4571 -- Another odd case, there are at least some cases of selected
4572 -- components where the selected component is not marked as having
4573 -- an entity, even though the selector does have an entity
4575 elsif Nkind (N) = N_Selected_Component
4576 and then Present (Entity (Selector_Name (N)))
4577 then
4578 Enode := Selector_Name (N);
4580 else
4581 return False;
4582 end if;
4584 -- Now test the entity we got to see if it is a bad case
4586 case Ekind (Entity (Enode)) is
4588 when E_Package =>
4589 Error_Msg_N
4590 ("package name cannot be used as operand", Enode);
4592 when Generic_Unit_Kind =>
4593 Error_Msg_N
4594 ("generic unit name cannot be used as operand", Enode);
4596 when Type_Kind =>
4597 Error_Msg_N
4598 ("subtype name cannot be used as operand", Enode);
4600 when Entry_Kind =>
4601 Error_Msg_N
4602 ("entry name cannot be used as operand", Enode);
4604 when E_Procedure =>
4605 Error_Msg_N
4606 ("procedure name cannot be used as operand", Enode);
4608 when E_Exception =>
4609 Error_Msg_N
4610 ("exception name cannot be used as operand", Enode);
4612 when E_Block | E_Label | E_Loop =>
4613 Error_Msg_N
4614 ("label name cannot be used as operand", Enode);
4616 when others =>
4617 return False;
4619 end case;
4621 return True;
4622 end Junk_Operand;
4624 --------------------
4625 -- Operator_Check --
4626 --------------------
4628 procedure Operator_Check (N : Node_Id) is
4629 begin
4630 Remove_Abstract_Operations (N);
4632 -- Test for case of no interpretation found for operator
4634 if Etype (N) = Any_Type then
4635 declare
4636 L : Node_Id;
4637 R : Node_Id;
4638 Op_Id : Entity_Id := Empty;
4640 begin
4641 R := Right_Opnd (N);
4643 if Nkind (N) in N_Binary_Op then
4644 L := Left_Opnd (N);
4645 else
4646 L := Empty;
4647 end if;
4649 -- If either operand has no type, then don't complain further,
4650 -- since this simply means that we have a propagated error.
4652 if R = Error
4653 or else Etype (R) = Any_Type
4654 or else (Nkind (N) in N_Binary_Op and then Etype (L) = Any_Type)
4655 then
4656 return;
4658 -- We explicitly check for the case of concatenation of component
4659 -- with component to avoid reporting spurious matching array types
4660 -- that might happen to be lurking in distant packages (such as
4661 -- run-time packages). This also prevents inconsistencies in the
4662 -- messages for certain ACVC B tests, which can vary depending on
4663 -- types declared in run-time interfaces. Another improvement when
4664 -- aggregates are present is to look for a well-typed operand.
4666 elsif Present (Candidate_Type)
4667 and then (Nkind (N) /= N_Op_Concat
4668 or else Is_Array_Type (Etype (L))
4669 or else Is_Array_Type (Etype (R)))
4670 then
4672 if Nkind (N) = N_Op_Concat then
4673 if Etype (L) /= Any_Composite
4674 and then Is_Array_Type (Etype (L))
4675 then
4676 Candidate_Type := Etype (L);
4678 elsif Etype (R) /= Any_Composite
4679 and then Is_Array_Type (Etype (R))
4680 then
4681 Candidate_Type := Etype (R);
4682 end if;
4683 end if;
4685 Error_Msg_NE
4686 ("operator for} is not directly visible!",
4687 N, First_Subtype (Candidate_Type));
4688 Error_Msg_N ("use clause would make operation legal!", N);
4689 return;
4691 -- If either operand is a junk operand (e.g. package name), then
4692 -- post appropriate error messages, but do not complain further.
4694 -- Note that the use of OR in this test instead of OR ELSE is
4695 -- quite deliberate, we may as well check both operands in the
4696 -- binary operator case.
4698 elsif Junk_Operand (R)
4699 or (Nkind (N) in N_Binary_Op and then Junk_Operand (L))
4700 then
4701 return;
4703 -- If we have a logical operator, one of whose operands is
4704 -- Boolean, then we know that the other operand cannot resolve to
4705 -- Boolean (since we got no interpretations), but in that case we
4706 -- pretty much know that the other operand should be Boolean, so
4707 -- resolve it that way (generating an error)
4709 elsif Nkind (N) = N_Op_And
4710 or else
4711 Nkind (N) = N_Op_Or
4712 or else
4713 Nkind (N) = N_Op_Xor
4714 then
4715 if Etype (L) = Standard_Boolean then
4716 Resolve (R, Standard_Boolean);
4717 return;
4718 elsif Etype (R) = Standard_Boolean then
4719 Resolve (L, Standard_Boolean);
4720 return;
4721 end if;
4723 -- For an arithmetic operator or comparison operator, if one
4724 -- of the operands is numeric, then we know the other operand
4725 -- is not the same numeric type. If it is a non-numeric type,
4726 -- then probably it is intended to match the other operand.
4728 elsif Nkind (N) = N_Op_Add or else
4729 Nkind (N) = N_Op_Divide or else
4730 Nkind (N) = N_Op_Ge or else
4731 Nkind (N) = N_Op_Gt or else
4732 Nkind (N) = N_Op_Le or else
4733 Nkind (N) = N_Op_Lt or else
4734 Nkind (N) = N_Op_Mod or else
4735 Nkind (N) = N_Op_Multiply or else
4736 Nkind (N) = N_Op_Rem or else
4737 Nkind (N) = N_Op_Subtract
4738 then
4739 if Is_Numeric_Type (Etype (L))
4740 and then not Is_Numeric_Type (Etype (R))
4741 then
4742 Resolve (R, Etype (L));
4743 return;
4745 elsif Is_Numeric_Type (Etype (R))
4746 and then not Is_Numeric_Type (Etype (L))
4747 then
4748 Resolve (L, Etype (R));
4749 return;
4750 end if;
4752 -- Comparisons on A'Access are common enough to deserve a
4753 -- special message.
4755 elsif (Nkind (N) = N_Op_Eq or else
4756 Nkind (N) = N_Op_Ne)
4757 and then Ekind (Etype (L)) = E_Access_Attribute_Type
4758 and then Ekind (Etype (R)) = E_Access_Attribute_Type
4759 then
4760 Error_Msg_N
4761 ("two access attributes cannot be compared directly", N);
4762 Error_Msg_N
4763 ("\use qualified expression for one of the operands",
4765 return;
4767 -- Another one for C programmers
4769 elsif Nkind (N) = N_Op_Concat
4770 and then Valid_Boolean_Arg (Etype (L))
4771 and then Valid_Boolean_Arg (Etype (R))
4772 then
4773 Error_Msg_N ("invalid operands for concatenation", N);
4774 Error_Msg_N ("\maybe AND was meant", N);
4775 return;
4777 -- A special case for comparison of access parameter with null
4779 elsif Nkind (N) = N_Op_Eq
4780 and then Is_Entity_Name (L)
4781 and then Nkind (Parent (Entity (L))) = N_Parameter_Specification
4782 and then Nkind (Parameter_Type (Parent (Entity (L)))) =
4783 N_Access_Definition
4784 and then Nkind (R) = N_Null
4785 then
4786 Error_Msg_N ("access parameter is not allowed to be null", L);
4787 Error_Msg_N ("\(call would raise Constraint_Error)", L);
4788 return;
4789 end if;
4791 -- If we fall through then just give general message. Note that in
4792 -- the following messages, if the operand is overloaded we choose
4793 -- an arbitrary type to complain about, but that is probably more
4794 -- useful than not giving a type at all.
4796 if Nkind (N) in N_Unary_Op then
4797 Error_Msg_Node_2 := Etype (R);
4798 Error_Msg_N ("operator& not defined for}", N);
4799 return;
4801 else
4802 if Nkind (N) in N_Binary_Op then
4803 if not Is_Overloaded (L)
4804 and then not Is_Overloaded (R)
4805 and then Base_Type (Etype (L)) = Base_Type (Etype (R))
4806 then
4807 Error_Msg_Node_2 := First_Subtype (Etype (R));
4808 Error_Msg_N ("there is no applicable operator& for}", N);
4810 else
4811 -- Another attempt to find a fix: one of the candidate
4812 -- interpretations may not be use-visible. This has
4813 -- already been checked for predefined operators, so
4814 -- we examine only user-defined functions.
4816 Op_Id := Get_Name_Entity_Id (Chars (N));
4818 while Present (Op_Id) loop
4819 if Ekind (Op_Id) /= E_Operator
4820 and then Is_Overloadable (Op_Id)
4821 then
4822 if not Is_Immediately_Visible (Op_Id)
4823 and then not In_Use (Scope (Op_Id))
4824 and then not Is_Abstract_Subprogram (Op_Id)
4825 and then not Is_Hidden (Op_Id)
4826 and then Ekind (Scope (Op_Id)) = E_Package
4827 and then
4828 Has_Compatible_Type
4829 (L, Etype (First_Formal (Op_Id)))
4830 and then Present
4831 (Next_Formal (First_Formal (Op_Id)))
4832 and then
4833 Has_Compatible_Type
4835 Etype (Next_Formal (First_Formal (Op_Id))))
4836 then
4837 Error_Msg_N
4838 ("No legal interpretation for operator&", N);
4839 Error_Msg_NE
4840 ("\use clause on& would make operation legal",
4841 N, Scope (Op_Id));
4842 exit;
4843 end if;
4844 end if;
4846 Op_Id := Homonym (Op_Id);
4847 end loop;
4849 if No (Op_Id) then
4850 Error_Msg_N ("invalid operand types for operator&", N);
4852 if Nkind (N) /= N_Op_Concat then
4853 Error_Msg_NE ("\left operand has}!", N, Etype (L));
4854 Error_Msg_NE ("\right operand has}!", N, Etype (R));
4855 end if;
4856 end if;
4857 end if;
4858 end if;
4859 end if;
4860 end;
4861 end if;
4862 end Operator_Check;
4864 -----------------------------------------
4865 -- Process_Implicit_Dereference_Prefix --
4866 -----------------------------------------
4868 procedure Process_Implicit_Dereference_Prefix
4869 (E : Entity_Id;
4870 P : Entity_Id)
4872 Ref : Node_Id;
4874 begin
4875 if Present (E)
4876 and then (Operating_Mode = Check_Semantics or else not Expander_Active)
4877 then
4878 -- We create a dummy reference to E to ensure that the reference
4879 -- is not considered as part of an assignment (an implicit
4880 -- dereference can never assign to its prefix). The Comes_From_Source
4881 -- attribute needs to be propagated for accurate warnings.
4883 Ref := New_Reference_To (E, Sloc (P));
4884 Set_Comes_From_Source (Ref, Comes_From_Source (P));
4885 Generate_Reference (E, Ref);
4886 end if;
4887 end Process_Implicit_Dereference_Prefix;
4889 --------------------------------
4890 -- Remove_Abstract_Operations --
4891 --------------------------------
4893 procedure Remove_Abstract_Operations (N : Node_Id) is
4894 Abstract_Op : Entity_Id := Empty;
4895 Address_Kludge : Boolean := False;
4896 I : Interp_Index;
4897 It : Interp;
4899 -- AI-310: If overloaded, remove abstract non-dispatching operations. We
4900 -- activate this if either extensions are enabled, or if the abstract
4901 -- operation in question comes from a predefined file. This latter test
4902 -- allows us to use abstract to make operations invisible to users. In
4903 -- particular, if type Address is non-private and abstract subprograms
4904 -- are used to hide its operators, they will be truly hidden.
4906 type Operand_Position is (First_Op, Second_Op);
4907 Univ_Type : constant Entity_Id := Universal_Interpretation (N);
4909 procedure Remove_Address_Interpretations (Op : Operand_Position);
4910 -- Ambiguities may arise when the operands are literal and the address
4911 -- operations in s-auxdec are visible. In that case, remove the
4912 -- interpretation of a literal as Address, to retain the semantics of
4913 -- Address as a private type.
4915 ------------------------------------
4916 -- Remove_Address_Interpretations --
4917 ------------------------------------
4919 procedure Remove_Address_Interpretations (Op : Operand_Position) is
4920 Formal : Entity_Id;
4922 begin
4923 if Is_Overloaded (N) then
4924 Get_First_Interp (N, I, It);
4925 while Present (It.Nam) loop
4926 Formal := First_Entity (It.Nam);
4928 if Op = Second_Op then
4929 Formal := Next_Entity (Formal);
4930 end if;
4932 if Is_Descendent_Of_Address (Etype (Formal)) then
4933 Address_Kludge := True;
4934 Remove_Interp (I);
4935 end if;
4937 Get_Next_Interp (I, It);
4938 end loop;
4939 end if;
4940 end Remove_Address_Interpretations;
4942 -- Start of processing for Remove_Abstract_Operations
4944 begin
4945 if Is_Overloaded (N) then
4946 Get_First_Interp (N, I, It);
4948 while Present (It.Nam) loop
4949 if Is_Overloadable (It.Nam)
4950 and then Is_Abstract_Subprogram (It.Nam)
4951 and then not Is_Dispatching_Operation (It.Nam)
4952 then
4953 Abstract_Op := It.Nam;
4955 if Is_Descendent_Of_Address (It.Typ) then
4956 Address_Kludge := True;
4957 Remove_Interp (I);
4958 exit;
4960 -- In Ada 2005, this operation does not participate in Overload
4961 -- resolution. If the operation is defined in a predefined
4962 -- unit, it is one of the operations declared abstract in some
4963 -- variants of System, and it must be removed as well.
4965 elsif Ada_Version >= Ada_05
4966 or else Is_Predefined_File_Name
4967 (Unit_File_Name (Get_Source_Unit (It.Nam)))
4968 then
4969 Remove_Interp (I);
4970 exit;
4971 end if;
4972 end if;
4974 Get_Next_Interp (I, It);
4975 end loop;
4977 if No (Abstract_Op) then
4979 -- If some interpretation yields an integer type, it is still
4980 -- possible that there are address interpretations. Remove them
4981 -- if one operand is a literal, to avoid spurious ambiguities
4982 -- on systems where Address is a visible integer type.
4984 if Is_Overloaded (N)
4985 and then Nkind (N) in N_Op
4986 and then Is_Integer_Type (Etype (N))
4987 then
4988 if Nkind (N) in N_Binary_Op then
4989 if Nkind (Right_Opnd (N)) = N_Integer_Literal then
4990 Remove_Address_Interpretations (Second_Op);
4992 elsif Nkind (Right_Opnd (N)) = N_Integer_Literal then
4993 Remove_Address_Interpretations (First_Op);
4994 end if;
4995 end if;
4996 end if;
4998 elsif Nkind (N) in N_Op then
5000 -- Remove interpretations that treat literals as addresses. This
5001 -- is never appropriate, even when Address is defined as a visible
5002 -- Integer type. The reason is that we would really prefer Address
5003 -- to behave as a private type, even in this case, which is there
5004 -- only to accomodate oddities of VMS address sizes. If Address is
5005 -- a visible integer type, we get lots of overload ambiguities.
5007 if Nkind (N) in N_Binary_Op then
5008 declare
5009 U1 : constant Boolean :=
5010 Present (Universal_Interpretation (Right_Opnd (N)));
5011 U2 : constant Boolean :=
5012 Present (Universal_Interpretation (Left_Opnd (N)));
5014 begin
5015 if U1 then
5016 Remove_Address_Interpretations (Second_Op);
5017 end if;
5019 if U2 then
5020 Remove_Address_Interpretations (First_Op);
5021 end if;
5023 if not (U1 and U2) then
5025 -- Remove corresponding predefined operator, which is
5026 -- always added to the overload set.
5028 Get_First_Interp (N, I, It);
5029 while Present (It.Nam) loop
5030 if Scope (It.Nam) = Standard_Standard
5031 and then Base_Type (It.Typ) =
5032 Base_Type (Etype (Abstract_Op))
5033 then
5034 Remove_Interp (I);
5035 end if;
5037 Get_Next_Interp (I, It);
5038 end loop;
5040 elsif Is_Overloaded (N)
5041 and then Present (Univ_Type)
5042 then
5043 -- If both operands have a universal interpretation,
5044 -- it is still necessary to remove interpretations that
5045 -- yield Address. Any remaining ambiguities will be
5046 -- removed in Disambiguate.
5048 Get_First_Interp (N, I, It);
5049 while Present (It.Nam) loop
5050 if Is_Descendent_Of_Address (It.Typ) then
5051 Remove_Interp (I);
5053 elsif not Is_Type (It.Nam) then
5054 Set_Entity (N, It.Nam);
5055 end if;
5057 Get_Next_Interp (I, It);
5058 end loop;
5059 end if;
5060 end;
5061 end if;
5063 elsif Nkind (N) = N_Function_Call
5064 and then
5065 (Nkind (Name (N)) = N_Operator_Symbol
5066 or else
5067 (Nkind (Name (N)) = N_Expanded_Name
5068 and then
5069 Nkind (Selector_Name (Name (N))) = N_Operator_Symbol))
5070 then
5072 declare
5073 Arg1 : constant Node_Id := First (Parameter_Associations (N));
5074 U1 : constant Boolean :=
5075 Present (Universal_Interpretation (Arg1));
5076 U2 : constant Boolean :=
5077 Present (Next (Arg1)) and then
5078 Present (Universal_Interpretation (Next (Arg1)));
5080 begin
5081 if U1 then
5082 Remove_Address_Interpretations (First_Op);
5083 end if;
5085 if U2 then
5086 Remove_Address_Interpretations (Second_Op);
5087 end if;
5089 if not (U1 and U2) then
5090 Get_First_Interp (N, I, It);
5091 while Present (It.Nam) loop
5092 if Scope (It.Nam) = Standard_Standard
5093 and then It.Typ = Base_Type (Etype (Abstract_Op))
5094 then
5095 Remove_Interp (I);
5096 end if;
5098 Get_Next_Interp (I, It);
5099 end loop;
5100 end if;
5101 end;
5102 end if;
5104 -- If the removal has left no valid interpretations, emit an error
5105 -- message now and label node as illegal.
5107 if Present (Abstract_Op) then
5108 Get_First_Interp (N, I, It);
5110 if No (It.Nam) then
5112 -- Removal of abstract operation left no viable candidate
5114 Set_Etype (N, Any_Type);
5115 Error_Msg_Sloc := Sloc (Abstract_Op);
5116 Error_Msg_NE
5117 ("cannot call abstract operation& declared#", N, Abstract_Op);
5119 -- In Ada 2005, an abstract operation may disable predefined
5120 -- operators. Since the context is not yet known, we mark the
5121 -- predefined operators as potentially hidden. Do not include
5122 -- predefined operators when addresses are involved since this
5123 -- case is handled separately.
5125 elsif Ada_Version >= Ada_05
5126 and then not Address_Kludge
5127 then
5128 while Present (It.Nam) loop
5129 if Is_Numeric_Type (It.Typ)
5130 and then Scope (It.Typ) = Standard_Standard
5131 then
5132 Set_Abstract_Op (I, Abstract_Op);
5133 end if;
5135 Get_Next_Interp (I, It);
5136 end loop;
5137 end if;
5138 end if;
5139 end if;
5140 end Remove_Abstract_Operations;
5142 -----------------------
5143 -- Try_Indirect_Call --
5144 -----------------------
5146 function Try_Indirect_Call
5147 (N : Node_Id;
5148 Nam : Entity_Id;
5149 Typ : Entity_Id) return Boolean
5151 Actual : Node_Id;
5152 Formal : Entity_Id;
5153 Call_OK : Boolean;
5155 begin
5156 Normalize_Actuals (N, Designated_Type (Typ), False, Call_OK);
5158 Actual := First_Actual (N);
5159 Formal := First_Formal (Designated_Type (Typ));
5160 while Present (Actual) and then Present (Formal) loop
5161 if not Has_Compatible_Type (Actual, Etype (Formal)) then
5162 return False;
5163 end if;
5165 Next (Actual);
5166 Next_Formal (Formal);
5167 end loop;
5169 if No (Actual) and then No (Formal) then
5170 Add_One_Interp (N, Nam, Etype (Designated_Type (Typ)));
5172 -- Nam is a candidate interpretation for the name in the call,
5173 -- if it is not an indirect call.
5175 if not Is_Type (Nam)
5176 and then Is_Entity_Name (Name (N))
5177 then
5178 Set_Entity (Name (N), Nam);
5179 end if;
5181 return True;
5182 else
5183 return False;
5184 end if;
5185 end Try_Indirect_Call;
5187 ----------------------
5188 -- Try_Indexed_Call --
5189 ----------------------
5191 function Try_Indexed_Call
5192 (N : Node_Id;
5193 Nam : Entity_Id;
5194 Typ : Entity_Id;
5195 Skip_First : Boolean) return Boolean
5197 Actuals : constant List_Id := Parameter_Associations (N);
5198 Actual : Node_Id;
5199 Index : Entity_Id;
5201 begin
5202 Actual := First (Actuals);
5204 -- If the call was originally written in prefix form, skip the first
5205 -- actual, which is obviously not defaulted.
5207 if Skip_First then
5208 Next (Actual);
5209 end if;
5211 Index := First_Index (Typ);
5212 while Present (Actual) and then Present (Index) loop
5214 -- If the parameter list has a named association, the expression
5215 -- is definitely a call and not an indexed component.
5217 if Nkind (Actual) = N_Parameter_Association then
5218 return False;
5219 end if;
5221 if not Has_Compatible_Type (Actual, Etype (Index)) then
5222 return False;
5223 end if;
5225 Next (Actual);
5226 Next_Index (Index);
5227 end loop;
5229 if No (Actual) and then No (Index) then
5230 Add_One_Interp (N, Nam, Component_Type (Typ));
5232 -- Nam is a candidate interpretation for the name in the call,
5233 -- if it is not an indirect call.
5235 if not Is_Type (Nam)
5236 and then Is_Entity_Name (Name (N))
5237 then
5238 Set_Entity (Name (N), Nam);
5239 end if;
5241 return True;
5242 else
5243 return False;
5244 end if;
5245 end Try_Indexed_Call;
5247 --------------------------
5248 -- Try_Object_Operation --
5249 --------------------------
5251 function Try_Object_Operation (N : Node_Id) return Boolean is
5252 K : constant Node_Kind := Nkind (Parent (N));
5253 Loc : constant Source_Ptr := Sloc (N);
5254 Candidate : Entity_Id := Empty;
5255 Is_Subprg_Call : constant Boolean := K = N_Procedure_Call_Statement
5256 or else K = N_Function_Call;
5257 Obj : constant Node_Id := Prefix (N);
5258 Subprog : constant Node_Id :=
5259 Make_Identifier (Sloc (Selector_Name (N)),
5260 Chars => Chars (Selector_Name (N)));
5261 -- Identifier on which possible interpretations will be collected
5263 Success : Boolean := False;
5265 Report_Error : Boolean := False;
5266 -- If no candidate interpretation matches the context, redo the
5267 -- analysis with error enabled to provide additional information.
5269 Actual : Node_Id;
5270 New_Call_Node : Node_Id := Empty;
5271 Node_To_Replace : Node_Id;
5272 Obj_Type : Entity_Id := Etype (Obj);
5274 function Valid_Candidate
5275 (Success : Boolean;
5276 Call : Node_Id;
5277 Subp : Entity_Id) return Entity_Id;
5278 -- If the subprogram is a valid interpretation, record it, and add
5279 -- to the list of interpretations of Subprog.
5281 procedure Complete_Object_Operation
5282 (Call_Node : Node_Id;
5283 Node_To_Replace : Node_Id);
5284 -- Make Subprog the name of Call_Node, replace Node_To_Replace with
5285 -- Call_Node, insert the object (or its dereference) as the first actual
5286 -- in the call, and complete the analysis of the call.
5288 procedure Report_Ambiguity (Op : Entity_Id);
5289 -- If a prefixed procedure call is ambiguous, indicate whether the
5290 -- call includes an implicit dereference or an implicit 'Access.
5292 procedure Transform_Object_Operation
5293 (Call_Node : out Node_Id;
5294 Node_To_Replace : out Node_Id);
5295 -- Transform Obj.Operation (X, Y,,) into Operation (Obj, X, Y ..)
5296 -- Call_Node is the resulting subprogram call,
5297 -- Node_To_Replace is either N or the parent of N, and Subprog
5298 -- is a reference to the subprogram we are trying to match.
5300 function Try_Class_Wide_Operation
5301 (Call_Node : Node_Id;
5302 Node_To_Replace : Node_Id) return Boolean;
5303 -- Traverse all ancestor types looking for a class-wide subprogram
5304 -- for which the current operation is a valid non-dispatching call.
5306 procedure Try_One_Prefix_Interpretation (T : Entity_Id);
5307 -- If prefix is overloaded, its interpretation may include different
5308 -- tagged types, and we must examine the primitive operations and
5309 -- the class-wide operations of each in order to find candidate
5310 -- interpretations for the call as a whole.
5312 function Try_Primitive_Operation
5313 (Call_Node : Node_Id;
5314 Node_To_Replace : Node_Id) return Boolean;
5315 -- Traverse the list of primitive subprograms looking for a dispatching
5316 -- operation for which the current node is a valid call .
5318 ---------------------
5319 -- Valid_Candidate --
5320 ---------------------
5322 function Valid_Candidate
5323 (Success : Boolean;
5324 Call : Node_Id;
5325 Subp : Entity_Id) return Entity_Id
5327 Comp_Type : Entity_Id;
5329 begin
5330 -- If the subprogram is a valid interpretation, record it in global
5331 -- variable Subprog, to collect all possible overloadings.
5333 if Success then
5334 if Subp /= Entity (Subprog) then
5335 Add_One_Interp (Subprog, Subp, Etype (Subp));
5336 end if;
5337 end if;
5339 -- If the call may be an indexed call, retrieve component type
5340 -- of resulting expression, and add possible interpretation.
5342 Comp_Type := Empty;
5344 if Nkind (Call) = N_Function_Call
5345 and then Nkind (Parent (N)) = N_Indexed_Component
5346 and then Needs_One_Actual (Subp)
5347 then
5348 if Is_Array_Type (Etype (Subp)) then
5349 Comp_Type := Component_Type (Etype (Subp));
5351 elsif Is_Access_Type (Etype (Subp))
5352 and then Is_Array_Type (Designated_Type (Etype (Subp)))
5353 then
5354 Comp_Type := Component_Type (Designated_Type (Etype (Subp)));
5355 end if;
5356 end if;
5358 if Present (Comp_Type)
5359 and then Etype (Subprog) /= Comp_Type
5360 then
5361 Add_One_Interp (Subprog, Subp, Comp_Type);
5362 end if;
5364 if Etype (Call) /= Any_Type then
5365 return Subp;
5366 else
5367 return Empty;
5368 end if;
5369 end Valid_Candidate;
5371 -------------------------------
5372 -- Complete_Object_Operation --
5373 -------------------------------
5375 procedure Complete_Object_Operation
5376 (Call_Node : Node_Id;
5377 Node_To_Replace : Node_Id)
5379 Formal_Type : constant Entity_Id :=
5380 Etype (First_Formal (Entity (Subprog)));
5381 First_Actual : Node_Id;
5383 begin
5384 -- Place the name of the operation, with its interpretations,
5385 -- on the rewritten call.
5387 Set_Name (Call_Node, Subprog);
5389 First_Actual := First (Parameter_Associations (Call_Node));
5391 -- For cross-reference purposes, treat the new node as being in
5392 -- the source if the original one is.
5394 Set_Comes_From_Source (Subprog, Comes_From_Source (N));
5395 Set_Comes_From_Source (Call_Node, Comes_From_Source (N));
5397 if Nkind (N) = N_Selected_Component
5398 and then not Inside_A_Generic
5399 then
5400 Set_Entity (Selector_Name (N), Entity (Subprog));
5401 end if;
5403 -- If need be, rewrite first actual as an explicit dereference
5404 -- If the call is overloaded, the rewriting can only be done
5405 -- once the primitive operation is identified.
5407 if Is_Overloaded (Subprog) then
5409 -- The prefix itself may be overloaded, and its interpretations
5410 -- must be propagated to the new actual in the call.
5412 if Is_Overloaded (Obj) then
5413 Save_Interps (Obj, First_Actual);
5414 end if;
5416 Rewrite (First_Actual, Obj);
5418 elsif not Is_Access_Type (Formal_Type)
5419 and then Is_Access_Type (Etype (Obj))
5420 then
5421 Rewrite (First_Actual,
5422 Make_Explicit_Dereference (Sloc (Obj), Obj));
5423 Analyze (First_Actual);
5425 -- If we need to introduce an explicit dereference, verify that
5426 -- the resulting actual is compatible with the mode of the formal.
5428 if Ekind (First_Formal (Entity (Subprog))) /= E_In_Parameter
5429 and then Is_Access_Constant (Etype (Obj))
5430 then
5431 Error_Msg_NE
5432 ("expect variable in call to&", Prefix (N), Entity (Subprog));
5433 end if;
5435 -- Conversely, if the formal is an access parameter and the
5436 -- object is not, replace the actual with a 'Access reference.
5437 -- Its analysis will check that the object is aliased.
5439 elsif Is_Access_Type (Formal_Type)
5440 and then not Is_Access_Type (Etype (Obj))
5441 then
5442 Rewrite (First_Actual,
5443 Make_Attribute_Reference (Loc,
5444 Attribute_Name => Name_Access,
5445 Prefix => Relocate_Node (Obj)));
5447 if not Is_Aliased_View (Obj) then
5448 Error_Msg_NE
5449 ("object in prefixed call to& must be aliased"
5450 & " (RM-2005 4.3.1 (13))",
5451 Prefix (First_Actual), Subprog);
5452 end if;
5454 Analyze (First_Actual);
5456 else
5457 if Is_Overloaded (Obj) then
5458 Save_Interps (Obj, First_Actual);
5459 end if;
5461 Rewrite (First_Actual, Obj);
5462 end if;
5464 Rewrite (Node_To_Replace, Call_Node);
5466 -- Propagate the interpretations collected in subprog to the new
5467 -- function call node, to be resolved from context.
5469 if Is_Overloaded (Subprog) then
5470 Save_Interps (Subprog, Node_To_Replace);
5471 else
5472 Analyze (Node_To_Replace);
5473 end if;
5474 end Complete_Object_Operation;
5476 ----------------------
5477 -- Report_Ambiguity --
5478 ----------------------
5480 procedure Report_Ambiguity (Op : Entity_Id) is
5481 Access_Formal : constant Boolean :=
5482 Is_Access_Type (Etype (First_Formal (Op)));
5483 Access_Actual : constant Boolean :=
5484 Is_Access_Type (Etype (Prefix (N)));
5486 begin
5487 Error_Msg_Sloc := Sloc (Op);
5489 if Access_Formal and then not Access_Actual then
5490 if Nkind (Parent (Op)) = N_Full_Type_Declaration then
5491 Error_Msg_N
5492 ("\possible interpretation"
5493 & " (inherited, with implicit 'Access) #", N);
5494 else
5495 Error_Msg_N
5496 ("\possible interpretation (with implicit 'Access) #", N);
5497 end if;
5499 elsif not Access_Formal and then Access_Actual then
5500 if Nkind (Parent (Op)) = N_Full_Type_Declaration then
5501 Error_Msg_N
5502 ("\possible interpretation"
5503 & " ( inherited, with implicit dereference) #", N);
5504 else
5505 Error_Msg_N
5506 ("\possible interpretation (with implicit dereference) #", N);
5507 end if;
5509 else
5510 if Nkind (Parent (Op)) = N_Full_Type_Declaration then
5511 Error_Msg_N ("\possible interpretation (inherited)#", N);
5512 else
5513 Error_Msg_N ("\possible interpretation#", N);
5514 end if;
5515 end if;
5516 end Report_Ambiguity;
5518 --------------------------------
5519 -- Transform_Object_Operation --
5520 --------------------------------
5522 procedure Transform_Object_Operation
5523 (Call_Node : out Node_Id;
5524 Node_To_Replace : out Node_Id)
5526 Parent_Node : constant Node_Id := Parent (N);
5528 Dummy : constant Node_Id := New_Copy (Obj);
5529 -- Placeholder used as a first parameter in the call, replaced
5530 -- eventually by the proper object.
5532 Actuals : List_Id;
5533 Actual : Node_Id;
5535 begin
5536 -- Common case covering 1) Call to a procedure and 2) Call to a
5537 -- function that has some additional actuals.
5539 if (Nkind (Parent_Node) = N_Function_Call
5540 or else
5541 Nkind (Parent_Node) = N_Procedure_Call_Statement)
5543 -- N is a selected component node containing the name of the
5544 -- subprogram. If N is not the name of the parent node we must
5545 -- not replace the parent node by the new construct. This case
5546 -- occurs when N is a parameterless call to a subprogram that
5547 -- is an actual parameter of a call to another subprogram. For
5548 -- example:
5549 -- Some_Subprogram (..., Obj.Operation, ...)
5551 and then Name (Parent_Node) = N
5552 then
5553 Node_To_Replace := Parent_Node;
5555 Actuals := Parameter_Associations (Parent_Node);
5557 if Present (Actuals) then
5558 Prepend (Dummy, Actuals);
5559 else
5560 Actuals := New_List (Dummy);
5561 end if;
5563 if Nkind (Parent_Node) = N_Procedure_Call_Statement then
5564 Call_Node :=
5565 Make_Procedure_Call_Statement (Loc,
5566 Name => New_Copy (Subprog),
5567 Parameter_Associations => Actuals);
5569 else
5570 Call_Node :=
5571 Make_Function_Call (Loc,
5572 Name => New_Copy (Subprog),
5573 Parameter_Associations => Actuals);
5575 end if;
5577 -- Before analysis, the function call appears as an indexed component
5578 -- if there are no named associations.
5580 elsif Nkind (Parent_Node) = N_Indexed_Component
5581 and then N = Prefix (Parent_Node)
5582 then
5583 Node_To_Replace := Parent_Node;
5585 Actuals := Expressions (Parent_Node);
5587 Actual := First (Actuals);
5588 while Present (Actual) loop
5589 Analyze (Actual);
5590 Next (Actual);
5591 end loop;
5593 Prepend (Dummy, Actuals);
5595 Call_Node :=
5596 Make_Function_Call (Loc,
5597 Name => New_Copy (Subprog),
5598 Parameter_Associations => Actuals);
5600 -- Parameterless call: Obj.F is rewritten as F (Obj)
5602 else
5603 Node_To_Replace := N;
5605 Call_Node :=
5606 Make_Function_Call (Loc,
5607 Name => New_Copy (Subprog),
5608 Parameter_Associations => New_List (Dummy));
5609 end if;
5610 end Transform_Object_Operation;
5612 ------------------------------
5613 -- Try_Class_Wide_Operation --
5614 ------------------------------
5616 function Try_Class_Wide_Operation
5617 (Call_Node : Node_Id;
5618 Node_To_Replace : Node_Id) return Boolean
5620 Anc_Type : Entity_Id;
5621 Matching_Op : Entity_Id := Empty;
5622 Error : Boolean;
5624 procedure Traverse_Homonyms
5625 (Anc_Type : Entity_Id;
5626 Error : out Boolean);
5627 -- Traverse the homonym chain of the subprogram searching for those
5628 -- homonyms whose first formal has the Anc_Type's class-wide type,
5629 -- or an anonymous access type designating the class-wide type. If an
5630 -- ambiguity is detected, then Error is set to True.
5632 procedure Traverse_Interfaces
5633 (Anc_Type : Entity_Id;
5634 Error : out Boolean);
5635 -- Traverse the list of interfaces, if any, associated with Anc_Type
5636 -- and search for acceptable class-wide homonyms associated with each
5637 -- interface. If an ambiguity is detected, then Error is set to True.
5639 -----------------------
5640 -- Traverse_Homonyms --
5641 -----------------------
5643 procedure Traverse_Homonyms
5644 (Anc_Type : Entity_Id;
5645 Error : out Boolean)
5647 Cls_Type : Entity_Id;
5648 Hom : Entity_Id;
5649 Hom_Ref : Node_Id;
5650 Success : Boolean;
5652 begin
5653 Error := False;
5655 Cls_Type := Class_Wide_Type (Anc_Type);
5657 Hom := Current_Entity (Subprog);
5659 -- Find operation whose first parameter is of the class-wide
5660 -- type, a subtype thereof, or an anonymous access to same.
5662 while Present (Hom) loop
5663 if (Ekind (Hom) = E_Procedure
5664 or else
5665 Ekind (Hom) = E_Function)
5666 and then Scope (Hom) = Scope (Anc_Type)
5667 and then Present (First_Formal (Hom))
5668 and then
5669 (Base_Type (Etype (First_Formal (Hom))) = Cls_Type
5670 or else
5671 (Is_Access_Type (Etype (First_Formal (Hom)))
5672 and then
5673 Ekind (Etype (First_Formal (Hom))) =
5674 E_Anonymous_Access_Type
5675 and then
5676 Base_Type
5677 (Designated_Type (Etype (First_Formal (Hom)))) =
5678 Cls_Type))
5679 then
5680 Set_Etype (Call_Node, Any_Type);
5681 Set_Is_Overloaded (Call_Node, False);
5682 Success := False;
5684 if No (Matching_Op) then
5685 Hom_Ref := New_Reference_To (Hom, Sloc (Subprog));
5686 Set_Etype (Call_Node, Any_Type);
5687 Set_Parent (Call_Node, Parent (Node_To_Replace));
5689 Set_Name (Call_Node, Hom_Ref);
5691 Analyze_One_Call
5692 (N => Call_Node,
5693 Nam => Hom,
5694 Report => Report_Error,
5695 Success => Success,
5696 Skip_First => True);
5698 Matching_Op :=
5699 Valid_Candidate (Success, Call_Node, Hom);
5701 else
5702 Analyze_One_Call
5703 (N => Call_Node,
5704 Nam => Hom,
5705 Report => Report_Error,
5706 Success => Success,
5707 Skip_First => True);
5709 if Present (Valid_Candidate (Success, Call_Node, Hom))
5710 and then Nkind (Call_Node) /= N_Function_Call
5711 then
5712 Error_Msg_NE ("ambiguous call to&", N, Hom);
5713 Report_Ambiguity (Matching_Op);
5714 Report_Ambiguity (Hom);
5715 Error := True;
5716 return;
5717 end if;
5718 end if;
5719 end if;
5721 Hom := Homonym (Hom);
5722 end loop;
5723 end Traverse_Homonyms;
5725 -------------------------
5726 -- Traverse_Interfaces --
5727 -------------------------
5729 procedure Traverse_Interfaces
5730 (Anc_Type : Entity_Id;
5731 Error : out Boolean)
5733 Intface : Node_Id;
5734 Intface_List : constant List_Id :=
5735 Abstract_Interface_List (Anc_Type);
5737 begin
5738 Error := False;
5740 if Is_Non_Empty_List (Intface_List) then
5741 Intface := First (Intface_List);
5742 while Present (Intface) loop
5744 -- Look for acceptable class-wide homonyms associated with
5745 -- the interface.
5747 Traverse_Homonyms (Etype (Intface), Error);
5749 if Error then
5750 return;
5751 end if;
5753 -- Continue the search by looking at each of the interface's
5754 -- associated interface ancestors.
5756 Traverse_Interfaces (Etype (Intface), Error);
5758 if Error then
5759 return;
5760 end if;
5762 Next (Intface);
5763 end loop;
5764 end if;
5765 end Traverse_Interfaces;
5767 -- Start of processing for Try_Class_Wide_Operation
5769 begin
5770 -- Loop through ancestor types (including interfaces), traversing the
5771 -- homonym chain of the subprogram, and trying out those homonyms
5772 -- whose first formal has the class-wide type of the ancestor, or an
5773 -- anonymous access type designating the class-wide type.
5775 Anc_Type := Obj_Type;
5776 loop
5777 -- Look for a match among homonyms associated with the ancestor
5779 Traverse_Homonyms (Anc_Type, Error);
5781 if Error then
5782 return True;
5783 end if;
5785 -- Continue the search for matches among homonyms associated with
5786 -- any interfaces implemented by the ancestor.
5788 Traverse_Interfaces (Anc_Type, Error);
5790 if Error then
5791 return True;
5792 end if;
5794 exit when Etype (Anc_Type) = Anc_Type;
5795 Anc_Type := Etype (Anc_Type);
5796 end loop;
5798 if Present (Matching_Op) then
5799 Set_Etype (Call_Node, Etype (Matching_Op));
5800 end if;
5802 return Present (Matching_Op);
5803 end Try_Class_Wide_Operation;
5805 -----------------------------------
5806 -- Try_One_Prefix_Interpretation --
5807 -----------------------------------
5809 procedure Try_One_Prefix_Interpretation (T : Entity_Id) is
5810 begin
5811 Obj_Type := T;
5813 if Is_Access_Type (Obj_Type) then
5814 Obj_Type := Designated_Type (Obj_Type);
5815 end if;
5817 if Ekind (Obj_Type) = E_Private_Subtype then
5818 Obj_Type := Base_Type (Obj_Type);
5819 end if;
5821 if Is_Class_Wide_Type (Obj_Type) then
5822 Obj_Type := Etype (Class_Wide_Type (Obj_Type));
5823 end if;
5825 -- The type may have be obtained through a limited_with clause,
5826 -- in which case the primitive operations are available on its
5827 -- non-limited view. If still incomplete, retrieve full view.
5829 if Ekind (Obj_Type) = E_Incomplete_Type
5830 and then From_With_Type (Obj_Type)
5831 then
5832 Obj_Type := Get_Full_View (Non_Limited_View (Obj_Type));
5833 end if;
5835 -- If the object is not tagged, or the type is still an incomplete
5836 -- type, this is not a prefixed call.
5838 if not Is_Tagged_Type (Obj_Type)
5839 or else Is_Incomplete_Type (Obj_Type)
5840 then
5841 return;
5842 end if;
5844 if Try_Primitive_Operation
5845 (Call_Node => New_Call_Node,
5846 Node_To_Replace => Node_To_Replace)
5847 or else
5848 Try_Class_Wide_Operation
5849 (Call_Node => New_Call_Node,
5850 Node_To_Replace => Node_To_Replace)
5851 then
5852 null;
5853 end if;
5854 end Try_One_Prefix_Interpretation;
5856 -----------------------------
5857 -- Try_Primitive_Operation --
5858 -----------------------------
5860 function Try_Primitive_Operation
5861 (Call_Node : Node_Id;
5862 Node_To_Replace : Node_Id) return Boolean
5864 Elmt : Elmt_Id;
5865 Prim_Op : Entity_Id;
5866 Matching_Op : Entity_Id := Empty;
5867 Prim_Op_Ref : Node_Id := Empty;
5869 Corr_Type : Entity_Id := Empty;
5870 -- If the prefix is a synchronized type, the controlling type of
5871 -- the primitive operation is the corresponding record type, else
5872 -- this is the object type itself.
5874 Success : Boolean := False;
5876 function Collect_Generic_Type_Ops (T : Entity_Id) return Elist_Id;
5877 -- For tagged types the candidate interpretations are found in
5878 -- the list of primitive operations of the type and its ancestors.
5879 -- For formal tagged types we have to find the operations declared
5880 -- in the same scope as the type (including in the generic formal
5881 -- part) because the type itself carries no primitive operations,
5882 -- except for formal derived types that inherit the operations of
5883 -- the parent and progenitors.
5885 function Valid_First_Argument_Of (Op : Entity_Id) return Boolean;
5886 -- Verify that the prefix, dereferenced if need be, is a valid
5887 -- controlling argument in a call to Op. The remaining actuals
5888 -- are checked in the subsequent call to Analyze_One_Call.
5890 ------------------------------
5891 -- Collect_Generic_Type_Ops --
5892 ------------------------------
5894 function Collect_Generic_Type_Ops (T : Entity_Id) return Elist_Id is
5895 Bas : constant Entity_Id := Base_Type (T);
5896 Candidates : constant Elist_Id := New_Elmt_List;
5897 Subp : Entity_Id;
5898 Formal : Entity_Id;
5900 begin
5901 if Is_Derived_Type (T) then
5902 return Primitive_Operations (T);
5904 else
5905 -- Scan the list of entities declared in the same scope as
5906 -- the type. In general this will be an open scope, given that
5907 -- the call we are analyzing can only appear within a generic
5908 -- declaration or body (either the one that declares T, or a
5909 -- child unit).
5911 Subp := First_Entity (Scope (T));
5912 while Present (Subp) loop
5913 if Is_Overloadable (Subp) then
5914 Formal := First_Formal (Subp);
5916 if Present (Formal)
5917 and then Is_Controlling_Formal (Formal)
5918 and then
5919 (Base_Type (Etype (Formal)) = Bas
5920 or else
5921 (Is_Access_Type (Etype (Formal))
5922 and then Designated_Type (Etype (Formal)) = Bas))
5923 then
5924 Append_Elmt (Subp, Candidates);
5925 end if;
5926 end if;
5928 Next_Entity (Subp);
5929 end loop;
5931 return Candidates;
5932 end if;
5933 end Collect_Generic_Type_Ops;
5935 -----------------------------
5936 -- Valid_First_Argument_Of --
5937 -----------------------------
5939 function Valid_First_Argument_Of (Op : Entity_Id) return Boolean is
5940 Typ : constant Entity_Id := Etype (First_Formal (Op));
5942 begin
5943 -- Simple case. Object may be a subtype of the tagged type
5944 -- or may be the corresponding record of a synchronized type.
5946 return Obj_Type = Typ
5947 or else Base_Type (Obj_Type) = Typ
5949 or else Corr_Type = Typ
5951 -- Prefix can be dereferenced
5953 or else
5954 (Is_Access_Type (Corr_Type)
5955 and then Designated_Type (Corr_Type) = Typ)
5957 -- Formal is an access parameter, for which the object
5958 -- can provide an access.
5960 or else
5961 (Ekind (Typ) = E_Anonymous_Access_Type
5962 and then Designated_Type (Typ) = Base_Type (Corr_Type));
5963 end Valid_First_Argument_Of;
5965 -- Start of processing for Try_Primitive_Operation
5967 begin
5968 -- Look for subprograms in the list of primitive operations The name
5969 -- must be identical, and the kind of call indicates the expected
5970 -- kind of operation (function or procedure). If the type is a
5971 -- (tagged) synchronized type, the primitive ops are attached to
5972 -- the corresponding record type.
5974 if Is_Concurrent_Type (Obj_Type) then
5975 Corr_Type := Corresponding_Record_Type (Obj_Type);
5976 Elmt := First_Elmt (Primitive_Operations (Corr_Type));
5978 elsif not Is_Generic_Type (Obj_Type) then
5979 Corr_Type := Obj_Type;
5980 Elmt := First_Elmt (Primitive_Operations (Obj_Type));
5982 else
5983 Corr_Type := Obj_Type;
5984 Elmt := First_Elmt (Collect_Generic_Type_Ops (Obj_Type));
5985 end if;
5987 while Present (Elmt) loop
5988 Prim_Op := Node (Elmt);
5990 if Chars (Prim_Op) = Chars (Subprog)
5991 and then Present (First_Formal (Prim_Op))
5992 and then Valid_First_Argument_Of (Prim_Op)
5993 and then
5994 (Nkind (Call_Node) = N_Function_Call)
5995 = (Ekind (Prim_Op) = E_Function)
5996 then
5997 -- Ada 2005 (AI-251): If this primitive operation corresponds
5998 -- with an immediate ancestor interface there is no need to add
5999 -- it to the list of interpretations; the corresponding aliased
6000 -- primitive is also in this list of primitive operations and
6001 -- will be used instead.
6003 if (Present (Abstract_Interface_Alias (Prim_Op))
6004 and then Is_Ancestor (Find_Dispatching_Type
6005 (Alias (Prim_Op)), Corr_Type))
6006 or else
6008 -- Do not consider hidden primitives unless the type is
6009 -- in an open scope or we are within an instance, where
6010 -- visibility is known to be correct.
6012 (Is_Hidden (Prim_Op)
6013 and then not Is_Immediately_Visible (Obj_Type)
6014 and then not In_Instance)
6015 then
6016 goto Continue;
6017 end if;
6019 Set_Etype (Call_Node, Any_Type);
6020 Set_Is_Overloaded (Call_Node, False);
6022 if No (Matching_Op) then
6023 Prim_Op_Ref := New_Reference_To (Prim_Op, Sloc (Subprog));
6024 Candidate := Prim_Op;
6026 Set_Parent (Call_Node, Parent (Node_To_Replace));
6028 Set_Name (Call_Node, Prim_Op_Ref);
6029 Success := False;
6031 Analyze_One_Call
6032 (N => Call_Node,
6033 Nam => Prim_Op,
6034 Report => Report_Error,
6035 Success => Success,
6036 Skip_First => True);
6038 Matching_Op := Valid_Candidate (Success, Call_Node, Prim_Op);
6040 else
6042 -- More than one interpretation, collect for subsequent
6043 -- disambiguation. If this is a procedure call and there
6044 -- is another match, report ambiguity now.
6046 Analyze_One_Call
6047 (N => Call_Node,
6048 Nam => Prim_Op,
6049 Report => Report_Error,
6050 Success => Success,
6051 Skip_First => True);
6053 if Present (Valid_Candidate (Success, Call_Node, Prim_Op))
6054 and then Nkind (Call_Node) /= N_Function_Call
6055 then
6056 Error_Msg_NE ("ambiguous call to&", N, Prim_Op);
6057 Report_Ambiguity (Matching_Op);
6058 Report_Ambiguity (Prim_Op);
6059 return True;
6060 end if;
6061 end if;
6062 end if;
6064 <<Continue>>
6065 Next_Elmt (Elmt);
6066 end loop;
6068 if Present (Matching_Op) then
6069 Set_Etype (Call_Node, Etype (Matching_Op));
6070 end if;
6072 return Present (Matching_Op);
6073 end Try_Primitive_Operation;
6075 -- Start of processing for Try_Object_Operation
6077 begin
6078 Analyze_Expression (Obj);
6080 -- Analyze the actuals if node is known to be a subprogram call
6082 if Is_Subprg_Call and then N = Name (Parent (N)) then
6083 Actual := First (Parameter_Associations (Parent (N)));
6084 while Present (Actual) loop
6085 Analyze_Expression (Actual);
6086 Next (Actual);
6087 end loop;
6088 end if;
6090 -- Build a subprogram call node, using a copy of Obj as its first
6091 -- actual. This is a placeholder, to be replaced by an explicit
6092 -- dereference when needed.
6094 Transform_Object_Operation
6095 (Call_Node => New_Call_Node,
6096 Node_To_Replace => Node_To_Replace);
6098 Set_Etype (New_Call_Node, Any_Type);
6099 Set_Etype (Subprog, Any_Type);
6100 Set_Parent (New_Call_Node, Parent (Node_To_Replace));
6102 if not Is_Overloaded (Obj) then
6103 Try_One_Prefix_Interpretation (Obj_Type);
6105 else
6106 declare
6107 I : Interp_Index;
6108 It : Interp;
6109 begin
6110 Get_First_Interp (Obj, I, It);
6111 while Present (It.Nam) loop
6112 Try_One_Prefix_Interpretation (It.Typ);
6113 Get_Next_Interp (I, It);
6114 end loop;
6115 end;
6116 end if;
6118 if Etype (New_Call_Node) /= Any_Type then
6119 Complete_Object_Operation
6120 (Call_Node => New_Call_Node,
6121 Node_To_Replace => Node_To_Replace);
6122 return True;
6124 elsif Present (Candidate) then
6126 -- The argument list is not type correct. Re-analyze with error
6127 -- reporting enabled, and use one of the possible candidates.
6128 -- In all_errors mode, re-analyze all failed interpretations.
6130 if All_Errors_Mode then
6131 Report_Error := True;
6132 if Try_Primitive_Operation
6133 (Call_Node => New_Call_Node,
6134 Node_To_Replace => Node_To_Replace)
6136 or else
6137 Try_Class_Wide_Operation
6138 (Call_Node => New_Call_Node,
6139 Node_To_Replace => Node_To_Replace)
6140 then
6141 null;
6142 end if;
6144 else
6145 Analyze_One_Call
6146 (N => New_Call_Node,
6147 Nam => Candidate,
6148 Report => True,
6149 Success => Success,
6150 Skip_First => True);
6151 end if;
6153 return True; -- No need for further errors.
6155 else
6156 -- There was no candidate operation, so report it as an error
6157 -- in the caller: Analyze_Selected_Component.
6159 return False;
6160 end if;
6161 end Try_Object_Operation;
6163 end Sem_Ch4;