]> gcc.gnu.org Git - gcc.git/blame - gcc/ada/sem_ch4.adb
1aexcept.adb, [...]: Merge header, formatting and other trivial changes from ACT.
[gcc.git] / gcc / ada / sem_ch4.adb
CommitLineData
996ae0b0
RK
1------------------------------------------------------------------------------
2-- --
3-- GNAT COMPILER COMPONENTS --
4-- --
5-- S E M _ C H 4 --
6-- --
7-- B o d y --
8-- --
07fc65c4 9-- Copyright (C) 1992-2002, Free Software Foundation, Inc. --
996ae0b0
RK
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. --
71ff80dc 23-- Extensive contributions were provided by Ada Core Technologies Inc. --
996ae0b0
RK
24-- --
25------------------------------------------------------------------------------
26
27with Atree; use Atree;
28with Debug; use Debug;
29with Einfo; use Einfo;
30with Errout; use Errout;
31with Exp_Util; use Exp_Util;
32with Hostparm; use Hostparm;
33with Itypes; use Itypes;
34with Lib.Xref; use Lib.Xref;
35with Namet; use Namet;
36with Nlists; use Nlists;
37with Nmake; use Nmake;
38with Opt; use Opt;
39with Output; use Output;
40with Restrict; use Restrict;
41with Sem; use Sem;
42with Sem_Cat; use Sem_Cat;
43with Sem_Ch3; use Sem_Ch3;
44with Sem_Ch8; use Sem_Ch8;
45with Sem_Dist; use Sem_Dist;
46with Sem_Eval; use Sem_Eval;
47with Sem_Res; use Sem_Res;
48with Sem_Util; use Sem_Util;
49with Sem_Type; use Sem_Type;
50with Stand; use Stand;
51with Sinfo; use Sinfo;
52with Snames; use Snames;
53with Tbuild; use Tbuild;
54
55with GNAT.Spelling_Checker; use GNAT.Spelling_Checker;
56
57package body Sem_Ch4 is
58
59 -----------------------
60 -- Local Subprograms --
61 -----------------------
62
63 procedure Analyze_Expression (N : Node_Id);
64 -- For expressions that are not names, this is just a call to analyze.
65 -- If the expression is a name, it may be a call to a parameterless
66 -- function, and if so must be converted into an explicit call node
67 -- and analyzed as such. This deproceduring must be done during the first
68 -- pass of overload resolution, because otherwise a procedure call with
69 -- overloaded actuals may fail to resolve. See 4327-001 for an example.
70
71 procedure Analyze_Operator_Call (N : Node_Id; Op_Id : Entity_Id);
72 -- Analyze a call of the form "+"(x, y), etc. The prefix of the call
73 -- is an operator name or an expanded name whose selector is an operator
74 -- name, and one possible interpretation is as a predefined operator.
75
76 procedure Analyze_Overloaded_Selected_Component (N : Node_Id);
77 -- If the prefix of a selected_component is overloaded, the proper
78 -- interpretation that yields a record type with the proper selector
79 -- name must be selected.
80
81 procedure Analyze_User_Defined_Binary_Op (N : Node_Id; Op_Id : Entity_Id);
82 -- Procedure to analyze a user defined binary operator, which is resolved
83 -- like a function, but instead of a list of actuals it is presented
84 -- with the left and right operands of an operator node.
85
86 procedure Analyze_User_Defined_Unary_Op (N : Node_Id; Op_Id : Entity_Id);
87 -- Procedure to analyze a user defined unary operator, which is resolved
88 -- like a function, but instead of a list of actuals, it is presented with
89 -- the operand of the operator node.
90
91 procedure Ambiguous_Operands (N : Node_Id);
92 -- for equality, membership, and comparison operators with overloaded
93 -- arguments, list possible interpretations.
94
95 procedure Insert_Explicit_Dereference (N : Node_Id);
96 -- In a context that requires a composite or subprogram type and
97 -- where a prefix is an access type, insert an explicit dereference.
98
99 procedure Analyze_One_Call
100 (N : Node_Id;
101 Nam : Entity_Id;
102 Report : Boolean;
103 Success : out Boolean);
104 -- Check one interpretation of an overloaded subprogram name for
105 -- compatibility with the types of the actuals in a call. If there is a
106 -- single interpretation which does not match, post error if Report is
107 -- set to True.
108 --
109 -- Nam is the entity that provides the formals against which the actuals
110 -- are checked. Nam is either the name of a subprogram, or the internal
111 -- subprogram type constructed for an access_to_subprogram. If the actuals
112 -- are compatible with Nam, then Nam is added to the list of candidate
113 -- interpretations for N, and Success is set to True.
114
115 procedure Check_Misspelled_Selector
116 (Prefix : Entity_Id;
117 Sel : Node_Id);
118 -- Give possible misspelling diagnostic if Sel is likely to be
119 -- a misspelling of one of the selectors of the Prefix.
120 -- This is called by Analyze_Selected_Component after producing
121 -- an invalid selector error message.
122
123 function Defined_In_Scope (T : Entity_Id; S : Entity_Id) return Boolean;
124 -- Verify that type T is declared in scope S. Used to find intepretations
125 -- for operators given by expanded names. This is abstracted as a separate
126 -- function to handle extensions to System, where S is System, but T is
127 -- declared in the extension.
128
129 procedure Find_Arithmetic_Types
130 (L, R : Node_Id;
131 Op_Id : Entity_Id;
132 N : Node_Id);
133 -- L and R are the operands of an arithmetic operator. Find
134 -- consistent pairs of interpretations for L and R that have a
135 -- numeric type consistent with the semantics of the operator.
136
137 procedure Find_Comparison_Types
138 (L, R : Node_Id;
139 Op_Id : Entity_Id;
140 N : Node_Id);
141 -- L and R are operands of a comparison operator. Find consistent
142 -- pairs of interpretations for L and R.
143
144 procedure Find_Concatenation_Types
145 (L, R : Node_Id;
146 Op_Id : Entity_Id;
147 N : Node_Id);
148 -- For the four varieties of concatenation.
149
150 procedure Find_Equality_Types
151 (L, R : Node_Id;
152 Op_Id : Entity_Id;
153 N : Node_Id);
154 -- Ditto for equality operators.
155
156 procedure Find_Boolean_Types
157 (L, R : Node_Id;
158 Op_Id : Entity_Id;
159 N : Node_Id);
160 -- Ditto for binary logical operations.
161
162 procedure Find_Negation_Types
163 (R : Node_Id;
164 Op_Id : Entity_Id;
165 N : Node_Id);
166 -- Find consistent interpretation for operand of negation operator.
167
168 procedure Find_Non_Universal_Interpretations
169 (N : Node_Id;
170 R : Node_Id;
171 Op_Id : Entity_Id;
172 T1 : Entity_Id);
173 -- For equality and comparison operators, the result is always boolean,
174 -- and the legality of the operation is determined from the visibility
175 -- of the operand types. If one of the operands has a universal interpre-
176 -- tation, the legality check uses some compatible non-universal
177 -- interpretation of the other operand. N can be an operator node, or
178 -- a function call whose name is an operator designator.
179
180 procedure Find_Unary_Types
181 (R : Node_Id;
182 Op_Id : Entity_Id;
183 N : Node_Id);
184 -- Unary arithmetic types: plus, minus, abs.
185
186 procedure Check_Arithmetic_Pair
187 (T1, T2 : Entity_Id;
188 Op_Id : Entity_Id;
189 N : Node_Id);
190 -- Subsidiary procedure to Find_Arithmetic_Types. T1 and T2 are valid
191 -- types for left and right operand. Determine whether they constitute
192 -- a valid pair for the given operator, and record the corresponding
193 -- interpretation of the operator node. The node N may be an operator
194 -- node (the usual case) or a function call whose prefix is an operator
195 -- designator. In both cases Op_Id is the operator name itself.
196
197 procedure Diagnose_Call (N : Node_Id; Nam : Node_Id);
198 -- Give detailed information on overloaded call where none of the
199 -- interpretations match. N is the call node, Nam the designator for
200 -- the overloaded entity being called.
201
202 function Junk_Operand (N : Node_Id) return Boolean;
203 -- Test for an operand that is an inappropriate entity (e.g. a package
204 -- name or a label). If so, issue an error message and return True. If
205 -- the operand is not an inappropriate entity kind, return False.
206
207 procedure Operator_Check (N : Node_Id);
208 -- Verify that an operator has received some valid interpretation.
209 -- If none was found, determine whether a use clause would make the
210 -- operation legal. The variable Candidate_Type (defined in Sem_Type) is
211 -- set for every type compatible with the operator, even if the operator
212 -- for the type is not directly visible. The routine uses this type to emit
213 -- a more informative message.
214
215 function Try_Indexed_Call
216 (N : Node_Id;
217 Nam : Entity_Id;
218 Typ : Entity_Id)
219 return Boolean;
220 -- If a function has defaults for all its actuals, a call to it may
221 -- in fact be an indexing on the result of the call. Try_Indexed_Call
222 -- attempts the interpretation as an indexing, prior to analysis as
223 -- a call. If both are possible, the node is overloaded with both
224 -- interpretations (same symbol but two different types).
225
226 function Try_Indirect_Call
227 (N : Node_Id;
228 Nam : Entity_Id;
229 Typ : Entity_Id)
230 return Boolean;
231 -- Similarly, a function F that needs no actuals can return an access
232 -- to a subprogram, and the call F (X) interpreted as F.all (X). In
233 -- this case the call may be overloaded with both interpretations.
234
235 ------------------------
236 -- Ambiguous_Operands --
237 ------------------------
238
239 procedure Ambiguous_Operands (N : Node_Id) is
240 procedure List_Interps (Opnd : Node_Id);
241
242 procedure List_Interps (Opnd : Node_Id) is
243 Index : Interp_Index;
244 It : Interp;
245 Nam : Node_Id;
246 Err : Node_Id := N;
247
248 begin
249 if Is_Overloaded (Opnd) then
250 if Nkind (Opnd) in N_Op then
251 Nam := Opnd;
252
253 elsif Nkind (Opnd) = N_Function_Call then
254 Nam := Name (Opnd);
255
256 else
257 return;
258 end if;
259
260 else
261 return;
262 end if;
263
264 if Opnd = Left_Opnd (N) then
265 Error_Msg_N
266 ("\left operand has the following interpretations", N);
267 else
268 Error_Msg_N
269 ("\right operand has the following interpretations", N);
270 Err := Opnd;
271 end if;
272
273 Get_First_Interp (Nam, Index, It);
274
275 while Present (It.Nam) loop
276
277 if Scope (It.Nam) = Standard_Standard
278 and then Scope (It.Typ) /= Standard_Standard
279 then
280 Error_Msg_Sloc := Sloc (Parent (It.Typ));
281 Error_Msg_NE (" & (inherited) declared#!", Err, It.Nam);
282
283 else
284 Error_Msg_Sloc := Sloc (It.Nam);
285 Error_Msg_NE (" & declared#!", Err, It.Nam);
286 end if;
287
288 Get_Next_Interp (Index, It);
289 end loop;
290 end List_Interps;
291
292 begin
293 if Nkind (N) = N_In
294 or else Nkind (N) = N_Not_In
295 then
296 Error_Msg_N ("ambiguous operands for membership", N);
297
298 elsif Nkind (N) = N_Op_Eq
299 or else Nkind (N) = N_Op_Ne
300 then
301 Error_Msg_N ("ambiguous operands for equality", N);
302
303 else
304 Error_Msg_N ("ambiguous operands for comparison", N);
305 end if;
306
307 if All_Errors_Mode then
308 List_Interps (Left_Opnd (N));
309 List_Interps (Right_Opnd (N));
310 else
311
312 if OpenVMS then
313 Error_Msg_N (
314 "\use '/'R'E'P'O'R'T'_'E'R'R'O'R'S'='F'U'L'L for details",
315 N);
316 else
317 Error_Msg_N ("\use -gnatf for details", N);
318 end if;
319 end if;
320 end Ambiguous_Operands;
321
322 -----------------------
323 -- Analyze_Aggregate --
324 -----------------------
325
326 -- Most of the analysis of Aggregates requires that the type be known,
327 -- and is therefore put off until resolution.
328
329 procedure Analyze_Aggregate (N : Node_Id) is
330 begin
331 if No (Etype (N)) then
332 Set_Etype (N, Any_Composite);
333 end if;
334 end Analyze_Aggregate;
335
336 -----------------------
337 -- Analyze_Allocator --
338 -----------------------
339
340 procedure Analyze_Allocator (N : Node_Id) is
341 Loc : constant Source_Ptr := Sloc (N);
07fc65c4 342 Sav_Errs : constant Nat := Serious_Errors_Detected;
996ae0b0
RK
343 E : Node_Id := Expression (N);
344 Acc_Type : Entity_Id;
345 Type_Id : Entity_Id;
346
347 begin
348 Check_Restriction (No_Allocators, N);
349
350 if Nkind (E) = N_Qualified_Expression then
351 Acc_Type := Create_Itype (E_Allocator_Type, N);
352 Set_Etype (Acc_Type, Acc_Type);
353 Init_Size_Align (Acc_Type);
354 Find_Type (Subtype_Mark (E));
355 Type_Id := Entity (Subtype_Mark (E));
356 Check_Fully_Declared (Type_Id, N);
357 Set_Directly_Designated_Type (Acc_Type, Type_Id);
358
359 if Is_Protected_Type (Type_Id) then
360 Check_Restriction (No_Protected_Type_Allocators, N);
361 end if;
362
363 if Is_Limited_Type (Type_Id)
364 and then Comes_From_Source (N)
365 and then not In_Instance_Body
366 then
367 Error_Msg_N ("initialization not allowed for limited types", N);
368 end if;
369
370 Analyze_And_Resolve (Expression (E), Type_Id);
371
372 -- A qualified expression requires an exact match of the type,
373 -- class-wide matching is not allowed.
374
375 if Is_Class_Wide_Type (Type_Id)
376 and then Base_Type (Etype (Expression (E))) /= Base_Type (Type_Id)
377 then
378 Wrong_Type (Expression (E), Type_Id);
379 end if;
380
381 Check_Non_Static_Context (Expression (E));
382
383 -- We don't analyze the qualified expression itself because it's
384 -- part of the allocator
385
386 Set_Etype (E, Type_Id);
387
388 else
389 declare
390 Def_Id : Entity_Id;
391
392 begin
393 -- If the allocator includes a N_Subtype_Indication then a
394 -- constraint is present, otherwise the node is a subtype mark.
395 -- Introduce an explicit subtype declaration into the tree
396 -- defining some anonymous subtype and rewrite the allocator to
397 -- use this subtype rather than the subtype indication.
398
399 -- It is important to introduce the explicit subtype declaration
400 -- so that the bounds of the subtype indication are attached to
401 -- the tree in case the allocator is inside a generic unit.
402
403 if Nkind (E) = N_Subtype_Indication then
404
405 -- A constraint is only allowed for a composite type in Ada
406 -- 95. In Ada 83, a constraint is also allowed for an
407 -- access-to-composite type, but the constraint is ignored.
408
409 Find_Type (Subtype_Mark (E));
410
411 if Is_Elementary_Type (Entity (Subtype_Mark (E))) then
412 if not (Ada_83
413 and then Is_Access_Type (Entity (Subtype_Mark (E))))
414 then
415 Error_Msg_N ("constraint not allowed here", E);
416
417 if Nkind (Constraint (E))
418 = N_Index_Or_Discriminant_Constraint
419 then
420 Error_Msg_N
421 ("\if qualified expression was meant, " &
422 "use apostrophe", Constraint (E));
423 end if;
424 end if;
425
426 -- Get rid of the bogus constraint:
427
428 Rewrite (E, New_Copy_Tree (Subtype_Mark (E)));
429 Analyze_Allocator (N);
430 return;
431 end if;
432
433 if Expander_Active then
434 Def_Id :=
435 Make_Defining_Identifier (Loc, New_Internal_Name ('S'));
436
437 Insert_Action (E,
438 Make_Subtype_Declaration (Loc,
439 Defining_Identifier => Def_Id,
440 Subtype_Indication => Relocate_Node (E)));
441
07fc65c4 442 if Sav_Errs /= Serious_Errors_Detected
996ae0b0
RK
443 and then Nkind (Constraint (E))
444 = N_Index_Or_Discriminant_Constraint
445 then
446 Error_Msg_N
447 ("if qualified expression was meant, " &
448 "use apostrophe!", Constraint (E));
449 end if;
450
451 E := New_Occurrence_Of (Def_Id, Loc);
452 Rewrite (Expression (N), E);
453 end if;
454 end if;
455
456 Type_Id := Process_Subtype (E, N);
457 Acc_Type := Create_Itype (E_Allocator_Type, N);
458 Set_Etype (Acc_Type, Acc_Type);
459 Init_Size_Align (Acc_Type);
460 Set_Directly_Designated_Type (Acc_Type, Type_Id);
461 Check_Fully_Declared (Type_Id, N);
462
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
466
467 if Is_Indefinite_Subtype (Type_Id)
07fc65c4 468 and then Serious_Errors_Detected = Sav_Errs
996ae0b0
RK
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;
480
481 if Is_Abstract (Type_Id) then
482 Error_Msg_N ("cannot allocate abstract object", E);
483 end if;
484
485 if Has_Task (Designated_Type (Acc_Type)) then
486 Check_Restriction (No_Task_Allocators, N);
487 end if;
488
489 Set_Etype (N, Acc_Type);
490
491 if not Is_Library_Level_Entity (Acc_Type) then
492 Check_Restriction (No_Local_Allocators, N);
493 end if;
494
07fc65c4 495 if Serious_Errors_Detected > Sav_Errs then
996ae0b0
RK
496 Set_Error_Posted (N);
497 Set_Etype (N, Any_Type);
498 end if;
499
500 end Analyze_Allocator;
501
502 ---------------------------
503 -- Analyze_Arithmetic_Op --
504 ---------------------------
505
506 procedure Analyze_Arithmetic_Op (N : Node_Id) is
507 L : constant Node_Id := Left_Opnd (N);
508 R : constant Node_Id := Right_Opnd (N);
509 Op_Id : Entity_Id;
510
511 begin
512 Candidate_Type := Empty;
513 Analyze_Expression (L);
514 Analyze_Expression (R);
515
516 -- If the entity is already set, the node is the instantiation of
517 -- a generic node with a non-local reference, or was manufactured
518 -- by a call to Make_Op_xxx. In either case the entity is known to
519 -- be valid, and we do not need to collect interpretations, instead
520 -- we just get the single possible interpretation.
521
522 Op_Id := Entity (N);
523
524 if Present (Op_Id) then
525 if Ekind (Op_Id) = E_Operator then
526
527 if (Nkind (N) = N_Op_Divide or else
528 Nkind (N) = N_Op_Mod or else
529 Nkind (N) = N_Op_Multiply or else
530 Nkind (N) = N_Op_Rem)
531 and then Treat_Fixed_As_Integer (N)
532 then
533 null;
534 else
535 Set_Etype (N, Any_Type);
536 Find_Arithmetic_Types (L, R, Op_Id, N);
537 end if;
538
539 else
540 Set_Etype (N, Any_Type);
541 Add_One_Interp (N, Op_Id, Etype (Op_Id));
542 end if;
543
544 -- Entity is not already set, so we do need to collect interpretations
545
546 else
547 Op_Id := Get_Name_Entity_Id (Chars (N));
548 Set_Etype (N, Any_Type);
549
550 while Present (Op_Id) loop
551 if Ekind (Op_Id) = E_Operator
552 and then Present (Next_Entity (First_Entity (Op_Id)))
553 then
554 Find_Arithmetic_Types (L, R, Op_Id, N);
555
556 -- The following may seem superfluous, because an operator cannot
557 -- be generic, but this ignores the cleverness of the author of
558 -- ACVC bc1013a.
559
560 elsif Is_Overloadable (Op_Id) then
561 Analyze_User_Defined_Binary_Op (N, Op_Id);
562 end if;
563
564 Op_Id := Homonym (Op_Id);
565 end loop;
566 end if;
567
568 Operator_Check (N);
569 end Analyze_Arithmetic_Op;
570
571 ------------------
572 -- Analyze_Call --
573 ------------------
574
575 -- Function, procedure, and entry calls are checked here. The Name
576 -- in the call may be overloaded. The actuals have been analyzed
577 -- and may themselves be overloaded. On exit from this procedure, the node
578 -- N may have zero, one or more interpretations. In the first case an error
579 -- message is produced. In the last case, the node is flagged as overloaded
580 -- and the interpretations are collected in All_Interp.
581
582 -- If the name is an Access_To_Subprogram, it cannot be overloaded, but
583 -- the type-checking is similar to that of other calls.
584
585 procedure Analyze_Call (N : Node_Id) is
586 Actuals : constant List_Id := Parameter_Associations (N);
587 Nam : Node_Id := Name (N);
588 X : Interp_Index;
589 It : Interp;
590 Nam_Ent : Entity_Id;
591 Success : Boolean := False;
592
593 function Name_Denotes_Function return Boolean;
594 -- If the type of the name is an access to subprogram, this may be
595 -- the type of a name, or the return type of the function being called.
596 -- If the name is not an entity then it can denote a protected function.
597 -- Until we distinguish Etype from Return_Type, we must use this
598 -- routine to resolve the meaning of the name in the call.
599
600 ---------------------------
601 -- Name_Denotes_Function --
602 ---------------------------
603
604 function Name_Denotes_Function return Boolean is
605 begin
606 if Is_Entity_Name (Nam) then
607 return Ekind (Entity (Nam)) = E_Function;
608
609 elsif Nkind (Nam) = N_Selected_Component then
610 return Ekind (Entity (Selector_Name (Nam))) = E_Function;
611
612 else
613 return False;
614 end if;
615 end Name_Denotes_Function;
616
617 -- Start of processing for Analyze_Call
618
619 begin
620 -- Initialize the type of the result of the call to the error type,
621 -- which will be reset if the type is successfully resolved.
622
623 Set_Etype (N, Any_Type);
624
625 if not Is_Overloaded (Nam) then
626
627 -- Only one interpretation to check
628
629 if Ekind (Etype (Nam)) = E_Subprogram_Type then
630 Nam_Ent := Etype (Nam);
631
632 elsif Is_Access_Type (Etype (Nam))
633 and then Ekind (Designated_Type (Etype (Nam))) = E_Subprogram_Type
634 and then not Name_Denotes_Function
635 then
636 Nam_Ent := Designated_Type (Etype (Nam));
637 Insert_Explicit_Dereference (Nam);
638
639 -- Selected component case. Simple entry or protected operation,
640 -- where the entry name is given by the selector name.
641
642 elsif Nkind (Nam) = N_Selected_Component then
643 Nam_Ent := Entity (Selector_Name (Nam));
644
645 if Ekind (Nam_Ent) /= E_Entry
646 and then Ekind (Nam_Ent) /= E_Entry_Family
647 and then Ekind (Nam_Ent) /= E_Function
648 and then Ekind (Nam_Ent) /= E_Procedure
649 then
650 Error_Msg_N ("name in call is not a callable entity", Nam);
651 Set_Etype (N, Any_Type);
652 return;
653 end if;
654
655 -- If the name is an Indexed component, it can be a call to a member
656 -- of an entry family. The prefix must be a selected component whose
657 -- selector is the entry. Analyze_Procedure_Call normalizes several
658 -- kinds of call into this form.
659
660 elsif Nkind (Nam) = N_Indexed_Component then
661
662 if Nkind (Prefix (Nam)) = N_Selected_Component then
663 Nam_Ent := Entity (Selector_Name (Prefix (Nam)));
664
665 else
666 Error_Msg_N ("name in call is not a callable entity", Nam);
667 Set_Etype (N, Any_Type);
668 return;
669
670 end if;
671
672 elsif not Is_Entity_Name (Nam) then
673 Error_Msg_N ("name in call is not a callable entity", Nam);
674 Set_Etype (N, Any_Type);
675 return;
676
677 else
678 Nam_Ent := Entity (Nam);
679
680 -- If no interpretations, give error message
681
682 if not Is_Overloadable (Nam_Ent) then
683 declare
684 L : constant Boolean := Is_List_Member (N);
685 K : constant Node_Kind := Nkind (Parent (N));
686
687 begin
688 -- If the node is in a list whose parent is not an
689 -- expression then it must be an attempted procedure call.
690
691 if L and then K not in N_Subexpr then
692 if Ekind (Entity (Nam)) = E_Generic_Procedure then
693 Error_Msg_NE
694 ("must instantiate generic procedure& before call",
695 Nam, Entity (Nam));
696 else
697 Error_Msg_N
698 ("procedure or entry name expected", Nam);
699 end if;
700
701 -- Check for tasking cases where only an entry call will do
702
703 elsif not L
704 and then (K = N_Entry_Call_Alternative
705 or else K = N_Triggering_Alternative)
706 then
707 Error_Msg_N ("entry name expected", Nam);
708
709 -- Otherwise give general error message
710
711 else
712 Error_Msg_N ("invalid prefix in call", Nam);
713 end if;
714
715 return;
716 end;
717 end if;
718 end if;
719
720 Analyze_One_Call (N, Nam_Ent, True, Success);
721
722 else
723 -- An overloaded selected component must denote overloaded
724 -- operations of a concurrent type. The interpretations are
725 -- attached to the simple name of those operations.
726
727 if Nkind (Nam) = N_Selected_Component then
728 Nam := Selector_Name (Nam);
729 end if;
730
731 Get_First_Interp (Nam, X, It);
732
733 while Present (It.Nam) loop
734 Nam_Ent := It.Nam;
735
736 -- Name may be call that returns an access to subprogram, or more
737 -- generally an overloaded expression one of whose interpretations
738 -- yields an access to subprogram. If the name is an entity, we
739 -- do not dereference, because the node is a call that returns
740 -- the access type: note difference between f(x), where the call
741 -- may return an access subprogram type, and f(x)(y), where the
742 -- type returned by the call to f is implicitly dereferenced to
743 -- analyze the outer call.
744
745 if Is_Access_Type (Nam_Ent) then
746 Nam_Ent := Designated_Type (Nam_Ent);
747
748 elsif Is_Access_Type (Etype (Nam_Ent))
749 and then not Is_Entity_Name (Nam)
750 and then Ekind (Designated_Type (Etype (Nam_Ent)))
751 = E_Subprogram_Type
752 then
753 Nam_Ent := Designated_Type (Etype (Nam_Ent));
754 end if;
755
756 Analyze_One_Call (N, Nam_Ent, False, Success);
757
758 -- If the interpretation succeeds, mark the proper type of the
759 -- prefix (any valid candidate will do). If not, remove the
760 -- candidate interpretation. This only needs to be done for
761 -- overloaded protected operations, for other entities disambi-
762 -- guation is done directly in Resolve.
763
764 if Success then
765 Set_Etype (Nam, It.Typ);
766
767 elsif Nkind (Name (N)) = N_Selected_Component then
768 Remove_Interp (X);
769 end if;
770
771 Get_Next_Interp (X, It);
772 end loop;
773
774 -- If the name is the result of a function call, it can only
775 -- be a call to a function returning an access to subprogram.
776 -- Insert explicit dereference.
777
778 if Nkind (Nam) = N_Function_Call then
779 Insert_Explicit_Dereference (Nam);
780 end if;
781
782 if Etype (N) = Any_Type then
783
784 -- None of the interpretations is compatible with the actuals
785
786 Diagnose_Call (N, Nam);
787
788 -- Special checks for uninstantiated put routines
789
790 if Nkind (N) = N_Procedure_Call_Statement
791 and then Is_Entity_Name (Nam)
792 and then Chars (Nam) = Name_Put
793 and then List_Length (Actuals) = 1
794 then
795 declare
796 Arg : constant Node_Id := First (Actuals);
797 Typ : Entity_Id;
798
799 begin
800 if Nkind (Arg) = N_Parameter_Association then
801 Typ := Etype (Explicit_Actual_Parameter (Arg));
802 else
803 Typ := Etype (Arg);
804 end if;
805
806 if Is_Signed_Integer_Type (Typ) then
807 Error_Msg_N
808 ("possible missing instantiation of " &
809 "'Text_'I'O.'Integer_'I'O!", Nam);
810
811 elsif Is_Modular_Integer_Type (Typ) then
812 Error_Msg_N
813 ("possible missing instantiation of " &
814 "'Text_'I'O.'Modular_'I'O!", Nam);
815
816 elsif Is_Floating_Point_Type (Typ) then
817 Error_Msg_N
818 ("possible missing instantiation of " &
819 "'Text_'I'O.'Float_'I'O!", Nam);
820
821 elsif Is_Ordinary_Fixed_Point_Type (Typ) then
822 Error_Msg_N
823 ("possible missing instantiation of " &
824 "'Text_'I'O.'Fixed_'I'O!", Nam);
825
826 elsif Is_Decimal_Fixed_Point_Type (Typ) then
827 Error_Msg_N
828 ("possible missing instantiation of " &
829 "'Text_'I'O.'Decimal_'I'O!", Nam);
830
831 elsif Is_Enumeration_Type (Typ) then
832 Error_Msg_N
833 ("possible missing instantiation of " &
834 "'Text_'I'O.'Enumeration_'I'O!", Nam);
835 end if;
836 end;
837 end if;
838
839 elsif not Is_Overloaded (N)
840 and then Is_Entity_Name (Nam)
841 then
842 -- Resolution yields a single interpretation. Verify that
843 -- is has the proper capitalization.
844
845 Set_Entity_With_Style_Check (Nam, Entity (Nam));
846 Generate_Reference (Entity (Nam), Nam);
847
848 Set_Etype (Nam, Etype (Entity (Nam)));
849 end if;
850
851 End_Interp_List;
852 end if;
853 end Analyze_Call;
854
855 ---------------------------
856 -- Analyze_Comparison_Op --
857 ---------------------------
858
859 procedure Analyze_Comparison_Op (N : Node_Id) is
860 L : constant Node_Id := Left_Opnd (N);
861 R : constant Node_Id := Right_Opnd (N);
862 Op_Id : Entity_Id := Entity (N);
863
864 begin
865 Set_Etype (N, Any_Type);
866 Candidate_Type := Empty;
867
868 Analyze_Expression (L);
869 Analyze_Expression (R);
870
871 if Present (Op_Id) then
872
873 if Ekind (Op_Id) = E_Operator then
874 Find_Comparison_Types (L, R, Op_Id, N);
875 else
876 Add_One_Interp (N, Op_Id, Etype (Op_Id));
877 end if;
878
879 if Is_Overloaded (L) then
880 Set_Etype (L, Intersect_Types (L, R));
881 end if;
882
883 else
884 Op_Id := Get_Name_Entity_Id (Chars (N));
885
886 while Present (Op_Id) loop
887
888 if Ekind (Op_Id) = E_Operator then
889 Find_Comparison_Types (L, R, Op_Id, N);
890 else
891 Analyze_User_Defined_Binary_Op (N, Op_Id);
892 end if;
893
894 Op_Id := Homonym (Op_Id);
895 end loop;
896 end if;
897
898 Operator_Check (N);
899 end Analyze_Comparison_Op;
900
901 ---------------------------
902 -- Analyze_Concatenation --
903 ---------------------------
904
905 -- If the only one-dimensional array type in scope is String,
906 -- this is the resulting type of the operation. Otherwise there
907 -- will be a concatenation operation defined for each user-defined
908 -- one-dimensional array.
909
910 procedure Analyze_Concatenation (N : Node_Id) is
911 L : constant Node_Id := Left_Opnd (N);
912 R : constant Node_Id := Right_Opnd (N);
913 Op_Id : Entity_Id := Entity (N);
914 LT : Entity_Id;
915 RT : Entity_Id;
916
917 begin
918 Set_Etype (N, Any_Type);
919 Candidate_Type := Empty;
920
921 Analyze_Expression (L);
922 Analyze_Expression (R);
923
924 -- If the entity is present, the node appears in an instance,
925 -- and denotes a predefined concatenation operation. The resulting
926 -- type is obtained from the arguments when possible.
927
928 if Present (Op_Id) then
929 if Ekind (Op_Id) = E_Operator then
930
931 LT := Base_Type (Etype (L));
932 RT := Base_Type (Etype (R));
933
934 if Is_Array_Type (LT)
935 and then (RT = LT or else RT = Base_Type (Component_Type (LT)))
936 then
937 Add_One_Interp (N, Op_Id, LT);
938
939 elsif Is_Array_Type (RT)
940 and then LT = Base_Type (Component_Type (RT))
941 then
942 Add_One_Interp (N, Op_Id, RT);
943
944 else
945 Add_One_Interp (N, Op_Id, Etype (Op_Id));
946 end if;
947
948 else
949 Add_One_Interp (N, Op_Id, Etype (Op_Id));
950 end if;
951
952 else
953 Op_Id := Get_Name_Entity_Id (Name_Op_Concat);
954
955 while Present (Op_Id) loop
956 if Ekind (Op_Id) = E_Operator then
957 Find_Concatenation_Types (L, R, Op_Id, N);
958 else
959 Analyze_User_Defined_Binary_Op (N, Op_Id);
960 end if;
961
962 Op_Id := Homonym (Op_Id);
963 end loop;
964 end if;
965
966 Operator_Check (N);
967 end Analyze_Concatenation;
968
969 ------------------------------------
970 -- Analyze_Conditional_Expression --
971 ------------------------------------
972
973 procedure Analyze_Conditional_Expression (N : Node_Id) is
974 Condition : constant Node_Id := First (Expressions (N));
975 Then_Expr : constant Node_Id := Next (Condition);
976 Else_Expr : constant Node_Id := Next (Then_Expr);
977
978 begin
979 Analyze_Expression (Condition);
980 Analyze_Expression (Then_Expr);
981 Analyze_Expression (Else_Expr);
982 Set_Etype (N, Etype (Then_Expr));
983 end Analyze_Conditional_Expression;
984
985 -------------------------
986 -- Analyze_Equality_Op --
987 -------------------------
988
989 procedure Analyze_Equality_Op (N : Node_Id) is
990 Loc : constant Source_Ptr := Sloc (N);
991 L : constant Node_Id := Left_Opnd (N);
992 R : constant Node_Id := Right_Opnd (N);
993 Op_Id : Entity_Id;
994
995 begin
996 Set_Etype (N, Any_Type);
997 Candidate_Type := Empty;
998
999 Analyze_Expression (L);
1000 Analyze_Expression (R);
1001
1002 -- If the entity is set, the node is a generic instance with a non-local
1003 -- reference to the predefined operator or to a user-defined function.
1004 -- It can also be an inequality that is expanded into the negation of a
1005 -- call to a user-defined equality operator.
1006
1007 -- For the predefined case, the result is Boolean, regardless of the
1008 -- type of the operands. The operands may even be limited, if they are
1009 -- generic actuals. If they are overloaded, label the left argument with
1010 -- the common type that must be present, or with the type of the formal
1011 -- of the user-defined function.
1012
1013 if Present (Entity (N)) then
1014
1015 Op_Id := Entity (N);
1016
1017 if Ekind (Op_Id) = E_Operator then
1018 Add_One_Interp (N, Op_Id, Standard_Boolean);
1019 else
1020 Add_One_Interp (N, Op_Id, Etype (Op_Id));
1021 end if;
1022
1023 if Is_Overloaded (L) then
1024
1025 if Ekind (Op_Id) = E_Operator then
1026 Set_Etype (L, Intersect_Types (L, R));
1027 else
1028 Set_Etype (L, Etype (First_Formal (Op_Id)));
1029 end if;
1030 end if;
1031
1032 else
1033 Op_Id := Get_Name_Entity_Id (Chars (N));
1034
1035 while Present (Op_Id) loop
1036
1037 if Ekind (Op_Id) = E_Operator then
1038 Find_Equality_Types (L, R, Op_Id, N);
1039 else
1040 Analyze_User_Defined_Binary_Op (N, Op_Id);
1041 end if;
1042
1043 Op_Id := Homonym (Op_Id);
1044 end loop;
1045 end if;
1046
1047 -- If there was no match, and the operator is inequality, this may
1048 -- be a case where inequality has not been made explicit, as for
1049 -- tagged types. Analyze the node as the negation of an equality
1050 -- operation. This cannot be done earlier, because before analysis
1051 -- we cannot rule out the presence of an explicit inequality.
1052
1053 if Etype (N) = Any_Type
1054 and then Nkind (N) = N_Op_Ne
1055 then
1056 Op_Id := Get_Name_Entity_Id (Name_Op_Eq);
1057
1058 while Present (Op_Id) loop
1059
1060 if Ekind (Op_Id) = E_Operator then
1061 Find_Equality_Types (L, R, Op_Id, N);
1062 else
1063 Analyze_User_Defined_Binary_Op (N, Op_Id);
1064 end if;
1065
1066 Op_Id := Homonym (Op_Id);
1067 end loop;
1068
1069 if Etype (N) /= Any_Type then
1070 Op_Id := Entity (N);
1071
1072 Rewrite (N,
1073 Make_Op_Not (Loc,
1074 Right_Opnd =>
1075 Make_Op_Eq (Loc,
1076 Left_Opnd => Relocate_Node (Left_Opnd (N)),
1077 Right_Opnd => Relocate_Node (Right_Opnd (N)))));
1078
1079 Set_Entity (Right_Opnd (N), Op_Id);
1080 Analyze (N);
1081 end if;
1082 end if;
1083
1084 Operator_Check (N);
1085 end Analyze_Equality_Op;
1086
1087 ----------------------------------
1088 -- Analyze_Explicit_Dereference --
1089 ----------------------------------
1090
1091 procedure Analyze_Explicit_Dereference (N : Node_Id) is
1092 Loc : constant Source_Ptr := Sloc (N);
1093 P : constant Node_Id := Prefix (N);
1094 T : Entity_Id;
1095 I : Interp_Index;
1096 It : Interp;
1097 New_N : Node_Id;
1098
1099 function Is_Function_Type return Boolean;
1100 -- Check whether node may be interpreted as an implicit function call.
1101
1102 function Is_Function_Type return Boolean is
1103 I : Interp_Index;
1104 It : Interp;
1105
1106 begin
1107 if not Is_Overloaded (N) then
1108 return Ekind (Base_Type (Etype (N))) = E_Subprogram_Type
1109 and then Etype (Base_Type (Etype (N))) /= Standard_Void_Type;
1110
1111 else
1112 Get_First_Interp (N, I, It);
1113
1114 while Present (It.Nam) loop
1115 if Ekind (Base_Type (It.Typ)) /= E_Subprogram_Type
1116 or else Etype (Base_Type (It.Typ)) = Standard_Void_Type
1117 then
1118 return False;
1119 end if;
1120
1121 Get_Next_Interp (I, It);
1122 end loop;
1123
1124 return True;
1125 end if;
1126 end Is_Function_Type;
1127
1128 begin
1129 Analyze (P);
1130 Set_Etype (N, Any_Type);
1131
1132 -- Test for remote access to subprogram type, and if so return
1133 -- after rewriting the original tree.
1134
1135 if Remote_AST_E_Dereference (P) then
1136 return;
1137 end if;
1138
1139 -- Normal processing for other than remote access to subprogram type
1140
1141 if not Is_Overloaded (P) then
1142 if Is_Access_Type (Etype (P)) then
1143
1144 -- Set the Etype. We need to go thru Is_For_Access_Subtypes
1145 -- to avoid other problems caused by the Private_Subtype
1146 -- and it is safe to go to the Base_Type because this is the
1147 -- same as converting the access value to its Base_Type.
1148
1149 declare
1150 DT : Entity_Id := Designated_Type (Etype (P));
1151
1152 begin
1153 if Ekind (DT) = E_Private_Subtype
1154 and then Is_For_Access_Subtype (DT)
1155 then
1156 DT := Base_Type (DT);
1157 end if;
1158
1159 Set_Etype (N, DT);
1160 end;
1161
1162 elsif Etype (P) /= Any_Type then
1163 Error_Msg_N ("prefix of dereference must be an access type", N);
1164 return;
1165 end if;
1166
1167 else
1168 Get_First_Interp (P, I, It);
1169
1170 while Present (It.Nam) loop
1171 T := It.Typ;
1172
1173 if Is_Access_Type (T) then
1174 Add_One_Interp (N, Designated_Type (T), Designated_Type (T));
1175 end if;
1176
1177 Get_Next_Interp (I, It);
1178 end loop;
1179
1180 End_Interp_List;
1181
1182 -- Error if no interpretation of the prefix has an access type.
1183
1184 if Etype (N) = Any_Type then
1185 Error_Msg_N
1186 ("access type required in prefix of explicit dereference", P);
1187 Set_Etype (N, Any_Type);
1188 return;
1189 end if;
1190 end if;
1191
1192 if Is_Function_Type
1193 and then Nkind (Parent (N)) /= N_Indexed_Component
1194
1195 and then (Nkind (Parent (N)) /= N_Function_Call
1196 or else N /= Name (Parent (N)))
1197
1198 and then (Nkind (Parent (N)) /= N_Procedure_Call_Statement
1199 or else N /= Name (Parent (N)))
1200
1201 and then Nkind (Parent (N)) /= N_Subprogram_Renaming_Declaration
1202 and then (Nkind (Parent (N)) /= N_Attribute_Reference
1203 or else
1204 (Attribute_Name (Parent (N)) /= Name_Address
1205 and then
1206 Attribute_Name (Parent (N)) /= Name_Access))
1207 then
1208 -- Name is a function call with no actuals, in a context that
1209 -- requires deproceduring (including as an actual in an enclosing
1210 -- function or procedure call). We can conceive of pathological cases
1211 -- where the prefix might include functions that return access to
1212 -- subprograms and others that return a regular type. Disambiguation
1213 -- of those will have to take place in Resolve. See e.g. 7117-014.
1214
1215 New_N :=
1216 Make_Function_Call (Loc,
1217 Name => Make_Explicit_Dereference (Loc, P),
1218 Parameter_Associations => New_List);
1219
1220 -- If the prefix is overloaded, remove operations that have formals,
1221 -- we know that this is a parameterless call.
1222
1223 if Is_Overloaded (P) then
1224 Get_First_Interp (P, I, It);
1225
1226 while Present (It.Nam) loop
1227 T := It.Typ;
1228
1229 if No (First_Formal (Base_Type (Designated_Type (T)))) then
1230 Set_Etype (P, T);
1231 else
1232 Remove_Interp (I);
1233 end if;
1234
1235 Get_Next_Interp (I, It);
1236 end loop;
1237 end if;
1238
1239 Rewrite (N, New_N);
1240 Analyze (N);
1241 end if;
1242
1243 -- A value of remote access-to-class-wide must not be dereferenced
1244 -- (RM E.2.2(16)).
1245
1246 Validate_Remote_Access_To_Class_Wide_Type (N);
1247
1248 end Analyze_Explicit_Dereference;
1249
1250 ------------------------
1251 -- Analyze_Expression --
1252 ------------------------
1253
1254 procedure Analyze_Expression (N : Node_Id) is
1255 begin
1256 Analyze (N);
1257 Check_Parameterless_Call (N);
1258 end Analyze_Expression;
1259
1260 ------------------------------------
1261 -- Analyze_Indexed_Component_Form --
1262 ------------------------------------
1263
1264 procedure Analyze_Indexed_Component_Form (N : Node_Id) is
1265 P : constant Node_Id := Prefix (N);
1266 Exprs : List_Id := Expressions (N);
1267 Exp : Node_Id;
1268 P_T : Entity_Id;
1269 E : Node_Id;
1270 U_N : Entity_Id;
1271
1272 procedure Process_Function_Call;
1273 -- Prefix in indexed component form is an overloadable entity,
1274 -- so the node is a function call. Reformat it as such.
1275
1276 procedure Process_Indexed_Component;
1277 -- Prefix in indexed component form is actually an indexed component.
1278 -- This routine processes it, knowing that the prefix is already
1279 -- resolved.
1280
1281 procedure Process_Indexed_Component_Or_Slice;
1282 -- An indexed component with a single index may designate a slice if
1283 -- the index is a subtype mark. This routine disambiguates these two
1284 -- cases by resolving the prefix to see if it is a subtype mark.
1285
1286 procedure Process_Overloaded_Indexed_Component;
1287 -- If the prefix of an indexed component is overloaded, the proper
1288 -- interpretation is selected by the index types and the context.
1289
1290 ---------------------------
1291 -- Process_Function_Call --
1292 ---------------------------
1293
1294 procedure Process_Function_Call is
1295 Actual : Node_Id;
1296
1297 begin
1298 Change_Node (N, N_Function_Call);
1299 Set_Name (N, P);
1300 Set_Parameter_Associations (N, Exprs);
1301 Actual := First (Parameter_Associations (N));
1302
1303 while Present (Actual) loop
1304 Analyze (Actual);
1305 Check_Parameterless_Call (Actual);
1306 Next_Actual (Actual);
1307 end loop;
1308
1309 Analyze_Call (N);
1310 end Process_Function_Call;
1311
1312 -------------------------------
1313 -- Process_Indexed_Component --
1314 -------------------------------
1315
1316 procedure Process_Indexed_Component is
1317 Exp : Node_Id;
1318 Array_Type : Entity_Id;
1319 Index : Node_Id;
1320 Entry_Family : Entity_Id;
1321
1322 begin
1323 Exp := First (Exprs);
1324
1325 if Is_Overloaded (P) then
1326 Process_Overloaded_Indexed_Component;
1327
1328 else
1329 Array_Type := Etype (P);
1330
1331 -- Prefix must be appropriate for an array type.
1332 -- Dereference the prefix if it is an access type.
1333
1334 if Is_Access_Type (Array_Type) then
1335 Array_Type := Designated_Type (Array_Type);
07fc65c4
GB
1336
1337 if Warn_On_Dereference then
1338 Error_Msg_N ("?implicit dereference", N);
1339 end if;
996ae0b0
RK
1340 end if;
1341
1342 if Is_Array_Type (Array_Type) then
1343 null;
1344
1345 elsif (Is_Entity_Name (P)
1346 and then
1347 Ekind (Entity (P)) = E_Entry_Family)
1348 or else
1349 (Nkind (P) = N_Selected_Component
1350 and then
1351 Is_Entity_Name (Selector_Name (P))
1352 and then
1353 Ekind (Entity (Selector_Name (P))) = E_Entry_Family)
1354 then
1355 if Is_Entity_Name (P) then
1356 Entry_Family := Entity (P);
1357 else
1358 Entry_Family := Entity (Selector_Name (P));
1359 end if;
1360
1361 Analyze (Exp);
1362 Set_Etype (N, Any_Type);
1363
1364 if not Has_Compatible_Type
1365 (Exp, Entry_Index_Type (Entry_Family))
1366 then
1367 Error_Msg_N ("invalid index type in entry name", N);
1368
1369 elsif Present (Next (Exp)) then
1370 Error_Msg_N ("too many subscripts in entry reference", N);
1371
1372 else
1373 Set_Etype (N, Etype (P));
1374 end if;
1375
1376 return;
1377
1378 elsif Is_Record_Type (Array_Type)
1379 and then Remote_AST_I_Dereference (P)
1380 then
1381 return;
1382
1383 elsif Array_Type = Any_Type then
1384 Set_Etype (N, Any_Type);
1385 return;
1386
1387 -- Here we definitely have a bad indexing
1388
1389 else
1390 if Nkind (Parent (N)) = N_Requeue_Statement
1391 and then
1392 ((Is_Entity_Name (P)
1393 and then Ekind (Entity (P)) = E_Entry)
1394 or else
1395 (Nkind (P) = N_Selected_Component
1396 and then Is_Entity_Name (Selector_Name (P))
1397 and then Ekind (Entity (Selector_Name (P))) = E_Entry))
1398 then
1399 Error_Msg_N
1400 ("REQUEUE does not permit parameters", First (Exprs));
1401
1402 elsif Is_Entity_Name (P)
1403 and then Etype (P) = Standard_Void_Type
1404 then
1405 Error_Msg_NE ("incorrect use of&", P, Entity (P));
1406
1407 else
1408 Error_Msg_N ("array type required in indexed component", P);
1409 end if;
1410
1411 Set_Etype (N, Any_Type);
1412 return;
1413 end if;
1414
1415 Index := First_Index (Array_Type);
1416
1417 while Present (Index) and then Present (Exp) loop
1418 if not Has_Compatible_Type (Exp, Etype (Index)) then
1419 Wrong_Type (Exp, Etype (Index));
1420 Set_Etype (N, Any_Type);
1421 return;
1422 end if;
1423
1424 Next_Index (Index);
1425 Next (Exp);
1426 end loop;
1427
1428 Set_Etype (N, Component_Type (Array_Type));
1429
1430 if Present (Index) then
1431 Error_Msg_N
1432 ("too few subscripts in array reference", First (Exprs));
1433
1434 elsif Present (Exp) then
1435 Error_Msg_N ("too many subscripts in array reference", Exp);
1436 end if;
1437 end if;
1438
1439 end Process_Indexed_Component;
1440
1441 ----------------------------------------
1442 -- Process_Indexed_Component_Or_Slice --
1443 ----------------------------------------
1444
1445 procedure Process_Indexed_Component_Or_Slice is
1446 begin
1447 Exp := First (Exprs);
1448
1449 while Present (Exp) loop
1450 Analyze_Expression (Exp);
1451 Next (Exp);
1452 end loop;
1453
1454 Exp := First (Exprs);
1455
1456 -- If one index is present, and it is a subtype name, then the
1457 -- node denotes a slice (note that the case of an explicit range
1458 -- for a slice was already built as an N_Slice node in the first
1459 -- place, so that case is not handled here).
1460
1461 -- We use a replace rather than a rewrite here because this is one
1462 -- of the cases in which the tree built by the parser is plain wrong.
1463
1464 if No (Next (Exp))
1465 and then Is_Entity_Name (Exp)
1466 and then Is_Type (Entity (Exp))
1467 then
1468 Replace (N,
1469 Make_Slice (Sloc (N),
1470 Prefix => P,
1471 Discrete_Range => New_Copy (Exp)));
1472 Analyze (N);
1473
1474 -- Otherwise (more than one index present, or single index is not
1475 -- a subtype name), then we have the indexed component case.
1476
1477 else
1478 Process_Indexed_Component;
1479 end if;
1480 end Process_Indexed_Component_Or_Slice;
1481
1482 ------------------------------------------
1483 -- Process_Overloaded_Indexed_Component --
1484 ------------------------------------------
1485
1486 procedure Process_Overloaded_Indexed_Component is
1487 Exp : Node_Id;
1488 I : Interp_Index;
1489 It : Interp;
1490 Typ : Entity_Id;
1491 Index : Node_Id;
1492 Found : Boolean;
1493
1494 begin
1495 Set_Etype (N, Any_Type);
1496 Get_First_Interp (P, I, It);
1497
1498 while Present (It.Nam) loop
1499 Typ := It.Typ;
1500
1501 if Is_Access_Type (Typ) then
1502 Typ := Designated_Type (Typ);
07fc65c4
GB
1503
1504 if Warn_On_Dereference then
1505 Error_Msg_N ("?implicit dereference", N);
1506 end if;
996ae0b0
RK
1507 end if;
1508
1509 if Is_Array_Type (Typ) then
1510
1511 -- Got a candidate: verify that index types are compatible
1512
1513 Index := First_Index (Typ);
1514 Found := True;
1515
1516 Exp := First (Exprs);
1517
1518 while Present (Index) and then Present (Exp) loop
1519 if Has_Compatible_Type (Exp, Etype (Index)) then
1520 null;
1521 else
1522 Found := False;
1523 Remove_Interp (I);
1524 exit;
1525 end if;
1526
1527 Next_Index (Index);
1528 Next (Exp);
1529 end loop;
1530
1531 if Found and then No (Index) and then No (Exp) then
1532 Add_One_Interp (N,
1533 Etype (Component_Type (Typ)),
1534 Etype (Component_Type (Typ)));
1535 end if;
1536 end if;
1537
1538 Get_Next_Interp (I, It);
1539 end loop;
1540
1541 if Etype (N) = Any_Type then
1542 Error_Msg_N ("no legal interpetation for indexed component", N);
1543 Set_Is_Overloaded (N, False);
1544 end if;
1545
1546 End_Interp_List;
1547 end Process_Overloaded_Indexed_Component;
1548
1549 ------------------------------------
1550 -- Analyze_Indexed_Component_Form --
1551 ------------------------------------
1552
1553 begin
1554 -- Get name of array, function or type
1555
1556 Analyze (P);
1557 P_T := Base_Type (Etype (P));
1558
1559 if Is_Entity_Name (P)
1560 or else Nkind (P) = N_Operator_Symbol
1561 then
1562 U_N := Entity (P);
1563
1564 if Ekind (U_N) in Type_Kind then
1565
1566 -- Reformat node as a type conversion.
1567
1568 E := Remove_Head (Exprs);
1569
1570 if Present (First (Exprs)) then
1571 Error_Msg_N
1572 ("argument of type conversion must be single expression", N);
1573 end if;
1574
1575 Change_Node (N, N_Type_Conversion);
1576 Set_Subtype_Mark (N, P);
1577 Set_Etype (N, U_N);
1578 Set_Expression (N, E);
1579
1580 -- After changing the node, call for the specific Analysis
1581 -- routine directly, to avoid a double call to the expander.
1582
1583 Analyze_Type_Conversion (N);
1584 return;
1585 end if;
1586
1587 if Is_Overloadable (U_N) then
1588 Process_Function_Call;
1589
1590 elsif Ekind (Etype (P)) = E_Subprogram_Type
1591 or else (Is_Access_Type (Etype (P))
1592 and then
1593 Ekind (Designated_Type (Etype (P))) = E_Subprogram_Type)
1594 then
1595 -- Call to access_to-subprogram with possible implicit dereference
1596
1597 Process_Function_Call;
1598
1599 elsif Ekind (U_N) = E_Generic_Function
1600 or else Ekind (U_N) = E_Generic_Procedure
1601 then
1602 -- A common beginner's (or C++ templates fan) error.
1603
1604 Error_Msg_N ("generic subprogram cannot be called", N);
1605 Set_Etype (N, Any_Type);
1606 return;
1607
1608 else
1609 Process_Indexed_Component_Or_Slice;
1610 end if;
1611
1612 -- If not an entity name, prefix is an expression that may denote
1613 -- an array or an access-to-subprogram.
1614
1615 else
1616
1617 if (Ekind (P_T) = E_Subprogram_Type)
1618 or else (Is_Access_Type (P_T)
1619 and then
1620 Ekind (Designated_Type (P_T)) = E_Subprogram_Type)
1621 then
1622 Process_Function_Call;
1623
1624 elsif Nkind (P) = N_Selected_Component
1625 and then Ekind (Entity (Selector_Name (P))) = E_Function
1626 then
1627 Process_Function_Call;
1628
1629 else
1630 -- Indexed component, slice, or a call to a member of a family
1631 -- entry, which will be converted to an entry call later.
1632 Process_Indexed_Component_Or_Slice;
1633 end if;
1634 end if;
1635 end Analyze_Indexed_Component_Form;
1636
1637 ------------------------
1638 -- Analyze_Logical_Op --
1639 ------------------------
1640
1641 procedure Analyze_Logical_Op (N : Node_Id) is
1642 L : constant Node_Id := Left_Opnd (N);
1643 R : constant Node_Id := Right_Opnd (N);
1644 Op_Id : Entity_Id := Entity (N);
1645
1646 begin
1647 Set_Etype (N, Any_Type);
1648 Candidate_Type := Empty;
1649
1650 Analyze_Expression (L);
1651 Analyze_Expression (R);
1652
1653 if Present (Op_Id) then
1654
1655 if Ekind (Op_Id) = E_Operator then
1656 Find_Boolean_Types (L, R, Op_Id, N);
1657 else
1658 Add_One_Interp (N, Op_Id, Etype (Op_Id));
1659 end if;
1660
1661 else
1662 Op_Id := Get_Name_Entity_Id (Chars (N));
1663
1664 while Present (Op_Id) loop
1665 if Ekind (Op_Id) = E_Operator then
1666 Find_Boolean_Types (L, R, Op_Id, N);
1667 else
1668 Analyze_User_Defined_Binary_Op (N, Op_Id);
1669 end if;
1670
1671 Op_Id := Homonym (Op_Id);
1672 end loop;
1673 end if;
1674
1675 Operator_Check (N);
1676 end Analyze_Logical_Op;
1677
1678 ---------------------------
1679 -- Analyze_Membership_Op --
1680 ---------------------------
1681
1682 procedure Analyze_Membership_Op (N : Node_Id) is
1683 L : constant Node_Id := Left_Opnd (N);
1684 R : constant Node_Id := Right_Opnd (N);
1685
1686 Index : Interp_Index;
1687 It : Interp;
1688 Found : Boolean := False;
1689 I_F : Interp_Index;
1690 T_F : Entity_Id;
1691
1692 procedure Try_One_Interp (T1 : Entity_Id);
1693 -- Routine to try one proposed interpretation. Note that the context
1694 -- of the operation plays no role in resolving the arguments, so that
1695 -- if there is more than one interpretation of the operands that is
1696 -- compatible with a membership test, the operation is ambiguous.
1697
1698 procedure Try_One_Interp (T1 : Entity_Id) is
1699 begin
1700 if Has_Compatible_Type (R, T1) then
1701 if Found
1702 and then Base_Type (T1) /= Base_Type (T_F)
1703 then
1704 It := Disambiguate (L, I_F, Index, Any_Type);
1705
1706 if It = No_Interp then
1707 Ambiguous_Operands (N);
1708 Set_Etype (L, Any_Type);
1709 return;
1710
1711 else
1712 T_F := It.Typ;
1713 end if;
1714
1715 else
1716 Found := True;
1717 T_F := T1;
1718 I_F := Index;
1719 end if;
1720
1721 Set_Etype (L, T_F);
1722 end if;
1723
1724 end Try_One_Interp;
1725
1726 -- Start of processing for Analyze_Membership_Op
1727
1728 begin
1729 Analyze_Expression (L);
1730
1731 if Nkind (R) = N_Range
1732 or else (Nkind (R) = N_Attribute_Reference
1733 and then Attribute_Name (R) = Name_Range)
1734 then
1735 Analyze (R);
1736
1737 if not Is_Overloaded (L) then
1738 Try_One_Interp (Etype (L));
1739
1740 else
1741 Get_First_Interp (L, Index, It);
1742
1743 while Present (It.Typ) loop
1744 Try_One_Interp (It.Typ);
1745 Get_Next_Interp (Index, It);
1746 end loop;
1747 end if;
1748
1749 -- If not a range, it can only be a subtype mark, or else there
1750 -- is a more basic error, to be diagnosed in Find_Type.
1751
1752 else
1753 Find_Type (R);
1754
1755 if Is_Entity_Name (R) then
1756 Check_Fully_Declared (Entity (R), R);
1757 end if;
1758 end if;
1759
1760 -- Compatibility between expression and subtype mark or range is
1761 -- checked during resolution. The result of the operation is Boolean
1762 -- in any case.
1763
1764 Set_Etype (N, Standard_Boolean);
1765 end Analyze_Membership_Op;
1766
1767 ----------------------
1768 -- Analyze_Negation --
1769 ----------------------
1770
1771 procedure Analyze_Negation (N : Node_Id) is
1772 R : constant Node_Id := Right_Opnd (N);
1773 Op_Id : Entity_Id := Entity (N);
1774
1775 begin
1776 Set_Etype (N, Any_Type);
1777 Candidate_Type := Empty;
1778
1779 Analyze_Expression (R);
1780
1781 if Present (Op_Id) then
1782 if Ekind (Op_Id) = E_Operator then
1783 Find_Negation_Types (R, Op_Id, N);
1784 else
1785 Add_One_Interp (N, Op_Id, Etype (Op_Id));
1786 end if;
1787
1788 else
1789 Op_Id := Get_Name_Entity_Id (Chars (N));
1790
1791 while Present (Op_Id) loop
1792 if Ekind (Op_Id) = E_Operator then
1793 Find_Negation_Types (R, Op_Id, N);
1794 else
1795 Analyze_User_Defined_Unary_Op (N, Op_Id);
1796 end if;
1797
1798 Op_Id := Homonym (Op_Id);
1799 end loop;
1800 end if;
1801
1802 Operator_Check (N);
1803 end Analyze_Negation;
1804
1805 -------------------
1806 -- Analyze_Null --
1807 -------------------
1808
1809 procedure Analyze_Null (N : Node_Id) is
1810 begin
1811 Set_Etype (N, Any_Access);
1812 end Analyze_Null;
1813
1814 ----------------------
1815 -- Analyze_One_Call --
1816 ----------------------
1817
1818 procedure Analyze_One_Call
1819 (N : Node_Id;
1820 Nam : Entity_Id;
1821 Report : Boolean;
1822 Success : out Boolean)
1823 is
1824 Actuals : constant List_Id := Parameter_Associations (N);
1825 Prev_T : constant Entity_Id := Etype (N);
1826 Formal : Entity_Id;
1827 Actual : Node_Id;
1828 Is_Indexed : Boolean := False;
1829 Subp_Type : constant Entity_Id := Etype (Nam);
1830 Norm_OK : Boolean;
1831
1832 procedure Set_Name;
1833 -- If candidate interpretation matches, indicate name and type of
1834 -- result on call node.
1835
1836 --------------
1837 -- Set_Name --
1838 --------------
1839
1840 procedure Set_Name is
1841 begin
1842 Add_One_Interp (N, Nam, Etype (Nam));
1843 Success := True;
1844
1845 -- If the prefix of the call is a name, indicate the entity
1846 -- being called. If it is not a name, it is an expression that
1847 -- denotes an access to subprogram or else an entry or family. In
1848 -- the latter case, the name is a selected component, and the entity
1849 -- being called is noted on the selector.
1850
1851 if not Is_Type (Nam) then
1852 if Is_Entity_Name (Name (N))
1853 or else Nkind (Name (N)) = N_Operator_Symbol
1854 then
1855 Set_Entity (Name (N), Nam);
1856
1857 elsif Nkind (Name (N)) = N_Selected_Component then
1858 Set_Entity (Selector_Name (Name (N)), Nam);
1859 end if;
1860 end if;
1861
1862 if Debug_Flag_E and not Report then
1863 Write_Str (" Overloaded call ");
1864 Write_Int (Int (N));
1865 Write_Str (" compatible with ");
1866 Write_Int (Int (Nam));
1867 Write_Eol;
1868 end if;
1869 end Set_Name;
1870
1871 -- Start of processing for Analyze_One_Call
1872
1873 begin
1874 Success := False;
1875
1876 -- If the subprogram has no formals, or if all the formals have
1877 -- defaults, and the return type is an array type, the node may
1878 -- denote an indexing of the result of a parameterless call.
1879
1880 if Needs_No_Actuals (Nam)
1881 and then Present (Actuals)
1882 then
1883 if Is_Array_Type (Subp_Type) then
1884 Is_Indexed := Try_Indexed_Call (N, Nam, Subp_Type);
1885
1886 elsif Is_Access_Type (Subp_Type)
1887 and then Is_Array_Type (Designated_Type (Subp_Type))
1888 then
1889 Is_Indexed :=
1890 Try_Indexed_Call (N, Nam, Designated_Type (Subp_Type));
1891
1892 elsif Is_Access_Type (Subp_Type)
1893 and then Ekind (Designated_Type (Subp_Type)) = E_Subprogram_Type
1894 then
1895 Is_Indexed := Try_Indirect_Call (N, Nam, Subp_Type);
1896 end if;
1897
1898 end if;
1899
1900 Normalize_Actuals (N, Nam, (Report and not Is_Indexed), Norm_OK);
1901
1902 if not Norm_OK then
1903
1904 -- Mismatch in number or names of parameters
1905
1906 if Debug_Flag_E then
1907 Write_Str (" normalization fails in call ");
1908 Write_Int (Int (N));
1909 Write_Str (" with subprogram ");
1910 Write_Int (Int (Nam));
1911 Write_Eol;
1912 end if;
1913
1914 -- If the context expects a function call, discard any interpretation
1915 -- that is a procedure. If the node is not overloaded, leave as is for
1916 -- better error reporting when type mismatch is found.
1917
1918 elsif Nkind (N) = N_Function_Call
1919 and then Is_Overloaded (Name (N))
1920 and then Ekind (Nam) = E_Procedure
1921 then
1922 return;
1923
1924 -- Ditto for function calls in a procedure context.
1925
1926 elsif Nkind (N) = N_Procedure_Call_Statement
1927 and then Is_Overloaded (Name (N))
1928 and then Etype (Nam) /= Standard_Void_Type
1929 then
1930 return;
1931
1932 elsif not Present (Actuals) then
1933
1934 -- If Normalize succeeds, then there are default parameters for
1935 -- all formals.
1936
1937 Set_Name;
1938
1939 elsif Ekind (Nam) = E_Operator then
1940
1941 if Nkind (N) = N_Procedure_Call_Statement then
1942 return;
1943 end if;
1944
1945 -- This can occur when the prefix of the call is an operator
1946 -- name or an expanded name whose selector is an operator name.
1947
1948 Analyze_Operator_Call (N, Nam);
1949
1950 if Etype (N) /= Prev_T then
1951
1952 -- There may be a user-defined operator that hides the
1953 -- current interpretation. We must check for this independently
1954 -- of the analysis of the call with the user-defined operation,
1955 -- because the parameter names may be wrong and yet the hiding
1956 -- takes place. Fixes b34014o.
1957
1958 if Is_Overloaded (Name (N)) then
1959 declare
1960 I : Interp_Index;
1961 It : Interp;
1962
1963 begin
1964 Get_First_Interp (Name (N), I, It);
1965
1966 while Present (It.Nam) loop
1967
1968 if Ekind (It.Nam) /= E_Operator
1969 and then Hides_Op (It.Nam, Nam)
1970 and then
1971 Has_Compatible_Type
1972 (First_Actual (N), Etype (First_Formal (It.Nam)))
1973 and then (No (Next_Actual (First_Actual (N)))
1974 or else Has_Compatible_Type
1975 (Next_Actual (First_Actual (N)),
1976 Etype (Next_Formal (First_Formal (It.Nam)))))
1977 then
1978 Set_Etype (N, Prev_T);
1979 return;
1980 end if;
1981
1982 Get_Next_Interp (I, It);
1983 end loop;
1984 end;
1985 end if;
1986
1987 -- If operator matches formals, record its name on the call.
1988 -- If the operator is overloaded, Resolve will select the
1989 -- correct one from the list of interpretations. The call
1990 -- node itself carries the first candidate.
1991
1992 Set_Entity (Name (N), Nam);
1993 Success := True;
1994
1995 elsif Report and then Etype (N) = Any_Type then
1996 Error_Msg_N ("incompatible arguments for operator", N);
1997 end if;
1998
1999 else
2000 -- Normalize_Actuals has chained the named associations in the
2001 -- correct order of the formals.
2002
2003 Actual := First_Actual (N);
2004 Formal := First_Formal (Nam);
2005
2006 while Present (Actual) and then Present (Formal) loop
2007
2008 if (Nkind (Parent (Actual)) /= N_Parameter_Association
2009 or else Chars (Selector_Name (Parent (Actual))) = Chars (Formal))
2010 then
2011 if Has_Compatible_Type (Actual, Etype (Formal)) then
2012 Next_Actual (Actual);
2013 Next_Formal (Formal);
2014
2015 else
2016 if Debug_Flag_E then
2017 Write_Str (" type checking fails in call ");
2018 Write_Int (Int (N));
2019 Write_Str (" with formal ");
2020 Write_Int (Int (Formal));
2021 Write_Str (" in subprogram ");
2022 Write_Int (Int (Nam));
2023 Write_Eol;
2024 end if;
2025
2026 if Report and not Is_Indexed then
2027
2028 Wrong_Type (Actual, Etype (Formal));
2029
2030 if Nkind (Actual) = N_Op_Eq
2031 and then Nkind (Left_Opnd (Actual)) = N_Identifier
2032 then
2033 Formal := First_Formal (Nam);
2034
2035 while Present (Formal) loop
2036
2037 if Chars (Left_Opnd (Actual)) = Chars (Formal) then
2038 Error_Msg_N
2039 ("possible misspelling of `=>`!", Actual);
2040 exit;
2041 end if;
2042
2043 Next_Formal (Formal);
2044 end loop;
2045 end if;
2046
2047 if All_Errors_Mode then
2048 Error_Msg_Sloc := Sloc (Nam);
2049
2050 if Is_Overloadable (Nam)
2051 and then Present (Alias (Nam))
2052 and then not Comes_From_Source (Nam)
2053 then
2054 Error_Msg_NE
2055 (" ==> in call to &#(inherited)!", Actual, Nam);
2056 else
2057 Error_Msg_NE (" ==> in call to &#!", Actual, Nam);
2058 end if;
2059 end if;
2060 end if;
2061
2062 return;
2063 end if;
2064
2065 else
2066 -- Normalize_Actuals has verified that a default value exists
2067 -- for this formal. Current actual names a subsequent formal.
2068
2069 Next_Formal (Formal);
2070 end if;
2071 end loop;
2072
2073 -- On exit, all actuals match.
2074
2075 Set_Name;
2076 end if;
2077 end Analyze_One_Call;
2078
2079 ----------------------------
2080 -- Analyze_Operator_Call --
2081 ----------------------------
2082
2083 procedure Analyze_Operator_Call (N : Node_Id; Op_Id : Entity_Id) is
2084 Op_Name : constant Name_Id := Chars (Op_Id);
2085 Act1 : constant Node_Id := First_Actual (N);
2086 Act2 : constant Node_Id := Next_Actual (Act1);
2087
2088 begin
2089 if Present (Act2) then
2090
2091 -- Maybe binary operators
2092
2093 if Present (Next_Actual (Act2)) then
2094
2095 -- Too many actuals for an operator
2096
2097 return;
2098
2099 elsif Op_Name = Name_Op_Add
2100 or else Op_Name = Name_Op_Subtract
2101 or else Op_Name = Name_Op_Multiply
2102 or else Op_Name = Name_Op_Divide
2103 or else Op_Name = Name_Op_Mod
2104 or else Op_Name = Name_Op_Rem
2105 or else Op_Name = Name_Op_Expon
2106 then
2107 Find_Arithmetic_Types (Act1, Act2, Op_Id, N);
2108
2109 elsif Op_Name = Name_Op_And
2110 or else Op_Name = Name_Op_Or
2111 or else Op_Name = Name_Op_Xor
2112 then
2113 Find_Boolean_Types (Act1, Act2, Op_Id, N);
2114
2115 elsif Op_Name = Name_Op_Lt
2116 or else Op_Name = Name_Op_Le
2117 or else Op_Name = Name_Op_Gt
2118 or else Op_Name = Name_Op_Ge
2119 then
2120 Find_Comparison_Types (Act1, Act2, Op_Id, N);
2121
2122 elsif Op_Name = Name_Op_Eq
2123 or else Op_Name = Name_Op_Ne
2124 then
2125 Find_Equality_Types (Act1, Act2, Op_Id, N);
2126
2127 elsif Op_Name = Name_Op_Concat then
2128 Find_Concatenation_Types (Act1, Act2, Op_Id, N);
2129
2130 -- Is this else null correct, or should it be an abort???
2131
2132 else
2133 null;
2134 end if;
2135
2136 else
2137 -- Unary operators
2138
2139 if Op_Name = Name_Op_Subtract or else
2140 Op_Name = Name_Op_Add or else
2141 Op_Name = Name_Op_Abs
2142 then
2143 Find_Unary_Types (Act1, Op_Id, N);
2144
2145 elsif
2146 Op_Name = Name_Op_Not
2147 then
2148 Find_Negation_Types (Act1, Op_Id, N);
2149
2150 -- Is this else null correct, or should it be an abort???
2151
2152 else
2153 null;
2154 end if;
2155 end if;
2156 end Analyze_Operator_Call;
2157
2158 -------------------------------------------
2159 -- Analyze_Overloaded_Selected_Component --
2160 -------------------------------------------
2161
2162 procedure Analyze_Overloaded_Selected_Component (N : Node_Id) is
2163 Comp : Entity_Id;
2164 Nam : Node_Id := Prefix (N);
2165 Sel : Node_Id := Selector_Name (N);
2166 I : Interp_Index;
2167 It : Interp;
2168 T : Entity_Id;
2169
2170 begin
2171 Get_First_Interp (Nam, I, It);
2172
2173 Set_Etype (Sel, Any_Type);
2174
2175 while Present (It.Typ) loop
2176 if Is_Access_Type (It.Typ) then
2177 T := Designated_Type (It.Typ);
07fc65c4
GB
2178
2179 if Warn_On_Dereference then
2180 Error_Msg_N ("?implicit dereference", N);
2181 end if;
2182
996ae0b0
RK
2183 else
2184 T := It.Typ;
2185 end if;
2186
2187 if Is_Record_Type (T) then
2188 Comp := First_Entity (T);
2189
2190 while Present (Comp) loop
2191
2192 if Chars (Comp) = Chars (Sel)
2193 and then Is_Visible_Component (Comp)
2194 then
2195 Set_Entity_With_Style_Check (Sel, Comp);
2196 Generate_Reference (Comp, Sel);
2197
2198 Set_Etype (Sel, Etype (Comp));
2199 Add_One_Interp (N, Etype (Comp), Etype (Comp));
2200
2201 -- This also specifies a candidate to resolve the name.
2202 -- Further overloading will be resolved from context.
2203
2204 Set_Etype (Nam, It.Typ);
2205 end if;
2206
2207 Next_Entity (Comp);
2208 end loop;
2209
2210 elsif Is_Concurrent_Type (T) then
2211 Comp := First_Entity (T);
2212
2213 while Present (Comp)
2214 and then Comp /= First_Private_Entity (T)
2215 loop
2216 if Chars (Comp) = Chars (Sel) then
2217 if Is_Overloadable (Comp) then
2218 Add_One_Interp (Sel, Comp, Etype (Comp));
2219 else
2220 Set_Entity_With_Style_Check (Sel, Comp);
2221 Generate_Reference (Comp, Sel);
2222 end if;
2223
2224 Set_Etype (Sel, Etype (Comp));
2225 Set_Etype (N, Etype (Comp));
2226 Set_Etype (Nam, It.Typ);
2227
2228 -- For access type case, introduce explicit deference for
2229 -- more uniform treatment of entry calls.
2230
2231 if Is_Access_Type (Etype (Nam)) then
2232 Insert_Explicit_Dereference (Nam);
07fc65c4
GB
2233
2234 if Warn_On_Dereference then
2235 Error_Msg_N ("?implicit dereference", N);
2236 end if;
996ae0b0
RK
2237 end if;
2238 end if;
2239
2240 Next_Entity (Comp);
2241 end loop;
2242
2243 Set_Is_Overloaded (N, Is_Overloaded (Sel));
996ae0b0
RK
2244 end if;
2245
2246 Get_Next_Interp (I, It);
2247 end loop;
2248
2249 if Etype (N) = Any_Type then
2250 Error_Msg_NE ("undefined selector& for overloaded prefix", N, Sel);
2251 Set_Entity (Sel, Any_Id);
2252 Set_Etype (Sel, Any_Type);
2253 end if;
2254
2255 end Analyze_Overloaded_Selected_Component;
2256
2257 ----------------------------------
2258 -- Analyze_Qualified_Expression --
2259 ----------------------------------
2260
2261 procedure Analyze_Qualified_Expression (N : Node_Id) is
2262 Mark : constant Entity_Id := Subtype_Mark (N);
2263 T : Entity_Id;
2264
2265 begin
2266 Set_Etype (N, Any_Type);
2267 Find_Type (Mark);
2268 T := Entity (Mark);
2269
2270 if T = Any_Type then
2271 return;
2272 end if;
2273 Check_Fully_Declared (T, N);
2274
2275 Analyze_Expression (Expression (N));
2276 Set_Etype (N, T);
2277 end Analyze_Qualified_Expression;
2278
2279 -------------------
2280 -- Analyze_Range --
2281 -------------------
2282
2283 procedure Analyze_Range (N : Node_Id) is
2284 L : constant Node_Id := Low_Bound (N);
2285 H : constant Node_Id := High_Bound (N);
2286 I1, I2 : Interp_Index;
2287 It1, It2 : Interp;
2288
2289 procedure Check_Common_Type (T1, T2 : Entity_Id);
2290 -- Verify the compatibility of two types, and choose the
2291 -- non universal one if the other is universal.
2292
2293 procedure Check_High_Bound (T : Entity_Id);
2294 -- Test one interpretation of the low bound against all those
2295 -- of the high bound.
2296
2297 -----------------------
2298 -- Check_Common_Type --
2299 -----------------------
2300
2301 procedure Check_Common_Type (T1, T2 : Entity_Id) is
2302 begin
2303 if Covers (T1, T2) or else Covers (T2, T1) then
2304 if T1 = Universal_Integer
2305 or else T1 = Universal_Real
2306 or else T1 = Any_Character
2307 then
2308 Add_One_Interp (N, Base_Type (T2), Base_Type (T2));
2309
2310 elsif (T1 = T2) then
2311 Add_One_Interp (N, T1, T1);
2312
2313 else
2314 Add_One_Interp (N, Base_Type (T1), Base_Type (T1));
2315 end if;
2316 end if;
2317 end Check_Common_Type;
2318
2319 ----------------------
2320 -- Check_High_Bound --
2321 ----------------------
2322
2323 procedure Check_High_Bound (T : Entity_Id) is
2324 begin
2325 if not Is_Overloaded (H) then
2326 Check_Common_Type (T, Etype (H));
2327 else
2328 Get_First_Interp (H, I2, It2);
2329
2330 while Present (It2.Typ) loop
2331 Check_Common_Type (T, It2.Typ);
2332 Get_Next_Interp (I2, It2);
2333 end loop;
2334 end if;
2335 end Check_High_Bound;
2336
2337 -- Start of processing for Analyze_Range
2338
2339 begin
2340 Set_Etype (N, Any_Type);
2341 Analyze_Expression (L);
2342 Analyze_Expression (H);
2343
2344 if Etype (L) = Any_Type or else Etype (H) = Any_Type then
2345 return;
2346
2347 else
2348 if not Is_Overloaded (L) then
2349 Check_High_Bound (Etype (L));
2350 else
2351 Get_First_Interp (L, I1, It1);
2352
2353 while Present (It1.Typ) loop
2354 Check_High_Bound (It1.Typ);
2355 Get_Next_Interp (I1, It1);
2356 end loop;
2357 end if;
2358
2359 -- If result is Any_Type, then we did not find a compatible pair
2360
2361 if Etype (N) = Any_Type then
2362 Error_Msg_N ("incompatible types in range ", N);
2363 end if;
2364 end if;
2365 end Analyze_Range;
2366
2367 -----------------------
2368 -- Analyze_Reference --
2369 -----------------------
2370
2371 procedure Analyze_Reference (N : Node_Id) is
2372 P : constant Node_Id := Prefix (N);
2373 Acc_Type : Entity_Id;
2374
2375 begin
2376 Analyze (P);
2377 Acc_Type := Create_Itype (E_Allocator_Type, N);
2378 Set_Etype (Acc_Type, Acc_Type);
2379 Init_Size_Align (Acc_Type);
2380 Set_Directly_Designated_Type (Acc_Type, Etype (P));
2381 Set_Etype (N, Acc_Type);
2382 end Analyze_Reference;
2383
2384 --------------------------------
2385 -- Analyze_Selected_Component --
2386 --------------------------------
2387
2388 -- Prefix is a record type or a task or protected type. In the
2389 -- later case, the selector must denote a visible entry.
2390
2391 procedure Analyze_Selected_Component (N : Node_Id) is
2392 Name : constant Node_Id := Prefix (N);
2393 Sel : constant Node_Id := Selector_Name (N);
2394 Comp : Entity_Id;
2395 Entity_List : Entity_Id;
2396 Prefix_Type : Entity_Id;
2397 Act_Decl : Node_Id;
2398 In_Scope : Boolean;
2399 Parent_N : Node_Id;
2400
2401 -- Start of processing for Analyze_Selected_Component
2402
2403 begin
2404 Set_Etype (N, Any_Type);
2405
2406 if Is_Overloaded (Name) then
2407 Analyze_Overloaded_Selected_Component (N);
2408 return;
2409
2410 elsif Etype (Name) = Any_Type then
2411 Set_Entity (Sel, Any_Id);
2412 Set_Etype (Sel, Any_Type);
2413 return;
2414
2415 else
2416 -- Function calls that are prefixes of selected components must be
2417 -- fully resolved in case we need to build an actual subtype, or
2418 -- do some other operation requiring a fully resolved prefix.
2419
2420 -- Note: Resolving all Nkinds of nodes here doesn't work.
2421 -- (Breaks 2129-008) ???.
2422
2423 if Nkind (Name) = N_Function_Call then
2424 Resolve (Name, Etype (Name));
2425 end if;
2426
2427 Prefix_Type := Etype (Name);
2428 end if;
2429
2430 if Is_Access_Type (Prefix_Type) then
07fc65c4
GB
2431
2432 -- A RACW object can never be used as prefix of a selected
2433 -- component since that means it is dereferenced without
2434 -- being a controlling operand of a dispatching operation
2435 -- (RM E.2.2(15)).
2436
996ae0b0
RK
2437 if Is_Remote_Access_To_Class_Wide_Type (Prefix_Type)
2438 and then Comes_From_Source (N)
2439 then
996ae0b0
RK
2440 Error_Msg_N
2441 ("invalid dereference of a remote access to class-wide value",
2442 N);
07fc65c4
GB
2443
2444 -- Normal case of selected component applied to access type
2445
2446 else
2447 if Warn_On_Dereference then
2448 Error_Msg_N ("?implicit dereference", N);
2449 end if;
996ae0b0 2450 end if;
07fc65c4 2451
996ae0b0
RK
2452 Prefix_Type := Designated_Type (Prefix_Type);
2453 end if;
2454
2455 if Ekind (Prefix_Type) = E_Private_Subtype then
2456 Prefix_Type := Base_Type (Prefix_Type);
2457 end if;
2458
2459 Entity_List := Prefix_Type;
2460
2461 -- For class-wide types, use the entity list of the root type. This
2462 -- indirection is specially important for private extensions because
2463 -- only the root type get switched (not the class-wide type).
2464
2465 if Is_Class_Wide_Type (Prefix_Type) then
2466 Entity_List := Root_Type (Prefix_Type);
2467 end if;
2468
2469 Comp := First_Entity (Entity_List);
2470
2471 -- If the selector has an original discriminant, the node appears in
2472 -- an instance. Replace the discriminant with the corresponding one
2473 -- in the current discriminated type. For nested generics, this must
2474 -- be done transitively, so note the new original discriminant.
2475
2476 if Nkind (Sel) = N_Identifier
2477 and then Present (Original_Discriminant (Sel))
2478 then
2479 Comp := Find_Corresponding_Discriminant (Sel, Prefix_Type);
2480
2481 -- Mark entity before rewriting, for completeness and because
2482 -- subsequent semantic checks might examine the original node.
2483
2484 Set_Entity (Sel, Comp);
2485 Rewrite (Selector_Name (N),
2486 New_Occurrence_Of (Comp, Sloc (N)));
2487 Set_Original_Discriminant (Selector_Name (N), Comp);
2488 Set_Etype (N, Etype (Comp));
2489
2490 if Is_Access_Type (Etype (Name)) then
2491 Insert_Explicit_Dereference (Name);
07fc65c4
GB
2492
2493 if Warn_On_Dereference then
2494 Error_Msg_N ("?implicit dereference", N);
2495 end if;
996ae0b0
RK
2496 end if;
2497
2498 elsif Is_Record_Type (Prefix_Type) then
2499
2500 -- Find component with given name
2501
2502 while Present (Comp) loop
2503
2504 if Chars (Comp) = Chars (Sel)
2505 and then Is_Visible_Component (Comp)
2506 then
2507 Set_Entity_With_Style_Check (Sel, Comp);
2508 Generate_Reference (Comp, Sel);
2509
2510 Set_Etype (Sel, Etype (Comp));
2511
2512 if Ekind (Comp) = E_Discriminant then
2513 if Is_Unchecked_Union (Prefix_Type) then
2514 Error_Msg_N
2515 ("cannot reference discriminant of Unchecked_Union",
2516 Sel);
2517 end if;
2518
2519 if Is_Generic_Type (Prefix_Type)
2520 or else
2521 Is_Generic_Type (Root_Type (Prefix_Type))
2522 then
2523 Set_Original_Discriminant (Sel, Comp);
2524 end if;
2525 end if;
2526
2527 -- Resolve the prefix early otherwise it is not possible to
2528 -- build the actual subtype of the component: it may need
2529 -- to duplicate this prefix and duplication is only allowed
2530 -- on fully resolved expressions.
2531
2532 Resolve (Name, Etype (Name));
2533
2534 -- We never need an actual subtype for the case of a selection
2535 -- for a indexed component of a non-packed array, since in
2536 -- this case gigi generates all the checks and can find the
2537 -- necessary bounds information.
2538
2539 -- We also do not need an actual subtype for the case of
2540 -- a first, last, length, or range attribute applied to a
2541 -- non-packed array, since gigi can again get the bounds in
2542 -- these cases (gigi cannot handle the packed case, since it
2543 -- has the bounds of the packed array type, not the original
2544 -- bounds of the type). However, if the prefix is itself a
2545 -- selected component, as in a.b.c (i), gigi may regard a.b.c
2546 -- as a dynamic-sized temporary, so we do generate an actual
2547 -- subtype for this case.
2548
2549 Parent_N := Parent (N);
2550
2551 if not Is_Packed (Etype (Comp))
2552 and then
2553 ((Nkind (Parent_N) = N_Indexed_Component
2554 and then Nkind (Name) /= N_Selected_Component)
2555 or else
2556 (Nkind (Parent_N) = N_Attribute_Reference
2557 and then (Attribute_Name (Parent_N) = Name_First
2558 or else
2559 Attribute_Name (Parent_N) = Name_Last
2560 or else
2561 Attribute_Name (Parent_N) = Name_Length
2562 or else
2563 Attribute_Name (Parent_N) = Name_Range)))
2564 then
2565 Set_Etype (N, Etype (Comp));
2566
2567 -- In all other cases, we currently build an actual subtype. It
2568 -- seems likely that many of these cases can be avoided, but
2569 -- right now, the front end makes direct references to the
2570 -- bounds (e.g. in egnerating a length check), and if we do
2571 -- not make an actual subtype, we end up getting a direct
2572 -- reference to a discriminant which will not do.
2573
2574 else
2575 Act_Decl :=
2576 Build_Actual_Subtype_Of_Component (Etype (Comp), N);
2577 Insert_Action (N, Act_Decl);
2578
2579 if No (Act_Decl) then
2580 Set_Etype (N, Etype (Comp));
2581
2582 else
2583 -- Component type depends on discriminants. Enter the
2584 -- main attributes of the subtype.
2585
2586 declare
2587 Subt : Entity_Id := Defining_Identifier (Act_Decl);
2588
2589 begin
2590 Set_Etype (Subt, Base_Type (Etype (Comp)));
2591 Set_Ekind (Subt, Ekind (Etype (Comp)));
2592 Set_Etype (N, Subt);
2593 end;
2594 end if;
2595 end if;
2596
2597 return;
2598 end if;
2599
2600 Next_Entity (Comp);
2601 end loop;
2602
2603 elsif Is_Private_Type (Prefix_Type) then
2604
2605 -- Allow access only to discriminants of the type. If the
2606 -- type has no full view, gigi uses the parent type for
2607 -- the components, so we do the same here.
2608
2609 if No (Full_View (Prefix_Type)) then
2610 Entity_List := Root_Type (Base_Type (Prefix_Type));
2611 Comp := First_Entity (Entity_List);
2612 end if;
2613
2614 while Present (Comp) loop
2615
2616 if Chars (Comp) = Chars (Sel) then
2617 if Ekind (Comp) = E_Discriminant then
2618 Set_Entity_With_Style_Check (Sel, Comp);
2619 Generate_Reference (Comp, Sel);
2620
2621 Set_Etype (Sel, Etype (Comp));
2622 Set_Etype (N, Etype (Comp));
2623
2624 if Is_Generic_Type (Prefix_Type)
2625 or else
2626 Is_Generic_Type (Root_Type (Prefix_Type))
2627 then
2628 Set_Original_Discriminant (Sel, Comp);
2629 end if;
2630
2631 else
2632 Error_Msg_NE
2633 ("invisible selector for }",
2634 N, First_Subtype (Prefix_Type));
2635 Set_Entity (Sel, Any_Id);
2636 Set_Etype (N, Any_Type);
2637 end if;
2638
2639 return;
2640 end if;
2641
2642 Next_Entity (Comp);
2643 end loop;
2644
2645 elsif Is_Concurrent_Type (Prefix_Type) then
2646
2647 -- Prefix is concurrent type. Find visible operation with given name
2648 -- For a task, this can only include entries or discriminants if
2649 -- the task type is not an enclosing scope. If it is an enclosing
2650 -- scope (e.g. in an inner task) then all entities are visible, but
2651 -- the prefix must denote the enclosing scope, i.e. can only be
2652 -- a direct name or an expanded name.
2653
2654 Set_Etype (Sel, Any_Type);
2655 In_Scope := In_Open_Scopes (Prefix_Type);
2656
2657 while Present (Comp) loop
2658 if Chars (Comp) = Chars (Sel) then
2659 if Is_Overloadable (Comp) then
2660 Add_One_Interp (Sel, Comp, Etype (Comp));
2661
2662 elsif Ekind (Comp) = E_Discriminant
2663 or else Ekind (Comp) = E_Entry_Family
2664 or else (In_Scope
2665 and then Is_Entity_Name (Name))
2666 then
2667 Set_Entity_With_Style_Check (Sel, Comp);
2668 Generate_Reference (Comp, Sel);
2669
2670 else
2671 goto Next_Comp;
2672 end if;
2673
2674 Set_Etype (Sel, Etype (Comp));
2675 Set_Etype (N, Etype (Comp));
2676
2677 if Ekind (Comp) = E_Discriminant then
2678 Set_Original_Discriminant (Sel, Comp);
2679 end if;
2680
2681 -- For access type case, introduce explicit deference for
2682 -- more uniform treatment of entry calls.
2683
2684 if Is_Access_Type (Etype (Name)) then
2685 Insert_Explicit_Dereference (Name);
07fc65c4
GB
2686
2687 if Warn_On_Dereference then
2688 Error_Msg_N ("?implicit dereference", N);
2689 end if;
996ae0b0
RK
2690 end if;
2691 end if;
2692
2693 <<Next_Comp>>
2694 Next_Entity (Comp);
2695 exit when not In_Scope
2696 and then Comp = First_Private_Entity (Prefix_Type);
2697 end loop;
2698
2699 Set_Is_Overloaded (N, Is_Overloaded (Sel));
2700
2701 else
2702 -- Invalid prefix
2703
2704 Error_Msg_NE ("invalid prefix in selected component&", N, Sel);
2705 end if;
2706
2707 -- If N still has no type, the component is not defined in the prefix.
2708
2709 if Etype (N) = Any_Type then
2710
2711 -- If the prefix is a single concurrent object, use its name in
2712 -- the error message, rather than that of its anonymous type.
2713
2714 if Is_Concurrent_Type (Prefix_Type)
2715 and then Is_Internal_Name (Chars (Prefix_Type))
2716 and then not Is_Derived_Type (Prefix_Type)
2717 and then Is_Entity_Name (Name)
2718 then
2719
2720 Error_Msg_Node_2 := Entity (Name);
2721 Error_Msg_NE ("no selector& for&", N, Sel);
2722
2723 Check_Misspelled_Selector (Entity_List, Sel);
2724
de76a39c
GB
2725 elsif Is_Generic_Type (Prefix_Type)
2726 and then Ekind (Prefix_Type) = E_Record_Type_With_Private
07fc65c4 2727 and then Prefix_Type /= Etype (Prefix_Type)
de76a39c
GB
2728 and then Is_Record_Type (Etype (Prefix_Type))
2729 then
2730 -- If this is a derived formal type, the parent may have a
2731 -- different visibility at this point. Try for an inherited
2732 -- component before reporting an error.
2733
2734 Set_Etype (Prefix (N), Etype (Prefix_Type));
2735 Analyze_Selected_Component (N);
2736 return;
2737
996ae0b0
RK
2738 else
2739 if Ekind (Prefix_Type) = E_Record_Subtype then
2740
2741 -- Check whether this is a component of the base type
2742 -- which is absent from a statically constrained subtype.
2743 -- This will raise constraint error at run-time, but is
2744 -- not a compile-time error. When the selector is illegal
2745 -- for base type as well fall through and generate a
2746 -- compilation error anyway.
2747
2748 Comp := First_Component (Base_Type (Prefix_Type));
2749
2750 while Present (Comp) loop
2751
2752 if Chars (Comp) = Chars (Sel)
2753 and then Is_Visible_Component (Comp)
2754 then
2755 Set_Entity_With_Style_Check (Sel, Comp);
2756 Generate_Reference (Comp, Sel);
2757 Set_Etype (Sel, Etype (Comp));
2758 Set_Etype (N, Etype (Comp));
2759
2760 -- Emit appropriate message. Gigi will replace the
2761 -- node subsequently with the appropriate Raise.
2762
2763 Apply_Compile_Time_Constraint_Error
2764 (N, "component not present in }?",
07fc65c4 2765 CE_Discriminant_Check_Failed,
996ae0b0
RK
2766 Ent => Prefix_Type, Rep => False);
2767 Set_Raises_Constraint_Error (N);
2768 return;
2769 end if;
2770
2771 Next_Component (Comp);
2772 end loop;
2773
2774 end if;
2775
2776 Error_Msg_Node_2 := First_Subtype (Prefix_Type);
2777 Error_Msg_NE ("no selector& for}", N, Sel);
2778
2779 Check_Misspelled_Selector (Entity_List, Sel);
2780
2781 end if;
2782
2783 Set_Entity (Sel, Any_Id);
2784 Set_Etype (Sel, Any_Type);
2785 end if;
2786 end Analyze_Selected_Component;
2787
2788 ---------------------------
2789 -- Analyze_Short_Circuit --
2790 ---------------------------
2791
2792 procedure Analyze_Short_Circuit (N : Node_Id) is
2793 L : constant Node_Id := Left_Opnd (N);
2794 R : constant Node_Id := Right_Opnd (N);
2795 Ind : Interp_Index;
2796 It : Interp;
2797
2798 begin
2799 Analyze_Expression (L);
2800 Analyze_Expression (R);
2801 Set_Etype (N, Any_Type);
2802
2803 if not Is_Overloaded (L) then
2804
2805 if Root_Type (Etype (L)) = Standard_Boolean
2806 and then Has_Compatible_Type (R, Etype (L))
2807 then
2808 Add_One_Interp (N, Etype (L), Etype (L));
2809 end if;
2810
2811 else
2812 Get_First_Interp (L, Ind, It);
2813
2814 while Present (It.Typ) loop
2815 if Root_Type (It.Typ) = Standard_Boolean
2816 and then Has_Compatible_Type (R, It.Typ)
2817 then
2818 Add_One_Interp (N, It.Typ, It.Typ);
2819 end if;
2820
2821 Get_Next_Interp (Ind, It);
2822 end loop;
2823 end if;
2824
2825 -- Here we have failed to find an interpretation. Clearly we
2826 -- know that it is not the case that both operands can have
2827 -- an interpretation of Boolean, but this is by far the most
2828 -- likely intended interpretation. So we simply resolve both
2829 -- operands as Booleans, and at least one of these resolutions
2830 -- will generate an error message, and we do not need to give
2831 -- a further error message on the short circuit operation itself.
2832
2833 if Etype (N) = Any_Type then
2834 Resolve (L, Standard_Boolean);
2835 Resolve (R, Standard_Boolean);
2836 Set_Etype (N, Standard_Boolean);
2837 end if;
2838 end Analyze_Short_Circuit;
2839
2840 -------------------
2841 -- Analyze_Slice --
2842 -------------------
2843
2844 procedure Analyze_Slice (N : Node_Id) is
2845 P : constant Node_Id := Prefix (N);
2846 D : constant Node_Id := Discrete_Range (N);
2847 Array_Type : Entity_Id;
2848
2849 procedure Analyze_Overloaded_Slice;
2850 -- If the prefix is overloaded, select those interpretations that
2851 -- yield a one-dimensional array type.
2852
2853 procedure Analyze_Overloaded_Slice is
2854 I : Interp_Index;
2855 It : Interp;
2856 Typ : Entity_Id;
2857
2858 begin
2859 Set_Etype (N, Any_Type);
2860 Get_First_Interp (P, I, It);
2861
2862 while Present (It.Nam) loop
2863 Typ := It.Typ;
2864
2865 if Is_Access_Type (Typ) then
2866 Typ := Designated_Type (Typ);
07fc65c4
GB
2867
2868 if Warn_On_Dereference then
2869 Error_Msg_N ("?implicit dereference", N);
2870 end if;
996ae0b0
RK
2871 end if;
2872
2873 if Is_Array_Type (Typ)
2874 and then Number_Dimensions (Typ) = 1
2875 and then Has_Compatible_Type (D, Etype (First_Index (Typ)))
2876 then
2877 Add_One_Interp (N, Typ, Typ);
2878 end if;
2879
2880 Get_Next_Interp (I, It);
2881 end loop;
2882
2883 if Etype (N) = Any_Type then
2884 Error_Msg_N ("expect array type in prefix of slice", N);
2885 end if;
2886 end Analyze_Overloaded_Slice;
2887
2888 -- Start of processing for Analyze_Slice
2889
2890 begin
2891 -- Analyze the prefix if not done already
2892
2893 if No (Etype (P)) then
2894 Analyze (P);
2895 end if;
2896
2897 Analyze (D);
2898
2899 if Is_Overloaded (P) then
2900 Analyze_Overloaded_Slice;
2901
2902 else
2903 Array_Type := Etype (P);
2904 Set_Etype (N, Any_Type);
2905
2906 if Is_Access_Type (Array_Type) then
2907 Array_Type := Designated_Type (Array_Type);
07fc65c4
GB
2908
2909 if Warn_On_Dereference then
2910 Error_Msg_N ("?implicit dereference", N);
2911 end if;
996ae0b0
RK
2912 end if;
2913
2914 if not Is_Array_Type (Array_Type) then
2915 Wrong_Type (P, Any_Array);
2916
2917 elsif Number_Dimensions (Array_Type) > 1 then
2918 Error_Msg_N
2919 ("type is not one-dimensional array in slice prefix", N);
2920
2921 elsif not
2922 Has_Compatible_Type (D, Etype (First_Index (Array_Type)))
2923 then
2924 Wrong_Type (D, Etype (First_Index (Array_Type)));
2925
2926 else
2927 Set_Etype (N, Array_Type);
2928 end if;
2929 end if;
2930 end Analyze_Slice;
2931
2932 -----------------------------
2933 -- Analyze_Type_Conversion --
2934 -----------------------------
2935
2936 procedure Analyze_Type_Conversion (N : Node_Id) is
2937 Expr : constant Node_Id := Expression (N);
2938 T : Entity_Id;
2939
2940 begin
2941 -- If Conversion_OK is set, then the Etype is already set, and the
2942 -- only processing required is to analyze the expression. This is
2943 -- used to construct certain "illegal" conversions which are not
2944 -- allowed by Ada semantics, but can be handled OK by Gigi, see
2945 -- Sinfo for further details.
2946
2947 if Conversion_OK (N) then
2948 Analyze (Expr);
2949 return;
2950 end if;
2951
2952 -- Otherwise full type analysis is required, as well as some semantic
2953 -- checks to make sure the argument of the conversion is appropriate.
2954
2955 Find_Type (Subtype_Mark (N));
2956 T := Entity (Subtype_Mark (N));
2957 Set_Etype (N, T);
2958 Check_Fully_Declared (T, N);
2959 Analyze_Expression (Expr);
2960 Validate_Remote_Type_Type_Conversion (N);
2961
2962 -- Only remaining step is validity checks on the argument. These
2963 -- are skipped if the conversion does not come from the source.
2964
2965 if not Comes_From_Source (N) then
2966 return;
2967
2968 elsif Nkind (Expr) = N_Null then
2969 Error_Msg_N ("argument of conversion cannot be null", N);
2970 Error_Msg_N ("\use qualified expression instead", N);
2971 Set_Etype (N, Any_Type);
2972
2973 elsif Nkind (Expr) = N_Aggregate then
2974 Error_Msg_N ("argument of conversion cannot be aggregate", N);
2975 Error_Msg_N ("\use qualified expression instead", N);
2976
2977 elsif Nkind (Expr) = N_Allocator then
2978 Error_Msg_N ("argument of conversion cannot be an allocator", N);
2979 Error_Msg_N ("\use qualified expression instead", N);
2980
2981 elsif Nkind (Expr) = N_String_Literal then
2982 Error_Msg_N ("argument of conversion cannot be string literal", N);
2983 Error_Msg_N ("\use qualified expression instead", N);
2984
2985 elsif Nkind (Expr) = N_Character_Literal then
2986 if Ada_83 then
2987 Resolve (Expr, T);
2988 else
2989 Error_Msg_N ("argument of conversion cannot be character literal",
2990 N);
2991 Error_Msg_N ("\use qualified expression instead", N);
2992 end if;
2993
2994 elsif Nkind (Expr) = N_Attribute_Reference
2995 and then
2996 (Attribute_Name (Expr) = Name_Access or else
2997 Attribute_Name (Expr) = Name_Unchecked_Access or else
2998 Attribute_Name (Expr) = Name_Unrestricted_Access)
2999 then
3000 Error_Msg_N ("argument of conversion cannot be access", N);
3001 Error_Msg_N ("\use qualified expression instead", N);
3002 end if;
3003
3004 end Analyze_Type_Conversion;
3005
3006 ----------------------
3007 -- Analyze_Unary_Op --
3008 ----------------------
3009
3010 procedure Analyze_Unary_Op (N : Node_Id) is
3011 R : constant Node_Id := Right_Opnd (N);
3012 Op_Id : Entity_Id := Entity (N);
3013
3014 begin
3015 Set_Etype (N, Any_Type);
3016 Candidate_Type := Empty;
3017
3018 Analyze_Expression (R);
3019
3020 if Present (Op_Id) then
3021 if Ekind (Op_Id) = E_Operator then
3022 Find_Unary_Types (R, Op_Id, N);
3023 else
3024 Add_One_Interp (N, Op_Id, Etype (Op_Id));
3025 end if;
3026
3027 else
3028 Op_Id := Get_Name_Entity_Id (Chars (N));
3029
3030 while Present (Op_Id) loop
3031
3032 if Ekind (Op_Id) = E_Operator then
3033 if No (Next_Entity (First_Entity (Op_Id))) then
3034 Find_Unary_Types (R, Op_Id, N);
3035 end if;
3036
3037 elsif Is_Overloadable (Op_Id) then
3038 Analyze_User_Defined_Unary_Op (N, Op_Id);
3039 end if;
3040
3041 Op_Id := Homonym (Op_Id);
3042 end loop;
3043 end if;
3044
3045 Operator_Check (N);
3046 end Analyze_Unary_Op;
3047
3048 ----------------------------------
3049 -- Analyze_Unchecked_Expression --
3050 ----------------------------------
3051
3052 procedure Analyze_Unchecked_Expression (N : Node_Id) is
3053 begin
3054 Analyze (Expression (N), Suppress => All_Checks);
3055 Set_Etype (N, Etype (Expression (N)));
3056 Save_Interps (Expression (N), N);
3057 end Analyze_Unchecked_Expression;
3058
3059 ---------------------------------------
3060 -- Analyze_Unchecked_Type_Conversion --
3061 ---------------------------------------
3062
3063 procedure Analyze_Unchecked_Type_Conversion (N : Node_Id) is
3064 begin
3065 Find_Type (Subtype_Mark (N));
3066 Analyze_Expression (Expression (N));
3067 Set_Etype (N, Entity (Subtype_Mark (N)));
3068 end Analyze_Unchecked_Type_Conversion;
3069
3070 ------------------------------------
3071 -- Analyze_User_Defined_Binary_Op --
3072 ------------------------------------
3073
3074 procedure Analyze_User_Defined_Binary_Op
3075 (N : Node_Id;
3076 Op_Id : Entity_Id)
3077 is
3078 begin
3079 -- Only do analysis if the operator Comes_From_Source, since otherwise
3080 -- the operator was generated by the expander, and all such operators
3081 -- always refer to the operators in package Standard.
3082
3083 if Comes_From_Source (N) then
3084 declare
3085 F1 : constant Entity_Id := First_Formal (Op_Id);
3086 F2 : constant Entity_Id := Next_Formal (F1);
3087
3088 begin
3089 -- Verify that Op_Id is a visible binary function. Note that since
3090 -- we know Op_Id is overloaded, potentially use visible means use
3091 -- visible for sure (RM 9.4(11)).
3092
3093 if Ekind (Op_Id) = E_Function
3094 and then Present (F2)
3095 and then (Is_Immediately_Visible (Op_Id)
3096 or else Is_Potentially_Use_Visible (Op_Id))
3097 and then Has_Compatible_Type (Left_Opnd (N), Etype (F1))
3098 and then Has_Compatible_Type (Right_Opnd (N), Etype (F2))
3099 then
3100 Add_One_Interp (N, Op_Id, Etype (Op_Id));
3101
3102 if Debug_Flag_E then
3103 Write_Str ("user defined operator ");
3104 Write_Name (Chars (Op_Id));
3105 Write_Str (" on node ");
3106 Write_Int (Int (N));
3107 Write_Eol;
3108 end if;
3109 end if;
3110 end;
3111 end if;
3112 end Analyze_User_Defined_Binary_Op;
3113
3114 -----------------------------------
3115 -- Analyze_User_Defined_Unary_Op --
3116 -----------------------------------
3117
3118 procedure Analyze_User_Defined_Unary_Op
3119 (N : Node_Id;
3120 Op_Id : Entity_Id)
3121 is
3122 begin
3123 -- Only do analysis if the operator Comes_From_Source, since otherwise
3124 -- the operator was generated by the expander, and all such operators
3125 -- always refer to the operators in package Standard.
3126
3127 if Comes_From_Source (N) then
3128 declare
3129 F : constant Entity_Id := First_Formal (Op_Id);
3130
3131 begin
3132 -- Verify that Op_Id is a visible unary function. Note that since
3133 -- we know Op_Id is overloaded, potentially use visible means use
3134 -- visible for sure (RM 9.4(11)).
3135
3136 if Ekind (Op_Id) = E_Function
3137 and then No (Next_Formal (F))
3138 and then (Is_Immediately_Visible (Op_Id)
3139 or else Is_Potentially_Use_Visible (Op_Id))
3140 and then Has_Compatible_Type (Right_Opnd (N), Etype (F))
3141 then
3142 Add_One_Interp (N, Op_Id, Etype (Op_Id));
3143 end if;
3144 end;
3145 end if;
3146 end Analyze_User_Defined_Unary_Op;
3147
3148 ---------------------------
3149 -- Check_Arithmetic_Pair --
3150 ---------------------------
3151
3152 procedure Check_Arithmetic_Pair
3153 (T1, T2 : Entity_Id;
3154 Op_Id : Entity_Id;
3155 N : Node_Id)
3156 is
3157 Op_Name : constant Name_Id := Chars (Op_Id);
3158
3159 function Specific_Type (T1, T2 : Entity_Id) return Entity_Id;
3160 -- Get specific type (i.e. non-universal type if there is one)
3161
3162 function Specific_Type (T1, T2 : Entity_Id) return Entity_Id is
3163 begin
3164 if T1 = Universal_Integer or else T1 = Universal_Real then
3165 return Base_Type (T2);
3166 else
3167 return Base_Type (T1);
3168 end if;
3169 end Specific_Type;
3170
3171 -- Start of processing for Check_Arithmetic_Pair
3172
3173 begin
3174 if Op_Name = Name_Op_Add or else Op_Name = Name_Op_Subtract then
3175
3176 if Is_Numeric_Type (T1)
3177 and then Is_Numeric_Type (T2)
3178 and then (Covers (T1, T2) or else Covers (T2, T1))
3179 then
3180 Add_One_Interp (N, Op_Id, Specific_Type (T1, T2));
3181 end if;
3182
3183 elsif Op_Name = Name_Op_Multiply or else Op_Name = Name_Op_Divide then
3184
3185 if Is_Fixed_Point_Type (T1)
3186 and then (Is_Fixed_Point_Type (T2)
3187 or else T2 = Universal_Real)
3188 then
3189 -- If Treat_Fixed_As_Integer is set then the Etype is already set
3190 -- and no further processing is required (this is the case of an
3191 -- operator constructed by Exp_Fixd for a fixed point operation)
3192 -- Otherwise add one interpretation with universal fixed result
3193 -- If the operator is given in functional notation, it comes
3194 -- from source and Fixed_As_Integer cannot apply.
3195
3196 if Nkind (N) not in N_Op
3197 or else not Treat_Fixed_As_Integer (N) then
3198 Add_One_Interp (N, Op_Id, Universal_Fixed);
3199 end if;
3200
3201 elsif Is_Fixed_Point_Type (T2)
3202 and then (Nkind (N) not in N_Op
3203 or else not Treat_Fixed_As_Integer (N))
3204 and then T1 = Universal_Real
3205 then
3206 Add_One_Interp (N, Op_Id, Universal_Fixed);
3207
3208 elsif Is_Numeric_Type (T1)
3209 and then Is_Numeric_Type (T2)
3210 and then (Covers (T1, T2) or else Covers (T2, T1))
3211 then
3212 Add_One_Interp (N, Op_Id, Specific_Type (T1, T2));
3213
3214 elsif Is_Fixed_Point_Type (T1)
3215 and then (Base_Type (T2) = Base_Type (Standard_Integer)
3216 or else T2 = Universal_Integer)
3217 then
3218 Add_One_Interp (N, Op_Id, T1);
3219
3220 elsif T2 = Universal_Real
3221 and then Base_Type (T1) = Base_Type (Standard_Integer)
3222 and then Op_Name = Name_Op_Multiply
3223 then
3224 Add_One_Interp (N, Op_Id, Any_Fixed);
3225
3226 elsif T1 = Universal_Real
3227 and then Base_Type (T2) = Base_Type (Standard_Integer)
3228 then
3229 Add_One_Interp (N, Op_Id, Any_Fixed);
3230
3231 elsif Is_Fixed_Point_Type (T2)
3232 and then (Base_Type (T1) = Base_Type (Standard_Integer)
3233 or else T1 = Universal_Integer)
3234 and then Op_Name = Name_Op_Multiply
3235 then
3236 Add_One_Interp (N, Op_Id, T2);
3237
3238 elsif T1 = Universal_Real and then T2 = Universal_Integer then
3239 Add_One_Interp (N, Op_Id, T1);
3240
3241 elsif T2 = Universal_Real
3242 and then T1 = Universal_Integer
3243 and then Op_Name = Name_Op_Multiply
3244 then
3245 Add_One_Interp (N, Op_Id, T2);
3246 end if;
3247
3248 elsif Op_Name = Name_Op_Mod or else Op_Name = Name_Op_Rem then
3249
3250 -- Note: The fixed-point operands case with Treat_Fixed_As_Integer
3251 -- set does not require any special processing, since the Etype is
3252 -- already set (case of operation constructed by Exp_Fixed).
3253
3254 if Is_Integer_Type (T1)
3255 and then (Covers (T1, T2) or else Covers (T2, T1))
3256 then
3257 Add_One_Interp (N, Op_Id, Specific_Type (T1, T2));
3258 end if;
3259
3260 elsif Op_Name = Name_Op_Expon then
3261
3262 if Is_Numeric_Type (T1)
3263 and then not Is_Fixed_Point_Type (T1)
3264 and then (Base_Type (T2) = Base_Type (Standard_Integer)
3265 or else T2 = Universal_Integer)
3266 then
3267 Add_One_Interp (N, Op_Id, Base_Type (T1));
3268 end if;
3269
3270 else pragma Assert (Nkind (N) in N_Op_Shift);
3271
3272 -- If not one of the predefined operators, the node may be one
3273 -- of the intrinsic functions. Its kind is always specific, and
3274 -- we can use it directly, rather than the name of the operation.
3275
3276 if Is_Integer_Type (T1)
3277 and then (Base_Type (T2) = Base_Type (Standard_Integer)
3278 or else T2 = Universal_Integer)
3279 then
3280 Add_One_Interp (N, Op_Id, Base_Type (T1));
3281 end if;
3282 end if;
3283 end Check_Arithmetic_Pair;
3284
3285 -------------------------------
3286 -- Check_Misspelled_Selector --
3287 -------------------------------
3288
3289 procedure Check_Misspelled_Selector
3290 (Prefix : Entity_Id;
3291 Sel : Node_Id)
3292 is
3293 Max_Suggestions : constant := 2;
3294 Nr_Of_Suggestions : Natural := 0;
3295
3296 Suggestion_1 : Entity_Id := Empty;
3297 Suggestion_2 : Entity_Id := Empty;
3298
3299 Comp : Entity_Id;
3300
3301 begin
3302 -- All the components of the prefix of selector Sel are matched
3303 -- against Sel and a count is maintained of possible misspellings.
3304 -- When at the end of the analysis there are one or two (not more!)
3305 -- possible misspellings, these misspellings will be suggested as
3306 -- possible correction.
3307
3308 if not (Is_Private_Type (Prefix) or Is_Record_Type (Prefix)) then
3309 -- Concurrent types should be handled as well ???
3310 return;
3311 end if;
3312
3313 Get_Name_String (Chars (Sel));
3314
3315 declare
3316 S : constant String (1 .. Name_Len) :=
3317 Name_Buffer (1 .. Name_Len);
3318
3319 begin
3320 Comp := First_Entity (Prefix);
3321
3322 while Nr_Of_Suggestions <= Max_Suggestions
3323 and then Present (Comp)
3324 loop
3325
3326 if Is_Visible_Component (Comp) then
3327 Get_Name_String (Chars (Comp));
3328
3329 if Is_Bad_Spelling_Of (Name_Buffer (1 .. Name_Len), S) then
3330 Nr_Of_Suggestions := Nr_Of_Suggestions + 1;
3331
3332 case Nr_Of_Suggestions is
3333 when 1 => Suggestion_1 := Comp;
3334 when 2 => Suggestion_2 := Comp;
3335 when others => exit;
3336 end case;
3337 end if;
3338 end if;
3339
3340 Comp := Next_Entity (Comp);
3341 end loop;
3342
3343 -- Report at most two suggestions
3344
3345 if Nr_Of_Suggestions = 1 then
3346 Error_Msg_NE ("\possible misspelling of&", Sel, Suggestion_1);
3347
3348 elsif Nr_Of_Suggestions = 2 then
3349 Error_Msg_Node_2 := Suggestion_2;
3350 Error_Msg_NE ("\possible misspelling of& or&",
3351 Sel, Suggestion_1);
3352 end if;
3353 end;
3354 end Check_Misspelled_Selector;
3355
3356 ----------------------
3357 -- Defined_In_Scope --
3358 ----------------------
3359
3360 function Defined_In_Scope (T : Entity_Id; S : Entity_Id) return Boolean
3361 is
3362 S1 : constant Entity_Id := Scope (Base_Type (T));
3363
3364 begin
3365 return S1 = S
3366 or else (S1 = System_Aux_Id and then S = Scope (S1));
3367 end Defined_In_Scope;
3368
3369 -------------------
3370 -- Diagnose_Call --
3371 -------------------
3372
3373 procedure Diagnose_Call (N : Node_Id; Nam : Node_Id) is
3374 Actual : Node_Id;
3375 X : Interp_Index;
3376 It : Interp;
3377 Success : Boolean;
3378
3379 begin
3380 if Extensions_Allowed then
3381 Actual := First_Actual (N);
3382
3383 while Present (Actual) loop
3384 if not Analyzed (Etype (Actual))
3385 and then From_With_Type (Etype (Actual))
3386 then
3387 Error_Msg_Qual_Level := 1;
3388 Error_Msg_NE
3389 ("missing with_clause for scope of imported type&",
3390 Actual, Etype (Actual));
3391 Error_Msg_Qual_Level := 0;
3392 end if;
3393
3394 Next_Actual (Actual);
3395 end loop;
3396 end if;
3397
3398 if All_Errors_Mode then
3399
3400 -- Analyze each candidate call again, with full error reporting
3401 -- for each.
3402
3403 Error_Msg_N ("\no candidate interpretations "
3404 & "match the actuals:!", Nam);
3405
3406 Get_First_Interp (Nam, X, It);
3407
3408 while Present (It.Nam) loop
3409 Analyze_One_Call (N, It.Nam, True, Success);
3410 Get_Next_Interp (X, It);
3411 end loop;
3412
3413 else
3414 if OpenVMS then
3415 Error_Msg_N
3416 ("invalid parameter list in call " &
3417 "('/'R'E'P'O'R'T'_'E'R'R'O'R'S'='F'U'L'L for details)!",
3418 Nam);
3419 else
3420 Error_Msg_N
3421 ("invalid parameter list in call (use -gnatf for details)!",
3422 Nam);
3423 end if;
3424 end if;
3425
3426 if Nkind (N) = N_Function_Call then
3427 Get_First_Interp (Nam, X, It);
3428
3429 while Present (It.Nam) loop
3430 if Ekind (It.Nam) = E_Function
3431 or else Ekind (It.Nam) = E_Operator
3432 then
3433 return;
3434 else
3435 Get_Next_Interp (X, It);
3436 end if;
3437 end loop;
3438
3439 -- If all interpretations are procedures, this deserves a
3440 -- more precise message. Ditto if this appears as the prefix
3441 -- of a selected component, which may be a lexical error.
3442
3443 Error_Msg_N (
3444 "\context requires function call, found procedure name", Nam);
3445
3446 if Nkind (Parent (N)) = N_Selected_Component
3447 and then N = Prefix (Parent (N))
3448 then
3449 Error_Msg_N (
3450 "\period should probably be semicolon", Parent (N));
3451 end if;
3452 end if;
3453 end Diagnose_Call;
3454
3455 ---------------------------
3456 -- Find_Arithmetic_Types --
3457 ---------------------------
3458
3459 procedure Find_Arithmetic_Types
3460 (L, R : Node_Id;
3461 Op_Id : Entity_Id;
3462 N : Node_Id)
3463 is
3464 Index1, Index2 : Interp_Index;
3465 It1, It2 : Interp;
3466
3467 procedure Check_Right_Argument (T : Entity_Id);
3468 -- Check right operand of operator
3469
3470 procedure Check_Right_Argument (T : Entity_Id) is
3471 begin
3472 if not Is_Overloaded (R) then
3473 Check_Arithmetic_Pair (T, Etype (R), Op_Id, N);
3474 else
3475 Get_First_Interp (R, Index2, It2);
3476
3477 while Present (It2.Typ) loop
3478 Check_Arithmetic_Pair (T, It2.Typ, Op_Id, N);
3479 Get_Next_Interp (Index2, It2);
3480 end loop;
3481 end if;
3482 end Check_Right_Argument;
3483
3484 -- Start processing for Find_Arithmetic_Types
3485
3486 begin
3487 if not Is_Overloaded (L) then
3488 Check_Right_Argument (Etype (L));
3489
3490 else
3491 Get_First_Interp (L, Index1, It1);
3492
3493 while Present (It1.Typ) loop
3494 Check_Right_Argument (It1.Typ);
3495 Get_Next_Interp (Index1, It1);
3496 end loop;
3497 end if;
3498
3499 end Find_Arithmetic_Types;
3500
3501 ------------------------
3502 -- Find_Boolean_Types --
3503 ------------------------
3504
3505 procedure Find_Boolean_Types
3506 (L, R : Node_Id;
3507 Op_Id : Entity_Id;
3508 N : Node_Id)
3509 is
3510 Index : Interp_Index;
3511 It : Interp;
3512
3513 procedure Check_Numeric_Argument (T : Entity_Id);
3514 -- Special case for logical operations one of whose operands is an
3515 -- integer literal. If both are literal the result is any modular type.
3516
3517 procedure Check_Numeric_Argument (T : Entity_Id) is
3518 begin
3519 if T = Universal_Integer then
3520 Add_One_Interp (N, Op_Id, Any_Modular);
3521
3522 elsif Is_Modular_Integer_Type (T) then
3523 Add_One_Interp (N, Op_Id, T);
3524 end if;
3525 end Check_Numeric_Argument;
3526
3527 -- Start of processing for Find_Boolean_Types
3528
3529 begin
3530 if not Is_Overloaded (L) then
3531
3532 if Etype (L) = Universal_Integer
3533 or else Etype (L) = Any_Modular
3534 then
3535 if not Is_Overloaded (R) then
3536 Check_Numeric_Argument (Etype (R));
3537
3538 else
3539 Get_First_Interp (R, Index, It);
3540
3541 while Present (It.Typ) loop
3542 Check_Numeric_Argument (It.Typ);
3543
3544 Get_Next_Interp (Index, It);
3545 end loop;
3546 end if;
3547
3548 elsif Valid_Boolean_Arg (Etype (L))
3549 and then Has_Compatible_Type (R, Etype (L))
3550 then
3551 Add_One_Interp (N, Op_Id, Etype (L));
3552 end if;
3553
3554 else
3555 Get_First_Interp (L, Index, It);
3556
3557 while Present (It.Typ) loop
3558 if Valid_Boolean_Arg (It.Typ)
3559 and then Has_Compatible_Type (R, It.Typ)
3560 then
3561 Add_One_Interp (N, Op_Id, It.Typ);
3562 end if;
3563
3564 Get_Next_Interp (Index, It);
3565 end loop;
3566 end if;
3567 end Find_Boolean_Types;
3568
3569 ---------------------------
3570 -- Find_Comparison_Types --
3571 ---------------------------
3572
3573 procedure Find_Comparison_Types
3574 (L, R : Node_Id;
3575 Op_Id : Entity_Id;
3576 N : Node_Id)
3577 is
3578 Index : Interp_Index;
3579 It : Interp;
3580 Found : Boolean := False;
3581 I_F : Interp_Index;
3582 T_F : Entity_Id;
3583 Scop : Entity_Id := Empty;
3584
3585 procedure Try_One_Interp (T1 : Entity_Id);
3586 -- Routine to try one proposed interpretation. Note that the context
3587 -- of the operator plays no role in resolving the arguments, so that
3588 -- if there is more than one interpretation of the operands that is
3589 -- compatible with comparison, the operation is ambiguous.
3590
3591 procedure Try_One_Interp (T1 : Entity_Id) is
3592 begin
3593
3594 -- If the operator is an expanded name, then the type of the operand
3595 -- must be defined in the corresponding scope. If the type is
3596 -- universal, the context will impose the correct type.
3597
3598 if Present (Scop)
3599 and then not Defined_In_Scope (T1, Scop)
3600 and then T1 /= Universal_Integer
3601 and then T1 /= Universal_Real
3602 and then T1 /= Any_String
3603 and then T1 /= Any_Composite
3604 then
3605 return;
3606 end if;
3607
3608 if Valid_Comparison_Arg (T1)
3609 and then Has_Compatible_Type (R, T1)
3610 then
3611 if Found
3612 and then Base_Type (T1) /= Base_Type (T_F)
3613 then
3614 It := Disambiguate (L, I_F, Index, Any_Type);
3615
3616 if It = No_Interp then
3617 Ambiguous_Operands (N);
3618 Set_Etype (L, Any_Type);
3619 return;
3620
3621 else
3622 T_F := It.Typ;
3623 end if;
3624
3625 else
3626 Found := True;
3627 T_F := T1;
3628 I_F := Index;
3629 end if;
3630
3631 Set_Etype (L, T_F);
3632 Find_Non_Universal_Interpretations (N, R, Op_Id, T1);
3633
3634 end if;
3635 end Try_One_Interp;
3636
3637 -- Start processing for Find_Comparison_Types
3638
3639 begin
3640
3641 if Nkind (N) = N_Function_Call
3642 and then Nkind (Name (N)) = N_Expanded_Name
3643 then
3644 Scop := Entity (Prefix (Name (N)));
3645
3646 -- The prefix may be a package renaming, and the subsequent test
3647 -- requires the original package.
3648
3649 if Ekind (Scop) = E_Package
3650 and then Present (Renamed_Entity (Scop))
3651 then
3652 Scop := Renamed_Entity (Scop);
3653 Set_Entity (Prefix (Name (N)), Scop);
3654 end if;
3655 end if;
3656
3657 if not Is_Overloaded (L) then
3658 Try_One_Interp (Etype (L));
3659
3660 else
3661 Get_First_Interp (L, Index, It);
3662
3663 while Present (It.Typ) loop
3664 Try_One_Interp (It.Typ);
3665 Get_Next_Interp (Index, It);
3666 end loop;
3667 end if;
3668 end Find_Comparison_Types;
3669
3670 ----------------------------------------
3671 -- Find_Non_Universal_Interpretations --
3672 ----------------------------------------
3673
3674 procedure Find_Non_Universal_Interpretations
3675 (N : Node_Id;
3676 R : Node_Id;
3677 Op_Id : Entity_Id;
3678 T1 : Entity_Id)
3679 is
3680 Index : Interp_Index;
3681 It : Interp;
3682
3683 begin
3684 if T1 = Universal_Integer
3685 or else T1 = Universal_Real
3686 then
3687 if not Is_Overloaded (R) then
3688 Add_One_Interp
3689 (N, Op_Id, Standard_Boolean, Base_Type (Etype (R)));
3690 else
3691 Get_First_Interp (R, Index, It);
3692
3693 while Present (It.Typ) loop
3694 if Covers (It.Typ, T1) then
3695 Add_One_Interp
3696 (N, Op_Id, Standard_Boolean, Base_Type (It.Typ));
3697 end if;
3698
3699 Get_Next_Interp (Index, It);
3700 end loop;
3701 end if;
3702 else
3703 Add_One_Interp (N, Op_Id, Standard_Boolean, Base_Type (T1));
3704 end if;
3705 end Find_Non_Universal_Interpretations;
3706
3707 ------------------------------
3708 -- Find_Concatenation_Types --
3709 ------------------------------
3710
3711 procedure Find_Concatenation_Types
3712 (L, R : Node_Id;
3713 Op_Id : Entity_Id;
3714 N : Node_Id)
3715 is
3716 Op_Type : constant Entity_Id := Etype (Op_Id);
3717
3718 begin
3719 if Is_Array_Type (Op_Type)
3720 and then not Is_Limited_Type (Op_Type)
3721
3722 and then (Has_Compatible_Type (L, Op_Type)
3723 or else
3724 Has_Compatible_Type (L, Component_Type (Op_Type)))
3725
3726 and then (Has_Compatible_Type (R, Op_Type)
3727 or else
3728 Has_Compatible_Type (R, Component_Type (Op_Type)))
3729 then
3730 Add_One_Interp (N, Op_Id, Op_Type);
3731 end if;
3732 end Find_Concatenation_Types;
3733
3734 -------------------------
3735 -- Find_Equality_Types --
3736 -------------------------
3737
3738 procedure Find_Equality_Types
3739 (L, R : Node_Id;
3740 Op_Id : Entity_Id;
3741 N : Node_Id)
3742 is
3743 Index : Interp_Index;
3744 It : Interp;
3745 Found : Boolean := False;
3746 I_F : Interp_Index;
3747 T_F : Entity_Id;
3748 Scop : Entity_Id := Empty;
3749
3750 procedure Try_One_Interp (T1 : Entity_Id);
3751 -- The context of the operator plays no role in resolving the
3752 -- arguments, so that if there is more than one interpretation
3753 -- of the operands that is compatible with equality, the construct
3754 -- is ambiguous and an error can be emitted now, after trying to
3755 -- disambiguate, i.e. applying preference rules.
3756
3757 procedure Try_One_Interp (T1 : Entity_Id) is
3758 begin
3759
3760 -- If the operator is an expanded name, then the type of the operand
3761 -- must be defined in the corresponding scope. If the type is
3762 -- universal, the context will impose the correct type. An anonymous
3763 -- type for a 'Access reference is also universal in this sense, as
3764 -- the actual type is obtained from context.
3765
3766 if Present (Scop)
3767 and then not Defined_In_Scope (T1, Scop)
3768 and then T1 /= Universal_Integer
3769 and then T1 /= Universal_Real
3770 and then T1 /= Any_Access
3771 and then T1 /= Any_String
3772 and then T1 /= Any_Composite
3773 and then (Ekind (T1) /= E_Access_Subprogram_Type
3774 or else Comes_From_Source (T1))
3775 then
3776 return;
3777 end if;
3778
3779 if T1 /= Standard_Void_Type
3780 and then not Is_Limited_Type (T1)
3781 and then not Is_Limited_Composite (T1)
3782 and then Ekind (T1) /= E_Anonymous_Access_Type
3783 and then Has_Compatible_Type (R, T1)
3784 then
3785 if Found
3786 and then Base_Type (T1) /= Base_Type (T_F)
3787 then
3788 It := Disambiguate (L, I_F, Index, Any_Type);
3789
3790 if It = No_Interp then
3791 Ambiguous_Operands (N);
3792 Set_Etype (L, Any_Type);
3793 return;
3794
3795 else
3796 T_F := It.Typ;
3797 end if;
3798
3799 else
3800 Found := True;
3801 T_F := T1;
3802 I_F := Index;
3803 end if;
3804
3805 if not Analyzed (L) then
3806 Set_Etype (L, T_F);
3807 end if;
3808
3809 Find_Non_Universal_Interpretations (N, R, Op_Id, T1);
3810
3811 if Etype (N) = Any_Type then
3812
3813 -- Operator was not visible.
3814
3815 Found := False;
3816 end if;
3817 end if;
3818 end Try_One_Interp;
3819
3820 -- Start of processing for Find_Equality_Types
3821
3822 begin
3823
3824 if Nkind (N) = N_Function_Call
3825 and then Nkind (Name (N)) = N_Expanded_Name
3826 then
3827 Scop := Entity (Prefix (Name (N)));
3828
3829 -- The prefix may be a package renaming, and the subsequent test
3830 -- requires the original package.
3831
3832 if Ekind (Scop) = E_Package
3833 and then Present (Renamed_Entity (Scop))
3834 then
3835 Scop := Renamed_Entity (Scop);
3836 Set_Entity (Prefix (Name (N)), Scop);
3837 end if;
3838 end if;
3839
3840 if not Is_Overloaded (L) then
3841 Try_One_Interp (Etype (L));
3842 else
3843
3844 Get_First_Interp (L, Index, It);
3845
3846 while Present (It.Typ) loop
3847 Try_One_Interp (It.Typ);
3848 Get_Next_Interp (Index, It);
3849 end loop;
3850 end if;
3851 end Find_Equality_Types;
3852
3853 -------------------------
3854 -- Find_Negation_Types --
3855 -------------------------
3856
3857 procedure Find_Negation_Types
3858 (R : Node_Id;
3859 Op_Id : Entity_Id;
3860 N : Node_Id)
3861 is
3862 Index : Interp_Index;
3863 It : Interp;
3864
3865 begin
3866 if not Is_Overloaded (R) then
3867
3868 if Etype (R) = Universal_Integer then
3869 Add_One_Interp (N, Op_Id, Any_Modular);
3870
3871 elsif Valid_Boolean_Arg (Etype (R)) then
3872 Add_One_Interp (N, Op_Id, Etype (R));
3873 end if;
3874
3875 else
3876 Get_First_Interp (R, Index, It);
3877
3878 while Present (It.Typ) loop
3879 if Valid_Boolean_Arg (It.Typ) then
3880 Add_One_Interp (N, Op_Id, It.Typ);
3881 end if;
3882
3883 Get_Next_Interp (Index, It);
3884 end loop;
3885 end if;
3886 end Find_Negation_Types;
3887
3888 ----------------------
3889 -- Find_Unary_Types --
3890 ----------------------
3891
3892 procedure Find_Unary_Types
3893 (R : Node_Id;
3894 Op_Id : Entity_Id;
3895 N : Node_Id)
3896 is
3897 Index : Interp_Index;
3898 It : Interp;
3899
3900 begin
3901 if not Is_Overloaded (R) then
3902 if Is_Numeric_Type (Etype (R)) then
3903 Add_One_Interp (N, Op_Id, Base_Type (Etype (R)));
3904 end if;
3905
3906 else
3907 Get_First_Interp (R, Index, It);
3908
3909 while Present (It.Typ) loop
3910 if Is_Numeric_Type (It.Typ) then
3911 Add_One_Interp (N, Op_Id, Base_Type (It.Typ));
3912 end if;
3913
3914 Get_Next_Interp (Index, It);
3915 end loop;
3916 end if;
3917 end Find_Unary_Types;
3918
3919 ---------------------------------
3920 -- Insert_Explicit_Dereference --
3921 ---------------------------------
3922
3923 procedure Insert_Explicit_Dereference (N : Node_Id) is
3924 New_Prefix : Node_Id := Relocate_Node (N);
3925 I : Interp_Index;
3926 It : Interp;
3927 T : Entity_Id;
3928
3929 begin
3930 Save_Interps (N, New_Prefix);
3931 Rewrite (N,
3932 Make_Explicit_Dereference (Sloc (N), Prefix => New_Prefix));
3933
3934 Set_Etype (N, Designated_Type (Etype (New_Prefix)));
3935
3936 if Is_Overloaded (New_Prefix) then
3937
3938 -- The deference is also overloaded, and its interpretations are the
3939 -- designated types of the interpretations of the original node.
3940
3941 Set_Is_Overloaded (N);
3942 Get_First_Interp (New_Prefix, I, It);
3943
3944 while Present (It.Nam) loop
3945 T := It.Typ;
3946
3947 if Is_Access_Type (T) then
3948 Add_One_Interp (N, Designated_Type (T), Designated_Type (T));
3949 end if;
3950
3951 Get_Next_Interp (I, It);
3952 end loop;
3953
3954 End_Interp_List;
3955 end if;
3956
3957 end Insert_Explicit_Dereference;
3958
3959 ------------------
3960 -- Junk_Operand --
3961 ------------------
3962
3963 function Junk_Operand (N : Node_Id) return Boolean is
3964 Enode : Node_Id;
3965
3966 begin
3967 if Error_Posted (N) then
3968 return False;
3969 end if;
3970
3971 -- Get entity to be tested
3972
3973 if Is_Entity_Name (N)
3974 and then Present (Entity (N))
3975 then
3976 Enode := N;
3977
3978 -- An odd case, a procedure name gets converted to a very peculiar
3979 -- function call, and here is where we detect this happening.
3980
3981 elsif Nkind (N) = N_Function_Call
3982 and then Is_Entity_Name (Name (N))
3983 and then Present (Entity (Name (N)))
3984 then
3985 Enode := Name (N);
3986
3987 -- Another odd case, there are at least some cases of selected
3988 -- components where the selected component is not marked as having
3989 -- an entity, even though the selector does have an entity
3990
3991 elsif Nkind (N) = N_Selected_Component
3992 and then Present (Entity (Selector_Name (N)))
3993 then
3994 Enode := Selector_Name (N);
3995
3996 else
3997 return False;
3998 end if;
3999
4000 -- Now test the entity we got to see if it a bad case
4001
4002 case Ekind (Entity (Enode)) is
4003
4004 when E_Package =>
4005 Error_Msg_N
4006 ("package name cannot be used as operand", Enode);
4007
4008 when Generic_Unit_Kind =>
4009 Error_Msg_N
4010 ("generic unit name cannot be used as operand", Enode);
4011
4012 when Type_Kind =>
4013 Error_Msg_N
4014 ("subtype name cannot be used as operand", Enode);
4015
4016 when Entry_Kind =>
4017 Error_Msg_N
4018 ("entry name cannot be used as operand", Enode);
4019
4020 when E_Procedure =>
4021 Error_Msg_N
4022 ("procedure name cannot be used as operand", Enode);
4023
4024 when E_Exception =>
4025 Error_Msg_N
4026 ("exception name cannot be used as operand", Enode);
4027
4028 when E_Block | E_Label | E_Loop =>
4029 Error_Msg_N
4030 ("label name cannot be used as operand", Enode);
4031
4032 when others =>
4033 return False;
4034
4035 end case;
4036
4037 return True;
4038 end Junk_Operand;
4039
4040 --------------------
4041 -- Operator_Check --
4042 --------------------
4043
4044 procedure Operator_Check (N : Node_Id) is
4045 begin
4046 -- Test for case of no interpretation found for operator
4047
4048 if Etype (N) = Any_Type then
4049 declare
4050 L : Node_Id;
4051 R : Node_Id;
4052
4053 begin
4054 R := Right_Opnd (N);
4055
4056 if Nkind (N) in N_Binary_Op then
4057 L := Left_Opnd (N);
4058 else
4059 L := Empty;
4060 end if;
4061
4062 -- If either operand has no type, then don't complain further,
4063 -- since this simply means that we have a propragated error.
4064
4065 if R = Error
4066 or else Etype (R) = Any_Type
4067 or else (Nkind (N) in N_Binary_Op and then Etype (L) = Any_Type)
4068 then
4069 return;
4070
4071 -- We explicitly check for the case of concatenation of
4072 -- component with component to avoid reporting spurious
4073 -- matching array types that might happen to be lurking
4074 -- in distant packages (such as run-time packages). This
4075 -- also prevents inconsistencies in the messages for certain
4076 -- ACVC B tests, which can vary depending on types declared
4077 -- in run-time interfaces. A further improvement, when
4078 -- aggregates are present, is to look for a well-typed operand.
4079
4080 elsif Present (Candidate_Type)
4081 and then (Nkind (N) /= N_Op_Concat
4082 or else Is_Array_Type (Etype (L))
4083 or else Is_Array_Type (Etype (R)))
4084 then
4085
4086 if Nkind (N) = N_Op_Concat then
4087 if Etype (L) /= Any_Composite
4088 and then Is_Array_Type (Etype (L))
4089 then
4090 Candidate_Type := Etype (L);
4091
4092 elsif Etype (R) /= Any_Composite
4093 and then Is_Array_Type (Etype (R))
4094 then
4095 Candidate_Type := Etype (R);
4096 end if;
4097 end if;
4098
4099 Error_Msg_NE
4100 ("operator for} is not directly visible!",
4101 N, First_Subtype (Candidate_Type));
4102 Error_Msg_N ("use clause would make operation legal!", N);
4103 return;
4104
4105 -- If either operand is a junk operand (e.g. package name), then
4106 -- post appropriate error messages, but do not complain further.
4107
4108 -- Note that the use of OR in this test instead of OR ELSE
4109 -- is quite deliberate, we may as well check both operands
4110 -- in the binary operator case.
4111
4112 elsif Junk_Operand (R)
4113 or (Nkind (N) in N_Binary_Op and then Junk_Operand (L))
4114 then
4115 return;
4116
4117 -- If we have a logical operator, one of whose operands is
4118 -- Boolean, then we know that the other operand cannot resolve
4119 -- to Boolean (since we got no interpretations), but in that
4120 -- case we pretty much know that the other operand should be
4121 -- Boolean, so resolve it that way (generating an error)
4122
4123 elsif Nkind (N) = N_Op_And
4124 or else
4125 Nkind (N) = N_Op_Or
4126 or else
4127 Nkind (N) = N_Op_Xor
4128 then
4129 if Etype (L) = Standard_Boolean then
4130 Resolve (R, Standard_Boolean);
4131 return;
4132 elsif Etype (R) = Standard_Boolean then
4133 Resolve (L, Standard_Boolean);
4134 return;
4135 end if;
4136
4137 -- For an arithmetic operator or comparison operator, if one
4138 -- of the operands is numeric, then we know the other operand
4139 -- is not the same numeric type. If it is a non-numeric type,
4140 -- then probably it is intended to match the other operand.
4141
4142 elsif Nkind (N) = N_Op_Add or else
4143 Nkind (N) = N_Op_Divide or else
4144 Nkind (N) = N_Op_Ge or else
4145 Nkind (N) = N_Op_Gt or else
4146 Nkind (N) = N_Op_Le or else
4147 Nkind (N) = N_Op_Lt or else
4148 Nkind (N) = N_Op_Mod or else
4149 Nkind (N) = N_Op_Multiply or else
4150 Nkind (N) = N_Op_Rem or else
4151 Nkind (N) = N_Op_Subtract
4152 then
4153 if Is_Numeric_Type (Etype (L))
4154 and then not Is_Numeric_Type (Etype (R))
4155 then
4156 Resolve (R, Etype (L));
4157 return;
4158
4159 elsif Is_Numeric_Type (Etype (R))
4160 and then not Is_Numeric_Type (Etype (L))
4161 then
4162 Resolve (L, Etype (R));
4163 return;
4164 end if;
4165
4166 -- Comparisons on A'Access are common enough to deserve a
4167 -- special message.
4168
4169 elsif (Nkind (N) = N_Op_Eq or else
4170 Nkind (N) = N_Op_Ne)
4171 and then Ekind (Etype (L)) = E_Access_Attribute_Type
4172 and then Ekind (Etype (R)) = E_Access_Attribute_Type
4173 then
4174 Error_Msg_N
4175 ("two access attributes cannot be compared directly", N);
4176 Error_Msg_N
4177 ("\they must be converted to an explicit type for comparison",
4178 N);
4179 return;
4180
4181 -- Another one for C programmers
4182
4183 elsif Nkind (N) = N_Op_Concat
4184 and then Valid_Boolean_Arg (Etype (L))
4185 and then Valid_Boolean_Arg (Etype (R))
4186 then
4187 Error_Msg_N ("invalid operands for concatenation", N);
4188 Error_Msg_N ("\maybe AND was meant", N);
4189 return;
4190
4191 -- A special case for comparison of access parameter with null
4192
4193 elsif Nkind (N) = N_Op_Eq
4194 and then Is_Entity_Name (L)
4195 and then Nkind (Parent (Entity (L))) = N_Parameter_Specification
4196 and then Nkind (Parameter_Type (Parent (Entity (L)))) =
4197 N_Access_Definition
4198 and then Nkind (R) = N_Null
4199 then
4200 Error_Msg_N ("access parameter is not allowed to be null", L);
4201 Error_Msg_N ("\(call would raise Constraint_Error)", L);
4202 return;
4203 end if;
4204
4205 -- If we fall through then just give general message. Note
4206 -- that in the following messages, if the operand is overloaded
4207 -- we choose an arbitrary type to complain about, but that is
4208 -- probably more useful than not giving a type at all.
4209
4210 if Nkind (N) in N_Unary_Op then
4211 Error_Msg_Node_2 := Etype (R);
4212 Error_Msg_N ("operator& not defined for}", N);
4213 return;
4214
4215 else
4216 Error_Msg_N ("invalid operand types for operator&", N);
4217
4218 if Nkind (N) in N_Binary_Op
4219 and then Nkind (N) /= N_Op_Concat
4220 then
4221 Error_Msg_NE ("\left operand has}!", N, Etype (L));
4222 Error_Msg_NE ("\right operand has}!", N, Etype (R));
4223 end if;
4224 end if;
4225 end;
4226 end if;
4227 end Operator_Check;
4228
4229 -----------------------
4230 -- Try_Indirect_Call --
4231 -----------------------
4232
4233 function Try_Indirect_Call
4234 (N : Node_Id;
4235 Nam : Entity_Id;
4236 Typ : Entity_Id)
4237 return Boolean
4238 is
4239 Actuals : List_Id := Parameter_Associations (N);
4240 Actual : Node_Id := First (Actuals);
4241 Formal : Entity_Id := First_Formal (Designated_Type (Typ));
4242
4243 begin
4244 while Present (Actual)
4245 and then Present (Formal)
4246 loop
4247 if not Has_Compatible_Type (Actual, Etype (Formal)) then
4248 return False;
4249 end if;
4250
4251 Next (Actual);
4252 Next_Formal (Formal);
4253 end loop;
4254
4255 if No (Actual) and then No (Formal) then
4256 Add_One_Interp (N, Nam, Etype (Designated_Type (Typ)));
4257
4258 -- Nam is a candidate interpretation for the name in the call,
4259 -- if it is not an indirect call.
4260
4261 if not Is_Type (Nam)
4262 and then Is_Entity_Name (Name (N))
4263 then
4264 Set_Entity (Name (N), Nam);
4265 end if;
4266
4267 return True;
4268 else
4269 return False;
4270 end if;
4271 end Try_Indirect_Call;
4272
4273 ----------------------
4274 -- Try_Indexed_Call --
4275 ----------------------
4276
4277 function Try_Indexed_Call
4278 (N : Node_Id;
4279 Nam : Entity_Id;
4280 Typ : Entity_Id)
4281 return Boolean
4282 is
4283 Actuals : List_Id := Parameter_Associations (N);
4284 Actual : Node_Id := First (Actuals);
4285 Index : Entity_Id := First_Index (Typ);
4286
4287 begin
4288 while Present (Actual)
4289 and then Present (Index)
4290 loop
4291 -- If the parameter list has a named association, the expression
4292 -- is definitely a call and not an indexed component.
4293
4294 if Nkind (Actual) = N_Parameter_Association then
4295 return False;
4296 end if;
4297
4298 if not Has_Compatible_Type (Actual, Etype (Index)) then
4299 return False;
4300 end if;
4301
4302 Next (Actual);
4303 Next_Index (Index);
4304 end loop;
4305
4306 if No (Actual) and then No (Index) then
4307 Add_One_Interp (N, Nam, Component_Type (Typ));
4308
4309 -- Nam is a candidate interpretation for the name in the call,
4310 -- if it is not an indirect call.
4311
4312 if not Is_Type (Nam)
4313 and then Is_Entity_Name (Name (N))
4314 then
4315 Set_Entity (Name (N), Nam);
4316 end if;
4317
4318 return True;
4319 else
4320 return False;
4321 end if;
4322
4323 end Try_Indexed_Call;
4324
4325end Sem_Ch4;
This page took 0.761747 seconds and 5 git commands to generate.