* gnu/regexp/CharIndexedReader.java: Removed.
[official-gcc.git] / gcc / ada / sem_ch4.adb
blob8722b77692df3c78ea1142c7062756dba62e0443
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-2004, Free Software Foundation, Inc. --
10 -- --
11 -- GNAT is free software; you can redistribute it and/or modify it under --
12 -- terms of the GNU General Public License as published by the Free Soft- --
13 -- ware Foundation; either version 2, or (at your option) any later ver- --
14 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
17 -- for more details. You should have received a copy of the GNU General --
18 -- Public License distributed with GNAT; see file COPYING. If not, write --
19 -- to the Free Software Foundation, 59 Temple Place - Suite 330, Boston, --
20 -- MA 02111-1307, USA. --
21 -- --
22 -- GNAT was originally developed by the GNAT team at New York University. --
23 -- Extensive contributions were provided by Ada Core Technologies Inc. --
24 -- --
25 ------------------------------------------------------------------------------
27 with Atree; use Atree;
28 with Checks; use Checks;
29 with Debug; use Debug;
30 with Einfo; use Einfo;
31 with Errout; use Errout;
32 with Exp_Util; use Exp_Util;
33 with Fname; use Fname;
34 with Itypes; use Itypes;
35 with Lib; use Lib;
36 with Lib.Xref; use Lib.Xref;
37 with Namet; use Namet;
38 with Nlists; use Nlists;
39 with Nmake; use Nmake;
40 with Opt; use Opt;
41 with Output; use Output;
42 with Restrict; use Restrict;
43 with Rident; use Rident;
44 with Sem; use Sem;
45 with Sem_Cat; use Sem_Cat;
46 with Sem_Ch3; use Sem_Ch3;
47 with Sem_Ch8; use Sem_Ch8;
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 -- Check one interpretation of an overloaded subprogram name for
104 -- compatibility with the types of the actuals in a call. If there is a
105 -- single interpretation which does not match, post error if Report is
106 -- set to True.
108 -- Nam is the entity that provides the formals against which the actuals
109 -- are checked. Nam is either the name of a subprogram, or the internal
110 -- subprogram type constructed for an access_to_subprogram. If the actuals
111 -- are compatible with Nam, then Nam is added to the list of candidate
112 -- interpretations for N, and Success is set to True.
114 procedure Check_Misspelled_Selector
115 (Prefix : Entity_Id;
116 Sel : Node_Id);
117 -- Give possible misspelling diagnostic if Sel is likely to be
118 -- a misspelling of one of the selectors of the Prefix.
119 -- This is called by Analyze_Selected_Component after producing
120 -- an invalid selector error message.
122 function Defined_In_Scope (T : Entity_Id; S : Entity_Id) return Boolean;
123 -- Verify that type T is declared in scope S. Used to find intepretations
124 -- for operators given by expanded names. This is abstracted as a separate
125 -- function to handle extensions to System, where S is System, but T is
126 -- declared in the extension.
128 procedure Find_Arithmetic_Types
129 (L, R : Node_Id;
130 Op_Id : Entity_Id;
131 N : Node_Id);
132 -- L and R are the operands of an arithmetic operator. Find
133 -- consistent pairs of interpretations for L and R that have a
134 -- numeric type consistent with the semantics of the operator.
136 procedure Find_Comparison_Types
137 (L, R : Node_Id;
138 Op_Id : Entity_Id;
139 N : Node_Id);
140 -- L and R are operands of a comparison operator. Find consistent
141 -- pairs of interpretations for L and R.
143 procedure Find_Concatenation_Types
144 (L, R : Node_Id;
145 Op_Id : Entity_Id;
146 N : Node_Id);
147 -- For the four varieties of concatenation.
149 procedure Find_Equality_Types
150 (L, R : Node_Id;
151 Op_Id : Entity_Id;
152 N : Node_Id);
153 -- Ditto for equality operators.
155 procedure Find_Boolean_Types
156 (L, R : Node_Id;
157 Op_Id : Entity_Id;
158 N : Node_Id);
159 -- Ditto for binary logical operations.
161 procedure Find_Negation_Types
162 (R : Node_Id;
163 Op_Id : Entity_Id;
164 N : Node_Id);
165 -- Find consistent interpretation for operand of negation operator.
167 procedure Find_Non_Universal_Interpretations
168 (N : Node_Id;
169 R : Node_Id;
170 Op_Id : Entity_Id;
171 T1 : Entity_Id);
172 -- For equality and comparison operators, the result is always boolean,
173 -- and the legality of the operation is determined from the visibility
174 -- of the operand types. If one of the operands has a universal interpre-
175 -- tation, the legality check uses some compatible non-universal
176 -- interpretation of the other operand. N can be an operator node, or
177 -- a function call whose name is an operator designator.
179 procedure Find_Unary_Types
180 (R : Node_Id;
181 Op_Id : Entity_Id;
182 N : Node_Id);
183 -- Unary arithmetic types: plus, minus, abs.
185 procedure Check_Arithmetic_Pair
186 (T1, T2 : Entity_Id;
187 Op_Id : Entity_Id;
188 N : Node_Id);
189 -- Subsidiary procedure to Find_Arithmetic_Types. T1 and T2 are valid
190 -- types for left and right operand. Determine whether they constitute
191 -- a valid pair for the given operator, and record the corresponding
192 -- interpretation of the operator node. The node N may be an operator
193 -- node (the usual case) or a function call whose prefix is an operator
194 -- designator. In both cases Op_Id is the operator name itself.
196 procedure Diagnose_Call (N : Node_Id; Nam : Node_Id);
197 -- Give detailed information on overloaded call where none of the
198 -- interpretations match. N is the call node, Nam the designator for
199 -- the overloaded entity being called.
201 function Junk_Operand (N : Node_Id) return Boolean;
202 -- Test for an operand that is an inappropriate entity (e.g. a package
203 -- name or a label). If so, issue an error message and return True. If
204 -- the operand is not an inappropriate entity kind, return False.
206 procedure Operator_Check (N : Node_Id);
207 -- Verify that an operator has received some valid interpretation.
208 -- If none was found, determine whether a use clause would make the
209 -- operation legal. The variable Candidate_Type (defined in Sem_Type) is
210 -- set for every type compatible with the operator, even if the operator
211 -- for the type is not directly visible. The routine uses this type to emit
212 -- a more informative message.
214 procedure Remove_Abstract_Operations (N : Node_Id);
215 -- Ada 2005: implementation of AI-310. An abstract non-dispatching
216 -- operation is not a candidate interpretation.
218 function Try_Indexed_Call
219 (N : Node_Id;
220 Nam : Entity_Id;
221 Typ : Entity_Id) return Boolean;
222 -- If a function has defaults for all its actuals, a call to it may
223 -- in fact be an indexing on the result of the call. Try_Indexed_Call
224 -- attempts the interpretation as an indexing, prior to analysis as
225 -- a call. If both are possible, the node is overloaded with both
226 -- interpretations (same symbol but two different types).
228 function Try_Indirect_Call
229 (N : Node_Id;
230 Nam : Entity_Id;
231 Typ : Entity_Id) return Boolean;
232 -- Similarly, a function F that needs no actuals can return an access
233 -- to a subprogram, and the call F (X) interpreted as F.all (X). In
234 -- this case the call may be overloaded with both interpretations.
236 ------------------------
237 -- Ambiguous_Operands --
238 ------------------------
240 procedure Ambiguous_Operands (N : Node_Id) is
241 procedure List_Operand_Interps (Opnd : Node_Id);
243 procedure List_Operand_Interps (Opnd : Node_Id) is
244 Nam : Node_Id;
245 Err : Node_Id := N;
247 begin
248 if Is_Overloaded (Opnd) then
249 if Nkind (Opnd) in N_Op then
250 Nam := Opnd;
252 elsif Nkind (Opnd) = N_Function_Call then
253 Nam := Name (Opnd);
255 else
256 return;
257 end if;
259 else
260 return;
261 end if;
263 if Opnd = Left_Opnd (N) then
264 Error_Msg_N
265 ("\left operand has the following interpretations", N);
266 else
267 Error_Msg_N
268 ("\right operand has the following interpretations", N);
269 Err := Opnd;
270 end if;
272 List_Interps (Nam, Err);
273 end List_Operand_Interps;
275 begin
276 if Nkind (N) = N_In
277 or else Nkind (N) = N_Not_In
278 then
279 Error_Msg_N ("ambiguous operands for membership", N);
281 elsif Nkind (N) = N_Op_Eq
282 or else Nkind (N) = N_Op_Ne
283 then
284 Error_Msg_N ("ambiguous operands for equality", N);
286 else
287 Error_Msg_N ("ambiguous operands for comparison", N);
288 end if;
290 if All_Errors_Mode then
291 List_Operand_Interps (Left_Opnd (N));
292 List_Operand_Interps (Right_Opnd (N));
293 else
294 Error_Msg_N ("\use -gnatf switch for details", N);
295 end if;
296 end Ambiguous_Operands;
298 -----------------------
299 -- Analyze_Aggregate --
300 -----------------------
302 -- Most of the analysis of Aggregates requires that the type be known,
303 -- and is therefore put off until resolution.
305 procedure Analyze_Aggregate (N : Node_Id) is
306 begin
307 if No (Etype (N)) then
308 Set_Etype (N, Any_Composite);
309 end if;
310 end Analyze_Aggregate;
312 -----------------------
313 -- Analyze_Allocator --
314 -----------------------
316 procedure Analyze_Allocator (N : Node_Id) is
317 Loc : constant Source_Ptr := Sloc (N);
318 Sav_Errs : constant Nat := Serious_Errors_Detected;
319 E : Node_Id := Expression (N);
320 Acc_Type : Entity_Id;
321 Type_Id : Entity_Id;
323 begin
324 Check_Restriction (No_Allocators, N);
326 if Nkind (E) = N_Qualified_Expression then
327 Acc_Type := Create_Itype (E_Allocator_Type, N);
328 Set_Etype (Acc_Type, Acc_Type);
329 Init_Size_Align (Acc_Type);
330 Find_Type (Subtype_Mark (E));
331 Type_Id := Entity (Subtype_Mark (E));
332 Check_Fully_Declared (Type_Id, N);
333 Set_Directly_Designated_Type (Acc_Type, Type_Id);
335 if Is_Limited_Type (Type_Id)
336 and then Comes_From_Source (N)
337 and then not In_Instance_Body
338 then
339 -- Ada 0Y (AI-287): Do not post an error if the expression
340 -- corresponds to a limited aggregate. Limited aggregates
341 -- are checked in sem_aggr in a per-component manner
342 -- (compare with handling of Get_Value subprogram).
344 if Extensions_Allowed
345 and then Nkind (Expression (E)) = N_Aggregate
346 then
347 null;
348 else
349 Error_Msg_N ("initialization not allowed for limited types", N);
350 Explain_Limited_Type (Type_Id, N);
351 end if;
352 end if;
354 Analyze_And_Resolve (Expression (E), Type_Id);
356 -- A qualified expression requires an exact match of the type,
357 -- class-wide matching is not allowed.
359 if Is_Class_Wide_Type (Type_Id)
360 and then Base_Type (Etype (Expression (E))) /= Base_Type (Type_Id)
361 then
362 Wrong_Type (Expression (E), Type_Id);
363 end if;
365 Check_Non_Static_Context (Expression (E));
367 -- We don't analyze the qualified expression itself because it's
368 -- part of the allocator
370 Set_Etype (E, Type_Id);
372 else
373 declare
374 Def_Id : Entity_Id;
376 begin
377 -- If the allocator includes a N_Subtype_Indication then a
378 -- constraint is present, otherwise the node is a subtype mark.
379 -- Introduce an explicit subtype declaration into the tree
380 -- defining some anonymous subtype and rewrite the allocator to
381 -- use this subtype rather than the subtype indication.
383 -- It is important to introduce the explicit subtype declaration
384 -- so that the bounds of the subtype indication are attached to
385 -- the tree in case the allocator is inside a generic unit.
387 if Nkind (E) = N_Subtype_Indication then
389 -- A constraint is only allowed for a composite type in Ada
390 -- 95. In Ada 83, a constraint is also allowed for an
391 -- access-to-composite type, but the constraint is ignored.
393 Find_Type (Subtype_Mark (E));
395 if Is_Elementary_Type (Entity (Subtype_Mark (E))) then
396 if not (Ada_83
397 and then Is_Access_Type (Entity (Subtype_Mark (E))))
398 then
399 Error_Msg_N ("constraint not allowed here", E);
401 if Nkind (Constraint (E))
402 = N_Index_Or_Discriminant_Constraint
403 then
404 Error_Msg_N
405 ("\if qualified expression was meant, " &
406 "use apostrophe", Constraint (E));
407 end if;
408 end if;
410 -- Get rid of the bogus constraint:
412 Rewrite (E, New_Copy_Tree (Subtype_Mark (E)));
413 Analyze_Allocator (N);
414 return;
415 end if;
417 if Expander_Active then
418 Def_Id :=
419 Make_Defining_Identifier (Loc, New_Internal_Name ('S'));
421 Insert_Action (E,
422 Make_Subtype_Declaration (Loc,
423 Defining_Identifier => Def_Id,
424 Subtype_Indication => Relocate_Node (E)));
426 if Sav_Errs /= Serious_Errors_Detected
427 and then 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;
435 E := New_Occurrence_Of (Def_Id, Loc);
436 Rewrite (Expression (N), E);
437 end if;
438 end if;
440 Type_Id := Process_Subtype (E, N);
441 Acc_Type := Create_Itype (E_Allocator_Type, N);
442 Set_Etype (Acc_Type, Acc_Type);
443 Init_Size_Align (Acc_Type);
444 Set_Directly_Designated_Type (Acc_Type, Type_Id);
445 Check_Fully_Declared (Type_Id, N);
447 -- Ada 0Y (AI-231)
449 if Can_Never_Be_Null (Type_Id) then
450 Error_Msg_N ("(Ada 0Y) qualified expression required",
451 Expression (N));
452 end if;
454 -- Check restriction against dynamically allocated protected
455 -- objects. Note that when limited aggregates are supported,
456 -- a similar test should be applied to an allocator with a
457 -- qualified expression ???
459 if Is_Protected_Type (Type_Id) then
460 Check_Restriction (No_Protected_Type_Allocators, N);
461 end if;
463 -- Check for missing initialization. Skip this check if we already
464 -- had errors on analyzing the allocator, since in that case these
465 -- are probably cascaded errors
467 if Is_Indefinite_Subtype (Type_Id)
468 and then Serious_Errors_Detected = Sav_Errs
469 then
470 if Is_Class_Wide_Type (Type_Id) then
471 Error_Msg_N
472 ("initialization required in class-wide allocation", N);
473 else
474 Error_Msg_N
475 ("initialization required in unconstrained allocation", N);
476 end if;
477 end if;
478 end;
479 end if;
481 if Is_Abstract (Type_Id) then
482 Error_Msg_N ("cannot allocate abstract object", E);
483 end if;
485 if Has_Task (Designated_Type (Acc_Type)) then
486 Check_Restriction (No_Tasking, N);
487 Check_Restriction (Max_Tasks, N);
488 Check_Restriction (No_Task_Allocators, N);
489 end if;
491 Set_Etype (N, Acc_Type);
493 if not Is_Library_Level_Entity (Acc_Type) then
494 Check_Restriction (No_Local_Allocators, N);
495 end if;
497 -- Ada 0Y (AI-231): Static checks
499 if Extensions_Allowed
500 and then (Null_Exclusion_Present (N)
501 or else Can_Never_Be_Null (Etype (N)))
502 then
503 Null_Exclusion_Static_Checks (N);
504 end if;
506 if Serious_Errors_Detected > Sav_Errs then
507 Set_Error_Posted (N);
508 Set_Etype (N, Any_Type);
509 end if;
510 end Analyze_Allocator;
512 ---------------------------
513 -- Analyze_Arithmetic_Op --
514 ---------------------------
516 procedure Analyze_Arithmetic_Op (N : Node_Id) is
517 L : constant Node_Id := Left_Opnd (N);
518 R : constant Node_Id := Right_Opnd (N);
519 Op_Id : Entity_Id;
521 begin
522 Candidate_Type := Empty;
523 Analyze_Expression (L);
524 Analyze_Expression (R);
526 -- If the entity is already set, the node is the instantiation of
527 -- a generic node with a non-local reference, or was manufactured
528 -- by a call to Make_Op_xxx. In either case the entity is known to
529 -- be valid, and we do not need to collect interpretations, instead
530 -- we just get the single possible interpretation.
532 Op_Id := Entity (N);
534 if Present (Op_Id) then
535 if Ekind (Op_Id) = E_Operator then
537 if (Nkind (N) = N_Op_Divide or else
538 Nkind (N) = N_Op_Mod or else
539 Nkind (N) = N_Op_Multiply or else
540 Nkind (N) = N_Op_Rem)
541 and then Treat_Fixed_As_Integer (N)
542 then
543 null;
544 else
545 Set_Etype (N, Any_Type);
546 Find_Arithmetic_Types (L, R, Op_Id, N);
547 end if;
549 else
550 Set_Etype (N, Any_Type);
551 Add_One_Interp (N, Op_Id, Etype (Op_Id));
552 end if;
554 -- Entity is not already set, so we do need to collect interpretations
556 else
557 Op_Id := Get_Name_Entity_Id (Chars (N));
558 Set_Etype (N, Any_Type);
560 while Present (Op_Id) loop
561 if Ekind (Op_Id) = E_Operator
562 and then Present (Next_Entity (First_Entity (Op_Id)))
563 then
564 Find_Arithmetic_Types (L, R, Op_Id, N);
566 -- The following may seem superfluous, because an operator cannot
567 -- be generic, but this ignores the cleverness of the author of
568 -- ACVC bc1013a.
570 elsif Is_Overloadable (Op_Id) then
571 Analyze_User_Defined_Binary_Op (N, Op_Id);
572 end if;
574 Op_Id := Homonym (Op_Id);
575 end loop;
576 end if;
578 Operator_Check (N);
579 end Analyze_Arithmetic_Op;
581 ------------------
582 -- Analyze_Call --
583 ------------------
585 -- Function, procedure, and entry calls are checked here. The Name
586 -- in the call may be overloaded. The actuals have been analyzed
587 -- and may themselves be overloaded. On exit from this procedure, the node
588 -- N may have zero, one or more interpretations. In the first case an error
589 -- message is produced. In the last case, the node is flagged as overloaded
590 -- and the interpretations are collected in All_Interp.
592 -- If the name is an Access_To_Subprogram, it cannot be overloaded, but
593 -- the type-checking is similar to that of other calls.
595 procedure Analyze_Call (N : Node_Id) is
596 Actuals : constant List_Id := Parameter_Associations (N);
597 Nam : Node_Id := Name (N);
598 X : Interp_Index;
599 It : Interp;
600 Nam_Ent : Entity_Id;
601 Success : Boolean := False;
603 function Name_Denotes_Function return Boolean;
604 -- If the type of the name is an access to subprogram, this may be
605 -- the type of a name, or the return type of the function being called.
606 -- If the name is not an entity then it can denote a protected function.
607 -- Until we distinguish Etype from Return_Type, we must use this
608 -- routine to resolve the meaning of the name in the call.
610 ---------------------------
611 -- Name_Denotes_Function --
612 ---------------------------
614 function Name_Denotes_Function return Boolean is
615 begin
616 if Is_Entity_Name (Nam) then
617 return Ekind (Entity (Nam)) = E_Function;
619 elsif Nkind (Nam) = N_Selected_Component then
620 return Ekind (Entity (Selector_Name (Nam))) = E_Function;
622 else
623 return False;
624 end if;
625 end Name_Denotes_Function;
627 -- Start of processing for Analyze_Call
629 begin
630 -- Initialize the type of the result of the call to the error type,
631 -- which will be reset if the type is successfully resolved.
633 Set_Etype (N, Any_Type);
635 if not Is_Overloaded (Nam) then
637 -- Only one interpretation to check
639 if Ekind (Etype (Nam)) = E_Subprogram_Type then
640 Nam_Ent := Etype (Nam);
642 elsif Is_Access_Type (Etype (Nam))
643 and then Ekind (Designated_Type (Etype (Nam))) = E_Subprogram_Type
644 and then not Name_Denotes_Function
645 then
646 Nam_Ent := Designated_Type (Etype (Nam));
647 Insert_Explicit_Dereference (Nam);
649 -- Selected component case. Simple entry or protected operation,
650 -- where the entry name is given by the selector name.
652 elsif Nkind (Nam) = N_Selected_Component then
653 Nam_Ent := Entity (Selector_Name (Nam));
655 if Ekind (Nam_Ent) /= E_Entry
656 and then Ekind (Nam_Ent) /= E_Entry_Family
657 and then Ekind (Nam_Ent) /= E_Function
658 and then Ekind (Nam_Ent) /= E_Procedure
659 then
660 Error_Msg_N ("name in call is not a callable entity", Nam);
661 Set_Etype (N, Any_Type);
662 return;
663 end if;
665 -- If the name is an Indexed component, it can be a call to a member
666 -- of an entry family. The prefix must be a selected component whose
667 -- selector is the entry. Analyze_Procedure_Call normalizes several
668 -- kinds of call into this form.
670 elsif Nkind (Nam) = N_Indexed_Component then
672 if Nkind (Prefix (Nam)) = N_Selected_Component then
673 Nam_Ent := Entity (Selector_Name (Prefix (Nam)));
675 else
676 Error_Msg_N ("name in call is not a callable entity", Nam);
677 Set_Etype (N, Any_Type);
678 return;
680 end if;
682 elsif not Is_Entity_Name (Nam) then
683 Error_Msg_N ("name in call is not a callable entity", Nam);
684 Set_Etype (N, Any_Type);
685 return;
687 else
688 Nam_Ent := Entity (Nam);
690 -- If no interpretations, give error message
692 if not Is_Overloadable (Nam_Ent) then
693 declare
694 L : constant Boolean := Is_List_Member (N);
695 K : constant Node_Kind := Nkind (Parent (N));
697 begin
698 -- If the node is in a list whose parent is not an
699 -- expression then it must be an attempted procedure call.
701 if L and then K not in N_Subexpr then
702 if Ekind (Entity (Nam)) = E_Generic_Procedure then
703 Error_Msg_NE
704 ("must instantiate generic procedure& before call",
705 Nam, Entity (Nam));
706 else
707 Error_Msg_N
708 ("procedure or entry name expected", Nam);
709 end if;
711 -- Check for tasking cases where only an entry call will do
713 elsif not L
714 and then (K = N_Entry_Call_Alternative
715 or else K = N_Triggering_Alternative)
716 then
717 Error_Msg_N ("entry name expected", Nam);
719 -- Otherwise give general error message
721 else
722 Error_Msg_N ("invalid prefix in call", Nam);
723 end if;
725 return;
726 end;
727 end if;
728 end if;
730 Analyze_One_Call (N, Nam_Ent, True, Success);
732 else
733 -- An overloaded selected component must denote overloaded
734 -- operations of a concurrent type. The interpretations are
735 -- attached to the simple name of those operations.
737 if Nkind (Nam) = N_Selected_Component then
738 Nam := Selector_Name (Nam);
739 end if;
741 Get_First_Interp (Nam, X, It);
743 while Present (It.Nam) loop
744 Nam_Ent := It.Nam;
746 -- Name may be call that returns an access to subprogram, or more
747 -- generally an overloaded expression one of whose interpretations
748 -- yields an access to subprogram. If the name is an entity, we
749 -- do not dereference, because the node is a call that returns
750 -- the access type: note difference between f(x), where the call
751 -- may return an access subprogram type, and f(x)(y), where the
752 -- type returned by the call to f is implicitly dereferenced to
753 -- analyze the outer call.
755 if Is_Access_Type (Nam_Ent) then
756 Nam_Ent := Designated_Type (Nam_Ent);
758 elsif Is_Access_Type (Etype (Nam_Ent))
759 and then not Is_Entity_Name (Nam)
760 and then Ekind (Designated_Type (Etype (Nam_Ent)))
761 = E_Subprogram_Type
762 then
763 Nam_Ent := Designated_Type (Etype (Nam_Ent));
764 end if;
766 Analyze_One_Call (N, Nam_Ent, False, Success);
768 -- If the interpretation succeeds, mark the proper type of the
769 -- prefix (any valid candidate will do). If not, remove the
770 -- candidate interpretation. This only needs to be done for
771 -- overloaded protected operations, for other entities disambi-
772 -- guation is done directly in Resolve.
774 if Success then
775 Set_Etype (Nam, It.Typ);
777 elsif Nkind (Name (N)) = N_Selected_Component
778 or else Nkind (Name (N)) = N_Function_Call
779 then
780 Remove_Interp (X);
781 end if;
783 Get_Next_Interp (X, It);
784 end loop;
786 -- If the name is the result of a function call, it can only
787 -- be a call to a function returning an access to subprogram.
788 -- Insert explicit dereference.
790 if Nkind (Nam) = N_Function_Call then
791 Insert_Explicit_Dereference (Nam);
792 end if;
794 if Etype (N) = Any_Type then
796 -- None of the interpretations is compatible with the actuals
798 Diagnose_Call (N, Nam);
800 -- Special checks for uninstantiated put routines
802 if Nkind (N) = N_Procedure_Call_Statement
803 and then Is_Entity_Name (Nam)
804 and then Chars (Nam) = Name_Put
805 and then List_Length (Actuals) = 1
806 then
807 declare
808 Arg : constant Node_Id := First (Actuals);
809 Typ : Entity_Id;
811 begin
812 if Nkind (Arg) = N_Parameter_Association then
813 Typ := Etype (Explicit_Actual_Parameter (Arg));
814 else
815 Typ := Etype (Arg);
816 end if;
818 if Is_Signed_Integer_Type (Typ) then
819 Error_Msg_N
820 ("possible missing instantiation of " &
821 "'Text_'I'O.'Integer_'I'O!", Nam);
823 elsif Is_Modular_Integer_Type (Typ) then
824 Error_Msg_N
825 ("possible missing instantiation of " &
826 "'Text_'I'O.'Modular_'I'O!", Nam);
828 elsif Is_Floating_Point_Type (Typ) then
829 Error_Msg_N
830 ("possible missing instantiation of " &
831 "'Text_'I'O.'Float_'I'O!", Nam);
833 elsif Is_Ordinary_Fixed_Point_Type (Typ) then
834 Error_Msg_N
835 ("possible missing instantiation of " &
836 "'Text_'I'O.'Fixed_'I'O!", Nam);
838 elsif Is_Decimal_Fixed_Point_Type (Typ) then
839 Error_Msg_N
840 ("possible missing instantiation of " &
841 "'Text_'I'O.'Decimal_'I'O!", Nam);
843 elsif Is_Enumeration_Type (Typ) then
844 Error_Msg_N
845 ("possible missing instantiation of " &
846 "'Text_'I'O.'Enumeration_'I'O!", Nam);
847 end if;
848 end;
849 end if;
851 elsif not Is_Overloaded (N)
852 and then Is_Entity_Name (Nam)
853 then
854 -- Resolution yields a single interpretation. Verify that
855 -- is has the proper capitalization.
857 Set_Entity_With_Style_Check (Nam, Entity (Nam));
858 Generate_Reference (Entity (Nam), Nam);
860 Set_Etype (Nam, Etype (Entity (Nam)));
861 else
862 Remove_Abstract_Operations (N);
863 end if;
865 End_Interp_List;
866 end if;
867 end Analyze_Call;
869 ---------------------------
870 -- Analyze_Comparison_Op --
871 ---------------------------
873 procedure Analyze_Comparison_Op (N : Node_Id) is
874 L : constant Node_Id := Left_Opnd (N);
875 R : constant Node_Id := Right_Opnd (N);
876 Op_Id : Entity_Id := Entity (N);
878 begin
879 Set_Etype (N, Any_Type);
880 Candidate_Type := Empty;
882 Analyze_Expression (L);
883 Analyze_Expression (R);
885 if Present (Op_Id) then
887 if Ekind (Op_Id) = E_Operator then
888 Find_Comparison_Types (L, R, Op_Id, N);
889 else
890 Add_One_Interp (N, Op_Id, Etype (Op_Id));
891 end if;
893 if Is_Overloaded (L) then
894 Set_Etype (L, Intersect_Types (L, R));
895 end if;
897 else
898 Op_Id := Get_Name_Entity_Id (Chars (N));
900 while Present (Op_Id) loop
902 if Ekind (Op_Id) = E_Operator then
903 Find_Comparison_Types (L, R, Op_Id, N);
904 else
905 Analyze_User_Defined_Binary_Op (N, Op_Id);
906 end if;
908 Op_Id := Homonym (Op_Id);
909 end loop;
910 end if;
912 Operator_Check (N);
913 end Analyze_Comparison_Op;
915 ---------------------------
916 -- Analyze_Concatenation --
917 ---------------------------
919 -- If the only one-dimensional array type in scope is String,
920 -- this is the resulting type of the operation. Otherwise there
921 -- will be a concatenation operation defined for each user-defined
922 -- one-dimensional array.
924 procedure Analyze_Concatenation (N : Node_Id) is
925 L : constant Node_Id := Left_Opnd (N);
926 R : constant Node_Id := Right_Opnd (N);
927 Op_Id : Entity_Id := Entity (N);
928 LT : Entity_Id;
929 RT : Entity_Id;
931 begin
932 Set_Etype (N, Any_Type);
933 Candidate_Type := Empty;
935 Analyze_Expression (L);
936 Analyze_Expression (R);
938 -- If the entity is present, the node appears in an instance,
939 -- and denotes a predefined concatenation operation. The resulting
940 -- type is obtained from the arguments when possible. If the arguments
941 -- are aggregates, the array type and the concatenation type must be
942 -- visible.
944 if Present (Op_Id) then
945 if Ekind (Op_Id) = E_Operator then
947 LT := Base_Type (Etype (L));
948 RT := Base_Type (Etype (R));
950 if Is_Array_Type (LT)
951 and then (RT = LT or else RT = Base_Type (Component_Type (LT)))
952 then
953 Add_One_Interp (N, Op_Id, LT);
955 elsif Is_Array_Type (RT)
956 and then LT = Base_Type (Component_Type (RT))
957 then
958 Add_One_Interp (N, Op_Id, RT);
960 -- If one operand is a string type or a user-defined array type,
961 -- and the other is a literal, result is of the specific type.
963 elsif
964 (Root_Type (LT) = Standard_String
965 or else Scope (LT) /= Standard_Standard)
966 and then Etype (R) = Any_String
967 then
968 Add_One_Interp (N, Op_Id, LT);
970 elsif
971 (Root_Type (RT) = Standard_String
972 or else Scope (RT) /= Standard_Standard)
973 and then Etype (L) = Any_String
974 then
975 Add_One_Interp (N, Op_Id, RT);
977 elsif not Is_Generic_Type (Etype (Op_Id)) then
978 Add_One_Interp (N, Op_Id, Etype (Op_Id));
980 else
981 -- Type and its operations must be visible.
983 Set_Entity (N, Empty);
984 Analyze_Concatenation (N);
986 end if;
988 else
989 Add_One_Interp (N, Op_Id, Etype (Op_Id));
990 end if;
992 else
993 Op_Id := Get_Name_Entity_Id (Name_Op_Concat);
995 while Present (Op_Id) loop
996 if Ekind (Op_Id) = E_Operator then
997 Find_Concatenation_Types (L, R, Op_Id, N);
998 else
999 Analyze_User_Defined_Binary_Op (N, Op_Id);
1000 end if;
1002 Op_Id := Homonym (Op_Id);
1003 end loop;
1004 end if;
1006 Operator_Check (N);
1007 end Analyze_Concatenation;
1009 ------------------------------------
1010 -- Analyze_Conditional_Expression --
1011 ------------------------------------
1013 procedure Analyze_Conditional_Expression (N : Node_Id) is
1014 Condition : constant Node_Id := First (Expressions (N));
1015 Then_Expr : constant Node_Id := Next (Condition);
1016 Else_Expr : constant Node_Id := Next (Then_Expr);
1018 begin
1019 Analyze_Expression (Condition);
1020 Analyze_Expression (Then_Expr);
1021 Analyze_Expression (Else_Expr);
1022 Set_Etype (N, Etype (Then_Expr));
1023 end Analyze_Conditional_Expression;
1025 -------------------------
1026 -- Analyze_Equality_Op --
1027 -------------------------
1029 procedure Analyze_Equality_Op (N : Node_Id) is
1030 Loc : constant Source_Ptr := Sloc (N);
1031 L : constant Node_Id := Left_Opnd (N);
1032 R : constant Node_Id := Right_Opnd (N);
1033 Op_Id : Entity_Id;
1035 begin
1036 Set_Etype (N, Any_Type);
1037 Candidate_Type := Empty;
1039 Analyze_Expression (L);
1040 Analyze_Expression (R);
1042 -- If the entity is set, the node is a generic instance with a non-local
1043 -- reference to the predefined operator or to a user-defined function.
1044 -- It can also be an inequality that is expanded into the negation of a
1045 -- call to a user-defined equality operator.
1047 -- For the predefined case, the result is Boolean, regardless of the
1048 -- type of the operands. The operands may even be limited, if they are
1049 -- generic actuals. If they are overloaded, label the left argument with
1050 -- the common type that must be present, or with the type of the formal
1051 -- of the user-defined function.
1053 if Present (Entity (N)) then
1055 Op_Id := Entity (N);
1057 if Ekind (Op_Id) = E_Operator then
1058 Add_One_Interp (N, Op_Id, Standard_Boolean);
1059 else
1060 Add_One_Interp (N, Op_Id, Etype (Op_Id));
1061 end if;
1063 if Is_Overloaded (L) then
1065 if Ekind (Op_Id) = E_Operator then
1066 Set_Etype (L, Intersect_Types (L, R));
1067 else
1068 Set_Etype (L, Etype (First_Formal (Op_Id)));
1069 end if;
1070 end if;
1072 else
1073 Op_Id := Get_Name_Entity_Id (Chars (N));
1075 while Present (Op_Id) loop
1077 if Ekind (Op_Id) = E_Operator then
1078 Find_Equality_Types (L, R, Op_Id, N);
1079 else
1080 Analyze_User_Defined_Binary_Op (N, Op_Id);
1081 end if;
1083 Op_Id := Homonym (Op_Id);
1084 end loop;
1085 end if;
1087 -- If there was no match, and the operator is inequality, this may
1088 -- be a case where inequality has not been made explicit, as for
1089 -- tagged types. Analyze the node as the negation of an equality
1090 -- operation. This cannot be done earlier, because before analysis
1091 -- we cannot rule out the presence of an explicit inequality.
1093 if Etype (N) = Any_Type
1094 and then Nkind (N) = N_Op_Ne
1095 then
1096 Op_Id := Get_Name_Entity_Id (Name_Op_Eq);
1098 while Present (Op_Id) loop
1100 if Ekind (Op_Id) = E_Operator then
1101 Find_Equality_Types (L, R, Op_Id, N);
1102 else
1103 Analyze_User_Defined_Binary_Op (N, Op_Id);
1104 end if;
1106 Op_Id := Homonym (Op_Id);
1107 end loop;
1109 if Etype (N) /= Any_Type then
1110 Op_Id := Entity (N);
1112 Rewrite (N,
1113 Make_Op_Not (Loc,
1114 Right_Opnd =>
1115 Make_Op_Eq (Loc,
1116 Left_Opnd => Relocate_Node (Left_Opnd (N)),
1117 Right_Opnd => Relocate_Node (Right_Opnd (N)))));
1119 Set_Entity (Right_Opnd (N), Op_Id);
1120 Analyze (N);
1121 end if;
1122 end if;
1124 Operator_Check (N);
1125 end Analyze_Equality_Op;
1127 ----------------------------------
1128 -- Analyze_Explicit_Dereference --
1129 ----------------------------------
1131 procedure Analyze_Explicit_Dereference (N : Node_Id) is
1132 Loc : constant Source_Ptr := Sloc (N);
1133 P : constant Node_Id := Prefix (N);
1134 T : Entity_Id;
1135 I : Interp_Index;
1136 It : Interp;
1137 New_N : Node_Id;
1139 function Is_Function_Type return Boolean;
1140 -- Check whether node may be interpreted as an implicit function call.
1142 function Is_Function_Type return Boolean is
1143 I : Interp_Index;
1144 It : Interp;
1146 begin
1147 if not Is_Overloaded (N) then
1148 return Ekind (Base_Type (Etype (N))) = E_Subprogram_Type
1149 and then Etype (Base_Type (Etype (N))) /= Standard_Void_Type;
1151 else
1152 Get_First_Interp (N, I, It);
1154 while Present (It.Nam) loop
1155 if Ekind (Base_Type (It.Typ)) /= E_Subprogram_Type
1156 or else Etype (Base_Type (It.Typ)) = Standard_Void_Type
1157 then
1158 return False;
1159 end if;
1161 Get_Next_Interp (I, It);
1162 end loop;
1164 return True;
1165 end if;
1166 end Is_Function_Type;
1168 begin
1169 Analyze (P);
1170 Set_Etype (N, Any_Type);
1172 -- Test for remote access to subprogram type, and if so return
1173 -- after rewriting the original tree.
1175 if Remote_AST_E_Dereference (P) then
1176 return;
1177 end if;
1179 -- Normal processing for other than remote access to subprogram type
1181 if not Is_Overloaded (P) then
1182 if Is_Access_Type (Etype (P)) then
1184 -- Set the Etype. We need to go thru Is_For_Access_Subtypes
1185 -- to avoid other problems caused by the Private_Subtype
1186 -- and it is safe to go to the Base_Type because this is the
1187 -- same as converting the access value to its Base_Type.
1189 declare
1190 DT : Entity_Id := Designated_Type (Etype (P));
1192 begin
1193 if Ekind (DT) = E_Private_Subtype
1194 and then Is_For_Access_Subtype (DT)
1195 then
1196 DT := Base_Type (DT);
1197 end if;
1199 Set_Etype (N, DT);
1200 end;
1202 elsif Etype (P) /= Any_Type then
1203 Error_Msg_N ("prefix of dereference must be an access type", N);
1204 return;
1205 end if;
1207 else
1208 Get_First_Interp (P, I, It);
1210 while Present (It.Nam) loop
1211 T := It.Typ;
1213 if Is_Access_Type (T) then
1214 Add_One_Interp (N, Designated_Type (T), Designated_Type (T));
1215 end if;
1217 Get_Next_Interp (I, It);
1218 end loop;
1220 End_Interp_List;
1222 -- Error if no interpretation of the prefix has an access type.
1224 if Etype (N) = Any_Type then
1225 Error_Msg_N
1226 ("access type required in prefix of explicit dereference", P);
1227 Set_Etype (N, Any_Type);
1228 return;
1229 end if;
1230 end if;
1232 if Is_Function_Type
1233 and then Nkind (Parent (N)) /= N_Indexed_Component
1235 and then (Nkind (Parent (N)) /= N_Function_Call
1236 or else N /= Name (Parent (N)))
1238 and then (Nkind (Parent (N)) /= N_Procedure_Call_Statement
1239 or else N /= Name (Parent (N)))
1241 and then Nkind (Parent (N)) /= N_Subprogram_Renaming_Declaration
1242 and then (Nkind (Parent (N)) /= N_Attribute_Reference
1243 or else
1244 (Attribute_Name (Parent (N)) /= Name_Address
1245 and then
1246 Attribute_Name (Parent (N)) /= Name_Access))
1247 then
1248 -- Name is a function call with no actuals, in a context that
1249 -- requires deproceduring (including as an actual in an enclosing
1250 -- function or procedure call). We can conceive of pathological cases
1251 -- where the prefix might include functions that return access to
1252 -- subprograms and others that return a regular type. Disambiguation
1253 -- of those will have to take place in Resolve. See e.g. 7117-014.
1255 New_N :=
1256 Make_Function_Call (Loc,
1257 Name => Make_Explicit_Dereference (Loc, P),
1258 Parameter_Associations => New_List);
1260 -- If the prefix is overloaded, remove operations that have formals,
1261 -- we know that this is a parameterless call.
1263 if Is_Overloaded (P) then
1264 Get_First_Interp (P, I, It);
1266 while Present (It.Nam) loop
1267 T := It.Typ;
1269 if No (First_Formal (Base_Type (Designated_Type (T)))) then
1270 Set_Etype (P, T);
1271 else
1272 Remove_Interp (I);
1273 end if;
1275 Get_Next_Interp (I, It);
1276 end loop;
1277 end if;
1279 Rewrite (N, New_N);
1280 Analyze (N);
1281 end if;
1283 -- A value of remote access-to-class-wide must not be dereferenced
1284 -- (RM E.2.2(16)).
1286 Validate_Remote_Access_To_Class_Wide_Type (N);
1288 end Analyze_Explicit_Dereference;
1290 ------------------------
1291 -- Analyze_Expression --
1292 ------------------------
1294 procedure Analyze_Expression (N : Node_Id) is
1295 begin
1296 Analyze (N);
1297 Check_Parameterless_Call (N);
1298 end Analyze_Expression;
1300 ------------------------------------
1301 -- Analyze_Indexed_Component_Form --
1302 ------------------------------------
1304 procedure Analyze_Indexed_Component_Form (N : Node_Id) is
1305 P : constant Node_Id := Prefix (N);
1306 Exprs : constant List_Id := Expressions (N);
1307 Exp : Node_Id;
1308 P_T : Entity_Id;
1309 E : Node_Id;
1310 U_N : Entity_Id;
1312 procedure Process_Function_Call;
1313 -- Prefix in indexed component form is an overloadable entity,
1314 -- so the node is a function call. Reformat it as such.
1316 procedure Process_Indexed_Component;
1317 -- Prefix in indexed component form is actually an indexed component.
1318 -- This routine processes it, knowing that the prefix is already
1319 -- resolved.
1321 procedure Process_Indexed_Component_Or_Slice;
1322 -- An indexed component with a single index may designate a slice if
1323 -- the index is a subtype mark. This routine disambiguates these two
1324 -- cases by resolving the prefix to see if it is a subtype mark.
1326 procedure Process_Overloaded_Indexed_Component;
1327 -- If the prefix of an indexed component is overloaded, the proper
1328 -- interpretation is selected by the index types and the context.
1330 ---------------------------
1331 -- Process_Function_Call --
1332 ---------------------------
1334 procedure Process_Function_Call is
1335 Actual : Node_Id;
1337 begin
1338 Change_Node (N, N_Function_Call);
1339 Set_Name (N, P);
1340 Set_Parameter_Associations (N, Exprs);
1341 Actual := First (Parameter_Associations (N));
1343 while Present (Actual) loop
1344 Analyze (Actual);
1345 Check_Parameterless_Call (Actual);
1346 Next_Actual (Actual);
1347 end loop;
1349 Analyze_Call (N);
1350 end Process_Function_Call;
1352 -------------------------------
1353 -- Process_Indexed_Component --
1354 -------------------------------
1356 procedure Process_Indexed_Component is
1357 Exp : Node_Id;
1358 Array_Type : Entity_Id;
1359 Index : Node_Id;
1360 Entry_Family : Entity_Id;
1362 begin
1363 Exp := First (Exprs);
1365 if Is_Overloaded (P) then
1366 Process_Overloaded_Indexed_Component;
1368 else
1369 Array_Type := Etype (P);
1371 -- Prefix must be appropriate for an array type.
1372 -- Dereference the prefix if it is an access type.
1374 if Is_Access_Type (Array_Type) then
1375 Array_Type := Designated_Type (Array_Type);
1376 Error_Msg_NW (Warn_On_Dereference, "?implicit dereference", N);
1377 end if;
1379 if Is_Array_Type (Array_Type) then
1380 null;
1382 elsif (Is_Entity_Name (P)
1383 and then
1384 Ekind (Entity (P)) = E_Entry_Family)
1385 or else
1386 (Nkind (P) = N_Selected_Component
1387 and then
1388 Is_Entity_Name (Selector_Name (P))
1389 and then
1390 Ekind (Entity (Selector_Name (P))) = E_Entry_Family)
1391 then
1392 if Is_Entity_Name (P) then
1393 Entry_Family := Entity (P);
1394 else
1395 Entry_Family := Entity (Selector_Name (P));
1396 end if;
1398 Analyze (Exp);
1399 Set_Etype (N, Any_Type);
1401 if not Has_Compatible_Type
1402 (Exp, Entry_Index_Type (Entry_Family))
1403 then
1404 Error_Msg_N ("invalid index type in entry name", N);
1406 elsif Present (Next (Exp)) then
1407 Error_Msg_N ("too many subscripts in entry reference", N);
1409 else
1410 Set_Etype (N, Etype (P));
1411 end if;
1413 return;
1415 elsif Is_Record_Type (Array_Type)
1416 and then Remote_AST_I_Dereference (P)
1417 then
1418 return;
1420 elsif Array_Type = Any_Type then
1421 Set_Etype (N, Any_Type);
1422 return;
1424 -- Here we definitely have a bad indexing
1426 else
1427 if Nkind (Parent (N)) = N_Requeue_Statement
1428 and then
1429 ((Is_Entity_Name (P)
1430 and then Ekind (Entity (P)) = E_Entry)
1431 or else
1432 (Nkind (P) = N_Selected_Component
1433 and then Is_Entity_Name (Selector_Name (P))
1434 and then Ekind (Entity (Selector_Name (P))) = E_Entry))
1435 then
1436 Error_Msg_N
1437 ("REQUEUE does not permit parameters", First (Exprs));
1439 elsif Is_Entity_Name (P)
1440 and then Etype (P) = Standard_Void_Type
1441 then
1442 Error_Msg_NE ("incorrect use of&", P, Entity (P));
1444 else
1445 Error_Msg_N ("array type required in indexed component", P);
1446 end if;
1448 Set_Etype (N, Any_Type);
1449 return;
1450 end if;
1452 Index := First_Index (Array_Type);
1454 while Present (Index) and then Present (Exp) loop
1455 if not Has_Compatible_Type (Exp, Etype (Index)) then
1456 Wrong_Type (Exp, Etype (Index));
1457 Set_Etype (N, Any_Type);
1458 return;
1459 end if;
1461 Next_Index (Index);
1462 Next (Exp);
1463 end loop;
1465 Set_Etype (N, Component_Type (Array_Type));
1467 if Present (Index) then
1468 Error_Msg_N
1469 ("too few subscripts in array reference", First (Exprs));
1471 elsif Present (Exp) then
1472 Error_Msg_N ("too many subscripts in array reference", Exp);
1473 end if;
1474 end if;
1476 end Process_Indexed_Component;
1478 ----------------------------------------
1479 -- Process_Indexed_Component_Or_Slice --
1480 ----------------------------------------
1482 procedure Process_Indexed_Component_Or_Slice is
1483 begin
1484 Exp := First (Exprs);
1486 while Present (Exp) loop
1487 Analyze_Expression (Exp);
1488 Next (Exp);
1489 end loop;
1491 Exp := First (Exprs);
1493 -- If one index is present, and it is a subtype name, then the
1494 -- node denotes a slice (note that the case of an explicit range
1495 -- for a slice was already built as an N_Slice node in the first
1496 -- place, so that case is not handled here).
1498 -- We use a replace rather than a rewrite here because this is one
1499 -- of the cases in which the tree built by the parser is plain wrong.
1501 if No (Next (Exp))
1502 and then Is_Entity_Name (Exp)
1503 and then Is_Type (Entity (Exp))
1504 then
1505 Replace (N,
1506 Make_Slice (Sloc (N),
1507 Prefix => P,
1508 Discrete_Range => New_Copy (Exp)));
1509 Analyze (N);
1511 -- Otherwise (more than one index present, or single index is not
1512 -- a subtype name), then we have the indexed component case.
1514 else
1515 Process_Indexed_Component;
1516 end if;
1517 end Process_Indexed_Component_Or_Slice;
1519 ------------------------------------------
1520 -- Process_Overloaded_Indexed_Component --
1521 ------------------------------------------
1523 procedure Process_Overloaded_Indexed_Component is
1524 Exp : Node_Id;
1525 I : Interp_Index;
1526 It : Interp;
1527 Typ : Entity_Id;
1528 Index : Node_Id;
1529 Found : Boolean;
1531 begin
1532 Set_Etype (N, Any_Type);
1533 Get_First_Interp (P, I, It);
1535 while Present (It.Nam) loop
1536 Typ := It.Typ;
1538 if Is_Access_Type (Typ) then
1539 Typ := Designated_Type (Typ);
1540 Error_Msg_NW (Warn_On_Dereference, "?implicit dereference", N);
1541 end if;
1543 if Is_Array_Type (Typ) then
1545 -- Got a candidate: verify that index types are compatible
1547 Index := First_Index (Typ);
1548 Found := True;
1550 Exp := First (Exprs);
1552 while Present (Index) and then Present (Exp) loop
1553 if Has_Compatible_Type (Exp, Etype (Index)) then
1554 null;
1555 else
1556 Found := False;
1557 Remove_Interp (I);
1558 exit;
1559 end if;
1561 Next_Index (Index);
1562 Next (Exp);
1563 end loop;
1565 if Found and then No (Index) and then No (Exp) then
1566 Add_One_Interp (N,
1567 Etype (Component_Type (Typ)),
1568 Etype (Component_Type (Typ)));
1569 end if;
1570 end if;
1572 Get_Next_Interp (I, It);
1573 end loop;
1575 if Etype (N) = Any_Type then
1576 Error_Msg_N ("no legal interpetation for indexed component", N);
1577 Set_Is_Overloaded (N, False);
1578 end if;
1580 End_Interp_List;
1581 end Process_Overloaded_Indexed_Component;
1583 ------------------------------------
1584 -- Analyze_Indexed_Component_Form --
1585 ------------------------------------
1587 begin
1588 -- Get name of array, function or type
1590 Analyze (P);
1591 if Nkind (N) = N_Function_Call
1592 or else Nkind (N) = N_Procedure_Call_Statement
1593 then
1594 -- If P is an explicit dereference whose prefix is of a
1595 -- remote access-to-subprogram type, then N has already
1596 -- been rewritten as a subprogram call and analyzed.
1598 return;
1599 end if;
1601 pragma Assert (Nkind (N) = N_Indexed_Component);
1603 P_T := Base_Type (Etype (P));
1605 if Is_Entity_Name (P)
1606 or else Nkind (P) = N_Operator_Symbol
1607 then
1608 U_N := Entity (P);
1610 if Ekind (U_N) in Type_Kind then
1612 -- Reformat node as a type conversion.
1614 E := Remove_Head (Exprs);
1616 if Present (First (Exprs)) then
1617 Error_Msg_N
1618 ("argument of type conversion must be single expression", N);
1619 end if;
1621 Change_Node (N, N_Type_Conversion);
1622 Set_Subtype_Mark (N, P);
1623 Set_Etype (N, U_N);
1624 Set_Expression (N, E);
1626 -- After changing the node, call for the specific Analysis
1627 -- routine directly, to avoid a double call to the expander.
1629 Analyze_Type_Conversion (N);
1630 return;
1631 end if;
1633 if Is_Overloadable (U_N) then
1634 Process_Function_Call;
1636 elsif Ekind (Etype (P)) = E_Subprogram_Type
1637 or else (Is_Access_Type (Etype (P))
1638 and then
1639 Ekind (Designated_Type (Etype (P))) = E_Subprogram_Type)
1640 then
1641 -- Call to access_to-subprogram with possible implicit dereference
1643 Process_Function_Call;
1645 elsif Is_Generic_Subprogram (U_N) then
1647 -- A common beginner's (or C++ templates fan) error.
1649 Error_Msg_N ("generic subprogram cannot be called", N);
1650 Set_Etype (N, Any_Type);
1651 return;
1653 else
1654 Process_Indexed_Component_Or_Slice;
1655 end if;
1657 -- If not an entity name, prefix is an expression that may denote
1658 -- an array or an access-to-subprogram.
1660 else
1661 if Ekind (P_T) = E_Subprogram_Type
1662 or else (Is_Access_Type (P_T)
1663 and then
1664 Ekind (Designated_Type (P_T)) = E_Subprogram_Type)
1665 then
1666 Process_Function_Call;
1668 elsif Nkind (P) = N_Selected_Component
1669 and then Ekind (Entity (Selector_Name (P))) = E_Function
1670 then
1671 Process_Function_Call;
1673 else
1674 -- Indexed component, slice, or a call to a member of a family
1675 -- entry, which will be converted to an entry call later.
1677 Process_Indexed_Component_Or_Slice;
1678 end if;
1679 end if;
1680 end Analyze_Indexed_Component_Form;
1682 ------------------------
1683 -- Analyze_Logical_Op --
1684 ------------------------
1686 procedure Analyze_Logical_Op (N : Node_Id) is
1687 L : constant Node_Id := Left_Opnd (N);
1688 R : constant Node_Id := Right_Opnd (N);
1689 Op_Id : Entity_Id := Entity (N);
1691 begin
1692 Set_Etype (N, Any_Type);
1693 Candidate_Type := Empty;
1695 Analyze_Expression (L);
1696 Analyze_Expression (R);
1698 if Present (Op_Id) then
1700 if Ekind (Op_Id) = E_Operator then
1701 Find_Boolean_Types (L, R, Op_Id, N);
1702 else
1703 Add_One_Interp (N, Op_Id, Etype (Op_Id));
1704 end if;
1706 else
1707 Op_Id := Get_Name_Entity_Id (Chars (N));
1709 while Present (Op_Id) loop
1710 if Ekind (Op_Id) = E_Operator then
1711 Find_Boolean_Types (L, R, Op_Id, N);
1712 else
1713 Analyze_User_Defined_Binary_Op (N, Op_Id);
1714 end if;
1716 Op_Id := Homonym (Op_Id);
1717 end loop;
1718 end if;
1720 Operator_Check (N);
1721 end Analyze_Logical_Op;
1723 ---------------------------
1724 -- Analyze_Membership_Op --
1725 ---------------------------
1727 procedure Analyze_Membership_Op (N : Node_Id) is
1728 L : constant Node_Id := Left_Opnd (N);
1729 R : constant Node_Id := Right_Opnd (N);
1731 Index : Interp_Index;
1732 It : Interp;
1733 Found : Boolean := False;
1734 I_F : Interp_Index;
1735 T_F : Entity_Id;
1737 procedure Try_One_Interp (T1 : Entity_Id);
1738 -- Routine to try one proposed interpretation. Note that the context
1739 -- of the operation plays no role in resolving the arguments, so that
1740 -- if there is more than one interpretation of the operands that is
1741 -- compatible with a membership test, the operation is ambiguous.
1743 procedure Try_One_Interp (T1 : Entity_Id) is
1744 begin
1745 if Has_Compatible_Type (R, T1) then
1746 if Found
1747 and then Base_Type (T1) /= Base_Type (T_F)
1748 then
1749 It := Disambiguate (L, I_F, Index, Any_Type);
1751 if It = No_Interp then
1752 Ambiguous_Operands (N);
1753 Set_Etype (L, Any_Type);
1754 return;
1756 else
1757 T_F := It.Typ;
1758 end if;
1760 else
1761 Found := True;
1762 T_F := T1;
1763 I_F := Index;
1764 end if;
1766 Set_Etype (L, T_F);
1767 end if;
1769 end Try_One_Interp;
1771 -- Start of processing for Analyze_Membership_Op
1773 begin
1774 Analyze_Expression (L);
1776 if Nkind (R) = N_Range
1777 or else (Nkind (R) = N_Attribute_Reference
1778 and then Attribute_Name (R) = Name_Range)
1779 then
1780 Analyze (R);
1782 if not Is_Overloaded (L) then
1783 Try_One_Interp (Etype (L));
1785 else
1786 Get_First_Interp (L, Index, It);
1788 while Present (It.Typ) loop
1789 Try_One_Interp (It.Typ);
1790 Get_Next_Interp (Index, It);
1791 end loop;
1792 end if;
1794 -- If not a range, it can only be a subtype mark, or else there
1795 -- is a more basic error, to be diagnosed in Find_Type.
1797 else
1798 Find_Type (R);
1800 if Is_Entity_Name (R) then
1801 Check_Fully_Declared (Entity (R), R);
1802 end if;
1803 end if;
1805 -- Compatibility between expression and subtype mark or range is
1806 -- checked during resolution. The result of the operation is Boolean
1807 -- in any case.
1809 Set_Etype (N, Standard_Boolean);
1810 end Analyze_Membership_Op;
1812 ----------------------
1813 -- Analyze_Negation --
1814 ----------------------
1816 procedure Analyze_Negation (N : Node_Id) is
1817 R : constant Node_Id := Right_Opnd (N);
1818 Op_Id : Entity_Id := Entity (N);
1820 begin
1821 Set_Etype (N, Any_Type);
1822 Candidate_Type := Empty;
1824 Analyze_Expression (R);
1826 if Present (Op_Id) then
1827 if Ekind (Op_Id) = E_Operator then
1828 Find_Negation_Types (R, Op_Id, N);
1829 else
1830 Add_One_Interp (N, Op_Id, Etype (Op_Id));
1831 end if;
1833 else
1834 Op_Id := Get_Name_Entity_Id (Chars (N));
1836 while Present (Op_Id) loop
1837 if Ekind (Op_Id) = E_Operator then
1838 Find_Negation_Types (R, Op_Id, N);
1839 else
1840 Analyze_User_Defined_Unary_Op (N, Op_Id);
1841 end if;
1843 Op_Id := Homonym (Op_Id);
1844 end loop;
1845 end if;
1847 Operator_Check (N);
1848 end Analyze_Negation;
1850 -------------------
1851 -- Analyze_Null --
1852 -------------------
1854 procedure Analyze_Null (N : Node_Id) is
1855 begin
1856 Set_Etype (N, Any_Access);
1857 end Analyze_Null;
1859 ----------------------
1860 -- Analyze_One_Call --
1861 ----------------------
1863 procedure Analyze_One_Call
1864 (N : Node_Id;
1865 Nam : Entity_Id;
1866 Report : Boolean;
1867 Success : out Boolean)
1869 Actuals : constant List_Id := Parameter_Associations (N);
1870 Prev_T : constant Entity_Id := Etype (N);
1871 Formal : Entity_Id;
1872 Actual : Node_Id;
1873 Is_Indexed : Boolean := False;
1874 Subp_Type : constant Entity_Id := Etype (Nam);
1875 Norm_OK : Boolean;
1877 procedure Indicate_Name_And_Type;
1878 -- If candidate interpretation matches, indicate name and type of
1879 -- result on call node.
1881 ----------------------------
1882 -- Indicate_Name_And_Type --
1883 ----------------------------
1885 procedure Indicate_Name_And_Type is
1886 begin
1887 Add_One_Interp (N, Nam, Etype (Nam));
1888 Success := True;
1890 -- If the prefix of the call is a name, indicate the entity
1891 -- being called. If it is not a name, it is an expression that
1892 -- denotes an access to subprogram or else an entry or family. In
1893 -- the latter case, the name is a selected component, and the entity
1894 -- being called is noted on the selector.
1896 if not Is_Type (Nam) then
1897 if Is_Entity_Name (Name (N))
1898 or else Nkind (Name (N)) = N_Operator_Symbol
1899 then
1900 Set_Entity (Name (N), Nam);
1902 elsif Nkind (Name (N)) = N_Selected_Component then
1903 Set_Entity (Selector_Name (Name (N)), Nam);
1904 end if;
1905 end if;
1907 if Debug_Flag_E and not Report then
1908 Write_Str (" Overloaded call ");
1909 Write_Int (Int (N));
1910 Write_Str (" compatible with ");
1911 Write_Int (Int (Nam));
1912 Write_Eol;
1913 end if;
1914 end Indicate_Name_And_Type;
1916 -- Start of processing for Analyze_One_Call
1918 begin
1919 Success := False;
1921 -- If the subprogram has no formals, or if all the formals have
1922 -- defaults, and the return type is an array type, the node may
1923 -- denote an indexing of the result of a parameterless call.
1925 if Needs_No_Actuals (Nam)
1926 and then Present (Actuals)
1927 then
1928 if Is_Array_Type (Subp_Type) then
1929 Is_Indexed := Try_Indexed_Call (N, Nam, Subp_Type);
1931 elsif Is_Access_Type (Subp_Type)
1932 and then Is_Array_Type (Designated_Type (Subp_Type))
1933 then
1934 Is_Indexed :=
1935 Try_Indexed_Call (N, Nam, Designated_Type (Subp_Type));
1937 elsif Is_Access_Type (Subp_Type)
1938 and then Ekind (Designated_Type (Subp_Type)) = E_Subprogram_Type
1939 then
1940 Is_Indexed := Try_Indirect_Call (N, Nam, Subp_Type);
1941 end if;
1943 end if;
1945 Normalize_Actuals (N, Nam, (Report and not Is_Indexed), Norm_OK);
1947 if not Norm_OK then
1949 -- Mismatch in number or names of parameters
1951 if Debug_Flag_E then
1952 Write_Str (" normalization fails in call ");
1953 Write_Int (Int (N));
1954 Write_Str (" with subprogram ");
1955 Write_Int (Int (Nam));
1956 Write_Eol;
1957 end if;
1959 -- If the context expects a function call, discard any interpretation
1960 -- that is a procedure. If the node is not overloaded, leave as is for
1961 -- better error reporting when type mismatch is found.
1963 elsif Nkind (N) = N_Function_Call
1964 and then Is_Overloaded (Name (N))
1965 and then Ekind (Nam) = E_Procedure
1966 then
1967 return;
1969 -- Ditto for function calls in a procedure context.
1971 elsif Nkind (N) = N_Procedure_Call_Statement
1972 and then Is_Overloaded (Name (N))
1973 and then Etype (Nam) /= Standard_Void_Type
1974 then
1975 return;
1977 elsif not Present (Actuals) then
1979 -- If Normalize succeeds, then there are default parameters for
1980 -- all formals.
1982 Indicate_Name_And_Type;
1984 elsif Ekind (Nam) = E_Operator then
1985 if Nkind (N) = N_Procedure_Call_Statement then
1986 return;
1987 end if;
1989 -- This can occur when the prefix of the call is an operator
1990 -- name or an expanded name whose selector is an operator name.
1992 Analyze_Operator_Call (N, Nam);
1994 if Etype (N) /= Prev_T then
1996 -- There may be a user-defined operator that hides the
1997 -- current interpretation. We must check for this independently
1998 -- of the analysis of the call with the user-defined operation,
1999 -- because the parameter names may be wrong and yet the hiding
2000 -- takes place. Fixes b34014o.
2002 if Is_Overloaded (Name (N)) then
2003 declare
2004 I : Interp_Index;
2005 It : Interp;
2007 begin
2008 Get_First_Interp (Name (N), I, It);
2010 while Present (It.Nam) loop
2012 if Ekind (It.Nam) /= E_Operator
2013 and then Hides_Op (It.Nam, Nam)
2014 and then
2015 Has_Compatible_Type
2016 (First_Actual (N), Etype (First_Formal (It.Nam)))
2017 and then (No (Next_Actual (First_Actual (N)))
2018 or else Has_Compatible_Type
2019 (Next_Actual (First_Actual (N)),
2020 Etype (Next_Formal (First_Formal (It.Nam)))))
2021 then
2022 Set_Etype (N, Prev_T);
2023 return;
2024 end if;
2026 Get_Next_Interp (I, It);
2027 end loop;
2028 end;
2029 end if;
2031 -- If operator matches formals, record its name on the call.
2032 -- If the operator is overloaded, Resolve will select the
2033 -- correct one from the list of interpretations. The call
2034 -- node itself carries the first candidate.
2036 Set_Entity (Name (N), Nam);
2037 Success := True;
2039 elsif Report and then Etype (N) = Any_Type then
2040 Error_Msg_N ("incompatible arguments for operator", N);
2041 end if;
2043 else
2044 -- Normalize_Actuals has chained the named associations in the
2045 -- correct order of the formals.
2047 Actual := First_Actual (N);
2048 Formal := First_Formal (Nam);
2050 while Present (Actual) and then Present (Formal) loop
2052 if Nkind (Parent (Actual)) /= N_Parameter_Association
2053 or else Chars (Selector_Name (Parent (Actual))) = Chars (Formal)
2054 then
2055 if Has_Compatible_Type (Actual, Etype (Formal)) then
2056 Next_Actual (Actual);
2057 Next_Formal (Formal);
2059 else
2060 if Debug_Flag_E then
2061 Write_Str (" type checking fails in call ");
2062 Write_Int (Int (N));
2063 Write_Str (" with formal ");
2064 Write_Int (Int (Formal));
2065 Write_Str (" in subprogram ");
2066 Write_Int (Int (Nam));
2067 Write_Eol;
2068 end if;
2070 if Report and not Is_Indexed then
2072 Wrong_Type (Actual, Etype (Formal));
2074 if Nkind (Actual) = N_Op_Eq
2075 and then Nkind (Left_Opnd (Actual)) = N_Identifier
2076 then
2077 Formal := First_Formal (Nam);
2079 while Present (Formal) loop
2081 if Chars (Left_Opnd (Actual)) = Chars (Formal) then
2082 Error_Msg_N
2083 ("possible misspelling of `='>`!", Actual);
2084 exit;
2085 end if;
2087 Next_Formal (Formal);
2088 end loop;
2089 end if;
2091 if All_Errors_Mode then
2092 Error_Msg_Sloc := Sloc (Nam);
2094 if Is_Overloadable (Nam)
2095 and then Present (Alias (Nam))
2096 and then not Comes_From_Source (Nam)
2097 then
2098 Error_Msg_NE
2099 (" =='> in call to &#(inherited)!", Actual, Nam);
2101 elsif Ekind (Nam) = E_Subprogram_Type then
2102 declare
2103 Access_To_Subprogram_Typ :
2104 constant Entity_Id :=
2105 Defining_Identifier
2106 (Associated_Node_For_Itype (Nam));
2107 begin
2108 Error_Msg_NE (
2109 " =='> in call to dereference of &#!",
2110 Actual, Access_To_Subprogram_Typ);
2111 end;
2113 else
2114 Error_Msg_NE (" =='> in call to &#!", Actual, Nam);
2116 end if;
2117 end if;
2118 end if;
2120 return;
2121 end if;
2123 else
2124 -- Normalize_Actuals has verified that a default value exists
2125 -- for this formal. Current actual names a subsequent formal.
2127 Next_Formal (Formal);
2128 end if;
2129 end loop;
2131 -- On exit, all actuals match.
2133 Indicate_Name_And_Type;
2134 end if;
2135 end Analyze_One_Call;
2137 ----------------------------
2138 -- Analyze_Operator_Call --
2139 ----------------------------
2141 procedure Analyze_Operator_Call (N : Node_Id; Op_Id : Entity_Id) is
2142 Op_Name : constant Name_Id := Chars (Op_Id);
2143 Act1 : constant Node_Id := First_Actual (N);
2144 Act2 : constant Node_Id := Next_Actual (Act1);
2146 begin
2147 if Present (Act2) then
2149 -- Maybe binary operators
2151 if Present (Next_Actual (Act2)) then
2153 -- Too many actuals for an operator
2155 return;
2157 elsif Op_Name = Name_Op_Add
2158 or else Op_Name = Name_Op_Subtract
2159 or else Op_Name = Name_Op_Multiply
2160 or else Op_Name = Name_Op_Divide
2161 or else Op_Name = Name_Op_Mod
2162 or else Op_Name = Name_Op_Rem
2163 or else Op_Name = Name_Op_Expon
2164 then
2165 Find_Arithmetic_Types (Act1, Act2, Op_Id, N);
2167 elsif Op_Name = Name_Op_And
2168 or else Op_Name = Name_Op_Or
2169 or else Op_Name = Name_Op_Xor
2170 then
2171 Find_Boolean_Types (Act1, Act2, Op_Id, N);
2173 elsif Op_Name = Name_Op_Lt
2174 or else Op_Name = Name_Op_Le
2175 or else Op_Name = Name_Op_Gt
2176 or else Op_Name = Name_Op_Ge
2177 then
2178 Find_Comparison_Types (Act1, Act2, Op_Id, N);
2180 elsif Op_Name = Name_Op_Eq
2181 or else Op_Name = Name_Op_Ne
2182 then
2183 Find_Equality_Types (Act1, Act2, Op_Id, N);
2185 elsif Op_Name = Name_Op_Concat then
2186 Find_Concatenation_Types (Act1, Act2, Op_Id, N);
2188 -- Is this else null correct, or should it be an abort???
2190 else
2191 null;
2192 end if;
2194 else
2195 -- Unary operators
2197 if Op_Name = Name_Op_Subtract or else
2198 Op_Name = Name_Op_Add or else
2199 Op_Name = Name_Op_Abs
2200 then
2201 Find_Unary_Types (Act1, Op_Id, N);
2203 elsif
2204 Op_Name = Name_Op_Not
2205 then
2206 Find_Negation_Types (Act1, Op_Id, N);
2208 -- Is this else null correct, or should it be an abort???
2210 else
2211 null;
2212 end if;
2213 end if;
2214 end Analyze_Operator_Call;
2216 -------------------------------------------
2217 -- Analyze_Overloaded_Selected_Component --
2218 -------------------------------------------
2220 procedure Analyze_Overloaded_Selected_Component (N : Node_Id) is
2221 Nam : constant Node_Id := Prefix (N);
2222 Sel : constant Node_Id := Selector_Name (N);
2223 Comp : Entity_Id;
2224 I : Interp_Index;
2225 It : Interp;
2226 T : Entity_Id;
2228 begin
2229 Get_First_Interp (Nam, I, It);
2231 Set_Etype (Sel, Any_Type);
2233 while Present (It.Typ) loop
2234 if Is_Access_Type (It.Typ) then
2235 T := Designated_Type (It.Typ);
2236 Error_Msg_NW (Warn_On_Dereference, "?implicit dereference", N);
2238 else
2239 T := It.Typ;
2240 end if;
2242 if Is_Record_Type (T) then
2243 Comp := First_Entity (T);
2245 while Present (Comp) loop
2247 if Chars (Comp) = Chars (Sel)
2248 and then Is_Visible_Component (Comp)
2249 then
2250 Set_Entity_With_Style_Check (Sel, Comp);
2251 Generate_Reference (Comp, Sel);
2253 Set_Etype (Sel, Etype (Comp));
2254 Add_One_Interp (N, Etype (Comp), Etype (Comp));
2256 -- This also specifies a candidate to resolve the name.
2257 -- Further overloading will be resolved from context.
2259 Set_Etype (Nam, It.Typ);
2260 end if;
2262 Next_Entity (Comp);
2263 end loop;
2265 elsif Is_Concurrent_Type (T) then
2266 Comp := First_Entity (T);
2268 while Present (Comp)
2269 and then Comp /= First_Private_Entity (T)
2270 loop
2271 if Chars (Comp) = Chars (Sel) then
2272 if Is_Overloadable (Comp) then
2273 Add_One_Interp (Sel, Comp, Etype (Comp));
2274 else
2275 Set_Entity_With_Style_Check (Sel, Comp);
2276 Generate_Reference (Comp, Sel);
2277 end if;
2279 Set_Etype (Sel, Etype (Comp));
2280 Set_Etype (N, Etype (Comp));
2281 Set_Etype (Nam, It.Typ);
2283 -- For access type case, introduce explicit deference for
2284 -- more uniform treatment of entry calls.
2286 if Is_Access_Type (Etype (Nam)) then
2287 Insert_Explicit_Dereference (Nam);
2288 Error_Msg_NW
2289 (Warn_On_Dereference, "?implicit dereference", N);
2290 end if;
2291 end if;
2293 Next_Entity (Comp);
2294 end loop;
2296 Set_Is_Overloaded (N, Is_Overloaded (Sel));
2297 end if;
2299 Get_Next_Interp (I, It);
2300 end loop;
2302 if Etype (N) = Any_Type then
2303 Error_Msg_NE ("undefined selector& for overloaded prefix", N, Sel);
2304 Set_Entity (Sel, Any_Id);
2305 Set_Etype (Sel, Any_Type);
2306 end if;
2308 end Analyze_Overloaded_Selected_Component;
2310 ----------------------------------
2311 -- Analyze_Qualified_Expression --
2312 ----------------------------------
2314 procedure Analyze_Qualified_Expression (N : Node_Id) is
2315 Mark : constant Entity_Id := Subtype_Mark (N);
2316 T : Entity_Id;
2318 begin
2319 Set_Etype (N, Any_Type);
2320 Find_Type (Mark);
2321 T := Entity (Mark);
2323 if T = Any_Type then
2324 return;
2325 end if;
2326 Check_Fully_Declared (T, N);
2328 Analyze_Expression (Expression (N));
2329 Set_Etype (N, T);
2330 end Analyze_Qualified_Expression;
2332 -------------------
2333 -- Analyze_Range --
2334 -------------------
2336 procedure Analyze_Range (N : Node_Id) is
2337 L : constant Node_Id := Low_Bound (N);
2338 H : constant Node_Id := High_Bound (N);
2339 I1, I2 : Interp_Index;
2340 It1, It2 : Interp;
2342 procedure Check_Common_Type (T1, T2 : Entity_Id);
2343 -- Verify the compatibility of two types, and choose the
2344 -- non universal one if the other is universal.
2346 procedure Check_High_Bound (T : Entity_Id);
2347 -- Test one interpretation of the low bound against all those
2348 -- of the high bound.
2350 procedure Check_Universal_Expression (N : Node_Id);
2351 -- In Ada83, reject bounds of a universal range that are not
2352 -- literals or entity names.
2354 -----------------------
2355 -- Check_Common_Type --
2356 -----------------------
2358 procedure Check_Common_Type (T1, T2 : Entity_Id) is
2359 begin
2360 if Covers (T1, T2) or else Covers (T2, T1) then
2361 if T1 = Universal_Integer
2362 or else T1 = Universal_Real
2363 or else T1 = Any_Character
2364 then
2365 Add_One_Interp (N, Base_Type (T2), Base_Type (T2));
2367 elsif T1 = T2 then
2368 Add_One_Interp (N, T1, T1);
2370 else
2371 Add_One_Interp (N, Base_Type (T1), Base_Type (T1));
2372 end if;
2373 end if;
2374 end Check_Common_Type;
2376 ----------------------
2377 -- Check_High_Bound --
2378 ----------------------
2380 procedure Check_High_Bound (T : Entity_Id) is
2381 begin
2382 if not Is_Overloaded (H) then
2383 Check_Common_Type (T, Etype (H));
2384 else
2385 Get_First_Interp (H, I2, It2);
2387 while Present (It2.Typ) loop
2388 Check_Common_Type (T, It2.Typ);
2389 Get_Next_Interp (I2, It2);
2390 end loop;
2391 end if;
2392 end Check_High_Bound;
2394 -----------------------------
2395 -- Is_Universal_Expression --
2396 -----------------------------
2398 procedure Check_Universal_Expression (N : Node_Id) is
2399 begin
2400 if Etype (N) = Universal_Integer
2401 and then Nkind (N) /= N_Integer_Literal
2402 and then not Is_Entity_Name (N)
2403 and then Nkind (N) /= N_Attribute_Reference
2404 then
2405 Error_Msg_N ("illegal bound in discrete range", N);
2406 end if;
2407 end Check_Universal_Expression;
2409 -- Start of processing for Analyze_Range
2411 begin
2412 Set_Etype (N, Any_Type);
2413 Analyze_Expression (L);
2414 Analyze_Expression (H);
2416 if Etype (L) = Any_Type or else Etype (H) = Any_Type then
2417 return;
2419 else
2420 if not Is_Overloaded (L) then
2421 Check_High_Bound (Etype (L));
2422 else
2423 Get_First_Interp (L, I1, It1);
2425 while Present (It1.Typ) loop
2426 Check_High_Bound (It1.Typ);
2427 Get_Next_Interp (I1, It1);
2428 end loop;
2429 end if;
2431 -- If result is Any_Type, then we did not find a compatible pair
2433 if Etype (N) = Any_Type then
2434 Error_Msg_N ("incompatible types in range ", N);
2435 end if;
2436 end if;
2438 if Ada_83
2439 and then
2440 (Nkind (Parent (N)) = N_Loop_Parameter_Specification
2441 or else Nkind (Parent (N)) = N_Constrained_Array_Definition)
2442 then
2443 Check_Universal_Expression (L);
2444 Check_Universal_Expression (H);
2445 end if;
2446 end Analyze_Range;
2448 -----------------------
2449 -- Analyze_Reference --
2450 -----------------------
2452 procedure Analyze_Reference (N : Node_Id) is
2453 P : constant Node_Id := Prefix (N);
2454 Acc_Type : Entity_Id;
2456 begin
2457 Analyze (P);
2458 Acc_Type := Create_Itype (E_Allocator_Type, N);
2459 Set_Etype (Acc_Type, Acc_Type);
2460 Init_Size_Align (Acc_Type);
2461 Set_Directly_Designated_Type (Acc_Type, Etype (P));
2462 Set_Etype (N, Acc_Type);
2463 end Analyze_Reference;
2465 --------------------------------
2466 -- Analyze_Selected_Component --
2467 --------------------------------
2469 -- Prefix is a record type or a task or protected type. In the
2470 -- later case, the selector must denote a visible entry.
2472 procedure Analyze_Selected_Component (N : Node_Id) is
2473 Name : constant Node_Id := Prefix (N);
2474 Sel : constant Node_Id := Selector_Name (N);
2475 Comp : Entity_Id;
2476 Entity_List : Entity_Id;
2477 Prefix_Type : Entity_Id;
2478 Act_Decl : Node_Id;
2479 In_Scope : Boolean;
2480 Parent_N : Node_Id;
2482 -- Start of processing for Analyze_Selected_Component
2484 begin
2485 Set_Etype (N, Any_Type);
2487 if Is_Overloaded (Name) then
2488 Analyze_Overloaded_Selected_Component (N);
2489 return;
2491 elsif Etype (Name) = Any_Type then
2492 Set_Entity (Sel, Any_Id);
2493 Set_Etype (Sel, Any_Type);
2494 return;
2496 else
2497 -- Function calls that are prefixes of selected components must be
2498 -- fully resolved in case we need to build an actual subtype, or
2499 -- do some other operation requiring a fully resolved prefix.
2501 -- Note: Resolving all Nkinds of nodes here doesn't work.
2502 -- (Breaks 2129-008) ???.
2504 if Nkind (Name) = N_Function_Call then
2505 Resolve (Name);
2506 end if;
2508 Prefix_Type := Etype (Name);
2509 end if;
2511 if Is_Access_Type (Prefix_Type) then
2513 -- A RACW object can never be used as prefix of a selected
2514 -- component since that means it is dereferenced without
2515 -- being a controlling operand of a dispatching operation
2516 -- (RM E.2.2(15)).
2518 if Is_Remote_Access_To_Class_Wide_Type (Prefix_Type)
2519 and then Comes_From_Source (N)
2520 then
2521 Error_Msg_N
2522 ("invalid dereference of a remote access to class-wide value",
2525 -- Normal case of selected component applied to access type
2527 else
2528 Error_Msg_NW (Warn_On_Dereference, "?implicit dereference", N);
2529 end if;
2531 Prefix_Type := Designated_Type (Prefix_Type);
2532 end if;
2534 if Ekind (Prefix_Type) = E_Private_Subtype then
2535 Prefix_Type := Base_Type (Prefix_Type);
2536 end if;
2538 Entity_List := Prefix_Type;
2540 -- For class-wide types, use the entity list of the root type. This
2541 -- indirection is specially important for private extensions because
2542 -- only the root type get switched (not the class-wide type).
2544 if Is_Class_Wide_Type (Prefix_Type) then
2545 Entity_List := Root_Type (Prefix_Type);
2546 end if;
2548 Comp := First_Entity (Entity_List);
2550 -- If the selector has an original discriminant, the node appears in
2551 -- an instance. Replace the discriminant with the corresponding one
2552 -- in the current discriminated type. For nested generics, this must
2553 -- be done transitively, so note the new original discriminant.
2555 if Nkind (Sel) = N_Identifier
2556 and then Present (Original_Discriminant (Sel))
2557 then
2558 Comp := Find_Corresponding_Discriminant (Sel, Prefix_Type);
2560 -- Mark entity before rewriting, for completeness and because
2561 -- subsequent semantic checks might examine the original node.
2563 Set_Entity (Sel, Comp);
2564 Rewrite (Selector_Name (N),
2565 New_Occurrence_Of (Comp, Sloc (N)));
2566 Set_Original_Discriminant (Selector_Name (N), Comp);
2567 Set_Etype (N, Etype (Comp));
2569 if Is_Access_Type (Etype (Name)) then
2570 Insert_Explicit_Dereference (Name);
2571 Error_Msg_NW (Warn_On_Dereference, "?implicit dereference", N);
2572 end if;
2574 elsif Is_Record_Type (Prefix_Type) then
2576 -- Find component with given name
2578 while Present (Comp) loop
2580 if Chars (Comp) = Chars (Sel)
2581 and then Is_Visible_Component (Comp)
2582 then
2583 Set_Entity_With_Style_Check (Sel, Comp);
2584 Generate_Reference (Comp, Sel);
2586 Set_Etype (Sel, Etype (Comp));
2588 if Ekind (Comp) = E_Discriminant then
2589 if Is_Unchecked_Union (Prefix_Type) then
2590 Error_Msg_N
2591 ("cannot reference discriminant of Unchecked_Union",
2592 Sel);
2593 end if;
2595 if Is_Generic_Type (Prefix_Type)
2596 or else
2597 Is_Generic_Type (Root_Type (Prefix_Type))
2598 then
2599 Set_Original_Discriminant (Sel, Comp);
2600 end if;
2601 end if;
2603 -- Resolve the prefix early otherwise it is not possible to
2604 -- build the actual subtype of the component: it may need
2605 -- to duplicate this prefix and duplication is only allowed
2606 -- on fully resolved expressions.
2608 Resolve (Name);
2610 -- We never need an actual subtype for the case of a selection
2611 -- for a indexed component of a non-packed array, since in
2612 -- this case gigi generates all the checks and can find the
2613 -- necessary bounds information.
2615 -- We also do not need an actual subtype for the case of
2616 -- a first, last, length, or range attribute applied to a
2617 -- non-packed array, since gigi can again get the bounds in
2618 -- these cases (gigi cannot handle the packed case, since it
2619 -- has the bounds of the packed array type, not the original
2620 -- bounds of the type). However, if the prefix is itself a
2621 -- selected component, as in a.b.c (i), gigi may regard a.b.c
2622 -- as a dynamic-sized temporary, so we do generate an actual
2623 -- subtype for this case.
2625 Parent_N := Parent (N);
2627 if not Is_Packed (Etype (Comp))
2628 and then
2629 ((Nkind (Parent_N) = N_Indexed_Component
2630 and then Nkind (Name) /= N_Selected_Component)
2631 or else
2632 (Nkind (Parent_N) = N_Attribute_Reference
2633 and then (Attribute_Name (Parent_N) = Name_First
2634 or else
2635 Attribute_Name (Parent_N) = Name_Last
2636 or else
2637 Attribute_Name (Parent_N) = Name_Length
2638 or else
2639 Attribute_Name (Parent_N) = Name_Range)))
2640 then
2641 Set_Etype (N, Etype (Comp));
2643 -- In all other cases, we currently build an actual subtype. It
2644 -- seems likely that many of these cases can be avoided, but
2645 -- right now, the front end makes direct references to the
2646 -- bounds (e.g. in generating a length check), and if we do
2647 -- not make an actual subtype, we end up getting a direct
2648 -- reference to a discriminant which will not do.
2650 else
2651 Act_Decl :=
2652 Build_Actual_Subtype_Of_Component (Etype (Comp), N);
2653 Insert_Action (N, Act_Decl);
2655 if No (Act_Decl) then
2656 Set_Etype (N, Etype (Comp));
2658 else
2659 -- Component type depends on discriminants. Enter the
2660 -- main attributes of the subtype.
2662 declare
2663 Subt : constant Entity_Id :=
2664 Defining_Identifier (Act_Decl);
2666 begin
2667 Set_Etype (Subt, Base_Type (Etype (Comp)));
2668 Set_Ekind (Subt, Ekind (Etype (Comp)));
2669 Set_Etype (N, Subt);
2670 end;
2671 end if;
2672 end if;
2674 return;
2675 end if;
2677 Next_Entity (Comp);
2678 end loop;
2680 elsif Is_Private_Type (Prefix_Type) then
2682 -- Allow access only to discriminants of the type. If the
2683 -- type has no full view, gigi uses the parent type for
2684 -- the components, so we do the same here.
2686 if No (Full_View (Prefix_Type)) then
2687 Entity_List := Root_Type (Base_Type (Prefix_Type));
2688 Comp := First_Entity (Entity_List);
2689 end if;
2691 while Present (Comp) loop
2693 if Chars (Comp) = Chars (Sel) then
2694 if Ekind (Comp) = E_Discriminant then
2695 Set_Entity_With_Style_Check (Sel, Comp);
2696 Generate_Reference (Comp, Sel);
2698 Set_Etype (Sel, Etype (Comp));
2699 Set_Etype (N, Etype (Comp));
2701 if Is_Generic_Type (Prefix_Type)
2702 or else
2703 Is_Generic_Type (Root_Type (Prefix_Type))
2704 then
2705 Set_Original_Discriminant (Sel, Comp);
2706 end if;
2708 else
2709 Error_Msg_NE
2710 ("invisible selector for }",
2711 N, First_Subtype (Prefix_Type));
2712 Set_Entity (Sel, Any_Id);
2713 Set_Etype (N, Any_Type);
2714 end if;
2716 return;
2717 end if;
2719 Next_Entity (Comp);
2720 end loop;
2722 elsif Is_Concurrent_Type (Prefix_Type) then
2724 -- Prefix is concurrent type. Find visible operation with given name
2725 -- For a task, this can only include entries or discriminants if
2726 -- the task type is not an enclosing scope. If it is an enclosing
2727 -- scope (e.g. in an inner task) then all entities are visible, but
2728 -- the prefix must denote the enclosing scope, i.e. can only be
2729 -- a direct name or an expanded name.
2731 Set_Etype (Sel, Any_Type);
2732 In_Scope := In_Open_Scopes (Prefix_Type);
2734 while Present (Comp) loop
2735 if Chars (Comp) = Chars (Sel) then
2736 if Is_Overloadable (Comp) then
2737 Add_One_Interp (Sel, Comp, Etype (Comp));
2739 elsif Ekind (Comp) = E_Discriminant
2740 or else Ekind (Comp) = E_Entry_Family
2741 or else (In_Scope
2742 and then Is_Entity_Name (Name))
2743 then
2744 Set_Entity_With_Style_Check (Sel, Comp);
2745 Generate_Reference (Comp, Sel);
2747 else
2748 goto Next_Comp;
2749 end if;
2751 Set_Etype (Sel, Etype (Comp));
2752 Set_Etype (N, Etype (Comp));
2754 if Ekind (Comp) = E_Discriminant then
2755 Set_Original_Discriminant (Sel, Comp);
2756 end if;
2758 -- For access type case, introduce explicit deference for
2759 -- more uniform treatment of entry calls.
2761 if Is_Access_Type (Etype (Name)) then
2762 Insert_Explicit_Dereference (Name);
2763 Error_Msg_NW
2764 (Warn_On_Dereference, "?implicit dereference", N);
2765 end if;
2766 end if;
2768 <<Next_Comp>>
2769 Next_Entity (Comp);
2770 exit when not In_Scope
2771 and then
2772 Comp = First_Private_Entity (Base_Type (Prefix_Type));
2773 end loop;
2775 Set_Is_Overloaded (N, Is_Overloaded (Sel));
2777 else
2778 -- Invalid prefix
2780 Error_Msg_NE ("invalid prefix in selected component&", N, Sel);
2781 end if;
2783 -- If N still has no type, the component is not defined in the prefix.
2785 if Etype (N) = Any_Type then
2787 -- If the prefix is a single concurrent object, use its name in
2788 -- the error message, rather than that of its anonymous type.
2790 if Is_Concurrent_Type (Prefix_Type)
2791 and then Is_Internal_Name (Chars (Prefix_Type))
2792 and then not Is_Derived_Type (Prefix_Type)
2793 and then Is_Entity_Name (Name)
2794 then
2796 Error_Msg_Node_2 := Entity (Name);
2797 Error_Msg_NE ("no selector& for&", N, Sel);
2799 Check_Misspelled_Selector (Entity_List, Sel);
2801 elsif Is_Generic_Type (Prefix_Type)
2802 and then Ekind (Prefix_Type) = E_Record_Type_With_Private
2803 and then Prefix_Type /= Etype (Prefix_Type)
2804 and then Is_Record_Type (Etype (Prefix_Type))
2805 then
2806 -- If this is a derived formal type, the parent may have a
2807 -- different visibility at this point. Try for an inherited
2808 -- component before reporting an error.
2810 Set_Etype (Prefix (N), Etype (Prefix_Type));
2811 Analyze_Selected_Component (N);
2812 return;
2814 elsif Ekind (Prefix_Type) = E_Record_Subtype_With_Private
2815 and then Is_Generic_Actual_Type (Prefix_Type)
2816 and then Present (Full_View (Prefix_Type))
2817 then
2818 -- Similarly, if this the actual for a formal derived type,
2819 -- the component inherited from the generic parent may not
2820 -- be visible in the actual, but the selected component is
2821 -- legal.
2823 declare
2824 Comp : Entity_Id;
2825 begin
2826 Comp :=
2827 First_Component (Generic_Parent_Type (Parent (Prefix_Type)));
2829 while Present (Comp) loop
2830 if Chars (Comp) = Chars (Sel) then
2831 Set_Entity_With_Style_Check (Sel, Comp);
2832 Set_Etype (Sel, Etype (Comp));
2833 Set_Etype (N, Etype (Comp));
2834 exit;
2835 end if;
2837 Next_Component (Comp);
2838 end loop;
2840 pragma Assert (Etype (N) /= Any_Type);
2841 end;
2843 else
2844 if Ekind (Prefix_Type) = E_Record_Subtype then
2846 -- Check whether this is a component of the base type
2847 -- which is absent from a statically constrained subtype.
2848 -- This will raise constraint error at run-time, but is
2849 -- not a compile-time error. When the selector is illegal
2850 -- for base type as well fall through and generate a
2851 -- compilation error anyway.
2853 Comp := First_Component (Base_Type (Prefix_Type));
2855 while Present (Comp) loop
2857 if Chars (Comp) = Chars (Sel)
2858 and then Is_Visible_Component (Comp)
2859 then
2860 Set_Entity_With_Style_Check (Sel, Comp);
2861 Generate_Reference (Comp, Sel);
2862 Set_Etype (Sel, Etype (Comp));
2863 Set_Etype (N, Etype (Comp));
2865 -- Emit appropriate message. Gigi will replace the
2866 -- node subsequently with the appropriate Raise.
2868 Apply_Compile_Time_Constraint_Error
2869 (N, "component not present in }?",
2870 CE_Discriminant_Check_Failed,
2871 Ent => Prefix_Type, Rep => False);
2872 Set_Raises_Constraint_Error (N);
2873 return;
2874 end if;
2876 Next_Component (Comp);
2877 end loop;
2879 end if;
2881 Error_Msg_Node_2 := First_Subtype (Prefix_Type);
2882 Error_Msg_NE ("no selector& for}", N, Sel);
2884 Check_Misspelled_Selector (Entity_List, Sel);
2886 end if;
2888 Set_Entity (Sel, Any_Id);
2889 Set_Etype (Sel, Any_Type);
2890 end if;
2891 end Analyze_Selected_Component;
2893 ---------------------------
2894 -- Analyze_Short_Circuit --
2895 ---------------------------
2897 procedure Analyze_Short_Circuit (N : Node_Id) is
2898 L : constant Node_Id := Left_Opnd (N);
2899 R : constant Node_Id := Right_Opnd (N);
2900 Ind : Interp_Index;
2901 It : Interp;
2903 begin
2904 Analyze_Expression (L);
2905 Analyze_Expression (R);
2906 Set_Etype (N, Any_Type);
2908 if not Is_Overloaded (L) then
2910 if Root_Type (Etype (L)) = Standard_Boolean
2911 and then Has_Compatible_Type (R, Etype (L))
2912 then
2913 Add_One_Interp (N, Etype (L), Etype (L));
2914 end if;
2916 else
2917 Get_First_Interp (L, Ind, It);
2919 while Present (It.Typ) loop
2920 if Root_Type (It.Typ) = Standard_Boolean
2921 and then Has_Compatible_Type (R, It.Typ)
2922 then
2923 Add_One_Interp (N, It.Typ, It.Typ);
2924 end if;
2926 Get_Next_Interp (Ind, It);
2927 end loop;
2928 end if;
2930 -- Here we have failed to find an interpretation. Clearly we
2931 -- know that it is not the case that both operands can have
2932 -- an interpretation of Boolean, but this is by far the most
2933 -- likely intended interpretation. So we simply resolve both
2934 -- operands as Booleans, and at least one of these resolutions
2935 -- will generate an error message, and we do not need to give
2936 -- a further error message on the short circuit operation itself.
2938 if Etype (N) = Any_Type then
2939 Resolve (L, Standard_Boolean);
2940 Resolve (R, Standard_Boolean);
2941 Set_Etype (N, Standard_Boolean);
2942 end if;
2943 end Analyze_Short_Circuit;
2945 -------------------
2946 -- Analyze_Slice --
2947 -------------------
2949 procedure Analyze_Slice (N : Node_Id) is
2950 P : constant Node_Id := Prefix (N);
2951 D : constant Node_Id := Discrete_Range (N);
2952 Array_Type : Entity_Id;
2954 procedure Analyze_Overloaded_Slice;
2955 -- If the prefix is overloaded, select those interpretations that
2956 -- yield a one-dimensional array type.
2958 procedure Analyze_Overloaded_Slice is
2959 I : Interp_Index;
2960 It : Interp;
2961 Typ : Entity_Id;
2963 begin
2964 Set_Etype (N, Any_Type);
2965 Get_First_Interp (P, I, It);
2967 while Present (It.Nam) loop
2968 Typ := It.Typ;
2970 if Is_Access_Type (Typ) then
2971 Typ := Designated_Type (Typ);
2972 Error_Msg_NW (Warn_On_Dereference, "?implicit dereference", N);
2973 end if;
2975 if Is_Array_Type (Typ)
2976 and then Number_Dimensions (Typ) = 1
2977 and then Has_Compatible_Type (D, Etype (First_Index (Typ)))
2978 then
2979 Add_One_Interp (N, Typ, Typ);
2980 end if;
2982 Get_Next_Interp (I, It);
2983 end loop;
2985 if Etype (N) = Any_Type then
2986 Error_Msg_N ("expect array type in prefix of slice", N);
2987 end if;
2988 end Analyze_Overloaded_Slice;
2990 -- Start of processing for Analyze_Slice
2992 begin
2993 -- Analyze the prefix if not done already
2995 if No (Etype (P)) then
2996 Analyze (P);
2997 end if;
2999 Analyze (D);
3001 if Is_Overloaded (P) then
3002 Analyze_Overloaded_Slice;
3004 else
3005 Array_Type := Etype (P);
3006 Set_Etype (N, Any_Type);
3008 if Is_Access_Type (Array_Type) then
3009 Array_Type := Designated_Type (Array_Type);
3010 Error_Msg_NW (Warn_On_Dereference, "?implicit dereference", N);
3011 end if;
3013 if not Is_Array_Type (Array_Type) then
3014 Wrong_Type (P, Any_Array);
3016 elsif Number_Dimensions (Array_Type) > 1 then
3017 Error_Msg_N
3018 ("type is not one-dimensional array in slice prefix", N);
3020 elsif not
3021 Has_Compatible_Type (D, Etype (First_Index (Array_Type)))
3022 then
3023 Wrong_Type (D, Etype (First_Index (Array_Type)));
3025 else
3026 Set_Etype (N, Array_Type);
3027 end if;
3028 end if;
3029 end Analyze_Slice;
3031 -----------------------------
3032 -- Analyze_Type_Conversion --
3033 -----------------------------
3035 procedure Analyze_Type_Conversion (N : Node_Id) is
3036 Expr : constant Node_Id := Expression (N);
3037 T : Entity_Id;
3039 begin
3040 -- If Conversion_OK is set, then the Etype is already set, and the
3041 -- only processing required is to analyze the expression. This is
3042 -- used to construct certain "illegal" conversions which are not
3043 -- allowed by Ada semantics, but can be handled OK by Gigi, see
3044 -- Sinfo for further details.
3046 if Conversion_OK (N) then
3047 Analyze (Expr);
3048 return;
3049 end if;
3051 -- Otherwise full type analysis is required, as well as some semantic
3052 -- checks to make sure the argument of the conversion is appropriate.
3054 Find_Type (Subtype_Mark (N));
3055 T := Entity (Subtype_Mark (N));
3056 Set_Etype (N, T);
3057 Check_Fully_Declared (T, N);
3058 Analyze_Expression (Expr);
3059 Validate_Remote_Type_Type_Conversion (N);
3061 -- Only remaining step is validity checks on the argument. These
3062 -- are skipped if the conversion does not come from the source.
3064 if not Comes_From_Source (N) then
3065 return;
3067 elsif Nkind (Expr) = N_Null then
3068 Error_Msg_N ("argument of conversion cannot be null", N);
3069 Error_Msg_N ("\use qualified expression instead", N);
3070 Set_Etype (N, Any_Type);
3072 elsif Nkind (Expr) = N_Aggregate then
3073 Error_Msg_N ("argument of conversion cannot be aggregate", N);
3074 Error_Msg_N ("\use qualified expression instead", N);
3076 elsif Nkind (Expr) = N_Allocator then
3077 Error_Msg_N ("argument of conversion cannot be an allocator", N);
3078 Error_Msg_N ("\use qualified expression instead", N);
3080 elsif Nkind (Expr) = N_String_Literal then
3081 Error_Msg_N ("argument of conversion cannot be string literal", N);
3082 Error_Msg_N ("\use qualified expression instead", N);
3084 elsif Nkind (Expr) = N_Character_Literal then
3085 if Ada_83 then
3086 Resolve (Expr, T);
3087 else
3088 Error_Msg_N ("argument of conversion cannot be character literal",
3090 Error_Msg_N ("\use qualified expression instead", N);
3091 end if;
3093 elsif Nkind (Expr) = N_Attribute_Reference
3094 and then
3095 (Attribute_Name (Expr) = Name_Access or else
3096 Attribute_Name (Expr) = Name_Unchecked_Access or else
3097 Attribute_Name (Expr) = Name_Unrestricted_Access)
3098 then
3099 Error_Msg_N ("argument of conversion cannot be access", N);
3100 Error_Msg_N ("\use qualified expression instead", N);
3101 end if;
3103 end Analyze_Type_Conversion;
3105 ----------------------
3106 -- Analyze_Unary_Op --
3107 ----------------------
3109 procedure Analyze_Unary_Op (N : Node_Id) is
3110 R : constant Node_Id := Right_Opnd (N);
3111 Op_Id : Entity_Id := Entity (N);
3113 begin
3114 Set_Etype (N, Any_Type);
3115 Candidate_Type := Empty;
3117 Analyze_Expression (R);
3119 if Present (Op_Id) then
3120 if Ekind (Op_Id) = E_Operator then
3121 Find_Unary_Types (R, Op_Id, N);
3122 else
3123 Add_One_Interp (N, Op_Id, Etype (Op_Id));
3124 end if;
3126 else
3127 Op_Id := Get_Name_Entity_Id (Chars (N));
3129 while Present (Op_Id) loop
3131 if Ekind (Op_Id) = E_Operator then
3132 if No (Next_Entity (First_Entity (Op_Id))) then
3133 Find_Unary_Types (R, Op_Id, N);
3134 end if;
3136 elsif Is_Overloadable (Op_Id) then
3137 Analyze_User_Defined_Unary_Op (N, Op_Id);
3138 end if;
3140 Op_Id := Homonym (Op_Id);
3141 end loop;
3142 end if;
3144 Operator_Check (N);
3145 end Analyze_Unary_Op;
3147 ----------------------------------
3148 -- Analyze_Unchecked_Expression --
3149 ----------------------------------
3151 procedure Analyze_Unchecked_Expression (N : Node_Id) is
3152 begin
3153 Analyze (Expression (N), Suppress => All_Checks);
3154 Set_Etype (N, Etype (Expression (N)));
3155 Save_Interps (Expression (N), N);
3156 end Analyze_Unchecked_Expression;
3158 ---------------------------------------
3159 -- Analyze_Unchecked_Type_Conversion --
3160 ---------------------------------------
3162 procedure Analyze_Unchecked_Type_Conversion (N : Node_Id) is
3163 begin
3164 Find_Type (Subtype_Mark (N));
3165 Analyze_Expression (Expression (N));
3166 Set_Etype (N, Entity (Subtype_Mark (N)));
3167 end Analyze_Unchecked_Type_Conversion;
3169 ------------------------------------
3170 -- Analyze_User_Defined_Binary_Op --
3171 ------------------------------------
3173 procedure Analyze_User_Defined_Binary_Op
3174 (N : Node_Id;
3175 Op_Id : Entity_Id)
3177 begin
3178 -- Only do analysis if the operator Comes_From_Source, since otherwise
3179 -- the operator was generated by the expander, and all such operators
3180 -- always refer to the operators in package Standard.
3182 if Comes_From_Source (N) then
3183 declare
3184 F1 : constant Entity_Id := First_Formal (Op_Id);
3185 F2 : constant Entity_Id := Next_Formal (F1);
3187 begin
3188 -- Verify that Op_Id is a visible binary function. Note that since
3189 -- we know Op_Id is overloaded, potentially use visible means use
3190 -- visible for sure (RM 9.4(11)).
3192 if Ekind (Op_Id) = E_Function
3193 and then Present (F2)
3194 and then (Is_Immediately_Visible (Op_Id)
3195 or else Is_Potentially_Use_Visible (Op_Id))
3196 and then Has_Compatible_Type (Left_Opnd (N), Etype (F1))
3197 and then Has_Compatible_Type (Right_Opnd (N), Etype (F2))
3198 then
3199 Add_One_Interp (N, Op_Id, Etype (Op_Id));
3201 if Debug_Flag_E then
3202 Write_Str ("user defined operator ");
3203 Write_Name (Chars (Op_Id));
3204 Write_Str (" on node ");
3205 Write_Int (Int (N));
3206 Write_Eol;
3207 end if;
3208 end if;
3209 end;
3210 end if;
3211 end Analyze_User_Defined_Binary_Op;
3213 -----------------------------------
3214 -- Analyze_User_Defined_Unary_Op --
3215 -----------------------------------
3217 procedure Analyze_User_Defined_Unary_Op
3218 (N : Node_Id;
3219 Op_Id : Entity_Id)
3221 begin
3222 -- Only do analysis if the operator Comes_From_Source, since otherwise
3223 -- the operator was generated by the expander, and all such operators
3224 -- always refer to the operators in package Standard.
3226 if Comes_From_Source (N) then
3227 declare
3228 F : constant Entity_Id := First_Formal (Op_Id);
3230 begin
3231 -- Verify that Op_Id is a visible unary function. Note that since
3232 -- we know Op_Id is overloaded, potentially use visible means use
3233 -- visible for sure (RM 9.4(11)).
3235 if Ekind (Op_Id) = E_Function
3236 and then No (Next_Formal (F))
3237 and then (Is_Immediately_Visible (Op_Id)
3238 or else Is_Potentially_Use_Visible (Op_Id))
3239 and then Has_Compatible_Type (Right_Opnd (N), Etype (F))
3240 then
3241 Add_One_Interp (N, Op_Id, Etype (Op_Id));
3242 end if;
3243 end;
3244 end if;
3245 end Analyze_User_Defined_Unary_Op;
3247 ---------------------------
3248 -- Check_Arithmetic_Pair --
3249 ---------------------------
3251 procedure Check_Arithmetic_Pair
3252 (T1, T2 : Entity_Id;
3253 Op_Id : Entity_Id;
3254 N : Node_Id)
3256 Op_Name : constant Name_Id := Chars (Op_Id);
3258 function Specific_Type (T1, T2 : Entity_Id) return Entity_Id;
3259 -- Get specific type (i.e. non-universal type if there is one)
3261 function Specific_Type (T1, T2 : Entity_Id) return Entity_Id is
3262 begin
3263 if T1 = Universal_Integer or else T1 = Universal_Real then
3264 return Base_Type (T2);
3265 else
3266 return Base_Type (T1);
3267 end if;
3268 end Specific_Type;
3270 -- Start of processing for Check_Arithmetic_Pair
3272 begin
3273 if Op_Name = Name_Op_Add or else Op_Name = Name_Op_Subtract then
3275 if Is_Numeric_Type (T1)
3276 and then Is_Numeric_Type (T2)
3277 and then (Covers (T1, T2) or else Covers (T2, T1))
3278 then
3279 Add_One_Interp (N, Op_Id, Specific_Type (T1, T2));
3280 end if;
3282 elsif Op_Name = Name_Op_Multiply or else Op_Name = Name_Op_Divide then
3284 if Is_Fixed_Point_Type (T1)
3285 and then (Is_Fixed_Point_Type (T2)
3286 or else T2 = Universal_Real)
3287 then
3288 -- If Treat_Fixed_As_Integer is set then the Etype is already set
3289 -- and no further processing is required (this is the case of an
3290 -- operator constructed by Exp_Fixd for a fixed point operation)
3291 -- Otherwise add one interpretation with universal fixed result
3292 -- If the operator is given in functional notation, it comes
3293 -- from source and Fixed_As_Integer cannot apply.
3295 if Nkind (N) not in N_Op
3296 or else not Treat_Fixed_As_Integer (N)
3297 then
3298 Add_One_Interp (N, Op_Id, Universal_Fixed);
3299 end if;
3301 elsif Is_Fixed_Point_Type (T2)
3302 and then (Nkind (N) not in N_Op
3303 or else not Treat_Fixed_As_Integer (N))
3304 and then T1 = Universal_Real
3305 then
3306 Add_One_Interp (N, Op_Id, Universal_Fixed);
3308 elsif Is_Numeric_Type (T1)
3309 and then Is_Numeric_Type (T2)
3310 and then (Covers (T1, T2) or else Covers (T2, T1))
3311 then
3312 Add_One_Interp (N, Op_Id, Specific_Type (T1, T2));
3314 elsif Is_Fixed_Point_Type (T1)
3315 and then (Base_Type (T2) = Base_Type (Standard_Integer)
3316 or else T2 = Universal_Integer)
3317 then
3318 Add_One_Interp (N, Op_Id, T1);
3320 elsif T2 = Universal_Real
3321 and then Base_Type (T1) = Base_Type (Standard_Integer)
3322 and then Op_Name = Name_Op_Multiply
3323 then
3324 Add_One_Interp (N, Op_Id, Any_Fixed);
3326 elsif T1 = Universal_Real
3327 and then Base_Type (T2) = Base_Type (Standard_Integer)
3328 then
3329 Add_One_Interp (N, Op_Id, Any_Fixed);
3331 elsif Is_Fixed_Point_Type (T2)
3332 and then (Base_Type (T1) = Base_Type (Standard_Integer)
3333 or else T1 = Universal_Integer)
3334 and then Op_Name = Name_Op_Multiply
3335 then
3336 Add_One_Interp (N, Op_Id, T2);
3338 elsif T1 = Universal_Real and then T2 = Universal_Integer then
3339 Add_One_Interp (N, Op_Id, T1);
3341 elsif T2 = Universal_Real
3342 and then T1 = Universal_Integer
3343 and then Op_Name = Name_Op_Multiply
3344 then
3345 Add_One_Interp (N, Op_Id, T2);
3346 end if;
3348 elsif Op_Name = Name_Op_Mod or else Op_Name = Name_Op_Rem then
3350 -- Note: The fixed-point operands case with Treat_Fixed_As_Integer
3351 -- set does not require any special processing, since the Etype is
3352 -- already set (case of operation constructed by Exp_Fixed).
3354 if Is_Integer_Type (T1)
3355 and then (Covers (T1, T2) or else Covers (T2, T1))
3356 then
3357 Add_One_Interp (N, Op_Id, Specific_Type (T1, T2));
3358 end if;
3360 elsif Op_Name = Name_Op_Expon then
3362 if Is_Numeric_Type (T1)
3363 and then not Is_Fixed_Point_Type (T1)
3364 and then (Base_Type (T2) = Base_Type (Standard_Integer)
3365 or else T2 = Universal_Integer)
3366 then
3367 Add_One_Interp (N, Op_Id, Base_Type (T1));
3368 end if;
3370 else pragma Assert (Nkind (N) in N_Op_Shift);
3372 -- If not one of the predefined operators, the node may be one
3373 -- of the intrinsic functions. Its kind is always specific, and
3374 -- we can use it directly, rather than the name of the operation.
3376 if Is_Integer_Type (T1)
3377 and then (Base_Type (T2) = Base_Type (Standard_Integer)
3378 or else T2 = Universal_Integer)
3379 then
3380 Add_One_Interp (N, Op_Id, Base_Type (T1));
3381 end if;
3382 end if;
3383 end Check_Arithmetic_Pair;
3385 -------------------------------
3386 -- Check_Misspelled_Selector --
3387 -------------------------------
3389 procedure Check_Misspelled_Selector
3390 (Prefix : Entity_Id;
3391 Sel : Node_Id)
3393 Max_Suggestions : constant := 2;
3394 Nr_Of_Suggestions : Natural := 0;
3396 Suggestion_1 : Entity_Id := Empty;
3397 Suggestion_2 : Entity_Id := Empty;
3399 Comp : Entity_Id;
3401 begin
3402 -- All the components of the prefix of selector Sel are matched
3403 -- against Sel and a count is maintained of possible misspellings.
3404 -- When at the end of the analysis there are one or two (not more!)
3405 -- possible misspellings, these misspellings will be suggested as
3406 -- possible correction.
3408 if not (Is_Private_Type (Prefix) or Is_Record_Type (Prefix)) then
3409 -- Concurrent types should be handled as well ???
3410 return;
3411 end if;
3413 Get_Name_String (Chars (Sel));
3415 declare
3416 S : constant String (1 .. Name_Len) :=
3417 Name_Buffer (1 .. Name_Len);
3419 begin
3420 Comp := First_Entity (Prefix);
3422 while Nr_Of_Suggestions <= Max_Suggestions
3423 and then Present (Comp)
3424 loop
3426 if Is_Visible_Component (Comp) then
3427 Get_Name_String (Chars (Comp));
3429 if Is_Bad_Spelling_Of (Name_Buffer (1 .. Name_Len), S) then
3430 Nr_Of_Suggestions := Nr_Of_Suggestions + 1;
3432 case Nr_Of_Suggestions is
3433 when 1 => Suggestion_1 := Comp;
3434 when 2 => Suggestion_2 := Comp;
3435 when others => exit;
3436 end case;
3437 end if;
3438 end if;
3440 Comp := Next_Entity (Comp);
3441 end loop;
3443 -- Report at most two suggestions
3445 if Nr_Of_Suggestions = 1 then
3446 Error_Msg_NE ("\possible misspelling of&", Sel, Suggestion_1);
3448 elsif Nr_Of_Suggestions = 2 then
3449 Error_Msg_Node_2 := Suggestion_2;
3450 Error_Msg_NE ("\possible misspelling of& or&",
3451 Sel, Suggestion_1);
3452 end if;
3453 end;
3454 end Check_Misspelled_Selector;
3456 ----------------------
3457 -- Defined_In_Scope --
3458 ----------------------
3460 function Defined_In_Scope (T : Entity_Id; S : Entity_Id) return Boolean
3462 S1 : constant Entity_Id := Scope (Base_Type (T));
3464 begin
3465 return S1 = S
3466 or else (S1 = System_Aux_Id and then S = Scope (S1));
3467 end Defined_In_Scope;
3469 -------------------
3470 -- Diagnose_Call --
3471 -------------------
3473 procedure Diagnose_Call (N : Node_Id; Nam : Node_Id) is
3474 Actual : Node_Id;
3475 X : Interp_Index;
3476 It : Interp;
3477 Success : Boolean;
3478 Err_Mode : Boolean;
3479 New_Nam : Node_Id;
3480 Void_Interp_Seen : Boolean := False;
3482 begin
3483 if Extensions_Allowed then
3484 Actual := First_Actual (N);
3486 while Present (Actual) loop
3487 -- Ada 0Y (AI-50217): Post an error in case of premature usage of
3488 -- an entity from the limited view.
3490 if not Analyzed (Etype (Actual))
3491 and then From_With_Type (Etype (Actual))
3492 then
3493 Error_Msg_Qual_Level := 1;
3494 Error_Msg_NE
3495 ("missing with_clause for scope of imported type&",
3496 Actual, Etype (Actual));
3497 Error_Msg_Qual_Level := 0;
3498 end if;
3500 Next_Actual (Actual);
3501 end loop;
3502 end if;
3504 -- Analyze each candidate call again, with full error reporting
3505 -- for each.
3507 Error_Msg_N
3508 ("no candidate interpretations match the actuals:!", Nam);
3509 Err_Mode := All_Errors_Mode;
3510 All_Errors_Mode := True;
3512 -- If this is a call to an operation of a concurrent type,
3513 -- the failed interpretations have been removed from the
3514 -- name. Recover them to provide full diagnostics.
3516 if Nkind (Parent (Nam)) = N_Selected_Component then
3517 Set_Entity (Nam, Empty);
3518 New_Nam := New_Copy_Tree (Parent (Nam));
3519 Set_Is_Overloaded (New_Nam, False);
3520 Set_Is_Overloaded (Selector_Name (New_Nam), False);
3521 Set_Parent (New_Nam, Parent (Parent (Nam)));
3522 Analyze_Selected_Component (New_Nam);
3523 Get_First_Interp (Selector_Name (New_Nam), X, It);
3524 else
3525 Get_First_Interp (Nam, X, It);
3526 end if;
3528 while Present (It.Nam) loop
3529 if Etype (It.Nam) = Standard_Void_Type then
3530 Void_Interp_Seen := True;
3531 end if;
3533 Analyze_One_Call (N, It.Nam, True, Success);
3534 Get_Next_Interp (X, It);
3535 end loop;
3537 if Nkind (N) = N_Function_Call then
3538 Get_First_Interp (Nam, X, It);
3540 while Present (It.Nam) loop
3541 if Ekind (It.Nam) = E_Function
3542 or else Ekind (It.Nam) = E_Operator
3543 then
3544 return;
3545 else
3546 Get_Next_Interp (X, It);
3547 end if;
3548 end loop;
3550 -- If all interpretations are procedures, this deserves a
3551 -- more precise message. Ditto if this appears as the prefix
3552 -- of a selected component, which may be a lexical error.
3554 Error_Msg_N (
3555 "\context requires function call, found procedure name", Nam);
3557 if Nkind (Parent (N)) = N_Selected_Component
3558 and then N = Prefix (Parent (N))
3559 then
3560 Error_Msg_N (
3561 "\period should probably be semicolon", Parent (N));
3562 end if;
3564 elsif Nkind (N) = N_Procedure_Call_Statement
3565 and then not Void_Interp_Seen
3566 then
3567 Error_Msg_N (
3568 "\function name found in procedure call", Nam);
3569 end if;
3571 All_Errors_Mode := Err_Mode;
3572 end Diagnose_Call;
3574 ---------------------------
3575 -- Find_Arithmetic_Types --
3576 ---------------------------
3578 procedure Find_Arithmetic_Types
3579 (L, R : Node_Id;
3580 Op_Id : Entity_Id;
3581 N : Node_Id)
3583 Index1, Index2 : Interp_Index;
3584 It1, It2 : Interp;
3586 procedure Check_Right_Argument (T : Entity_Id);
3587 -- Check right operand of operator
3589 procedure Check_Right_Argument (T : Entity_Id) is
3590 begin
3591 if not Is_Overloaded (R) then
3592 Check_Arithmetic_Pair (T, Etype (R), Op_Id, N);
3593 else
3594 Get_First_Interp (R, Index2, It2);
3596 while Present (It2.Typ) loop
3597 Check_Arithmetic_Pair (T, It2.Typ, Op_Id, N);
3598 Get_Next_Interp (Index2, It2);
3599 end loop;
3600 end if;
3601 end Check_Right_Argument;
3603 -- Start processing for Find_Arithmetic_Types
3605 begin
3606 if not Is_Overloaded (L) then
3607 Check_Right_Argument (Etype (L));
3609 else
3610 Get_First_Interp (L, Index1, It1);
3612 while Present (It1.Typ) loop
3613 Check_Right_Argument (It1.Typ);
3614 Get_Next_Interp (Index1, It1);
3615 end loop;
3616 end if;
3618 end Find_Arithmetic_Types;
3620 ------------------------
3621 -- Find_Boolean_Types --
3622 ------------------------
3624 procedure Find_Boolean_Types
3625 (L, R : Node_Id;
3626 Op_Id : Entity_Id;
3627 N : Node_Id)
3629 Index : Interp_Index;
3630 It : Interp;
3632 procedure Check_Numeric_Argument (T : Entity_Id);
3633 -- Special case for logical operations one of whose operands is an
3634 -- integer literal. If both are literal the result is any modular type.
3636 procedure Check_Numeric_Argument (T : Entity_Id) is
3637 begin
3638 if T = Universal_Integer then
3639 Add_One_Interp (N, Op_Id, Any_Modular);
3641 elsif Is_Modular_Integer_Type (T) then
3642 Add_One_Interp (N, Op_Id, T);
3643 end if;
3644 end Check_Numeric_Argument;
3646 -- Start of processing for Find_Boolean_Types
3648 begin
3649 if not Is_Overloaded (L) then
3651 if Etype (L) = Universal_Integer
3652 or else Etype (L) = Any_Modular
3653 then
3654 if not Is_Overloaded (R) then
3655 Check_Numeric_Argument (Etype (R));
3657 else
3658 Get_First_Interp (R, Index, It);
3660 while Present (It.Typ) loop
3661 Check_Numeric_Argument (It.Typ);
3663 Get_Next_Interp (Index, It);
3664 end loop;
3665 end if;
3667 elsif Valid_Boolean_Arg (Etype (L))
3668 and then Has_Compatible_Type (R, Etype (L))
3669 then
3670 Add_One_Interp (N, Op_Id, Etype (L));
3671 end if;
3673 else
3674 Get_First_Interp (L, Index, It);
3676 while Present (It.Typ) loop
3677 if Valid_Boolean_Arg (It.Typ)
3678 and then Has_Compatible_Type (R, It.Typ)
3679 then
3680 Add_One_Interp (N, Op_Id, It.Typ);
3681 end if;
3683 Get_Next_Interp (Index, It);
3684 end loop;
3685 end if;
3686 end Find_Boolean_Types;
3688 ---------------------------
3689 -- Find_Comparison_Types --
3690 ---------------------------
3692 procedure Find_Comparison_Types
3693 (L, R : Node_Id;
3694 Op_Id : Entity_Id;
3695 N : Node_Id)
3697 Index : Interp_Index;
3698 It : Interp;
3699 Found : Boolean := False;
3700 I_F : Interp_Index;
3701 T_F : Entity_Id;
3702 Scop : Entity_Id := Empty;
3704 procedure Try_One_Interp (T1 : Entity_Id);
3705 -- Routine to try one proposed interpretation. Note that the context
3706 -- of the operator plays no role in resolving the arguments, so that
3707 -- if there is more than one interpretation of the operands that is
3708 -- compatible with comparison, the operation is ambiguous.
3710 procedure Try_One_Interp (T1 : Entity_Id) is
3711 begin
3713 -- If the operator is an expanded name, then the type of the operand
3714 -- must be defined in the corresponding scope. If the type is
3715 -- universal, the context will impose the correct type.
3717 if Present (Scop)
3718 and then not Defined_In_Scope (T1, Scop)
3719 and then T1 /= Universal_Integer
3720 and then T1 /= Universal_Real
3721 and then T1 /= Any_String
3722 and then T1 /= Any_Composite
3723 then
3724 return;
3725 end if;
3727 if Valid_Comparison_Arg (T1)
3728 and then Has_Compatible_Type (R, T1)
3729 then
3730 if Found
3731 and then Base_Type (T1) /= Base_Type (T_F)
3732 then
3733 It := Disambiguate (L, I_F, Index, Any_Type);
3735 if It = No_Interp then
3736 Ambiguous_Operands (N);
3737 Set_Etype (L, Any_Type);
3738 return;
3740 else
3741 T_F := It.Typ;
3742 end if;
3744 else
3745 Found := True;
3746 T_F := T1;
3747 I_F := Index;
3748 end if;
3750 Set_Etype (L, T_F);
3751 Find_Non_Universal_Interpretations (N, R, Op_Id, T1);
3753 end if;
3754 end Try_One_Interp;
3756 -- Start processing for Find_Comparison_Types
3758 begin
3759 -- If left operand is aggregate, the right operand has to
3760 -- provide a usable type for it.
3762 if Nkind (L) = N_Aggregate
3763 and then Nkind (R) /= N_Aggregate
3764 then
3765 Find_Comparison_Types (R, L, Op_Id, N);
3766 return;
3767 end if;
3769 if Nkind (N) = N_Function_Call
3770 and then Nkind (Name (N)) = N_Expanded_Name
3771 then
3772 Scop := Entity (Prefix (Name (N)));
3774 -- The prefix may be a package renaming, and the subsequent test
3775 -- requires the original package.
3777 if Ekind (Scop) = E_Package
3778 and then Present (Renamed_Entity (Scop))
3779 then
3780 Scop := Renamed_Entity (Scop);
3781 Set_Entity (Prefix (Name (N)), Scop);
3782 end if;
3783 end if;
3785 if not Is_Overloaded (L) then
3786 Try_One_Interp (Etype (L));
3788 else
3789 Get_First_Interp (L, Index, It);
3791 while Present (It.Typ) loop
3792 Try_One_Interp (It.Typ);
3793 Get_Next_Interp (Index, It);
3794 end loop;
3795 end if;
3796 end Find_Comparison_Types;
3798 ----------------------------------------
3799 -- Find_Non_Universal_Interpretations --
3800 ----------------------------------------
3802 procedure Find_Non_Universal_Interpretations
3803 (N : Node_Id;
3804 R : Node_Id;
3805 Op_Id : Entity_Id;
3806 T1 : Entity_Id)
3808 Index : Interp_Index;
3809 It : Interp;
3811 begin
3812 if T1 = Universal_Integer
3813 or else T1 = Universal_Real
3814 then
3815 if not Is_Overloaded (R) then
3816 Add_One_Interp
3817 (N, Op_Id, Standard_Boolean, Base_Type (Etype (R)));
3818 else
3819 Get_First_Interp (R, Index, It);
3821 while Present (It.Typ) loop
3822 if Covers (It.Typ, T1) then
3823 Add_One_Interp
3824 (N, Op_Id, Standard_Boolean, Base_Type (It.Typ));
3825 end if;
3827 Get_Next_Interp (Index, It);
3828 end loop;
3829 end if;
3830 else
3831 Add_One_Interp (N, Op_Id, Standard_Boolean, Base_Type (T1));
3832 end if;
3833 end Find_Non_Universal_Interpretations;
3835 ------------------------------
3836 -- Find_Concatenation_Types --
3837 ------------------------------
3839 procedure Find_Concatenation_Types
3840 (L, R : Node_Id;
3841 Op_Id : Entity_Id;
3842 N : Node_Id)
3844 Op_Type : constant Entity_Id := Etype (Op_Id);
3846 begin
3847 if Is_Array_Type (Op_Type)
3848 and then not Is_Limited_Type (Op_Type)
3850 and then (Has_Compatible_Type (L, Op_Type)
3851 or else
3852 Has_Compatible_Type (L, Component_Type (Op_Type)))
3854 and then (Has_Compatible_Type (R, Op_Type)
3855 or else
3856 Has_Compatible_Type (R, Component_Type (Op_Type)))
3857 then
3858 Add_One_Interp (N, Op_Id, Op_Type);
3859 end if;
3860 end Find_Concatenation_Types;
3862 -------------------------
3863 -- Find_Equality_Types --
3864 -------------------------
3866 procedure Find_Equality_Types
3867 (L, R : Node_Id;
3868 Op_Id : Entity_Id;
3869 N : Node_Id)
3871 Index : Interp_Index;
3872 It : Interp;
3873 Found : Boolean := False;
3874 I_F : Interp_Index;
3875 T_F : Entity_Id;
3876 Scop : Entity_Id := Empty;
3878 procedure Try_One_Interp (T1 : Entity_Id);
3879 -- The context of the operator plays no role in resolving the
3880 -- arguments, so that if there is more than one interpretation
3881 -- of the operands that is compatible with equality, the construct
3882 -- is ambiguous and an error can be emitted now, after trying to
3883 -- disambiguate, i.e. applying preference rules.
3885 procedure Try_One_Interp (T1 : Entity_Id) is
3886 begin
3888 -- If the operator is an expanded name, then the type of the operand
3889 -- must be defined in the corresponding scope. If the type is
3890 -- universal, the context will impose the correct type. An anonymous
3891 -- type for a 'Access reference is also universal in this sense, as
3892 -- the actual type is obtained from context.
3894 if Present (Scop)
3895 and then not Defined_In_Scope (T1, Scop)
3896 and then T1 /= Universal_Integer
3897 and then T1 /= Universal_Real
3898 and then T1 /= Any_Access
3899 and then T1 /= Any_String
3900 and then T1 /= Any_Composite
3901 and then (Ekind (T1) /= E_Access_Subprogram_Type
3902 or else Comes_From_Source (T1))
3903 then
3904 return;
3905 end if;
3907 -- Ada 0Y (AI-230): Keep restriction imposed by Ada 83 and 95: Do not
3908 -- allow anonymous access types in equality operators.
3910 if not Extensions_Allowed
3911 and then Ekind (T1) = E_Anonymous_Access_Type
3912 then
3913 return;
3914 end if;
3916 if T1 /= Standard_Void_Type
3917 and then not Is_Limited_Type (T1)
3918 and then not Is_Limited_Composite (T1)
3919 and then Has_Compatible_Type (R, T1)
3920 then
3921 if Found
3922 and then Base_Type (T1) /= Base_Type (T_F)
3923 then
3924 It := Disambiguate (L, I_F, Index, Any_Type);
3926 if It = No_Interp then
3927 Ambiguous_Operands (N);
3928 Set_Etype (L, Any_Type);
3929 return;
3931 else
3932 T_F := It.Typ;
3933 end if;
3935 else
3936 Found := True;
3937 T_F := T1;
3938 I_F := Index;
3939 end if;
3941 if not Analyzed (L) then
3942 Set_Etype (L, T_F);
3943 end if;
3945 Find_Non_Universal_Interpretations (N, R, Op_Id, T1);
3947 if Etype (N) = Any_Type then
3949 -- Operator was not visible.
3951 Found := False;
3952 end if;
3953 end if;
3954 end Try_One_Interp;
3956 -- Start of processing for Find_Equality_Types
3958 begin
3959 -- If left operand is aggregate, the right operand has to
3960 -- provide a usable type for it.
3962 if Nkind (L) = N_Aggregate
3963 and then Nkind (R) /= N_Aggregate
3964 then
3965 Find_Equality_Types (R, L, Op_Id, N);
3966 return;
3967 end if;
3969 if Nkind (N) = N_Function_Call
3970 and then Nkind (Name (N)) = N_Expanded_Name
3971 then
3972 Scop := Entity (Prefix (Name (N)));
3974 -- The prefix may be a package renaming, and the subsequent test
3975 -- requires the original package.
3977 if Ekind (Scop) = E_Package
3978 and then Present (Renamed_Entity (Scop))
3979 then
3980 Scop := Renamed_Entity (Scop);
3981 Set_Entity (Prefix (Name (N)), Scop);
3982 end if;
3983 end if;
3985 if not Is_Overloaded (L) then
3986 Try_One_Interp (Etype (L));
3987 else
3989 Get_First_Interp (L, Index, It);
3991 while Present (It.Typ) loop
3992 Try_One_Interp (It.Typ);
3993 Get_Next_Interp (Index, It);
3994 end loop;
3995 end if;
3996 end Find_Equality_Types;
3998 -------------------------
3999 -- Find_Negation_Types --
4000 -------------------------
4002 procedure Find_Negation_Types
4003 (R : Node_Id;
4004 Op_Id : Entity_Id;
4005 N : Node_Id)
4007 Index : Interp_Index;
4008 It : Interp;
4010 begin
4011 if not Is_Overloaded (R) then
4013 if Etype (R) = Universal_Integer then
4014 Add_One_Interp (N, Op_Id, Any_Modular);
4016 elsif Valid_Boolean_Arg (Etype (R)) then
4017 Add_One_Interp (N, Op_Id, Etype (R));
4018 end if;
4020 else
4021 Get_First_Interp (R, Index, It);
4023 while Present (It.Typ) loop
4024 if Valid_Boolean_Arg (It.Typ) then
4025 Add_One_Interp (N, Op_Id, It.Typ);
4026 end if;
4028 Get_Next_Interp (Index, It);
4029 end loop;
4030 end if;
4031 end Find_Negation_Types;
4033 ----------------------
4034 -- Find_Unary_Types --
4035 ----------------------
4037 procedure Find_Unary_Types
4038 (R : Node_Id;
4039 Op_Id : Entity_Id;
4040 N : Node_Id)
4042 Index : Interp_Index;
4043 It : Interp;
4045 begin
4046 if not Is_Overloaded (R) then
4047 if Is_Numeric_Type (Etype (R)) then
4048 Add_One_Interp (N, Op_Id, Base_Type (Etype (R)));
4049 end if;
4051 else
4052 Get_First_Interp (R, Index, It);
4054 while Present (It.Typ) loop
4055 if Is_Numeric_Type (It.Typ) then
4056 Add_One_Interp (N, Op_Id, Base_Type (It.Typ));
4057 end if;
4059 Get_Next_Interp (Index, It);
4060 end loop;
4061 end if;
4062 end Find_Unary_Types;
4064 ------------------
4065 -- Junk_Operand --
4066 ------------------
4068 function Junk_Operand (N : Node_Id) return Boolean is
4069 Enode : Node_Id;
4071 begin
4072 if Error_Posted (N) then
4073 return False;
4074 end if;
4076 -- Get entity to be tested
4078 if Is_Entity_Name (N)
4079 and then Present (Entity (N))
4080 then
4081 Enode := N;
4083 -- An odd case, a procedure name gets converted to a very peculiar
4084 -- function call, and here is where we detect this happening.
4086 elsif Nkind (N) = N_Function_Call
4087 and then Is_Entity_Name (Name (N))
4088 and then Present (Entity (Name (N)))
4089 then
4090 Enode := Name (N);
4092 -- Another odd case, there are at least some cases of selected
4093 -- components where the selected component is not marked as having
4094 -- an entity, even though the selector does have an entity
4096 elsif Nkind (N) = N_Selected_Component
4097 and then Present (Entity (Selector_Name (N)))
4098 then
4099 Enode := Selector_Name (N);
4101 else
4102 return False;
4103 end if;
4105 -- Now test the entity we got to see if it a bad case
4107 case Ekind (Entity (Enode)) is
4109 when E_Package =>
4110 Error_Msg_N
4111 ("package name cannot be used as operand", Enode);
4113 when Generic_Unit_Kind =>
4114 Error_Msg_N
4115 ("generic unit name cannot be used as operand", Enode);
4117 when Type_Kind =>
4118 Error_Msg_N
4119 ("subtype name cannot be used as operand", Enode);
4121 when Entry_Kind =>
4122 Error_Msg_N
4123 ("entry name cannot be used as operand", Enode);
4125 when E_Procedure =>
4126 Error_Msg_N
4127 ("procedure name cannot be used as operand", Enode);
4129 when E_Exception =>
4130 Error_Msg_N
4131 ("exception name cannot be used as operand", Enode);
4133 when E_Block | E_Label | E_Loop =>
4134 Error_Msg_N
4135 ("label name cannot be used as operand", Enode);
4137 when others =>
4138 return False;
4140 end case;
4142 return True;
4143 end Junk_Operand;
4145 --------------------
4146 -- Operator_Check --
4147 --------------------
4149 procedure Operator_Check (N : Node_Id) is
4150 begin
4151 Remove_Abstract_Operations (N);
4153 -- Test for case of no interpretation found for operator
4155 if Etype (N) = Any_Type then
4156 declare
4157 L : Node_Id;
4158 R : Node_Id;
4160 begin
4161 R := Right_Opnd (N);
4163 if Nkind (N) in N_Binary_Op then
4164 L := Left_Opnd (N);
4165 else
4166 L := Empty;
4167 end if;
4169 -- If either operand has no type, then don't complain further,
4170 -- since this simply means that we have a propragated error.
4172 if R = Error
4173 or else Etype (R) = Any_Type
4174 or else (Nkind (N) in N_Binary_Op and then Etype (L) = Any_Type)
4175 then
4176 return;
4178 -- We explicitly check for the case of concatenation of
4179 -- component with component to avoid reporting spurious
4180 -- matching array types that might happen to be lurking
4181 -- in distant packages (such as run-time packages). This
4182 -- also prevents inconsistencies in the messages for certain
4183 -- ACVC B tests, which can vary depending on types declared
4184 -- in run-time interfaces. A further improvement, when
4185 -- aggregates are present, is to look for a well-typed operand.
4187 elsif Present (Candidate_Type)
4188 and then (Nkind (N) /= N_Op_Concat
4189 or else Is_Array_Type (Etype (L))
4190 or else Is_Array_Type (Etype (R)))
4191 then
4193 if Nkind (N) = N_Op_Concat then
4194 if Etype (L) /= Any_Composite
4195 and then Is_Array_Type (Etype (L))
4196 then
4197 Candidate_Type := Etype (L);
4199 elsif Etype (R) /= Any_Composite
4200 and then Is_Array_Type (Etype (R))
4201 then
4202 Candidate_Type := Etype (R);
4203 end if;
4204 end if;
4206 Error_Msg_NE
4207 ("operator for} is not directly visible!",
4208 N, First_Subtype (Candidate_Type));
4209 Error_Msg_N ("use clause would make operation legal!", N);
4210 return;
4212 -- If either operand is a junk operand (e.g. package name), then
4213 -- post appropriate error messages, but do not complain further.
4215 -- Note that the use of OR in this test instead of OR ELSE
4216 -- is quite deliberate, we may as well check both operands
4217 -- in the binary operator case.
4219 elsif Junk_Operand (R)
4220 or (Nkind (N) in N_Binary_Op and then Junk_Operand (L))
4221 then
4222 return;
4224 -- If we have a logical operator, one of whose operands is
4225 -- Boolean, then we know that the other operand cannot resolve
4226 -- to Boolean (since we got no interpretations), but in that
4227 -- case we pretty much know that the other operand should be
4228 -- Boolean, so resolve it that way (generating an error)
4230 elsif Nkind (N) = N_Op_And
4231 or else
4232 Nkind (N) = N_Op_Or
4233 or else
4234 Nkind (N) = N_Op_Xor
4235 then
4236 if Etype (L) = Standard_Boolean then
4237 Resolve (R, Standard_Boolean);
4238 return;
4239 elsif Etype (R) = Standard_Boolean then
4240 Resolve (L, Standard_Boolean);
4241 return;
4242 end if;
4244 -- For an arithmetic operator or comparison operator, if one
4245 -- of the operands is numeric, then we know the other operand
4246 -- is not the same numeric type. If it is a non-numeric type,
4247 -- then probably it is intended to match the other operand.
4249 elsif Nkind (N) = N_Op_Add or else
4250 Nkind (N) = N_Op_Divide or else
4251 Nkind (N) = N_Op_Ge or else
4252 Nkind (N) = N_Op_Gt or else
4253 Nkind (N) = N_Op_Le or else
4254 Nkind (N) = N_Op_Lt or else
4255 Nkind (N) = N_Op_Mod or else
4256 Nkind (N) = N_Op_Multiply or else
4257 Nkind (N) = N_Op_Rem or else
4258 Nkind (N) = N_Op_Subtract
4259 then
4260 if Is_Numeric_Type (Etype (L))
4261 and then not Is_Numeric_Type (Etype (R))
4262 then
4263 Resolve (R, Etype (L));
4264 return;
4266 elsif Is_Numeric_Type (Etype (R))
4267 and then not Is_Numeric_Type (Etype (L))
4268 then
4269 Resolve (L, Etype (R));
4270 return;
4271 end if;
4273 -- Comparisons on A'Access are common enough to deserve a
4274 -- special message.
4276 elsif (Nkind (N) = N_Op_Eq or else
4277 Nkind (N) = N_Op_Ne)
4278 and then Ekind (Etype (L)) = E_Access_Attribute_Type
4279 and then Ekind (Etype (R)) = E_Access_Attribute_Type
4280 then
4281 Error_Msg_N
4282 ("two access attributes cannot be compared directly", N);
4283 Error_Msg_N
4284 ("\they must be converted to an explicit type for comparison",
4286 return;
4288 -- Another one for C programmers
4290 elsif Nkind (N) = N_Op_Concat
4291 and then Valid_Boolean_Arg (Etype (L))
4292 and then Valid_Boolean_Arg (Etype (R))
4293 then
4294 Error_Msg_N ("invalid operands for concatenation", N);
4295 Error_Msg_N ("\maybe AND was meant", N);
4296 return;
4298 -- A special case for comparison of access parameter with null
4300 elsif Nkind (N) = N_Op_Eq
4301 and then Is_Entity_Name (L)
4302 and then Nkind (Parent (Entity (L))) = N_Parameter_Specification
4303 and then Nkind (Parameter_Type (Parent (Entity (L)))) =
4304 N_Access_Definition
4305 and then Nkind (R) = N_Null
4306 then
4307 Error_Msg_N ("access parameter is not allowed to be null", L);
4308 Error_Msg_N ("\(call would raise Constraint_Error)", L);
4309 return;
4310 end if;
4312 -- If we fall through then just give general message. Note
4313 -- that in the following messages, if the operand is overloaded
4314 -- we choose an arbitrary type to complain about, but that is
4315 -- probably more useful than not giving a type at all.
4317 if Nkind (N) in N_Unary_Op then
4318 Error_Msg_Node_2 := Etype (R);
4319 Error_Msg_N ("operator& not defined for}", N);
4320 return;
4322 else
4323 if Nkind (N) in N_Binary_Op then
4324 if not Is_Overloaded (L)
4325 and then not Is_Overloaded (R)
4326 and then Base_Type (Etype (L)) = Base_Type (Etype (R))
4327 then
4328 Error_Msg_Node_2 := Etype (R);
4329 Error_Msg_N ("there is no applicable operator& for}", N);
4331 else
4332 Error_Msg_N ("invalid operand types for operator&", N);
4334 if Nkind (N) /= N_Op_Concat then
4335 Error_Msg_NE ("\left operand has}!", N, Etype (L));
4336 Error_Msg_NE ("\right operand has}!", N, Etype (R));
4337 end if;
4338 end if;
4339 end if;
4340 end if;
4341 end;
4342 end if;
4343 end Operator_Check;
4345 --------------------------------
4346 -- Remove_Abstract_Operations --
4347 --------------------------------
4349 procedure Remove_Abstract_Operations (N : Node_Id) is
4350 I : Interp_Index;
4351 It : Interp;
4352 Abstract_Op : Entity_Id := Empty;
4354 -- AI-310: If overloaded, remove abstract non-dispatching
4355 -- operations. We activate this if either extensions are
4356 -- enabled, or if the abstract operation in question comes
4357 -- from a predefined file. This latter test allows us to
4358 -- use abstract to make operations invisible to users. In
4359 -- particular, if type Address is non-private and abstract
4360 -- subprograms are used to hide its operators, they will be
4361 -- truly hidden.
4363 type Operand_Position is (First_Op, Second_Op);
4365 procedure Remove_Address_Interpretations (Op : Operand_Position);
4366 -- Ambiguities may arise when the operands are literal and the
4367 -- address operations in s-auxdec are visible. In that case, remove
4368 -- the interpretation of a literal as Address, to retain the semantics
4369 -- of Address as a private type.
4371 ------------------------------------
4372 -- Remove_Address_Interpretations --
4373 ------------------------------------
4375 procedure Remove_Address_Interpretations (Op : Operand_Position) is
4376 Formal : Entity_Id;
4378 begin
4379 if Is_Overloaded (N) then
4380 Get_First_Interp (N, I, It);
4381 while Present (It.Nam) loop
4382 Formal := First_Entity (It.Nam);
4384 if Op = Second_Op then
4385 Formal := Next_Entity (Formal);
4386 end if;
4388 if Is_Descendent_Of_Address (Etype (Formal)) then
4389 Remove_Interp (I);
4390 end if;
4392 Get_Next_Interp (I, It);
4393 end loop;
4394 end if;
4395 end Remove_Address_Interpretations;
4397 -- Start of processing for Remove_Abstract_Operations
4399 begin
4400 if Is_Overloaded (N) then
4401 Get_First_Interp (N, I, It);
4403 while Present (It.Nam) loop
4404 if not Is_Type (It.Nam)
4405 and then Is_Abstract (It.Nam)
4406 and then not Is_Dispatching_Operation (It.Nam)
4407 and then
4408 (Extensions_Allowed
4409 or else Is_Predefined_File_Name
4410 (Unit_File_Name (Get_Source_Unit (It.Nam))))
4412 then
4413 Abstract_Op := It.Nam;
4414 Remove_Interp (I);
4415 exit;
4416 end if;
4418 Get_Next_Interp (I, It);
4419 end loop;
4421 if No (Abstract_Op) then
4422 return;
4424 elsif Nkind (N) in N_Op then
4425 -- Remove interpretations that treat literals as addresses.
4426 -- This is never appropriate.
4428 if Nkind (N) in N_Binary_Op then
4429 declare
4430 U1 : constant Boolean :=
4431 Present (Universal_Interpretation (Right_Opnd (N)));
4432 U2 : constant Boolean :=
4433 Present (Universal_Interpretation (Left_Opnd (N)));
4435 begin
4436 if U1 and then not U2 then
4437 Remove_Address_Interpretations (Second_Op);
4439 elsif U2 and then not U1 then
4440 Remove_Address_Interpretations (First_Op);
4441 end if;
4443 if not (U1 and U2) then
4445 -- Remove corresponding predefined operator, which is
4446 -- always added to the overload set.
4448 Get_First_Interp (N, I, It);
4449 while Present (It.Nam) loop
4450 if Scope (It.Nam) = Standard_Standard then
4451 Remove_Interp (I);
4452 end if;
4454 Get_Next_Interp (I, It);
4455 end loop;
4456 end if;
4457 end;
4458 end if;
4460 elsif Nkind (N) = N_Function_Call
4461 and then
4462 (Nkind (Name (N)) = N_Operator_Symbol
4463 or else
4464 (Nkind (Name (N)) = N_Expanded_Name
4465 and then
4466 Nkind (Selector_Name (Name (N))) = N_Operator_Symbol))
4467 then
4469 declare
4470 Arg1 : constant Node_Id := First (Parameter_Associations (N));
4471 U1 : constant Boolean :=
4472 Present (Universal_Interpretation (Arg1));
4473 U2 : constant Boolean :=
4474 Present (Next (Arg1)) and then
4475 Present (Universal_Interpretation (Next (Arg1)));
4477 begin
4478 if U1 and then not U2 then
4479 Remove_Address_Interpretations (First_Op);
4481 elsif U2 and then not U1 then
4482 Remove_Address_Interpretations (Second_Op);
4483 end if;
4485 if not (U1 and U2) then
4486 Get_First_Interp (N, I, It);
4487 while Present (It.Nam) loop
4488 if Scope (It.Nam) = Standard_Standard
4489 and then It.Typ = Base_Type (Etype (Abstract_Op))
4490 then
4491 Remove_Interp (I);
4492 end if;
4494 Get_Next_Interp (I, It);
4495 end loop;
4496 end if;
4497 end;
4498 end if;
4500 -- If the removal has left no valid interpretations, emit
4501 -- error message now and label node as illegal.
4503 if Present (Abstract_Op) then
4504 Get_First_Interp (N, I, It);
4506 if No (It.Nam) then
4508 -- Removal of abstract operation left no viable candidate.
4510 Set_Etype (N, Any_Type);
4511 Error_Msg_Sloc := Sloc (Abstract_Op);
4512 Error_Msg_NE
4513 ("cannot call abstract operation& declared#", N, Abstract_Op);
4514 end if;
4515 end if;
4516 end if;
4517 end Remove_Abstract_Operations;
4519 -----------------------
4520 -- Try_Indirect_Call --
4521 -----------------------
4523 function Try_Indirect_Call
4524 (N : Node_Id;
4525 Nam : Entity_Id;
4526 Typ : Entity_Id) return Boolean
4528 Actual : Node_Id;
4529 Formal : Entity_Id;
4530 Call_OK : Boolean;
4532 begin
4533 Normalize_Actuals (N, Designated_Type (Typ), False, Call_OK);
4534 Actual := First_Actual (N);
4535 Formal := First_Formal (Designated_Type (Typ));
4537 while Present (Actual)
4538 and then Present (Formal)
4539 loop
4540 if not Has_Compatible_Type (Actual, Etype (Formal)) then
4541 return False;
4542 end if;
4544 Next (Actual);
4545 Next_Formal (Formal);
4546 end loop;
4548 if No (Actual) and then No (Formal) then
4549 Add_One_Interp (N, Nam, Etype (Designated_Type (Typ)));
4551 -- Nam is a candidate interpretation for the name in the call,
4552 -- if it is not an indirect call.
4554 if not Is_Type (Nam)
4555 and then Is_Entity_Name (Name (N))
4556 then
4557 Set_Entity (Name (N), Nam);
4558 end if;
4560 return True;
4561 else
4562 return False;
4563 end if;
4564 end Try_Indirect_Call;
4566 ----------------------
4567 -- Try_Indexed_Call --
4568 ----------------------
4570 function Try_Indexed_Call
4571 (N : Node_Id;
4572 Nam : Entity_Id;
4573 Typ : Entity_Id) return Boolean
4575 Actuals : constant List_Id := Parameter_Associations (N);
4576 Actual : Node_Id;
4577 Index : Entity_Id;
4579 begin
4580 Actual := First (Actuals);
4581 Index := First_Index (Typ);
4582 while Present (Actual)
4583 and then Present (Index)
4584 loop
4585 -- If the parameter list has a named association, the expression
4586 -- is definitely a call and not an indexed component.
4588 if Nkind (Actual) = N_Parameter_Association then
4589 return False;
4590 end if;
4592 if not Has_Compatible_Type (Actual, Etype (Index)) then
4593 return False;
4594 end if;
4596 Next (Actual);
4597 Next_Index (Index);
4598 end loop;
4600 if No (Actual) and then No (Index) then
4601 Add_One_Interp (N, Nam, Component_Type (Typ));
4603 -- Nam is a candidate interpretation for the name in the call,
4604 -- if it is not an indirect call.
4606 if not Is_Type (Nam)
4607 and then Is_Entity_Name (Name (N))
4608 then
4609 Set_Entity (Name (N), Nam);
4610 end if;
4612 return True;
4613 else
4614 return False;
4615 end if;
4617 end Try_Indexed_Call;
4619 end Sem_Ch4;