718af47f17cd4a514604149150f1afaea8ad1a02
[gcc.git] / gcc / ada / sem_ch4.adb
1 ------------------------------------------------------------------------------
2 -- --
3 -- GNAT COMPILER COMPONENTS --
4 -- --
5 -- S E M _ C H 4 --
6 -- --
7 -- B o d y --
8 -- --
9 -- Copyright (C) 1992-2012, Free Software Foundation, Inc. --
10 -- --
11 -- GNAT is free software; you can redistribute it and/or modify it under --
12 -- terms of the GNU General Public License as published by the Free Soft- --
13 -- ware Foundation; either version 3, or (at your option) any later ver- --
14 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
17 -- for more details. You should have received a copy of the GNU General --
18 -- Public License distributed with GNAT; see file COPYING3. If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license. --
20 -- --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
23 -- --
24 ------------------------------------------------------------------------------
25
26 with Aspects; use Aspects;
27 with Atree; use Atree;
28 with Debug; use Debug;
29 with Einfo; use Einfo;
30 with Elists; use Elists;
31 with Errout; use Errout;
32 with Exp_Util; use Exp_Util;
33 with Fname; use Fname;
34 with Itypes; use Itypes;
35 with Lib; use Lib;
36 with Lib.Xref; use Lib.Xref;
37 with Namet; use Namet;
38 with Namet.Sp; use Namet.Sp;
39 with Nlists; use Nlists;
40 with Nmake; use Nmake;
41 with Opt; use Opt;
42 with Output; use Output;
43 with Restrict; use Restrict;
44 with Rident; use Rident;
45 with Sem; use Sem;
46 with Sem_Aux; use Sem_Aux;
47 with Sem_Case; use Sem_Case;
48 with Sem_Cat; use Sem_Cat;
49 with Sem_Ch3; use Sem_Ch3;
50 with Sem_Ch6; use Sem_Ch6;
51 with Sem_Ch8; use Sem_Ch8;
52 with Sem_Dim; use Sem_Dim;
53 with Sem_Disp; use Sem_Disp;
54 with Sem_Dist; use Sem_Dist;
55 with Sem_Eval; use Sem_Eval;
56 with Sem_Res; use Sem_Res;
57 with Sem_Type; use Sem_Type;
58 with Sem_Util; use Sem_Util;
59 with Sem_Warn; use Sem_Warn;
60 with Stand; use Stand;
61 with Sinfo; use Sinfo;
62 with Snames; use Snames;
63 with Tbuild; use Tbuild;
64 with Uintp; use Uintp;
65
66 package body Sem_Ch4 is
67
68 -----------------------
69 -- Local Subprograms --
70 -----------------------
71
72 procedure Analyze_Concatenation_Rest (N : Node_Id);
73 -- Does the "rest" of the work of Analyze_Concatenation, after the left
74 -- operand has been analyzed. See Analyze_Concatenation for details.
75
76 procedure Analyze_Expression (N : Node_Id);
77 -- For expressions that are not names, this is just a call to analyze.
78 -- If the expression is a name, it may be a call to a parameterless
79 -- function, and if so must be converted into an explicit call node
80 -- and analyzed as such. This deproceduring must be done during the first
81 -- pass of overload resolution, because otherwise a procedure call with
82 -- overloaded actuals may fail to resolve.
83
84 procedure Analyze_Operator_Call (N : Node_Id; Op_Id : Entity_Id);
85 -- Analyze a call of the form "+"(x, y), etc. The prefix of the call
86 -- is an operator name or an expanded name whose selector is an operator
87 -- name, and one possible interpretation is as a predefined operator.
88
89 procedure Analyze_Overloaded_Selected_Component (N : Node_Id);
90 -- If the prefix of a selected_component is overloaded, the proper
91 -- interpretation that yields a record type with the proper selector
92 -- name must be selected.
93
94 procedure Analyze_User_Defined_Binary_Op (N : Node_Id; Op_Id : Entity_Id);
95 -- Procedure to analyze a user defined binary operator, which is resolved
96 -- like a function, but instead of a list of actuals it is presented
97 -- with the left and right operands of an operator node.
98
99 procedure Analyze_User_Defined_Unary_Op (N : Node_Id; Op_Id : Entity_Id);
100 -- Procedure to analyze a user defined unary operator, which is resolved
101 -- like a function, but instead of a list of actuals, it is presented with
102 -- the operand of the operator node.
103
104 procedure Ambiguous_Operands (N : Node_Id);
105 -- For equality, membership, and comparison operators with overloaded
106 -- arguments, list possible interpretations.
107
108 procedure Analyze_One_Call
109 (N : Node_Id;
110 Nam : Entity_Id;
111 Report : Boolean;
112 Success : out Boolean;
113 Skip_First : Boolean := False);
114 -- Check one interpretation of an overloaded subprogram name for
115 -- compatibility with the types of the actuals in a call. If there is a
116 -- single interpretation which does not match, post error if Report is
117 -- set to True.
118 --
119 -- Nam is the entity that provides the formals against which the actuals
120 -- are checked. Nam is either the name of a subprogram, or the internal
121 -- subprogram type constructed for an access_to_subprogram. If the actuals
122 -- are compatible with Nam, then Nam is added to the list of candidate
123 -- interpretations for N, and Success is set to True.
124 --
125 -- The flag Skip_First is used when analyzing a call that was rewritten
126 -- from object notation. In this case the first actual may have to receive
127 -- an explicit dereference, depending on the first formal of the operation
128 -- being called. The caller will have verified that the object is legal
129 -- for the call. If the remaining parameters match, the first parameter
130 -- will rewritten as a dereference if needed, prior to completing analysis.
131
132 procedure Check_Misspelled_Selector
133 (Prefix : Entity_Id;
134 Sel : Node_Id);
135 -- Give possible misspelling diagnostic if Sel is likely to be a mis-
136 -- spelling of one of the selectors of the Prefix. This is called by
137 -- Analyze_Selected_Component after producing an invalid selector error
138 -- message.
139
140 function Defined_In_Scope (T : Entity_Id; S : Entity_Id) return Boolean;
141 -- Verify that type T is declared in scope S. Used to find interpretations
142 -- for operators given by expanded names. This is abstracted as a separate
143 -- function to handle extensions to System, where S is System, but T is
144 -- declared in the extension.
145
146 procedure Find_Arithmetic_Types
147 (L, R : Node_Id;
148 Op_Id : Entity_Id;
149 N : Node_Id);
150 -- L and R are the operands of an arithmetic operator. Find
151 -- consistent pairs of interpretations for L and R that have a
152 -- numeric type consistent with the semantics of the operator.
153
154 procedure Find_Comparison_Types
155 (L, R : Node_Id;
156 Op_Id : Entity_Id;
157 N : Node_Id);
158 -- L and R are operands of a comparison operator. Find consistent
159 -- pairs of interpretations for L and R.
160
161 procedure Find_Concatenation_Types
162 (L, R : Node_Id;
163 Op_Id : Entity_Id;
164 N : Node_Id);
165 -- For the four varieties of concatenation
166
167 procedure Find_Equality_Types
168 (L, R : Node_Id;
169 Op_Id : Entity_Id;
170 N : Node_Id);
171 -- Ditto for equality operators
172
173 procedure Find_Boolean_Types
174 (L, R : Node_Id;
175 Op_Id : Entity_Id;
176 N : Node_Id);
177 -- Ditto for binary logical operations
178
179 procedure Find_Negation_Types
180 (R : Node_Id;
181 Op_Id : Entity_Id;
182 N : Node_Id);
183 -- Find consistent interpretation for operand of negation operator
184
185 procedure Find_Non_Universal_Interpretations
186 (N : Node_Id;
187 R : Node_Id;
188 Op_Id : Entity_Id;
189 T1 : Entity_Id);
190 -- For equality and comparison operators, the result is always boolean,
191 -- and the legality of the operation is determined from the visibility
192 -- of the operand types. If one of the operands has a universal interpre-
193 -- tation, the legality check uses some compatible non-universal
194 -- interpretation of the other operand. N can be an operator node, or
195 -- a function call whose name is an operator designator. Any_Access, which
196 -- is the initial type of the literal NULL, is a universal type for the
197 -- purpose of this routine.
198
199 function Find_Primitive_Operation (N : Node_Id) return Boolean;
200 -- Find candidate interpretations for the name Obj.Proc when it appears
201 -- in a subprogram renaming declaration.
202
203 procedure Find_Unary_Types
204 (R : Node_Id;
205 Op_Id : Entity_Id;
206 N : Node_Id);
207 -- Unary arithmetic types: plus, minus, abs
208
209 procedure Check_Arithmetic_Pair
210 (T1, T2 : Entity_Id;
211 Op_Id : Entity_Id;
212 N : Node_Id);
213 -- Subsidiary procedure to Find_Arithmetic_Types. T1 and T2 are valid
214 -- types for left and right operand. Determine whether they constitute
215 -- a valid pair for the given operator, and record the corresponding
216 -- interpretation of the operator node. The node N may be an operator
217 -- node (the usual case) or a function call whose prefix is an operator
218 -- designator. In both cases Op_Id is the operator name itself.
219
220 procedure Diagnose_Call (N : Node_Id; Nam : Node_Id);
221 -- Give detailed information on overloaded call where none of the
222 -- interpretations match. N is the call node, Nam the designator for
223 -- the overloaded entity being called.
224
225 function Junk_Operand (N : Node_Id) return Boolean;
226 -- Test for an operand that is an inappropriate entity (e.g. a package
227 -- name or a label). If so, issue an error message and return True. If
228 -- the operand is not an inappropriate entity kind, return False.
229
230 procedure Operator_Check (N : Node_Id);
231 -- Verify that an operator has received some valid interpretation. If none
232 -- was found, determine whether a use clause would make the operation
233 -- legal. The variable Candidate_Type (defined in Sem_Type) is set for
234 -- every type compatible with the operator, even if the operator for the
235 -- type is not directly visible. The routine uses this type to emit a more
236 -- informative message.
237
238 function Process_Implicit_Dereference_Prefix
239 (E : Entity_Id;
240 P : Node_Id) return Entity_Id;
241 -- Called when P is the prefix of an implicit dereference, denoting an
242 -- object E. The function returns the designated type of the prefix, taking
243 -- into account that the designated type of an anonymous access type may be
244 -- a limited view, when the non-limited view is visible.
245 -- If in semantics only mode (-gnatc or generic), the function also records
246 -- that the prefix is a reference to E, if any. Normally, such a reference
247 -- is generated only when the implicit dereference is expanded into an
248 -- explicit one, but for consistency we must generate the reference when
249 -- expansion is disabled as well.
250
251 procedure Remove_Abstract_Operations (N : Node_Id);
252 -- Ada 2005: implementation of AI-310. An abstract non-dispatching
253 -- operation is not a candidate interpretation.
254
255 function Try_Container_Indexing
256 (N : Node_Id;
257 Prefix : Node_Id;
258 Exprs : List_Id) return Boolean;
259 -- AI05-0139: Generalized indexing to support iterators over containers
260
261 function Try_Indexed_Call
262 (N : Node_Id;
263 Nam : Entity_Id;
264 Typ : Entity_Id;
265 Skip_First : Boolean) return Boolean;
266 -- If a function has defaults for all its actuals, a call to it may in fact
267 -- be an indexing on the result of the call. Try_Indexed_Call attempts the
268 -- interpretation as an indexing, prior to analysis as a call. If both are
269 -- possible, the node is overloaded with both interpretations (same symbol
270 -- but two different types). If the call is written in prefix form, the
271 -- prefix becomes the first parameter in the call, and only the remaining
272 -- actuals must be checked for the presence of defaults.
273
274 function Try_Indirect_Call
275 (N : Node_Id;
276 Nam : Entity_Id;
277 Typ : Entity_Id) return Boolean;
278 -- Similarly, a function F that needs no actuals can return an access to a
279 -- subprogram, and the call F (X) interpreted as F.all (X). In this case
280 -- the call may be overloaded with both interpretations.
281
282 function Try_Object_Operation
283 (N : Node_Id;
284 CW_Test_Only : Boolean := False) return Boolean;
285 -- Ada 2005 (AI-252): Support the object.operation notation. If node N
286 -- is a call in this notation, it is transformed into a normal subprogram
287 -- call where the prefix is a parameter, and True is returned. If node
288 -- N is not of this form, it is unchanged, and False is returned. if
289 -- CW_Test_Only is true then N is an N_Selected_Component node which
290 -- is part of a call to an entry or procedure of a tagged concurrent
291 -- type and this routine is invoked to search for class-wide subprograms
292 -- conflicting with the target entity.
293
294 procedure wpo (T : Entity_Id);
295 pragma Warnings (Off, wpo);
296 -- Used for debugging: obtain list of primitive operations even if
297 -- type is not frozen and dispatch table is not built yet.
298
299 ------------------------
300 -- Ambiguous_Operands --
301 ------------------------
302
303 procedure Ambiguous_Operands (N : Node_Id) is
304 procedure List_Operand_Interps (Opnd : Node_Id);
305
306 --------------------------
307 -- List_Operand_Interps --
308 --------------------------
309
310 procedure List_Operand_Interps (Opnd : Node_Id) is
311 Nam : Node_Id;
312 Err : Node_Id := N;
313
314 begin
315 if Is_Overloaded (Opnd) then
316 if Nkind (Opnd) in N_Op then
317 Nam := Opnd;
318 elsif Nkind (Opnd) = N_Function_Call then
319 Nam := Name (Opnd);
320 elsif Ada_Version >= Ada_2012 then
321 declare
322 It : Interp;
323 I : Interp_Index;
324
325 begin
326 Get_First_Interp (Opnd, I, It);
327 while Present (It.Nam) loop
328 if Has_Implicit_Dereference (It.Typ) then
329 Error_Msg_N
330 ("can be interpreted as implicit dereference", Opnd);
331 return;
332 end if;
333
334 Get_Next_Interp (I, It);
335 end loop;
336 end;
337
338 return;
339 end if;
340
341 else
342 return;
343 end if;
344
345 if Opnd = Left_Opnd (N) then
346 Error_Msg_N ("\left operand has the following interpretations", N);
347 else
348 Error_Msg_N
349 ("\right operand has the following interpretations", N);
350 Err := Opnd;
351 end if;
352
353 List_Interps (Nam, Err);
354 end List_Operand_Interps;
355
356 -- Start of processing for Ambiguous_Operands
357
358 begin
359 if Nkind (N) in N_Membership_Test then
360 Error_Msg_N ("ambiguous operands for membership", N);
361
362 elsif Nkind_In (N, N_Op_Eq, N_Op_Ne) then
363 Error_Msg_N ("ambiguous operands for equality", N);
364
365 else
366 Error_Msg_N ("ambiguous operands for comparison", N);
367 end if;
368
369 if All_Errors_Mode then
370 List_Operand_Interps (Left_Opnd (N));
371 List_Operand_Interps (Right_Opnd (N));
372 else
373 Error_Msg_N ("\use -gnatf switch for details", N);
374 end if;
375 end Ambiguous_Operands;
376
377 -----------------------
378 -- Analyze_Aggregate --
379 -----------------------
380
381 -- Most of the analysis of Aggregates requires that the type be known,
382 -- and is therefore put off until resolution.
383
384 procedure Analyze_Aggregate (N : Node_Id) is
385 begin
386 if No (Etype (N)) then
387 Set_Etype (N, Any_Composite);
388 end if;
389 end Analyze_Aggregate;
390
391 -----------------------
392 -- Analyze_Allocator --
393 -----------------------
394
395 procedure Analyze_Allocator (N : Node_Id) is
396 Loc : constant Source_Ptr := Sloc (N);
397 Sav_Errs : constant Nat := Serious_Errors_Detected;
398 E : Node_Id := Expression (N);
399 Acc_Type : Entity_Id;
400 Type_Id : Entity_Id;
401 P : Node_Id;
402 C : Node_Id;
403
404 begin
405 Check_SPARK_Restriction ("allocator is not allowed", N);
406
407 -- Deal with allocator restrictions
408
409 -- In accordance with H.4(7), the No_Allocators restriction only applies
410 -- to user-written allocators. The same consideration applies to the
411 -- No_Allocators_Before_Elaboration restriction.
412
413 if Comes_From_Source (N) then
414 Check_Restriction (No_Allocators, N);
415
416 -- Processing for No_Allocators_After_Elaboration, loop to look at
417 -- enclosing context, checking task case and main subprogram case.
418
419 C := N;
420 P := Parent (C);
421 while Present (P) loop
422
423 -- In both cases we need a handled sequence of statements, where
424 -- the occurrence of the allocator is within the statements.
425
426 if Nkind (P) = N_Handled_Sequence_Of_Statements
427 and then Is_List_Member (C)
428 and then List_Containing (C) = Statements (P)
429 then
430 -- Check for allocator within task body, this is a definite
431 -- violation of No_Allocators_After_Elaboration we can detect.
432
433 if Nkind (Original_Node (Parent (P))) = N_Task_Body then
434 Check_Restriction (No_Allocators_After_Elaboration, N);
435 exit;
436 end if;
437
438 -- The other case is appearance in a subprogram body. This may
439 -- be a violation if this is a library level subprogram, and it
440 -- turns out to be used as the main program, but only the
441 -- binder knows that, so just record the occurrence.
442
443 if Nkind (Original_Node (Parent (P))) = N_Subprogram_Body
444 and then Nkind (Parent (Parent (P))) = N_Compilation_Unit
445 then
446 Set_Has_Allocator (Current_Sem_Unit);
447 end if;
448 end if;
449
450 C := P;
451 P := Parent (C);
452 end loop;
453 end if;
454
455 -- Ada 2012 (AI05-0111-3): Analyze the subpool_specification, if
456 -- any. The expected type for the name is any type. A non-overloading
457 -- rule then requires it to be of a type descended from
458 -- System.Storage_Pools.Subpools.Subpool_Handle.
459
460 -- This isn't exactly what the AI says, but it seems to be the right
461 -- rule. The AI should be fixed.???
462
463 declare
464 Subpool : constant Node_Id := Subpool_Handle_Name (N);
465
466 begin
467 if Present (Subpool) then
468 Analyze (Subpool);
469
470 if Is_Overloaded (Subpool) then
471 Error_Msg_N ("ambiguous subpool handle", Subpool);
472 end if;
473
474 -- Check that Etype (Subpool) is descended from Subpool_Handle
475
476 Resolve (Subpool);
477 end if;
478 end;
479
480 -- Analyze the qualified expression or subtype indication
481
482 if Nkind (E) = N_Qualified_Expression then
483 Acc_Type := Create_Itype (E_Allocator_Type, N);
484 Set_Etype (Acc_Type, Acc_Type);
485 Find_Type (Subtype_Mark (E));
486
487 -- Analyze the qualified expression, and apply the name resolution
488 -- rule given in 4.7(3).
489
490 Analyze (E);
491 Type_Id := Etype (E);
492 Set_Directly_Designated_Type (Acc_Type, Type_Id);
493
494 Resolve (Expression (E), Type_Id);
495
496 -- Allocators generated by the build-in-place expansion mechanism
497 -- are explicitly marked as coming from source but do not need to be
498 -- checked for limited initialization. To exclude this case, ensure
499 -- that the parent of the allocator is a source node.
500
501 if Is_Limited_Type (Type_Id)
502 and then Comes_From_Source (N)
503 and then Comes_From_Source (Parent (N))
504 and then not In_Instance_Body
505 then
506 if not OK_For_Limited_Init (Type_Id, Expression (E)) then
507 Error_Msg_N ("initialization not allowed for limited types", N);
508 Explain_Limited_Type (Type_Id, N);
509 end if;
510 end if;
511
512 -- A qualified expression requires an exact match of the type,
513 -- class-wide matching is not allowed.
514
515 -- if Is_Class_Wide_Type (Type_Id)
516 -- and then Base_Type
517 -- (Etype (Expression (E))) /= Base_Type (Type_Id)
518 -- then
519 -- Wrong_Type (Expression (E), Type_Id);
520 -- end if;
521
522 Check_Non_Static_Context (Expression (E));
523
524 -- We don't analyze the qualified expression itself because it's
525 -- part of the allocator
526
527 Set_Etype (E, Type_Id);
528
529 -- Case where allocator has a subtype indication
530
531 else
532 declare
533 Def_Id : Entity_Id;
534 Base_Typ : Entity_Id;
535
536 begin
537 -- If the allocator includes a N_Subtype_Indication then a
538 -- constraint is present, otherwise the node is a subtype mark.
539 -- Introduce an explicit subtype declaration into the tree
540 -- defining some anonymous subtype and rewrite the allocator to
541 -- use this subtype rather than the subtype indication.
542
543 -- It is important to introduce the explicit subtype declaration
544 -- so that the bounds of the subtype indication are attached to
545 -- the tree in case the allocator is inside a generic unit.
546
547 if Nkind (E) = N_Subtype_Indication then
548
549 -- A constraint is only allowed for a composite type in Ada
550 -- 95. In Ada 83, a constraint is also allowed for an
551 -- access-to-composite type, but the constraint is ignored.
552
553 Find_Type (Subtype_Mark (E));
554 Base_Typ := Entity (Subtype_Mark (E));
555
556 if Is_Elementary_Type (Base_Typ) then
557 if not (Ada_Version = Ada_83
558 and then Is_Access_Type (Base_Typ))
559 then
560 Error_Msg_N ("constraint not allowed here", E);
561
562 if Nkind (Constraint (E)) =
563 N_Index_Or_Discriminant_Constraint
564 then
565 Error_Msg_N -- CODEFIX
566 ("\if qualified expression was meant, " &
567 "use apostrophe", Constraint (E));
568 end if;
569 end if;
570
571 -- Get rid of the bogus constraint:
572
573 Rewrite (E, New_Copy_Tree (Subtype_Mark (E)));
574 Analyze_Allocator (N);
575 return;
576
577 -- Ada 2005, AI-363: if the designated type has a constrained
578 -- partial view, it cannot receive a discriminant constraint,
579 -- and the allocated object is unconstrained.
580
581 elsif Ada_Version >= Ada_2005
582 and then Effectively_Has_Constrained_Partial_View
583 (Typ => Base_Typ,
584 Scop => Current_Scope)
585 then
586 Error_Msg_N
587 ("constraint not allowed when type " &
588 "has a constrained partial view", Constraint (E));
589 end if;
590
591 if Expander_Active then
592 Def_Id := Make_Temporary (Loc, 'S');
593
594 Insert_Action (E,
595 Make_Subtype_Declaration (Loc,
596 Defining_Identifier => Def_Id,
597 Subtype_Indication => Relocate_Node (E)));
598
599 if Sav_Errs /= Serious_Errors_Detected
600 and then Nkind (Constraint (E)) =
601 N_Index_Or_Discriminant_Constraint
602 then
603 Error_Msg_N -- CODEFIX
604 ("if qualified expression was meant, " &
605 "use apostrophe!", Constraint (E));
606 end if;
607
608 E := New_Occurrence_Of (Def_Id, Loc);
609 Rewrite (Expression (N), E);
610 end if;
611 end if;
612
613 Type_Id := Process_Subtype (E, N);
614 Acc_Type := Create_Itype (E_Allocator_Type, N);
615 Set_Etype (Acc_Type, Acc_Type);
616 Set_Directly_Designated_Type (Acc_Type, Type_Id);
617 Check_Fully_Declared (Type_Id, N);
618
619 -- Ada 2005 (AI-231): If the designated type is itself an access
620 -- type that excludes null, its default initialization will
621 -- be a null object, and we can insert an unconditional raise
622 -- before the allocator.
623
624 -- Ada 2012 (AI-104): A not null indication here is altogether
625 -- illegal.
626
627 if Can_Never_Be_Null (Type_Id) then
628 declare
629 Not_Null_Check : constant Node_Id :=
630 Make_Raise_Constraint_Error (Sloc (E),
631 Reason => CE_Null_Not_Allowed);
632
633 begin
634 if Expander_Active then
635 Insert_Action (N, Not_Null_Check);
636 Analyze (Not_Null_Check);
637
638 else
639 Error_Msg_N ("null value not allowed here?", E);
640 end if;
641 end;
642 end if;
643
644 -- Check restriction against dynamically allocated protected
645 -- objects. Note that when limited aggregates are supported,
646 -- a similar test should be applied to an allocator with a
647 -- qualified expression ???
648
649 if Is_Protected_Type (Type_Id) then
650 Check_Restriction (No_Protected_Type_Allocators, N);
651 end if;
652
653 -- Check for missing initialization. Skip this check if we already
654 -- had errors on analyzing the allocator, since in that case these
655 -- are probably cascaded errors.
656
657 if Is_Indefinite_Subtype (Type_Id)
658 and then Serious_Errors_Detected = Sav_Errs
659 then
660 -- The build-in-place machinery may produce an allocator when
661 -- the designated type is indefinite but the underlying type is
662 -- not. In this case the unknown discriminants are meaningless
663 -- and should not trigger error messages. Check the parent node
664 -- because the allocator is marked as coming from source.
665
666 if Present (Underlying_Type (Type_Id))
667 and then not Is_Indefinite_Subtype (Underlying_Type (Type_Id))
668 and then not Comes_From_Source (Parent (N))
669 then
670 null;
671
672 elsif Is_Class_Wide_Type (Type_Id) then
673 Error_Msg_N
674 ("initialization required in class-wide allocation", N);
675
676 else
677 if Ada_Version < Ada_2005
678 and then Is_Limited_Type (Type_Id)
679 then
680 Error_Msg_N ("unconstrained allocation not allowed", N);
681
682 if Is_Array_Type (Type_Id) then
683 Error_Msg_N
684 ("\constraint with array bounds required", N);
685
686 elsif Has_Unknown_Discriminants (Type_Id) then
687 null;
688
689 else pragma Assert (Has_Discriminants (Type_Id));
690 Error_Msg_N
691 ("\constraint with discriminant values required", N);
692 end if;
693
694 -- Limited Ada 2005 and general non-limited case
695
696 else
697 Error_Msg_N
698 ("uninitialized unconstrained allocation not allowed",
699 N);
700
701 if Is_Array_Type (Type_Id) then
702 Error_Msg_N
703 ("\qualified expression or constraint with " &
704 "array bounds required", N);
705
706 elsif Has_Unknown_Discriminants (Type_Id) then
707 Error_Msg_N ("\qualified expression required", N);
708
709 else pragma Assert (Has_Discriminants (Type_Id));
710 Error_Msg_N
711 ("\qualified expression or constraint with " &
712 "discriminant values required", N);
713 end if;
714 end if;
715 end if;
716 end if;
717 end;
718 end if;
719
720 if Is_Abstract_Type (Type_Id) then
721 Error_Msg_N ("cannot allocate abstract object", E);
722 end if;
723
724 if Has_Task (Designated_Type (Acc_Type)) then
725 Check_Restriction (No_Tasking, N);
726 Check_Restriction (Max_Tasks, N);
727 Check_Restriction (No_Task_Allocators, N);
728 end if;
729
730 -- AI05-0013-1: No_Nested_Finalization forbids allocators if the access
731 -- type is nested, and the designated type needs finalization. The rule
732 -- is conservative in that class-wide types need finalization.
733
734 if Needs_Finalization (Designated_Type (Acc_Type))
735 and then not Is_Library_Level_Entity (Acc_Type)
736 then
737 Check_Restriction (No_Nested_Finalization, N);
738 end if;
739
740 -- Check that an allocator of a nested access type doesn't create a
741 -- protected object when restriction No_Local_Protected_Objects applies.
742 -- We don't have an equivalent to Has_Task for protected types, so only
743 -- cases where the designated type itself is a protected type are
744 -- currently checked. ???
745
746 if Is_Protected_Type (Designated_Type (Acc_Type))
747 and then not Is_Library_Level_Entity (Acc_Type)
748 then
749 Check_Restriction (No_Local_Protected_Objects, N);
750 end if;
751
752 -- If the No_Streams restriction is set, check that the type of the
753 -- object is not, and does not contain, any subtype derived from
754 -- Ada.Streams.Root_Stream_Type. Note that we guard the call to
755 -- Has_Stream just for efficiency reasons. There is no point in
756 -- spending time on a Has_Stream check if the restriction is not set.
757
758 if Restriction_Check_Required (No_Streams) then
759 if Has_Stream (Designated_Type (Acc_Type)) then
760 Check_Restriction (No_Streams, N);
761 end if;
762 end if;
763
764 Set_Etype (N, Acc_Type);
765
766 if not Is_Library_Level_Entity (Acc_Type) then
767 Check_Restriction (No_Local_Allocators, N);
768 end if;
769
770 if Serious_Errors_Detected > Sav_Errs then
771 Set_Error_Posted (N);
772 Set_Etype (N, Any_Type);
773 end if;
774 end Analyze_Allocator;
775
776 ---------------------------
777 -- Analyze_Arithmetic_Op --
778 ---------------------------
779
780 procedure Analyze_Arithmetic_Op (N : Node_Id) is
781 L : constant Node_Id := Left_Opnd (N);
782 R : constant Node_Id := Right_Opnd (N);
783 Op_Id : Entity_Id;
784
785 begin
786 Candidate_Type := Empty;
787 Analyze_Expression (L);
788 Analyze_Expression (R);
789
790 -- If the entity is already set, the node is the instantiation of a
791 -- generic node with a non-local reference, or was manufactured by a
792 -- call to Make_Op_xxx. In either case the entity is known to be valid,
793 -- and we do not need to collect interpretations, instead we just get
794 -- the single possible interpretation.
795
796 Op_Id := Entity (N);
797
798 if Present (Op_Id) then
799 if Ekind (Op_Id) = E_Operator then
800
801 if Nkind_In (N, N_Op_Divide, N_Op_Mod, N_Op_Multiply, N_Op_Rem)
802 and then Treat_Fixed_As_Integer (N)
803 then
804 null;
805 else
806 Set_Etype (N, Any_Type);
807 Find_Arithmetic_Types (L, R, Op_Id, N);
808 end if;
809
810 else
811 Set_Etype (N, Any_Type);
812 Add_One_Interp (N, Op_Id, Etype (Op_Id));
813 end if;
814
815 -- Entity is not already set, so we do need to collect interpretations
816
817 else
818 Op_Id := Get_Name_Entity_Id (Chars (N));
819 Set_Etype (N, Any_Type);
820
821 while Present (Op_Id) loop
822 if Ekind (Op_Id) = E_Operator
823 and then Present (Next_Entity (First_Entity (Op_Id)))
824 then
825 Find_Arithmetic_Types (L, R, Op_Id, N);
826
827 -- The following may seem superfluous, because an operator cannot
828 -- be generic, but this ignores the cleverness of the author of
829 -- ACVC bc1013a.
830
831 elsif Is_Overloadable (Op_Id) then
832 Analyze_User_Defined_Binary_Op (N, Op_Id);
833 end if;
834
835 Op_Id := Homonym (Op_Id);
836 end loop;
837 end if;
838
839 Operator_Check (N);
840 end Analyze_Arithmetic_Op;
841
842 ------------------
843 -- Analyze_Call --
844 ------------------
845
846 -- Function, procedure, and entry calls are checked here. The Name in
847 -- the call may be overloaded. The actuals have been analyzed and may
848 -- themselves be overloaded. On exit from this procedure, the node N
849 -- may have zero, one or more interpretations. In the first case an
850 -- error message is produced. In the last case, the node is flagged
851 -- as overloaded and the interpretations are collected in All_Interp.
852
853 -- If the name is an Access_To_Subprogram, it cannot be overloaded, but
854 -- the type-checking is similar to that of other calls.
855
856 procedure Analyze_Call (N : Node_Id) is
857 Actuals : constant List_Id := Parameter_Associations (N);
858 Nam : Node_Id;
859 X : Interp_Index;
860 It : Interp;
861 Nam_Ent : Entity_Id;
862 Success : Boolean := False;
863
864 Deref : Boolean := False;
865 -- Flag indicates whether an interpretation of the prefix is a
866 -- parameterless call that returns an access_to_subprogram.
867
868 procedure Check_Mixed_Parameter_And_Named_Associations;
869 -- Check that parameter and named associations are not mixed. This is
870 -- a restriction in SPARK mode.
871
872 function Name_Denotes_Function return Boolean;
873 -- If the type of the name is an access to subprogram, this may be the
874 -- type of a name, or the return type of the function being called. If
875 -- the name is not an entity then it can denote a protected function.
876 -- Until we distinguish Etype from Return_Type, we must use this routine
877 -- to resolve the meaning of the name in the call.
878
879 procedure No_Interpretation;
880 -- Output error message when no valid interpretation exists
881
882 --------------------------------------------------
883 -- Check_Mixed_Parameter_And_Named_Associations --
884 --------------------------------------------------
885
886 procedure Check_Mixed_Parameter_And_Named_Associations is
887 Actual : Node_Id;
888 Named_Seen : Boolean;
889
890 begin
891 Named_Seen := False;
892
893 Actual := First (Actuals);
894 while Present (Actual) loop
895 case Nkind (Actual) is
896 when N_Parameter_Association =>
897 if Named_Seen then
898 Check_SPARK_Restriction
899 ("named association cannot follow positional one",
900 Actual);
901 exit;
902 end if;
903 when others =>
904 Named_Seen := True;
905 end case;
906
907 Next (Actual);
908 end loop;
909 end Check_Mixed_Parameter_And_Named_Associations;
910
911 ---------------------------
912 -- Name_Denotes_Function --
913 ---------------------------
914
915 function Name_Denotes_Function return Boolean is
916 begin
917 if Is_Entity_Name (Nam) then
918 return Ekind (Entity (Nam)) = E_Function;
919
920 elsif Nkind (Nam) = N_Selected_Component then
921 return Ekind (Entity (Selector_Name (Nam))) = E_Function;
922
923 else
924 return False;
925 end if;
926 end Name_Denotes_Function;
927
928 -----------------------
929 -- No_Interpretation --
930 -----------------------
931
932 procedure No_Interpretation is
933 L : constant Boolean := Is_List_Member (N);
934 K : constant Node_Kind := Nkind (Parent (N));
935
936 begin
937 -- If the node is in a list whose parent is not an expression then it
938 -- must be an attempted procedure call.
939
940 if L and then K not in N_Subexpr then
941 if Ekind (Entity (Nam)) = E_Generic_Procedure then
942 Error_Msg_NE
943 ("must instantiate generic procedure& before call",
944 Nam, Entity (Nam));
945 else
946 Error_Msg_N
947 ("procedure or entry name expected", Nam);
948 end if;
949
950 -- Check for tasking cases where only an entry call will do
951
952 elsif not L
953 and then Nkind_In (K, N_Entry_Call_Alternative,
954 N_Triggering_Alternative)
955 then
956 Error_Msg_N ("entry name expected", Nam);
957
958 -- Otherwise give general error message
959
960 else
961 Error_Msg_N ("invalid prefix in call", Nam);
962 end if;
963 end No_Interpretation;
964
965 -- Start of processing for Analyze_Call
966
967 begin
968 if Restriction_Check_Required (SPARK) then
969 Check_Mixed_Parameter_And_Named_Associations;
970 end if;
971
972 -- Initialize the type of the result of the call to the error type,
973 -- which will be reset if the type is successfully resolved.
974
975 Set_Etype (N, Any_Type);
976
977 Nam := Name (N);
978
979 if not Is_Overloaded (Nam) then
980
981 -- Only one interpretation to check
982
983 if Ekind (Etype (Nam)) = E_Subprogram_Type then
984 Nam_Ent := Etype (Nam);
985
986 -- If the prefix is an access_to_subprogram, this may be an indirect
987 -- call. This is the case if the name in the call is not an entity
988 -- name, or if it is a function name in the context of a procedure
989 -- call. In this latter case, we have a call to a parameterless
990 -- function that returns a pointer_to_procedure which is the entity
991 -- being called. Finally, F (X) may be a call to a parameterless
992 -- function that returns a pointer to a function with parameters.
993
994 elsif Is_Access_Type (Etype (Nam))
995 and then Ekind (Designated_Type (Etype (Nam))) = E_Subprogram_Type
996 and then
997 (not Name_Denotes_Function
998 or else Nkind (N) = N_Procedure_Call_Statement
999 or else
1000 (Nkind (Parent (N)) /= N_Explicit_Dereference
1001 and then Is_Entity_Name (Nam)
1002 and then No (First_Formal (Entity (Nam)))
1003 and then Present (Actuals)))
1004 then
1005 Nam_Ent := Designated_Type (Etype (Nam));
1006 Insert_Explicit_Dereference (Nam);
1007
1008 -- Selected component case. Simple entry or protected operation,
1009 -- where the entry name is given by the selector name.
1010
1011 elsif Nkind (Nam) = N_Selected_Component then
1012 Nam_Ent := Entity (Selector_Name (Nam));
1013
1014 if not Ekind_In (Nam_Ent, E_Entry,
1015 E_Entry_Family,
1016 E_Function,
1017 E_Procedure)
1018 then
1019 Error_Msg_N ("name in call is not a callable entity", Nam);
1020 Set_Etype (N, Any_Type);
1021 return;
1022 end if;
1023
1024 -- If the name is an Indexed component, it can be a call to a member
1025 -- of an entry family. The prefix must be a selected component whose
1026 -- selector is the entry. Analyze_Procedure_Call normalizes several
1027 -- kinds of call into this form.
1028
1029 elsif Nkind (Nam) = N_Indexed_Component then
1030 if Nkind (Prefix (Nam)) = N_Selected_Component then
1031 Nam_Ent := Entity (Selector_Name (Prefix (Nam)));
1032 else
1033 Error_Msg_N ("name in call is not a callable entity", Nam);
1034 Set_Etype (N, Any_Type);
1035 return;
1036 end if;
1037
1038 elsif not Is_Entity_Name (Nam) then
1039 Error_Msg_N ("name in call is not a callable entity", Nam);
1040 Set_Etype (N, Any_Type);
1041 return;
1042
1043 else
1044 Nam_Ent := Entity (Nam);
1045
1046 -- If no interpretations, give error message
1047
1048 if not Is_Overloadable (Nam_Ent) then
1049 No_Interpretation;
1050 return;
1051 end if;
1052 end if;
1053
1054 -- Operations generated for RACW stub types are called only through
1055 -- dispatching, and can never be the static interpretation of a call.
1056
1057 if Is_RACW_Stub_Type_Operation (Nam_Ent) then
1058 No_Interpretation;
1059 return;
1060 end if;
1061
1062 Analyze_One_Call (N, Nam_Ent, True, Success);
1063
1064 -- If this is an indirect call, the return type of the access_to
1065 -- subprogram may be an incomplete type. At the point of the call,
1066 -- use the full type if available, and at the same time update the
1067 -- return type of the access_to_subprogram.
1068
1069 if Success
1070 and then Nkind (Nam) = N_Explicit_Dereference
1071 and then Ekind (Etype (N)) = E_Incomplete_Type
1072 and then Present (Full_View (Etype (N)))
1073 then
1074 Set_Etype (N, Full_View (Etype (N)));
1075 Set_Etype (Nam_Ent, Etype (N));
1076 end if;
1077
1078 else
1079 -- An overloaded selected component must denote overloaded operations
1080 -- of a concurrent type. The interpretations are attached to the
1081 -- simple name of those operations.
1082
1083 if Nkind (Nam) = N_Selected_Component then
1084 Nam := Selector_Name (Nam);
1085 end if;
1086
1087 Get_First_Interp (Nam, X, It);
1088
1089 while Present (It.Nam) loop
1090 Nam_Ent := It.Nam;
1091 Deref := False;
1092
1093 -- Name may be call that returns an access to subprogram, or more
1094 -- generally an overloaded expression one of whose interpretations
1095 -- yields an access to subprogram. If the name is an entity, we do
1096 -- not dereference, because the node is a call that returns the
1097 -- access type: note difference between f(x), where the call may
1098 -- return an access subprogram type, and f(x)(y), where the type
1099 -- returned by the call to f is implicitly dereferenced to analyze
1100 -- the outer call.
1101
1102 if Is_Access_Type (Nam_Ent) then
1103 Nam_Ent := Designated_Type (Nam_Ent);
1104
1105 elsif Is_Access_Type (Etype (Nam_Ent))
1106 and then
1107 (not Is_Entity_Name (Nam)
1108 or else Nkind (N) = N_Procedure_Call_Statement)
1109 and then Ekind (Designated_Type (Etype (Nam_Ent)))
1110 = E_Subprogram_Type
1111 then
1112 Nam_Ent := Designated_Type (Etype (Nam_Ent));
1113
1114 if Is_Entity_Name (Nam) then
1115 Deref := True;
1116 end if;
1117 end if;
1118
1119 -- If the call has been rewritten from a prefixed call, the first
1120 -- parameter has been analyzed, but may need a subsequent
1121 -- dereference, so skip its analysis now.
1122
1123 if N /= Original_Node (N)
1124 and then Nkind (Original_Node (N)) = Nkind (N)
1125 and then Nkind (Name (N)) /= Nkind (Name (Original_Node (N)))
1126 and then Present (Parameter_Associations (N))
1127 and then Present (Etype (First (Parameter_Associations (N))))
1128 then
1129 Analyze_One_Call
1130 (N, Nam_Ent, False, Success, Skip_First => True);
1131 else
1132 Analyze_One_Call (N, Nam_Ent, False, Success);
1133 end if;
1134
1135 -- If the interpretation succeeds, mark the proper type of the
1136 -- prefix (any valid candidate will do). If not, remove the
1137 -- candidate interpretation. This only needs to be done for
1138 -- overloaded protected operations, for other entities disambi-
1139 -- guation is done directly in Resolve.
1140
1141 if Success then
1142 if Deref
1143 and then Nkind (Parent (N)) /= N_Explicit_Dereference
1144 then
1145 Set_Entity (Nam, It.Nam);
1146 Insert_Explicit_Dereference (Nam);
1147 Set_Etype (Nam, Nam_Ent);
1148
1149 else
1150 Set_Etype (Nam, It.Typ);
1151 end if;
1152
1153 elsif Nkind_In (Name (N), N_Selected_Component,
1154 N_Function_Call)
1155 then
1156 Remove_Interp (X);
1157 end if;
1158
1159 Get_Next_Interp (X, It);
1160 end loop;
1161
1162 -- If the name is the result of a function call, it can only
1163 -- be a call to a function returning an access to subprogram.
1164 -- Insert explicit dereference.
1165
1166 if Nkind (Nam) = N_Function_Call then
1167 Insert_Explicit_Dereference (Nam);
1168 end if;
1169
1170 if Etype (N) = Any_Type then
1171
1172 -- None of the interpretations is compatible with the actuals
1173
1174 Diagnose_Call (N, Nam);
1175
1176 -- Special checks for uninstantiated put routines
1177
1178 if Nkind (N) = N_Procedure_Call_Statement
1179 and then Is_Entity_Name (Nam)
1180 and then Chars (Nam) = Name_Put
1181 and then List_Length (Actuals) = 1
1182 then
1183 declare
1184 Arg : constant Node_Id := First (Actuals);
1185 Typ : Entity_Id;
1186
1187 begin
1188 if Nkind (Arg) = N_Parameter_Association then
1189 Typ := Etype (Explicit_Actual_Parameter (Arg));
1190 else
1191 Typ := Etype (Arg);
1192 end if;
1193
1194 if Is_Signed_Integer_Type (Typ) then
1195 Error_Msg_N
1196 ("possible missing instantiation of " &
1197 "'Text_'I'O.'Integer_'I'O!", Nam);
1198
1199 elsif Is_Modular_Integer_Type (Typ) then
1200 Error_Msg_N
1201 ("possible missing instantiation of " &
1202 "'Text_'I'O.'Modular_'I'O!", Nam);
1203
1204 elsif Is_Floating_Point_Type (Typ) then
1205 Error_Msg_N
1206 ("possible missing instantiation of " &
1207 "'Text_'I'O.'Float_'I'O!", Nam);
1208
1209 elsif Is_Ordinary_Fixed_Point_Type (Typ) then
1210 Error_Msg_N
1211 ("possible missing instantiation of " &
1212 "'Text_'I'O.'Fixed_'I'O!", Nam);
1213
1214 elsif Is_Decimal_Fixed_Point_Type (Typ) then
1215 Error_Msg_N
1216 ("possible missing instantiation of " &
1217 "'Text_'I'O.'Decimal_'I'O!", Nam);
1218
1219 elsif Is_Enumeration_Type (Typ) then
1220 Error_Msg_N
1221 ("possible missing instantiation of " &
1222 "'Text_'I'O.'Enumeration_'I'O!", Nam);
1223 end if;
1224 end;
1225 end if;
1226
1227 elsif not Is_Overloaded (N)
1228 and then Is_Entity_Name (Nam)
1229 then
1230 -- Resolution yields a single interpretation. Verify that the
1231 -- reference has capitalization consistent with the declaration.
1232
1233 Set_Entity_With_Style_Check (Nam, Entity (Nam));
1234 Generate_Reference (Entity (Nam), Nam);
1235
1236 Set_Etype (Nam, Etype (Entity (Nam)));
1237 else
1238 Remove_Abstract_Operations (N);
1239 end if;
1240
1241 End_Interp_List;
1242 end if;
1243 end Analyze_Call;
1244
1245 -----------------------------
1246 -- Analyze_Case_Expression --
1247 -----------------------------
1248
1249 procedure Analyze_Case_Expression (N : Node_Id) is
1250 Expr : constant Node_Id := Expression (N);
1251 FirstX : constant Node_Id := Expression (First (Alternatives (N)));
1252 Alt : Node_Id;
1253 Exp_Type : Entity_Id;
1254 Exp_Btype : Entity_Id;
1255
1256 Dont_Care : Boolean;
1257 Others_Present : Boolean;
1258
1259 procedure Non_Static_Choice_Error (Choice : Node_Id);
1260 -- Error routine invoked by the generic instantiation below when
1261 -- the case expression has a non static choice.
1262
1263 package Case_Choices_Processing is new
1264 Generic_Choices_Processing
1265 (Get_Alternatives => Alternatives,
1266 Get_Choices => Discrete_Choices,
1267 Process_Empty_Choice => No_OP,
1268 Process_Non_Static_Choice => Non_Static_Choice_Error,
1269 Process_Associated_Node => No_OP);
1270 use Case_Choices_Processing;
1271
1272 -----------------------------
1273 -- Non_Static_Choice_Error --
1274 -----------------------------
1275
1276 procedure Non_Static_Choice_Error (Choice : Node_Id) is
1277 begin
1278 Flag_Non_Static_Expr
1279 ("choice given in case expression is not static!", Choice);
1280 end Non_Static_Choice_Error;
1281
1282 -- Start of processing for Analyze_Case_Expression
1283
1284 begin
1285 if Comes_From_Source (N) then
1286 Check_Compiler_Unit (N);
1287 end if;
1288
1289 Analyze_And_Resolve (Expr, Any_Discrete);
1290 Check_Unset_Reference (Expr);
1291 Exp_Type := Etype (Expr);
1292 Exp_Btype := Base_Type (Exp_Type);
1293
1294 Alt := First (Alternatives (N));
1295 while Present (Alt) loop
1296 Analyze (Expression (Alt));
1297 Next (Alt);
1298 end loop;
1299
1300 if not Is_Overloaded (FirstX) then
1301 Set_Etype (N, Etype (FirstX));
1302
1303 else
1304 declare
1305 I : Interp_Index;
1306 It : Interp;
1307
1308 begin
1309 Set_Etype (N, Any_Type);
1310
1311 Get_First_Interp (FirstX, I, It);
1312 while Present (It.Nam) loop
1313
1314 -- For each interpretation of the first expression, we only
1315 -- add the interpretation if every other expression in the
1316 -- case expression alternatives has a compatible type.
1317
1318 Alt := Next (First (Alternatives (N)));
1319 while Present (Alt) loop
1320 exit when not Has_Compatible_Type (Expression (Alt), It.Typ);
1321 Next (Alt);
1322 end loop;
1323
1324 if No (Alt) then
1325 Add_One_Interp (N, It.Typ, It.Typ);
1326 end if;
1327
1328 Get_Next_Interp (I, It);
1329 end loop;
1330 end;
1331 end if;
1332
1333 Exp_Btype := Base_Type (Exp_Type);
1334
1335 -- The expression must be of a discrete type which must be determinable
1336 -- independently of the context in which the expression occurs, but
1337 -- using the fact that the expression must be of a discrete type.
1338 -- Moreover, the type this expression must not be a character literal
1339 -- (which is always ambiguous).
1340
1341 -- If error already reported by Resolve, nothing more to do
1342
1343 if Exp_Btype = Any_Discrete
1344 or else Exp_Btype = Any_Type
1345 then
1346 return;
1347
1348 elsif Exp_Btype = Any_Character then
1349 Error_Msg_N
1350 ("character literal as case expression is ambiguous", Expr);
1351 return;
1352 end if;
1353
1354 -- If the case expression is a formal object of mode in out, then
1355 -- treat it as having a nonstatic subtype by forcing use of the base
1356 -- type (which has to get passed to Check_Case_Choices below). Also
1357 -- use base type when the case expression is parenthesized.
1358
1359 if Paren_Count (Expr) > 0
1360 or else (Is_Entity_Name (Expr)
1361 and then Ekind (Entity (Expr)) = E_Generic_In_Out_Parameter)
1362 then
1363 Exp_Type := Exp_Btype;
1364 end if;
1365
1366 -- Call instantiated Analyze_Choices which does the rest of the work
1367
1368 Analyze_Choices (N, Exp_Type, Dont_Care, Others_Present);
1369
1370 if Exp_Type = Universal_Integer and then not Others_Present then
1371 Error_Msg_N
1372 ("case on universal integer requires OTHERS choice", Expr);
1373 end if;
1374 end Analyze_Case_Expression;
1375
1376 ---------------------------
1377 -- Analyze_Comparison_Op --
1378 ---------------------------
1379
1380 procedure Analyze_Comparison_Op (N : Node_Id) is
1381 L : constant Node_Id := Left_Opnd (N);
1382 R : constant Node_Id := Right_Opnd (N);
1383 Op_Id : Entity_Id := Entity (N);
1384
1385 begin
1386 Set_Etype (N, Any_Type);
1387 Candidate_Type := Empty;
1388
1389 Analyze_Expression (L);
1390 Analyze_Expression (R);
1391
1392 if Present (Op_Id) then
1393 if Ekind (Op_Id) = E_Operator then
1394 Find_Comparison_Types (L, R, Op_Id, N);
1395 else
1396 Add_One_Interp (N, Op_Id, Etype (Op_Id));
1397 end if;
1398
1399 if Is_Overloaded (L) then
1400 Set_Etype (L, Intersect_Types (L, R));
1401 end if;
1402
1403 else
1404 Op_Id := Get_Name_Entity_Id (Chars (N));
1405 while Present (Op_Id) loop
1406 if Ekind (Op_Id) = E_Operator then
1407 Find_Comparison_Types (L, R, Op_Id, N);
1408 else
1409 Analyze_User_Defined_Binary_Op (N, Op_Id);
1410 end if;
1411
1412 Op_Id := Homonym (Op_Id);
1413 end loop;
1414 end if;
1415
1416 Operator_Check (N);
1417 end Analyze_Comparison_Op;
1418
1419 ---------------------------
1420 -- Analyze_Concatenation --
1421 ---------------------------
1422
1423 procedure Analyze_Concatenation (N : Node_Id) is
1424
1425 -- We wish to avoid deep recursion, because concatenations are often
1426 -- deeply nested, as in A&B&...&Z. Therefore, we walk down the left
1427 -- operands nonrecursively until we find something that is not a
1428 -- concatenation (A in this case), or has already been analyzed. We
1429 -- analyze that, and then walk back up the tree following Parent
1430 -- pointers, calling Analyze_Concatenation_Rest to do the rest of the
1431 -- work at each level. The Parent pointers allow us to avoid recursion,
1432 -- and thus avoid running out of memory.
1433
1434 NN : Node_Id := N;
1435 L : Node_Id;
1436
1437 begin
1438 Candidate_Type := Empty;
1439
1440 -- The following code is equivalent to:
1441
1442 -- Set_Etype (N, Any_Type);
1443 -- Analyze_Expression (Left_Opnd (N));
1444 -- Analyze_Concatenation_Rest (N);
1445
1446 -- where the Analyze_Expression call recurses back here if the left
1447 -- operand is a concatenation.
1448
1449 -- Walk down left operands
1450
1451 loop
1452 Set_Etype (NN, Any_Type);
1453 L := Left_Opnd (NN);
1454 exit when Nkind (L) /= N_Op_Concat or else Analyzed (L);
1455 NN := L;
1456 end loop;
1457
1458 -- Now (given the above example) NN is A&B and L is A
1459
1460 -- First analyze L ...
1461
1462 Analyze_Expression (L);
1463
1464 -- ... then walk NN back up until we reach N (where we started), calling
1465 -- Analyze_Concatenation_Rest along the way.
1466
1467 loop
1468 Analyze_Concatenation_Rest (NN);
1469 exit when NN = N;
1470 NN := Parent (NN);
1471 end loop;
1472 end Analyze_Concatenation;
1473
1474 --------------------------------
1475 -- Analyze_Concatenation_Rest --
1476 --------------------------------
1477
1478 -- If the only one-dimensional array type in scope is String,
1479 -- this is the resulting type of the operation. Otherwise there
1480 -- will be a concatenation operation defined for each user-defined
1481 -- one-dimensional array.
1482
1483 procedure Analyze_Concatenation_Rest (N : Node_Id) is
1484 L : constant Node_Id := Left_Opnd (N);
1485 R : constant Node_Id := Right_Opnd (N);
1486 Op_Id : Entity_Id := Entity (N);
1487 LT : Entity_Id;
1488 RT : Entity_Id;
1489
1490 begin
1491 Analyze_Expression (R);
1492
1493 -- If the entity is present, the node appears in an instance, and
1494 -- denotes a predefined concatenation operation. The resulting type is
1495 -- obtained from the arguments when possible. If the arguments are
1496 -- aggregates, the array type and the concatenation type must be
1497 -- visible.
1498
1499 if Present (Op_Id) then
1500 if Ekind (Op_Id) = E_Operator then
1501 LT := Base_Type (Etype (L));
1502 RT := Base_Type (Etype (R));
1503
1504 if Is_Array_Type (LT)
1505 and then (RT = LT or else RT = Base_Type (Component_Type (LT)))
1506 then
1507 Add_One_Interp (N, Op_Id, LT);
1508
1509 elsif Is_Array_Type (RT)
1510 and then LT = Base_Type (Component_Type (RT))
1511 then
1512 Add_One_Interp (N, Op_Id, RT);
1513
1514 -- If one operand is a string type or a user-defined array type,
1515 -- and the other is a literal, result is of the specific type.
1516
1517 elsif
1518 (Root_Type (LT) = Standard_String
1519 or else Scope (LT) /= Standard_Standard)
1520 and then Etype (R) = Any_String
1521 then
1522 Add_One_Interp (N, Op_Id, LT);
1523
1524 elsif
1525 (Root_Type (RT) = Standard_String
1526 or else Scope (RT) /= Standard_Standard)
1527 and then Etype (L) = Any_String
1528 then
1529 Add_One_Interp (N, Op_Id, RT);
1530
1531 elsif not Is_Generic_Type (Etype (Op_Id)) then
1532 Add_One_Interp (N, Op_Id, Etype (Op_Id));
1533
1534 else
1535 -- Type and its operations must be visible
1536
1537 Set_Entity (N, Empty);
1538 Analyze_Concatenation (N);
1539 end if;
1540
1541 else
1542 Add_One_Interp (N, Op_Id, Etype (Op_Id));
1543 end if;
1544
1545 else
1546 Op_Id := Get_Name_Entity_Id (Name_Op_Concat);
1547 while Present (Op_Id) loop
1548 if Ekind (Op_Id) = E_Operator then
1549
1550 -- Do not consider operators declared in dead code, they can
1551 -- not be part of the resolution.
1552
1553 if Is_Eliminated (Op_Id) then
1554 null;
1555 else
1556 Find_Concatenation_Types (L, R, Op_Id, N);
1557 end if;
1558
1559 else
1560 Analyze_User_Defined_Binary_Op (N, Op_Id);
1561 end if;
1562
1563 Op_Id := Homonym (Op_Id);
1564 end loop;
1565 end if;
1566
1567 Operator_Check (N);
1568 end Analyze_Concatenation_Rest;
1569
1570 -------------------------
1571 -- Analyze_Equality_Op --
1572 -------------------------
1573
1574 procedure Analyze_Equality_Op (N : Node_Id) is
1575 Loc : constant Source_Ptr := Sloc (N);
1576 L : constant Node_Id := Left_Opnd (N);
1577 R : constant Node_Id := Right_Opnd (N);
1578 Op_Id : Entity_Id;
1579
1580 begin
1581 Set_Etype (N, Any_Type);
1582 Candidate_Type := Empty;
1583
1584 Analyze_Expression (L);
1585 Analyze_Expression (R);
1586
1587 -- If the entity is set, the node is a generic instance with a non-local
1588 -- reference to the predefined operator or to a user-defined function.
1589 -- It can also be an inequality that is expanded into the negation of a
1590 -- call to a user-defined equality operator.
1591
1592 -- For the predefined case, the result is Boolean, regardless of the
1593 -- type of the operands. The operands may even be limited, if they are
1594 -- generic actuals. If they are overloaded, label the left argument with
1595 -- the common type that must be present, or with the type of the formal
1596 -- of the user-defined function.
1597
1598 if Present (Entity (N)) then
1599 Op_Id := Entity (N);
1600
1601 if Ekind (Op_Id) = E_Operator then
1602 Add_One_Interp (N, Op_Id, Standard_Boolean);
1603 else
1604 Add_One_Interp (N, Op_Id, Etype (Op_Id));
1605 end if;
1606
1607 if Is_Overloaded (L) then
1608 if Ekind (Op_Id) = E_Operator then
1609 Set_Etype (L, Intersect_Types (L, R));
1610 else
1611 Set_Etype (L, Etype (First_Formal (Op_Id)));
1612 end if;
1613 end if;
1614
1615 else
1616 Op_Id := Get_Name_Entity_Id (Chars (N));
1617 while Present (Op_Id) loop
1618 if Ekind (Op_Id) = E_Operator then
1619 Find_Equality_Types (L, R, Op_Id, N);
1620 else
1621 Analyze_User_Defined_Binary_Op (N, Op_Id);
1622 end if;
1623
1624 Op_Id := Homonym (Op_Id);
1625 end loop;
1626 end if;
1627
1628 -- If there was no match, and the operator is inequality, this may
1629 -- be a case where inequality has not been made explicit, as for
1630 -- tagged types. Analyze the node as the negation of an equality
1631 -- operation. This cannot be done earlier, because before analysis
1632 -- we cannot rule out the presence of an explicit inequality.
1633
1634 if Etype (N) = Any_Type
1635 and then Nkind (N) = N_Op_Ne
1636 then
1637 Op_Id := Get_Name_Entity_Id (Name_Op_Eq);
1638 while Present (Op_Id) loop
1639 if Ekind (Op_Id) = E_Operator then
1640 Find_Equality_Types (L, R, Op_Id, N);
1641 else
1642 Analyze_User_Defined_Binary_Op (N, Op_Id);
1643 end if;
1644
1645 Op_Id := Homonym (Op_Id);
1646 end loop;
1647
1648 if Etype (N) /= Any_Type then
1649 Op_Id := Entity (N);
1650
1651 Rewrite (N,
1652 Make_Op_Not (Loc,
1653 Right_Opnd =>
1654 Make_Op_Eq (Loc,
1655 Left_Opnd => Left_Opnd (N),
1656 Right_Opnd => Right_Opnd (N))));
1657
1658 Set_Entity (Right_Opnd (N), Op_Id);
1659 Analyze (N);
1660 end if;
1661 end if;
1662
1663 Operator_Check (N);
1664 end Analyze_Equality_Op;
1665
1666 ----------------------------------
1667 -- Analyze_Explicit_Dereference --
1668 ----------------------------------
1669
1670 procedure Analyze_Explicit_Dereference (N : Node_Id) is
1671 Loc : constant Source_Ptr := Sloc (N);
1672 P : constant Node_Id := Prefix (N);
1673 T : Entity_Id;
1674 I : Interp_Index;
1675 It : Interp;
1676 New_N : Node_Id;
1677
1678 function Is_Function_Type return Boolean;
1679 -- Check whether node may be interpreted as an implicit function call
1680
1681 ----------------------
1682 -- Is_Function_Type --
1683 ----------------------
1684
1685 function Is_Function_Type return Boolean is
1686 I : Interp_Index;
1687 It : Interp;
1688
1689 begin
1690 if not Is_Overloaded (N) then
1691 return Ekind (Base_Type (Etype (N))) = E_Subprogram_Type
1692 and then Etype (Base_Type (Etype (N))) /= Standard_Void_Type;
1693
1694 else
1695 Get_First_Interp (N, I, It);
1696 while Present (It.Nam) loop
1697 if Ekind (Base_Type (It.Typ)) /= E_Subprogram_Type
1698 or else Etype (Base_Type (It.Typ)) = Standard_Void_Type
1699 then
1700 return False;
1701 end if;
1702
1703 Get_Next_Interp (I, It);
1704 end loop;
1705
1706 return True;
1707 end if;
1708 end Is_Function_Type;
1709
1710 -- Start of processing for Analyze_Explicit_Dereference
1711
1712 begin
1713 -- If source node, check SPARK restriction. We guard this with the
1714 -- source node check, because ???
1715
1716 if Comes_From_Source (N) then
1717 Check_SPARK_Restriction ("explicit dereference is not allowed", N);
1718 end if;
1719
1720 -- In formal verification mode, keep track of all reads and writes
1721 -- through explicit dereferences.
1722
1723 if Alfa_Mode then
1724 Alfa.Generate_Dereference (N);
1725 end if;
1726
1727 Analyze (P);
1728 Set_Etype (N, Any_Type);
1729
1730 -- Test for remote access to subprogram type, and if so return
1731 -- after rewriting the original tree.
1732
1733 if Remote_AST_E_Dereference (P) then
1734 return;
1735 end if;
1736
1737 -- Normal processing for other than remote access to subprogram type
1738
1739 if not Is_Overloaded (P) then
1740 if Is_Access_Type (Etype (P)) then
1741
1742 -- Set the Etype. We need to go through Is_For_Access_Subtypes to
1743 -- avoid other problems caused by the Private_Subtype and it is
1744 -- safe to go to the Base_Type because this is the same as
1745 -- converting the access value to its Base_Type.
1746
1747 declare
1748 DT : Entity_Id := Designated_Type (Etype (P));
1749
1750 begin
1751 if Ekind (DT) = E_Private_Subtype
1752 and then Is_For_Access_Subtype (DT)
1753 then
1754 DT := Base_Type (DT);
1755 end if;
1756
1757 -- An explicit dereference is a legal occurrence of an
1758 -- incomplete type imported through a limited_with clause,
1759 -- if the full view is visible.
1760
1761 if From_With_Type (DT)
1762 and then not From_With_Type (Scope (DT))
1763 and then
1764 (Is_Immediately_Visible (Scope (DT))
1765 or else
1766 (Is_Child_Unit (Scope (DT))
1767 and then Is_Visible_Child_Unit (Scope (DT))))
1768 then
1769 Set_Etype (N, Available_View (DT));
1770
1771 else
1772 Set_Etype (N, DT);
1773 end if;
1774 end;
1775
1776 elsif Etype (P) /= Any_Type then
1777 Error_Msg_N ("prefix of dereference must be an access type", N);
1778 return;
1779 end if;
1780
1781 else
1782 Get_First_Interp (P, I, It);
1783 while Present (It.Nam) loop
1784 T := It.Typ;
1785
1786 if Is_Access_Type (T) then
1787 Add_One_Interp (N, Designated_Type (T), Designated_Type (T));
1788 end if;
1789
1790 Get_Next_Interp (I, It);
1791 end loop;
1792
1793 -- Error if no interpretation of the prefix has an access type
1794
1795 if Etype (N) = Any_Type then
1796 Error_Msg_N
1797 ("access type required in prefix of explicit dereference", P);
1798 Set_Etype (N, Any_Type);
1799 return;
1800 end if;
1801 end if;
1802
1803 if Is_Function_Type
1804 and then Nkind (Parent (N)) /= N_Indexed_Component
1805
1806 and then (Nkind (Parent (N)) /= N_Function_Call
1807 or else N /= Name (Parent (N)))
1808
1809 and then (Nkind (Parent (N)) /= N_Procedure_Call_Statement
1810 or else N /= Name (Parent (N)))
1811
1812 and then Nkind (Parent (N)) /= N_Subprogram_Renaming_Declaration
1813 and then (Nkind (Parent (N)) /= N_Attribute_Reference
1814 or else
1815 (Attribute_Name (Parent (N)) /= Name_Address
1816 and then
1817 Attribute_Name (Parent (N)) /= Name_Access))
1818 then
1819 -- Name is a function call with no actuals, in a context that
1820 -- requires deproceduring (including as an actual in an enclosing
1821 -- function or procedure call). There are some pathological cases
1822 -- where the prefix might include functions that return access to
1823 -- subprograms and others that return a regular type. Disambiguation
1824 -- of those has to take place in Resolve.
1825
1826 New_N :=
1827 Make_Function_Call (Loc,
1828 Name => Make_Explicit_Dereference (Loc, P),
1829 Parameter_Associations => New_List);
1830
1831 -- If the prefix is overloaded, remove operations that have formals,
1832 -- we know that this is a parameterless call.
1833
1834 if Is_Overloaded (P) then
1835 Get_First_Interp (P, I, It);
1836 while Present (It.Nam) loop
1837 T := It.Typ;
1838
1839 if No (First_Formal (Base_Type (Designated_Type (T)))) then
1840 Set_Etype (P, T);
1841 else
1842 Remove_Interp (I);
1843 end if;
1844
1845 Get_Next_Interp (I, It);
1846 end loop;
1847 end if;
1848
1849 Rewrite (N, New_N);
1850 Analyze (N);
1851
1852 elsif not Is_Function_Type
1853 and then Is_Overloaded (N)
1854 then
1855 -- The prefix may include access to subprograms and other access
1856 -- types. If the context selects the interpretation that is a
1857 -- function call (not a procedure call) we cannot rewrite the node
1858 -- yet, but we include the result of the call interpretation.
1859
1860 Get_First_Interp (N, I, It);
1861 while Present (It.Nam) loop
1862 if Ekind (Base_Type (It.Typ)) = E_Subprogram_Type
1863 and then Etype (Base_Type (It.Typ)) /= Standard_Void_Type
1864 and then Nkind (Parent (N)) /= N_Procedure_Call_Statement
1865 then
1866 Add_One_Interp (N, Etype (It.Typ), Etype (It.Typ));
1867 end if;
1868
1869 Get_Next_Interp (I, It);
1870 end loop;
1871 end if;
1872
1873 -- A value of remote access-to-class-wide must not be dereferenced
1874 -- (RM E.2.2(16)).
1875
1876 Validate_Remote_Access_To_Class_Wide_Type (N);
1877 end Analyze_Explicit_Dereference;
1878
1879 ------------------------
1880 -- Analyze_Expression --
1881 ------------------------
1882
1883 procedure Analyze_Expression (N : Node_Id) is
1884 begin
1885 Analyze (N);
1886 Check_Parameterless_Call (N);
1887 end Analyze_Expression;
1888
1889 -------------------------------------
1890 -- Analyze_Expression_With_Actions --
1891 -------------------------------------
1892
1893 procedure Analyze_Expression_With_Actions (N : Node_Id) is
1894 A : Node_Id;
1895
1896 begin
1897 A := First (Actions (N));
1898 loop
1899 Analyze (A);
1900 Next (A);
1901 exit when No (A);
1902 end loop;
1903
1904 Analyze_Expression (Expression (N));
1905 Set_Etype (N, Etype (Expression (N)));
1906 end Analyze_Expression_With_Actions;
1907
1908 ---------------------------
1909 -- Analyze_If_Expression --
1910 ---------------------------
1911
1912 procedure Analyze_If_Expression (N : Node_Id) is
1913 Condition : constant Node_Id := First (Expressions (N));
1914 Then_Expr : constant Node_Id := Next (Condition);
1915 Else_Expr : Node_Id;
1916
1917 begin
1918 -- Defend against error of missing expressions from previous error
1919
1920 if No (Then_Expr) then
1921 Check_Error_Detected;
1922 return;
1923 end if;
1924
1925 Check_SPARK_Restriction ("if expression is not allowed", N);
1926
1927 Else_Expr := Next (Then_Expr);
1928
1929 if Comes_From_Source (N) then
1930 Check_Compiler_Unit (N);
1931 end if;
1932
1933 Analyze_Expression (Condition);
1934 Analyze_Expression (Then_Expr);
1935
1936 if Present (Else_Expr) then
1937 Analyze_Expression (Else_Expr);
1938 end if;
1939
1940 -- If then expression not overloaded, then that decides the type
1941
1942 if not Is_Overloaded (Then_Expr) then
1943 Set_Etype (N, Etype (Then_Expr));
1944
1945 -- Case where then expression is overloaded
1946
1947 else
1948 declare
1949 I : Interp_Index;
1950 It : Interp;
1951
1952 begin
1953 Set_Etype (N, Any_Type);
1954
1955 -- Shouldn't the following statement be down in the ELSE of the
1956 -- following loop? ???
1957
1958 Get_First_Interp (Then_Expr, I, It);
1959
1960 -- if no Else_Expression the conditional must be boolean
1961
1962 if No (Else_Expr) then
1963 Set_Etype (N, Standard_Boolean);
1964
1965 -- Else_Expression Present. For each possible intepretation of
1966 -- the Then_Expression, add it only if the Else_Expression has
1967 -- a compatible type.
1968
1969 else
1970 while Present (It.Nam) loop
1971 if Has_Compatible_Type (Else_Expr, It.Typ) then
1972 Add_One_Interp (N, It.Typ, It.Typ);
1973 end if;
1974
1975 Get_Next_Interp (I, It);
1976 end loop;
1977 end if;
1978 end;
1979 end if;
1980 end Analyze_If_Expression;
1981
1982 ------------------------------------
1983 -- Analyze_Indexed_Component_Form --
1984 ------------------------------------
1985
1986 procedure Analyze_Indexed_Component_Form (N : Node_Id) is
1987 P : constant Node_Id := Prefix (N);
1988 Exprs : constant List_Id := Expressions (N);
1989 Exp : Node_Id;
1990 P_T : Entity_Id;
1991 E : Node_Id;
1992 U_N : Entity_Id;
1993
1994 procedure Process_Function_Call;
1995 -- Prefix in indexed component form is an overloadable entity,
1996 -- so the node is a function call. Reformat it as such.
1997
1998 procedure Process_Indexed_Component;
1999 -- Prefix in indexed component form is actually an indexed component.
2000 -- This routine processes it, knowing that the prefix is already
2001 -- resolved.
2002
2003 procedure Process_Indexed_Component_Or_Slice;
2004 -- An indexed component with a single index may designate a slice if
2005 -- the index is a subtype mark. This routine disambiguates these two
2006 -- cases by resolving the prefix to see if it is a subtype mark.
2007
2008 procedure Process_Overloaded_Indexed_Component;
2009 -- If the prefix of an indexed component is overloaded, the proper
2010 -- interpretation is selected by the index types and the context.
2011
2012 ---------------------------
2013 -- Process_Function_Call --
2014 ---------------------------
2015
2016 procedure Process_Function_Call is
2017 Actual : Node_Id;
2018
2019 begin
2020 Change_Node (N, N_Function_Call);
2021 Set_Name (N, P);
2022 Set_Parameter_Associations (N, Exprs);
2023
2024 -- Analyze actuals prior to analyzing the call itself
2025
2026 Actual := First (Parameter_Associations (N));
2027 while Present (Actual) loop
2028 Analyze (Actual);
2029 Check_Parameterless_Call (Actual);
2030
2031 -- Move to next actual. Note that we use Next, not Next_Actual
2032 -- here. The reason for this is a bit subtle. If a function call
2033 -- includes named associations, the parser recognizes the node as
2034 -- a call, and it is analyzed as such. If all associations are
2035 -- positional, the parser builds an indexed_component node, and
2036 -- it is only after analysis of the prefix that the construct
2037 -- is recognized as a call, in which case Process_Function_Call
2038 -- rewrites the node and analyzes the actuals. If the list of
2039 -- actuals is malformed, the parser may leave the node as an
2040 -- indexed component (despite the presence of named associations).
2041 -- The iterator Next_Actual is equivalent to Next if the list is
2042 -- positional, but follows the normalized chain of actuals when
2043 -- named associations are present. In this case normalization has
2044 -- not taken place, and actuals remain unanalyzed, which leads to
2045 -- subsequent crashes or loops if there is an attempt to continue
2046 -- analysis of the program.
2047
2048 Next (Actual);
2049 end loop;
2050
2051 Analyze_Call (N);
2052 end Process_Function_Call;
2053
2054 -------------------------------
2055 -- Process_Indexed_Component --
2056 -------------------------------
2057
2058 procedure Process_Indexed_Component is
2059 Exp : Node_Id;
2060 Array_Type : Entity_Id;
2061 Index : Node_Id;
2062 Pent : Entity_Id := Empty;
2063
2064 begin
2065 Exp := First (Exprs);
2066
2067 if Is_Overloaded (P) then
2068 Process_Overloaded_Indexed_Component;
2069
2070 else
2071 Array_Type := Etype (P);
2072
2073 if Is_Entity_Name (P) then
2074 Pent := Entity (P);
2075 elsif Nkind (P) = N_Selected_Component
2076 and then Is_Entity_Name (Selector_Name (P))
2077 then
2078 Pent := Entity (Selector_Name (P));
2079 end if;
2080
2081 -- Prefix must be appropriate for an array type, taking into
2082 -- account a possible implicit dereference.
2083
2084 if Is_Access_Type (Array_Type) then
2085 Error_Msg_NW (Warn_On_Dereference, "?implicit dereference", N);
2086 Array_Type := Process_Implicit_Dereference_Prefix (Pent, P);
2087 end if;
2088
2089 if Is_Array_Type (Array_Type) then
2090 null;
2091
2092 elsif Present (Pent) and then Ekind (Pent) = E_Entry_Family then
2093 Analyze (Exp);
2094 Set_Etype (N, Any_Type);
2095
2096 if not Has_Compatible_Type
2097 (Exp, Entry_Index_Type (Pent))
2098 then
2099 Error_Msg_N ("invalid index type in entry name", N);
2100
2101 elsif Present (Next (Exp)) then
2102 Error_Msg_N ("too many subscripts in entry reference", N);
2103
2104 else
2105 Set_Etype (N, Etype (P));
2106 end if;
2107
2108 return;
2109
2110 elsif Is_Record_Type (Array_Type)
2111 and then Remote_AST_I_Dereference (P)
2112 then
2113 return;
2114
2115 elsif Try_Container_Indexing (N, P, Exprs) then
2116 return;
2117
2118 elsif Array_Type = Any_Type then
2119 Set_Etype (N, Any_Type);
2120
2121 -- In most cases the analysis of the prefix will have emitted
2122 -- an error already, but if the prefix may be interpreted as a
2123 -- call in prefixed notation, the report is left to the caller.
2124 -- To prevent cascaded errors, report only if no previous ones.
2125
2126 if Serious_Errors_Detected = 0 then
2127 Error_Msg_N ("invalid prefix in indexed component", P);
2128
2129 if Nkind (P) = N_Expanded_Name then
2130 Error_Msg_NE ("\& is not visible", P, Selector_Name (P));
2131 end if;
2132 end if;
2133
2134 return;
2135
2136 -- Here we definitely have a bad indexing
2137
2138 else
2139 if Nkind (Parent (N)) = N_Requeue_Statement
2140 and then Present (Pent) and then Ekind (Pent) = E_Entry
2141 then
2142 Error_Msg_N
2143 ("REQUEUE does not permit parameters", First (Exprs));
2144
2145 elsif Is_Entity_Name (P)
2146 and then Etype (P) = Standard_Void_Type
2147 then
2148 Error_Msg_NE ("incorrect use of&", P, Entity (P));
2149
2150 else
2151 Error_Msg_N ("array type required in indexed component", P);
2152 end if;
2153
2154 Set_Etype (N, Any_Type);
2155 return;
2156 end if;
2157
2158 Index := First_Index (Array_Type);
2159 while Present (Index) and then Present (Exp) loop
2160 if not Has_Compatible_Type (Exp, Etype (Index)) then
2161 Wrong_Type (Exp, Etype (Index));
2162 Set_Etype (N, Any_Type);
2163 return;
2164 end if;
2165
2166 Next_Index (Index);
2167 Next (Exp);
2168 end loop;
2169
2170 Set_Etype (N, Component_Type (Array_Type));
2171 Check_Implicit_Dereference (N, Etype (N));
2172
2173 if Present (Index) then
2174 Error_Msg_N
2175 ("too few subscripts in array reference", First (Exprs));
2176
2177 elsif Present (Exp) then
2178 Error_Msg_N ("too many subscripts in array reference", Exp);
2179 end if;
2180 end if;
2181 end Process_Indexed_Component;
2182
2183 ----------------------------------------
2184 -- Process_Indexed_Component_Or_Slice --
2185 ----------------------------------------
2186
2187 procedure Process_Indexed_Component_Or_Slice is
2188 begin
2189 Exp := First (Exprs);
2190 while Present (Exp) loop
2191 Analyze_Expression (Exp);
2192 Next (Exp);
2193 end loop;
2194
2195 Exp := First (Exprs);
2196
2197 -- If one index is present, and it is a subtype name, then the
2198 -- node denotes a slice (note that the case of an explicit range
2199 -- for a slice was already built as an N_Slice node in the first
2200 -- place, so that case is not handled here).
2201
2202 -- We use a replace rather than a rewrite here because this is one
2203 -- of the cases in which the tree built by the parser is plain wrong.
2204
2205 if No (Next (Exp))
2206 and then Is_Entity_Name (Exp)
2207 and then Is_Type (Entity (Exp))
2208 then
2209 Replace (N,
2210 Make_Slice (Sloc (N),
2211 Prefix => P,
2212 Discrete_Range => New_Copy (Exp)));
2213 Analyze (N);
2214
2215 -- Otherwise (more than one index present, or single index is not
2216 -- a subtype name), then we have the indexed component case.
2217
2218 else
2219 Process_Indexed_Component;
2220 end if;
2221 end Process_Indexed_Component_Or_Slice;
2222
2223 ------------------------------------------
2224 -- Process_Overloaded_Indexed_Component --
2225 ------------------------------------------
2226
2227 procedure Process_Overloaded_Indexed_Component is
2228 Exp : Node_Id;
2229 I : Interp_Index;
2230 It : Interp;
2231 Typ : Entity_Id;
2232 Index : Node_Id;
2233 Found : Boolean;
2234
2235 begin
2236 Set_Etype (N, Any_Type);
2237
2238 Get_First_Interp (P, I, It);
2239 while Present (It.Nam) loop
2240 Typ := It.Typ;
2241
2242 if Is_Access_Type (Typ) then
2243 Typ := Designated_Type (Typ);
2244 Error_Msg_NW (Warn_On_Dereference, "?implicit dereference", N);
2245 end if;
2246
2247 if Is_Array_Type (Typ) then
2248
2249 -- Got a candidate: verify that index types are compatible
2250
2251 Index := First_Index (Typ);
2252 Found := True;
2253 Exp := First (Exprs);
2254 while Present (Index) and then Present (Exp) loop
2255 if Has_Compatible_Type (Exp, Etype (Index)) then
2256 null;
2257 else
2258 Found := False;
2259 Remove_Interp (I);
2260 exit;
2261 end if;
2262
2263 Next_Index (Index);
2264 Next (Exp);
2265 end loop;
2266
2267 if Found and then No (Index) and then No (Exp) then
2268 declare
2269 CT : constant Entity_Id :=
2270 Base_Type (Component_Type (Typ));
2271 begin
2272 Add_One_Interp (N, CT, CT);
2273 Check_Implicit_Dereference (N, CT);
2274 end;
2275 end if;
2276
2277 elsif Try_Container_Indexing (N, P, Exprs) then
2278 return;
2279
2280 end if;
2281
2282 Get_Next_Interp (I, It);
2283 end loop;
2284
2285 if Etype (N) = Any_Type then
2286 Error_Msg_N ("no legal interpretation for indexed component", N);
2287 Set_Is_Overloaded (N, False);
2288 end if;
2289
2290 End_Interp_List;
2291 end Process_Overloaded_Indexed_Component;
2292
2293 -- Start of processing for Analyze_Indexed_Component_Form
2294
2295 begin
2296 -- Get name of array, function or type
2297
2298 Analyze (P);
2299
2300 if Nkind (N) in N_Subprogram_Call then
2301
2302 -- If P is an explicit dereference whose prefix is of a
2303 -- remote access-to-subprogram type, then N has already
2304 -- been rewritten as a subprogram call and analyzed.
2305
2306 return;
2307 end if;
2308
2309 pragma Assert (Nkind (N) = N_Indexed_Component);
2310
2311 P_T := Base_Type (Etype (P));
2312
2313 if Is_Entity_Name (P) and then Present (Entity (P)) then
2314 U_N := Entity (P);
2315
2316 if Is_Type (U_N) then
2317
2318 -- Reformat node as a type conversion
2319
2320 E := Remove_Head (Exprs);
2321
2322 if Present (First (Exprs)) then
2323 Error_Msg_N
2324 ("argument of type conversion must be single expression", N);
2325 end if;
2326
2327 Change_Node (N, N_Type_Conversion);
2328 Set_Subtype_Mark (N, P);
2329 Set_Etype (N, U_N);
2330 Set_Expression (N, E);
2331
2332 -- After changing the node, call for the specific Analysis
2333 -- routine directly, to avoid a double call to the expander.
2334
2335 Analyze_Type_Conversion (N);
2336 return;
2337 end if;
2338
2339 if Is_Overloadable (U_N) then
2340 Process_Function_Call;
2341
2342 elsif Ekind (Etype (P)) = E_Subprogram_Type
2343 or else (Is_Access_Type (Etype (P))
2344 and then
2345 Ekind (Designated_Type (Etype (P))) =
2346 E_Subprogram_Type)
2347 then
2348 -- Call to access_to-subprogram with possible implicit dereference
2349
2350 Process_Function_Call;
2351
2352 elsif Is_Generic_Subprogram (U_N) then
2353
2354 -- A common beginner's (or C++ templates fan) error
2355
2356 Error_Msg_N ("generic subprogram cannot be called", N);
2357 Set_Etype (N, Any_Type);
2358 return;
2359
2360 else
2361 Process_Indexed_Component_Or_Slice;
2362 end if;
2363
2364 -- If not an entity name, prefix is an expression that may denote
2365 -- an array or an access-to-subprogram.
2366
2367 else
2368 if Ekind (P_T) = E_Subprogram_Type
2369 or else (Is_Access_Type (P_T)
2370 and then
2371 Ekind (Designated_Type (P_T)) = E_Subprogram_Type)
2372 then
2373 Process_Function_Call;
2374
2375 elsif Nkind (P) = N_Selected_Component
2376 and then Is_Overloadable (Entity (Selector_Name (P)))
2377 then
2378 Process_Function_Call;
2379
2380 else
2381 -- Indexed component, slice, or a call to a member of a family
2382 -- entry, which will be converted to an entry call later.
2383
2384 Process_Indexed_Component_Or_Slice;
2385 end if;
2386 end if;
2387
2388 Analyze_Dimension (N);
2389 end Analyze_Indexed_Component_Form;
2390
2391 ------------------------
2392 -- Analyze_Logical_Op --
2393 ------------------------
2394
2395 procedure Analyze_Logical_Op (N : Node_Id) is
2396 L : constant Node_Id := Left_Opnd (N);
2397 R : constant Node_Id := Right_Opnd (N);
2398 Op_Id : Entity_Id := Entity (N);
2399
2400 begin
2401 Set_Etype (N, Any_Type);
2402 Candidate_Type := Empty;
2403
2404 Analyze_Expression (L);
2405 Analyze_Expression (R);
2406
2407 if Present (Op_Id) then
2408
2409 if Ekind (Op_Id) = E_Operator then
2410 Find_Boolean_Types (L, R, Op_Id, N);
2411 else
2412 Add_One_Interp (N, Op_Id, Etype (Op_Id));
2413 end if;
2414
2415 else
2416 Op_Id := Get_Name_Entity_Id (Chars (N));
2417 while Present (Op_Id) loop
2418 if Ekind (Op_Id) = E_Operator then
2419 Find_Boolean_Types (L, R, Op_Id, N);
2420 else
2421 Analyze_User_Defined_Binary_Op (N, Op_Id);
2422 end if;
2423
2424 Op_Id := Homonym (Op_Id);
2425 end loop;
2426 end if;
2427
2428 Operator_Check (N);
2429 end Analyze_Logical_Op;
2430
2431 ---------------------------
2432 -- Analyze_Membership_Op --
2433 ---------------------------
2434
2435 procedure Analyze_Membership_Op (N : Node_Id) is
2436 Loc : constant Source_Ptr := Sloc (N);
2437 L : constant Node_Id := Left_Opnd (N);
2438 R : constant Node_Id := Right_Opnd (N);
2439
2440 Index : Interp_Index;
2441 It : Interp;
2442 Found : Boolean := False;
2443 I_F : Interp_Index;
2444 T_F : Entity_Id;
2445
2446 procedure Try_One_Interp (T1 : Entity_Id);
2447 -- Routine to try one proposed interpretation. Note that the context
2448 -- of the operation plays no role in resolving the arguments, so that
2449 -- if there is more than one interpretation of the operands that is
2450 -- compatible with a membership test, the operation is ambiguous.
2451
2452 --------------------
2453 -- Try_One_Interp --
2454 --------------------
2455
2456 procedure Try_One_Interp (T1 : Entity_Id) is
2457 begin
2458 if Has_Compatible_Type (R, T1) then
2459 if Found
2460 and then Base_Type (T1) /= Base_Type (T_F)
2461 then
2462 It := Disambiguate (L, I_F, Index, Any_Type);
2463
2464 if It = No_Interp then
2465 Ambiguous_Operands (N);
2466 Set_Etype (L, Any_Type);
2467 return;
2468
2469 else
2470 T_F := It.Typ;
2471 end if;
2472
2473 else
2474 Found := True;
2475 T_F := T1;
2476 I_F := Index;
2477 end if;
2478
2479 Set_Etype (L, T_F);
2480 end if;
2481 end Try_One_Interp;
2482
2483 procedure Analyze_Set_Membership;
2484 -- If a set of alternatives is present, analyze each and find the
2485 -- common type to which they must all resolve.
2486
2487 ----------------------------
2488 -- Analyze_Set_Membership --
2489 ----------------------------
2490
2491 procedure Analyze_Set_Membership is
2492 Alt : Node_Id;
2493 Index : Interp_Index;
2494 It : Interp;
2495 Candidate_Interps : Node_Id;
2496 Common_Type : Entity_Id := Empty;
2497
2498 begin
2499 Analyze (L);
2500 Candidate_Interps := L;
2501
2502 if not Is_Overloaded (L) then
2503 Common_Type := Etype (L);
2504
2505 Alt := First (Alternatives (N));
2506 while Present (Alt) loop
2507 Analyze (Alt);
2508
2509 if not Has_Compatible_Type (Alt, Common_Type) then
2510 Wrong_Type (Alt, Common_Type);
2511 end if;
2512
2513 Next (Alt);
2514 end loop;
2515
2516 else
2517 Alt := First (Alternatives (N));
2518 while Present (Alt) loop
2519 Analyze (Alt);
2520 if not Is_Overloaded (Alt) then
2521 Common_Type := Etype (Alt);
2522
2523 else
2524 Get_First_Interp (Alt, Index, It);
2525 while Present (It.Typ) loop
2526 if not
2527 Has_Compatible_Type (Candidate_Interps, It.Typ)
2528 then
2529 Remove_Interp (Index);
2530 end if;
2531
2532 Get_Next_Interp (Index, It);
2533 end loop;
2534
2535 Get_First_Interp (Alt, Index, It);
2536
2537 if No (It.Typ) then
2538 Error_Msg_N ("alternative has no legal type", Alt);
2539 return;
2540 end if;
2541
2542 -- If alternative is not overloaded, we have a unique type
2543 -- for all of them.
2544
2545 Set_Etype (Alt, It.Typ);
2546 Get_Next_Interp (Index, It);
2547
2548 if No (It.Typ) then
2549 Set_Is_Overloaded (Alt, False);
2550 Common_Type := Etype (Alt);
2551 end if;
2552
2553 Candidate_Interps := Alt;
2554 end if;
2555
2556 Next (Alt);
2557 end loop;
2558 end if;
2559
2560 Set_Etype (N, Standard_Boolean);
2561
2562 if Present (Common_Type) then
2563 Set_Etype (L, Common_Type);
2564 Set_Is_Overloaded (L, False);
2565
2566 else
2567 Error_Msg_N ("cannot resolve membership operation", N);
2568 end if;
2569 end Analyze_Set_Membership;
2570
2571 -- Start of processing for Analyze_Membership_Op
2572
2573 begin
2574 Analyze_Expression (L);
2575
2576 if No (R)
2577 and then Ada_Version >= Ada_2012
2578 then
2579 Analyze_Set_Membership;
2580 return;
2581 end if;
2582
2583 if Nkind (R) = N_Range
2584 or else (Nkind (R) = N_Attribute_Reference
2585 and then Attribute_Name (R) = Name_Range)
2586 then
2587 Analyze (R);
2588
2589 if not Is_Overloaded (L) then
2590 Try_One_Interp (Etype (L));
2591
2592 else
2593 Get_First_Interp (L, Index, It);
2594 while Present (It.Typ) loop
2595 Try_One_Interp (It.Typ);
2596 Get_Next_Interp (Index, It);
2597 end loop;
2598 end if;
2599
2600 -- If not a range, it can be a subtype mark, or else it is a degenerate
2601 -- membership test with a singleton value, i.e. a test for equality,
2602 -- if the types are compatible.
2603
2604 else
2605 Analyze (R);
2606
2607 if Is_Entity_Name (R)
2608 and then Is_Type (Entity (R))
2609 then
2610 Find_Type (R);
2611 Check_Fully_Declared (Entity (R), R);
2612
2613 elsif Ada_Version >= Ada_2012
2614 and then Has_Compatible_Type (R, Etype (L))
2615 then
2616 if Nkind (N) = N_In then
2617 Rewrite (N,
2618 Make_Op_Eq (Loc,
2619 Left_Opnd => L,
2620 Right_Opnd => R));
2621 else
2622 Rewrite (N,
2623 Make_Op_Ne (Loc,
2624 Left_Opnd => L,
2625 Right_Opnd => R));
2626 end if;
2627
2628 Analyze (N);
2629 return;
2630
2631 else
2632 -- In all versions of the language, if we reach this point there
2633 -- is a previous error that will be diagnosed below.
2634
2635 Find_Type (R);
2636 end if;
2637 end if;
2638
2639 -- Compatibility between expression and subtype mark or range is
2640 -- checked during resolution. The result of the operation is Boolean
2641 -- in any case.
2642
2643 Set_Etype (N, Standard_Boolean);
2644
2645 if Comes_From_Source (N)
2646 and then Present (Right_Opnd (N))
2647 and then Is_CPP_Class (Etype (Etype (Right_Opnd (N))))
2648 then
2649 Error_Msg_N ("membership test not applicable to cpp-class types", N);
2650 end if;
2651 end Analyze_Membership_Op;
2652
2653 -----------------
2654 -- Analyze_Mod --
2655 -----------------
2656
2657 procedure Analyze_Mod (N : Node_Id) is
2658 begin
2659 -- A special warning check, if we have an expression of the form:
2660 -- expr mod 2 * literal
2661 -- where literal is 64 or less, then probably what was meant was
2662 -- expr mod 2 ** literal
2663 -- so issue an appropriate warning.
2664
2665 if Warn_On_Suspicious_Modulus_Value
2666 and then Nkind (Right_Opnd (N)) = N_Integer_Literal
2667 and then Intval (Right_Opnd (N)) = Uint_2
2668 and then Nkind (Parent (N)) = N_Op_Multiply
2669 and then Nkind (Right_Opnd (Parent (N))) = N_Integer_Literal
2670 and then Intval (Right_Opnd (Parent (N))) <= Uint_64
2671 then
2672 Error_Msg_N
2673 ("suspicious MOD value, was '*'* intended'??", Parent (N));
2674 end if;
2675
2676 -- Remaining processing is same as for other arithmetic operators
2677
2678 Analyze_Arithmetic_Op (N);
2679 end Analyze_Mod;
2680
2681 ----------------------
2682 -- Analyze_Negation --
2683 ----------------------
2684
2685 procedure Analyze_Negation (N : Node_Id) is
2686 R : constant Node_Id := Right_Opnd (N);
2687 Op_Id : Entity_Id := Entity (N);
2688
2689 begin
2690 Set_Etype (N, Any_Type);
2691 Candidate_Type := Empty;
2692
2693 Analyze_Expression (R);
2694
2695 if Present (Op_Id) then
2696 if Ekind (Op_Id) = E_Operator then
2697 Find_Negation_Types (R, Op_Id, N);
2698 else
2699 Add_One_Interp (N, Op_Id, Etype (Op_Id));
2700 end if;
2701
2702 else
2703 Op_Id := Get_Name_Entity_Id (Chars (N));
2704 while Present (Op_Id) loop
2705 if Ekind (Op_Id) = E_Operator then
2706 Find_Negation_Types (R, Op_Id, N);
2707 else
2708 Analyze_User_Defined_Unary_Op (N, Op_Id);
2709 end if;
2710
2711 Op_Id := Homonym (Op_Id);
2712 end loop;
2713 end if;
2714
2715 Operator_Check (N);
2716 end Analyze_Negation;
2717
2718 ------------------
2719 -- Analyze_Null --
2720 ------------------
2721
2722 procedure Analyze_Null (N : Node_Id) is
2723 begin
2724 Check_SPARK_Restriction ("null is not allowed", N);
2725
2726 Set_Etype (N, Any_Access);
2727 end Analyze_Null;
2728
2729 ----------------------
2730 -- Analyze_One_Call --
2731 ----------------------
2732
2733 procedure Analyze_One_Call
2734 (N : Node_Id;
2735 Nam : Entity_Id;
2736 Report : Boolean;
2737 Success : out Boolean;
2738 Skip_First : Boolean := False)
2739 is
2740 Actuals : constant List_Id := Parameter_Associations (N);
2741 Prev_T : constant Entity_Id := Etype (N);
2742
2743 Must_Skip : constant Boolean := Skip_First
2744 or else Nkind (Original_Node (N)) = N_Selected_Component
2745 or else
2746 (Nkind (Original_Node (N)) = N_Indexed_Component
2747 and then Nkind (Prefix (Original_Node (N)))
2748 = N_Selected_Component);
2749 -- The first formal must be omitted from the match when trying to find
2750 -- a primitive operation that is a possible interpretation, and also
2751 -- after the call has been rewritten, because the corresponding actual
2752 -- is already known to be compatible, and because this may be an
2753 -- indexing of a call with default parameters.
2754
2755 Formal : Entity_Id;
2756 Actual : Node_Id;
2757 Is_Indexed : Boolean := False;
2758 Is_Indirect : Boolean := False;
2759 Subp_Type : constant Entity_Id := Etype (Nam);
2760 Norm_OK : Boolean;
2761
2762 function Operator_Hidden_By (Fun : Entity_Id) return Boolean;
2763 -- There may be a user-defined operator that hides the current
2764 -- interpretation. We must check for this independently of the
2765 -- analysis of the call with the user-defined operation, because
2766 -- the parameter names may be wrong and yet the hiding takes place.
2767 -- This fixes a problem with ACATS test B34014O.
2768 --
2769 -- When the type Address is a visible integer type, and the DEC
2770 -- system extension is visible, the predefined operator may be
2771 -- hidden as well, by one of the address operations in auxdec.
2772 -- Finally, The abstract operations on address do not hide the
2773 -- predefined operator (this is the purpose of making them abstract).
2774
2775 procedure Indicate_Name_And_Type;
2776 -- If candidate interpretation matches, indicate name and type of
2777 -- result on call node.
2778
2779 ----------------------------
2780 -- Indicate_Name_And_Type --
2781 ----------------------------
2782
2783 procedure Indicate_Name_And_Type is
2784 begin
2785 Add_One_Interp (N, Nam, Etype (Nam));
2786 Check_Implicit_Dereference (N, Etype (Nam));
2787 Success := True;
2788
2789 -- If the prefix of the call is a name, indicate the entity
2790 -- being called. If it is not a name, it is an expression that
2791 -- denotes an access to subprogram or else an entry or family. In
2792 -- the latter case, the name is a selected component, and the entity
2793 -- being called is noted on the selector.
2794
2795 if not Is_Type (Nam) then
2796 if Is_Entity_Name (Name (N)) then
2797 Set_Entity (Name (N), Nam);
2798
2799 elsif Nkind (Name (N)) = N_Selected_Component then
2800 Set_Entity (Selector_Name (Name (N)), Nam);
2801 end if;
2802 end if;
2803
2804 if Debug_Flag_E and not Report then
2805 Write_Str (" Overloaded call ");
2806 Write_Int (Int (N));
2807 Write_Str (" compatible with ");
2808 Write_Int (Int (Nam));
2809 Write_Eol;
2810 end if;
2811 end Indicate_Name_And_Type;
2812
2813 ------------------------
2814 -- Operator_Hidden_By --
2815 ------------------------
2816
2817 function Operator_Hidden_By (Fun : Entity_Id) return Boolean is
2818 Act1 : constant Node_Id := First_Actual (N);
2819 Act2 : constant Node_Id := Next_Actual (Act1);
2820 Form1 : constant Entity_Id := First_Formal (Fun);
2821 Form2 : constant Entity_Id := Next_Formal (Form1);
2822
2823 begin
2824 if Ekind (Fun) /= E_Function
2825 or else Is_Abstract_Subprogram (Fun)
2826 then
2827 return False;
2828
2829 elsif not Has_Compatible_Type (Act1, Etype (Form1)) then
2830 return False;
2831
2832 elsif Present (Form2) then
2833 if
2834 No (Act2) or else not Has_Compatible_Type (Act2, Etype (Form2))
2835 then
2836 return False;
2837 end if;
2838
2839 elsif Present (Act2) then
2840 return False;
2841 end if;
2842
2843 -- Now we know that the arity of the operator matches the function,
2844 -- and the function call is a valid interpretation. The function
2845 -- hides the operator if it has the right signature, or if one of
2846 -- its operands is a non-abstract operation on Address when this is
2847 -- a visible integer type.
2848
2849 return Hides_Op (Fun, Nam)
2850 or else Is_Descendent_Of_Address (Etype (Form1))
2851 or else
2852 (Present (Form2)
2853 and then Is_Descendent_Of_Address (Etype (Form2)));
2854 end Operator_Hidden_By;
2855
2856 -- Start of processing for Analyze_One_Call
2857
2858 begin
2859 Success := False;
2860
2861 -- If the subprogram has no formals or if all the formals have defaults,
2862 -- and the return type is an array type, the node may denote an indexing
2863 -- of the result of a parameterless call. In Ada 2005, the subprogram
2864 -- may have one non-defaulted formal, and the call may have been written
2865 -- in prefix notation, so that the rebuilt parameter list has more than
2866 -- one actual.
2867
2868 if not Is_Overloadable (Nam)
2869 and then Ekind (Nam) /= E_Subprogram_Type
2870 and then Ekind (Nam) /= E_Entry_Family
2871 then
2872 return;
2873 end if;
2874
2875 -- An indexing requires at least one actual
2876
2877 if not Is_Empty_List (Actuals)
2878 and then
2879 (Needs_No_Actuals (Nam)
2880 or else
2881 (Needs_One_Actual (Nam)
2882 and then Present (Next_Actual (First (Actuals)))))
2883 then
2884 if Is_Array_Type (Subp_Type) then
2885 Is_Indexed := Try_Indexed_Call (N, Nam, Subp_Type, Must_Skip);
2886
2887 elsif Is_Access_Type (Subp_Type)
2888 and then Is_Array_Type (Designated_Type (Subp_Type))
2889 then
2890 Is_Indexed :=
2891 Try_Indexed_Call
2892 (N, Nam, Designated_Type (Subp_Type), Must_Skip);
2893
2894 -- The prefix can also be a parameterless function that returns an
2895 -- access to subprogram, in which case this is an indirect call.
2896 -- If this succeeds, an explicit dereference is added later on,
2897 -- in Analyze_Call or Resolve_Call.
2898
2899 elsif Is_Access_Type (Subp_Type)
2900 and then Ekind (Designated_Type (Subp_Type)) = E_Subprogram_Type
2901 then
2902 Is_Indirect := Try_Indirect_Call (N, Nam, Subp_Type);
2903 end if;
2904
2905 end if;
2906
2907 -- If the call has been transformed into a slice, it is of the form
2908 -- F (Subtype) where F is parameterless. The node has been rewritten in
2909 -- Try_Indexed_Call and there is nothing else to do.
2910
2911 if Is_Indexed
2912 and then Nkind (N) = N_Slice
2913 then
2914 return;
2915 end if;
2916
2917 Normalize_Actuals
2918 (N, Nam, (Report and not Is_Indexed and not Is_Indirect), Norm_OK);
2919
2920 if not Norm_OK then
2921
2922 -- If an indirect call is a possible interpretation, indicate
2923 -- success to the caller.
2924
2925 if Is_Indirect then
2926 Success := True;
2927 return;
2928
2929 -- Mismatch in number or names of parameters
2930
2931 elsif Debug_Flag_E then
2932 Write_Str (" normalization fails in call ");
2933 Write_Int (Int (N));
2934 Write_Str (" with subprogram ");
2935 Write_Int (Int (Nam));
2936 Write_Eol;
2937 end if;
2938
2939 -- If the context expects a function call, discard any interpretation
2940 -- that is a procedure. If the node is not overloaded, leave as is for
2941 -- better error reporting when type mismatch is found.
2942
2943 elsif Nkind (N) = N_Function_Call
2944 and then Is_Overloaded (Name (N))
2945 and then Ekind (Nam) = E_Procedure
2946 then
2947 return;
2948
2949 -- Ditto for function calls in a procedure context
2950
2951 elsif Nkind (N) = N_Procedure_Call_Statement
2952 and then Is_Overloaded (Name (N))
2953 and then Etype (Nam) /= Standard_Void_Type
2954 then
2955 return;
2956
2957 elsif No (Actuals) then
2958
2959 -- If Normalize succeeds, then there are default parameters for
2960 -- all formals.
2961
2962 Indicate_Name_And_Type;
2963
2964 elsif Ekind (Nam) = E_Operator then
2965 if Nkind (N) = N_Procedure_Call_Statement then
2966 return;
2967 end if;
2968
2969 -- This can occur when the prefix of the call is an operator
2970 -- name or an expanded name whose selector is an operator name.
2971
2972 Analyze_Operator_Call (N, Nam);
2973
2974 if Etype (N) /= Prev_T then
2975
2976 -- Check that operator is not hidden by a function interpretation
2977
2978 if Is_Overloaded (Name (N)) then
2979 declare
2980 I : Interp_Index;
2981 It : Interp;
2982
2983 begin
2984 Get_First_Interp (Name (N), I, It);
2985 while Present (It.Nam) loop
2986 if Operator_Hidden_By (It.Nam) then
2987 Set_Etype (N, Prev_T);
2988 return;
2989 end if;
2990
2991 Get_Next_Interp (I, It);
2992 end loop;
2993 end;
2994 end if;
2995
2996 -- If operator matches formals, record its name on the call.
2997 -- If the operator is overloaded, Resolve will select the
2998 -- correct one from the list of interpretations. The call
2999 -- node itself carries the first candidate.
3000
3001 Set_Entity (Name (N), Nam);
3002 Success := True;
3003
3004 elsif Report and then Etype (N) = Any_Type then
3005 Error_Msg_N ("incompatible arguments for operator", N);
3006 end if;
3007
3008 else
3009 -- Normalize_Actuals has chained the named associations in the
3010 -- correct order of the formals.
3011
3012 Actual := First_Actual (N);
3013 Formal := First_Formal (Nam);
3014
3015 -- If we are analyzing a call rewritten from object notation, skip
3016 -- first actual, which may be rewritten later as an explicit
3017 -- dereference.
3018
3019 if Must_Skip then
3020 Next_Actual (Actual);
3021 Next_Formal (Formal);
3022 end if;
3023
3024 while Present (Actual) and then Present (Formal) loop
3025 if Nkind (Parent (Actual)) /= N_Parameter_Association
3026 or else Chars (Selector_Name (Parent (Actual))) = Chars (Formal)
3027 then
3028 -- The actual can be compatible with the formal, but we must
3029 -- also check that the context is not an address type that is
3030 -- visibly an integer type, as is the case in VMS_64. In this
3031 -- case the use of literals is illegal, except in the body of
3032 -- descendents of system, where arithmetic operations on
3033 -- address are of course used.
3034
3035 if Has_Compatible_Type (Actual, Etype (Formal))
3036 and then
3037 (Etype (Actual) /= Universal_Integer
3038 or else not Is_Descendent_Of_Address (Etype (Formal))
3039 or else
3040 Is_Predefined_File_Name
3041 (Unit_File_Name (Get_Source_Unit (N))))
3042 then
3043 Next_Actual (Actual);
3044 Next_Formal (Formal);
3045
3046 else
3047 if Debug_Flag_E then
3048 Write_Str (" type checking fails in call ");
3049 Write_Int (Int (N));
3050 Write_Str (" with formal ");
3051 Write_Int (Int (Formal));
3052 Write_Str (" in subprogram ");
3053 Write_Int (Int (Nam));
3054 Write_Eol;
3055 end if;
3056
3057 if Report and not Is_Indexed and not Is_Indirect then
3058
3059 -- Ada 2005 (AI-251): Complete the error notification
3060 -- to help new Ada 2005 users.
3061
3062 if Is_Class_Wide_Type (Etype (Formal))
3063 and then Is_Interface (Etype (Etype (Formal)))
3064 and then not Interface_Present_In_Ancestor
3065 (Typ => Etype (Actual),
3066 Iface => Etype (Etype (Formal)))
3067 then
3068 Error_Msg_NE
3069 ("(Ada 2005) does not implement interface }",
3070 Actual, Etype (Etype (Formal)));
3071 end if;
3072
3073 Wrong_Type (Actual, Etype (Formal));
3074
3075 if Nkind (Actual) = N_Op_Eq
3076 and then Nkind (Left_Opnd (Actual)) = N_Identifier
3077 then
3078 Formal := First_Formal (Nam);
3079 while Present (Formal) loop
3080 if Chars (Left_Opnd (Actual)) = Chars (Formal) then
3081 Error_Msg_N -- CODEFIX
3082 ("possible misspelling of `='>`!", Actual);
3083 exit;
3084 end if;
3085
3086 Next_Formal (Formal);
3087 end loop;
3088 end if;
3089
3090 if All_Errors_Mode then
3091 Error_Msg_Sloc := Sloc (Nam);
3092
3093 if Etype (Formal) = Any_Type then
3094 Error_Msg_N
3095 ("there is no legal actual parameter", Actual);
3096 end if;
3097
3098 if Is_Overloadable (Nam)
3099 and then Present (Alias (Nam))
3100 and then not Comes_From_Source (Nam)
3101 then
3102 Error_Msg_NE
3103 ("\\ =='> in call to inherited operation & #!",
3104 Actual, Nam);
3105
3106 elsif Ekind (Nam) = E_Subprogram_Type then
3107 declare
3108 Access_To_Subprogram_Typ :
3109 constant Entity_Id :=
3110 Defining_Identifier
3111 (Associated_Node_For_Itype (Nam));
3112 begin
3113 Error_Msg_NE (
3114 "\\ =='> in call to dereference of &#!",
3115 Actual, Access_To_Subprogram_Typ);
3116 end;
3117
3118 else
3119 Error_Msg_NE
3120 ("\\ =='> in call to &#!", Actual, Nam);
3121
3122 end if;
3123 end if;
3124 end if;
3125
3126 return;
3127 end if;
3128
3129 else
3130 -- Normalize_Actuals has verified that a default value exists
3131 -- for this formal. Current actual names a subsequent formal.
3132
3133 Next_Formal (Formal);
3134 end if;
3135 end loop;
3136
3137 -- On exit, all actuals match
3138
3139 Indicate_Name_And_Type;
3140 end if;
3141 end Analyze_One_Call;
3142
3143 ---------------------------
3144 -- Analyze_Operator_Call --
3145 ---------------------------
3146
3147 procedure Analyze_Operator_Call (N : Node_Id; Op_Id : Entity_Id) is
3148 Op_Name : constant Name_Id := Chars (Op_Id);
3149 Act1 : constant Node_Id := First_Actual (N);
3150 Act2 : constant Node_Id := Next_Actual (Act1);
3151
3152 begin
3153 -- Binary operator case
3154
3155 if Present (Act2) then
3156
3157 -- If more than two operands, then not binary operator after all
3158
3159 if Present (Next_Actual (Act2)) then
3160 return;
3161 end if;
3162
3163 -- Otherwise action depends on operator
3164
3165 case Op_Name is
3166 when Name_Op_Add |
3167 Name_Op_Subtract |
3168 Name_Op_Multiply |
3169 Name_Op_Divide |
3170 Name_Op_Mod |
3171 Name_Op_Rem |
3172 Name_Op_Expon =>
3173 Find_Arithmetic_Types (Act1, Act2, Op_Id, N);
3174
3175 when Name_Op_And |
3176 Name_Op_Or |
3177 Name_Op_Xor =>
3178 Find_Boolean_Types (Act1, Act2, Op_Id, N);
3179
3180 when Name_Op_Lt |
3181 Name_Op_Le |
3182 Name_Op_Gt |
3183 Name_Op_Ge =>
3184 Find_Comparison_Types (Act1, Act2, Op_Id, N);
3185
3186 when Name_Op_Eq |
3187 Name_Op_Ne =>
3188 Find_Equality_Types (Act1, Act2, Op_Id, N);
3189
3190 when Name_Op_Concat =>
3191 Find_Concatenation_Types (Act1, Act2, Op_Id, N);
3192
3193 -- Is this when others, or should it be an abort???
3194
3195 when others =>
3196 null;
3197 end case;
3198
3199 -- Unary operator case
3200
3201 else
3202 case Op_Name is
3203 when Name_Op_Subtract |
3204 Name_Op_Add |
3205 Name_Op_Abs =>
3206 Find_Unary_Types (Act1, Op_Id, N);
3207
3208 when Name_Op_Not =>
3209 Find_Negation_Types (Act1, Op_Id, N);
3210
3211 -- Is this when others correct, or should it be an abort???
3212
3213 when others =>
3214 null;
3215 end case;
3216 end if;
3217 end Analyze_Operator_Call;
3218
3219 -------------------------------------------
3220 -- Analyze_Overloaded_Selected_Component --
3221 -------------------------------------------
3222
3223 procedure Analyze_Overloaded_Selected_Component (N : Node_Id) is
3224 Nam : constant Node_Id := Prefix (N);
3225 Sel : constant Node_Id := Selector_Name (N);
3226 Comp : Entity_Id;
3227 I : Interp_Index;
3228 It : Interp;
3229 T : Entity_Id;
3230
3231 begin
3232 Set_Etype (Sel, Any_Type);
3233
3234 Get_First_Interp (Nam, I, It);
3235 while Present (It.Typ) loop
3236 if Is_Access_Type (It.Typ) then
3237 T := Designated_Type (It.Typ);
3238 Error_Msg_NW (Warn_On_Dereference, "?implicit dereference", N);
3239 else
3240 T := It.Typ;
3241 end if;
3242
3243 -- Locate the component. For a private prefix the selector can denote
3244 -- a discriminant.
3245
3246 if Is_Record_Type (T) or else Is_Private_Type (T) then
3247
3248 -- If the prefix is a class-wide type, the visible components are
3249 -- those of the base type.
3250
3251 if Is_Class_Wide_Type (T) then
3252 T := Etype (T);
3253 end if;
3254
3255 Comp := First_Entity (T);
3256 while Present (Comp) loop
3257 if Chars (Comp) = Chars (Sel)
3258 and then Is_Visible_Component (Comp)
3259 then
3260
3261 -- AI05-105: if the context is an object renaming with
3262 -- an anonymous access type, the expected type of the
3263 -- object must be anonymous. This is a name resolution rule.
3264
3265 if Nkind (Parent (N)) /= N_Object_Renaming_Declaration
3266 or else No (Access_Definition (Parent (N)))
3267 or else Ekind (Etype (Comp)) = E_Anonymous_Access_Type
3268 or else
3269 Ekind (Etype (Comp)) = E_Anonymous_Access_Subprogram_Type
3270 then
3271 Set_Entity (Sel, Comp);
3272 Set_Etype (Sel, Etype (Comp));
3273 Add_One_Interp (N, Etype (Comp), Etype (Comp));
3274 Check_Implicit_Dereference (N, Etype (Comp));
3275
3276 -- This also specifies a candidate to resolve the name.
3277 -- Further overloading will be resolved from context.
3278 -- The selector name itself does not carry overloading
3279 -- information.
3280
3281 Set_Etype (Nam, It.Typ);
3282
3283 else
3284 -- Named access type in the context of a renaming
3285 -- declaration with an access definition. Remove
3286 -- inapplicable candidate.
3287
3288 Remove_Interp (I);
3289 end if;
3290 end if;
3291
3292 Next_Entity (Comp);
3293 end loop;
3294
3295 elsif Is_Concurrent_Type (T) then
3296 Comp := First_Entity (T);
3297 while Present (Comp)
3298 and then Comp /= First_Private_Entity (T)
3299 loop
3300 if Chars (Comp) = Chars (Sel) then
3301 if Is_Overloadable (Comp) then
3302 Add_One_Interp (Sel, Comp, Etype (Comp));
3303 else
3304 Set_Entity_With_Style_Check (Sel, Comp);
3305 Generate_Reference (Comp, Sel);
3306 end if;
3307
3308 Set_Etype (Sel, Etype (Comp));
3309 Set_Etype (N, Etype (Comp));
3310 Set_Etype (Nam, It.Typ);
3311
3312 -- For access type case, introduce explicit dereference for
3313 -- more uniform treatment of entry calls. Do this only once
3314 -- if several interpretations yield an access type.
3315
3316 if Is_Access_Type (Etype (Nam))
3317 and then Nkind (Nam) /= N_Explicit_Dereference
3318 then
3319 Insert_Explicit_Dereference (Nam);
3320 Error_Msg_NW
3321 (Warn_On_Dereference, "?implicit dereference", N);
3322 end if;
3323 end if;
3324
3325 Next_Entity (Comp);
3326 end loop;
3327
3328 Set_Is_Overloaded (N, Is_Overloaded (Sel));
3329 end if;
3330
3331 Get_Next_Interp (I, It);
3332 end loop;
3333
3334 if Etype (N) = Any_Type
3335 and then not Try_Object_Operation (N)
3336 then
3337 Error_Msg_NE ("undefined selector& for overloaded prefix", N, Sel);
3338 Set_Entity (Sel, Any_Id);
3339 Set_Etype (Sel, Any_Type);
3340 end if;
3341 end Analyze_Overloaded_Selected_Component;
3342
3343 ----------------------------------
3344 -- Analyze_Qualified_Expression --
3345 ----------------------------------
3346
3347 procedure Analyze_Qualified_Expression (N : Node_Id) is
3348 Mark : constant Entity_Id := Subtype_Mark (N);
3349 Expr : constant Node_Id := Expression (N);
3350 I : Interp_Index;
3351 It : Interp;
3352 T : Entity_Id;
3353
3354 begin
3355 Analyze_Expression (Expr);
3356
3357 Set_Etype (N, Any_Type);
3358 Find_Type (Mark);
3359 T := Entity (Mark);
3360 Set_Etype (N, T);
3361
3362 if T = Any_Type then
3363 return;
3364 end if;
3365
3366 Check_Fully_Declared (T, N);
3367
3368 -- If expected type is class-wide, check for exact match before
3369 -- expansion, because if the expression is a dispatching call it
3370 -- may be rewritten as explicit dereference with class-wide result.
3371 -- If expression is overloaded, retain only interpretations that
3372 -- will yield exact matches.
3373
3374 if Is_Class_Wide_Type (T) then
3375 if not Is_Overloaded (Expr) then
3376 if Base_Type (Etype (Expr)) /= Base_Type (T) then
3377 if Nkind (Expr) = N_Aggregate then
3378 Error_Msg_N ("type of aggregate cannot be class-wide", Expr);
3379 else
3380 Wrong_Type (Expr, T);
3381 end if;
3382 end if;
3383
3384 else
3385 Get_First_Interp (Expr, I, It);
3386
3387 while Present (It.Nam) loop
3388 if Base_Type (It.Typ) /= Base_Type (T) then
3389 Remove_Interp (I);
3390 end if;
3391
3392 Get_Next_Interp (I, It);
3393 end loop;
3394 end if;
3395 end if;
3396
3397 Set_Etype (N, T);
3398 end Analyze_Qualified_Expression;
3399
3400 -----------------------------------
3401 -- Analyze_Quantified_Expression --
3402 -----------------------------------
3403
3404 procedure Analyze_Quantified_Expression (N : Node_Id) is
3405 QE_Scop : Entity_Id;
3406
3407 function Is_Empty_Range (Typ : Entity_Id) return Boolean;
3408 -- If the iterator is part of a quantified expression, and the range is
3409 -- known to be statically empty, emit a warning and replace expression
3410 -- with its static value. Returns True if the replacement occurs.
3411
3412 --------------------
3413 -- Is_Empty_Range --
3414 --------------------
3415
3416 function Is_Empty_Range (Typ : Entity_Id) return Boolean is
3417 Loc : constant Source_Ptr := Sloc (N);
3418
3419 begin
3420 if Is_Array_Type (Typ)
3421 and then Compile_Time_Known_Bounds (Typ)
3422 and then
3423 (Expr_Value (Type_Low_Bound (Etype (First_Index (Typ)))) >
3424 Expr_Value (Type_High_Bound (Etype (First_Index (Typ)))))
3425 then
3426 Preanalyze_And_Resolve (Condition (N), Standard_Boolean);
3427
3428 if All_Present (N) then
3429 Error_Msg_N
3430 ("?quantified expression with ALL "
3431 & "over a null range has value True", N);
3432 Rewrite (N, New_Occurrence_Of (Standard_True, Loc));
3433
3434 else
3435 Error_Msg_N
3436 ("?quantified expression with SOME "
3437 & "over a null range has value False", N);
3438 Rewrite (N, New_Occurrence_Of (Standard_False, Loc));
3439 end if;
3440
3441 Analyze (N);
3442 return True;
3443
3444 else
3445 return False;
3446 end if;
3447 end Is_Empty_Range;
3448
3449 -- Start of processing for Analyze_Quantified_Expression
3450
3451 begin
3452 Check_SPARK_Restriction ("quantified expression is not allowed", N);
3453
3454 -- Create a scope to emulate the loop-like behavior of the quantified
3455 -- expression. The scope is needed to provide proper visibility of the
3456 -- loop variable.
3457
3458 QE_Scop := New_Internal_Entity (E_Loop, Current_Scope, Sloc (N), 'L');
3459 Set_Etype (QE_Scop, Standard_Void_Type);
3460 Set_Scope (QE_Scop, Current_Scope);
3461 Set_Parent (QE_Scop, N);
3462
3463 Push_Scope (QE_Scop);
3464
3465 -- All constituents are preanalyzed and resolved to avoid untimely
3466 -- generation of various temporaries and types. Full analysis and
3467 -- expansion is carried out when the quantified expression is
3468 -- transformed into an expression with actions.
3469
3470 if Present (Iterator_Specification (N)) then
3471 Preanalyze (Iterator_Specification (N));
3472
3473 if Is_Entity_Name (Name (Iterator_Specification (N)))
3474 and then Is_Empty_Range (Etype (Name (Iterator_Specification (N))))
3475 then
3476 return;
3477 end if;
3478
3479 else
3480 Preanalyze (Loop_Parameter_Specification (N));
3481 end if;
3482
3483 Preanalyze_And_Resolve (Condition (N), Standard_Boolean);
3484
3485 End_Scope;
3486
3487 Set_Etype (N, Standard_Boolean);
3488 end Analyze_Quantified_Expression;
3489
3490 -------------------
3491 -- Analyze_Range --
3492 -------------------
3493
3494 procedure Analyze_Range (N : Node_Id) is
3495 L : constant Node_Id := Low_Bound (N);
3496 H : constant Node_Id := High_Bound (N);
3497 I1, I2 : Interp_Index;
3498 It1, It2 : Interp;
3499
3500 procedure Check_Common_Type (T1, T2 : Entity_Id);
3501 -- Verify the compatibility of two types, and choose the
3502 -- non universal one if the other is universal.
3503
3504 procedure Check_High_Bound (T : Entity_Id);
3505 -- Test one interpretation of the low bound against all those
3506 -- of the high bound.
3507
3508 procedure Check_Universal_Expression (N : Node_Id);
3509 -- In Ada 83, reject bounds of a universal range that are not literals
3510 -- or entity names.
3511
3512 -----------------------
3513 -- Check_Common_Type --
3514 -----------------------
3515
3516 procedure Check_Common_Type (T1, T2 : Entity_Id) is
3517 begin
3518 if Covers (T1 => T1, T2 => T2)
3519 or else
3520 Covers (T1 => T2, T2 => T1)
3521 then
3522 if T1 = Universal_Integer
3523 or else T1 = Universal_Real
3524 or else T1 = Any_Character
3525 then
3526 Add_One_Interp (N, Base_Type (T2), Base_Type (T2));
3527
3528 elsif T1 = T2 then
3529 Add_One_Interp (N, T1, T1);
3530
3531 else
3532 Add_One_Interp (N, Base_Type (T1), Base_Type (T1));
3533 end if;
3534 end if;
3535 end Check_Common_Type;
3536
3537 ----------------------
3538 -- Check_High_Bound --
3539 ----------------------
3540
3541 procedure Check_High_Bound (T : Entity_Id) is
3542 begin
3543 if not Is_Overloaded (H) then
3544 Check_Common_Type (T, Etype (H));
3545 else
3546 Get_First_Interp (H, I2, It2);
3547 while Present (It2.Typ) loop
3548 Check_Common_Type (T, It2.Typ);
3549 Get_Next_Interp (I2, It2);
3550 end loop;
3551 end if;
3552 end Check_High_Bound;
3553
3554 -----------------------------
3555 -- Is_Universal_Expression --
3556 -----------------------------
3557
3558 procedure Check_Universal_Expression (N : Node_Id) is
3559 begin
3560 if Etype (N) = Universal_Integer
3561 and then Nkind (N) /= N_Integer_Literal
3562 and then not Is_Entity_Name (N)
3563 and then Nkind (N) /= N_Attribute_Reference
3564 then
3565 Error_Msg_N ("illegal bound in discrete range", N);
3566 end if;
3567 end Check_Universal_Expression;
3568
3569 -- Start of processing for Analyze_Range
3570
3571 begin
3572 Set_Etype (N, Any_Type);
3573 Analyze_Expression (L);
3574 Analyze_Expression (H);
3575
3576 if Etype (L) = Any_Type or else Etype (H) = Any_Type then
3577 return;
3578
3579 else
3580 if not Is_Overloaded (L) then
3581 Check_High_Bound (Etype (L));
3582 else
3583 Get_First_Interp (L, I1, It1);
3584 while Present (It1.Typ) loop
3585 Check_High_Bound (It1.Typ);
3586 Get_Next_Interp (I1, It1);
3587 end loop;
3588 end if;
3589
3590 -- If result is Any_Type, then we did not find a compatible pair
3591
3592 if Etype (N) = Any_Type then
3593 Error_Msg_N ("incompatible types in range ", N);
3594 end if;
3595 end if;
3596
3597 if Ada_Version = Ada_83
3598 and then
3599 (Nkind (Parent (N)) = N_Loop_Parameter_Specification
3600 or else Nkind (Parent (N)) = N_Constrained_Array_Definition)
3601 then
3602 Check_Universal_Expression (L);
3603 Check_Universal_Expression (H);
3604 end if;
3605 end Analyze_Range;
3606
3607 -----------------------
3608 -- Analyze_Reference --
3609 -----------------------
3610
3611 procedure Analyze_Reference (N : Node_Id) is
3612 P : constant Node_Id := Prefix (N);
3613 E : Entity_Id;
3614 T : Entity_Id;
3615 Acc_Type : Entity_Id;
3616
3617 begin
3618 Analyze (P);
3619
3620 -- An interesting error check, if we take the 'Reference of an object
3621 -- for which a pragma Atomic or Volatile has been given, and the type
3622 -- of the object is not Atomic or Volatile, then we are in trouble. The
3623 -- problem is that no trace of the atomic/volatile status will remain
3624 -- for the backend to respect when it deals with the resulting pointer,
3625 -- since the pointer type will not be marked atomic (it is a pointer to
3626 -- the base type of the object).
3627
3628 -- It is not clear if that can ever occur, but in case it does, we will
3629 -- generate an error message. Not clear if this message can ever be
3630 -- generated, and pretty clear that it represents a bug if it is, still
3631 -- seems worth checking, except in CodePeer mode where we do not really
3632 -- care and don't want to bother the user.
3633
3634 T := Etype (P);
3635
3636 if Is_Entity_Name (P)
3637 and then Is_Object_Reference (P)
3638 and then not CodePeer_Mode
3639 then
3640 E := Entity (P);
3641 T := Etype (P);
3642
3643 if (Has_Atomic_Components (E)
3644 and then not Has_Atomic_Components (T))
3645 or else
3646 (Has_Volatile_Components (E)
3647 and then not Has_Volatile_Components (T))
3648 or else (Is_Atomic (E) and then not Is_Atomic (T))
3649 or else (Is_Volatile (E) and then not Is_Volatile (T))
3650 then
3651 Error_Msg_N ("cannot take reference to Atomic/Volatile object", N);
3652 end if;
3653 end if;
3654
3655 -- Carry on with normal processing
3656
3657 Acc_Type := Create_Itype (E_Allocator_Type, N);
3658 Set_Etype (Acc_Type, Acc_Type);
3659 Set_Directly_Designated_Type (Acc_Type, Etype (P));
3660 Set_Etype (N, Acc_Type);
3661 end Analyze_Reference;
3662
3663 --------------------------------
3664 -- Analyze_Selected_Component --
3665 --------------------------------
3666
3667 -- Prefix is a record type or a task or protected type. In the latter case,
3668 -- the selector must denote a visible entry.
3669
3670 procedure Analyze_Selected_Component (N : Node_Id) is
3671 Name : constant Node_Id := Prefix (N);
3672 Sel : constant Node_Id := Selector_Name (N);
3673 Act_Decl : Node_Id;
3674 Comp : Entity_Id;
3675 Has_Candidate : Boolean := False;
3676 In_Scope : Boolean;
3677 Parent_N : Node_Id;
3678 Pent : Entity_Id := Empty;
3679 Prefix_Type : Entity_Id;
3680
3681 Type_To_Use : Entity_Id;
3682 -- In most cases this is the Prefix_Type, but if the Prefix_Type is
3683 -- a class-wide type, we use its root type, whose components are
3684 -- present in the class-wide type.
3685
3686 Is_Single_Concurrent_Object : Boolean;
3687 -- Set True if the prefix is a single task or a single protected object
3688
3689 procedure Find_Component_In_Instance (Rec : Entity_Id);
3690 -- In an instance, a component of a private extension may not be visible
3691 -- while it was visible in the generic. Search candidate scope for a
3692 -- component with the proper identifier. This is only done if all other
3693 -- searches have failed. When the match is found (it always will be),
3694 -- the Etype of both N and Sel are set from this component, and the
3695 -- entity of Sel is set to reference this component.
3696
3697 function Has_Mode_Conformant_Spec (Comp : Entity_Id) return Boolean;
3698 -- It is known that the parent of N denotes a subprogram call. Comp
3699 -- is an overloadable component of the concurrent type of the prefix.
3700 -- Determine whether all formals of the parent of N and Comp are mode
3701 -- conformant. If the parent node is not analyzed yet it may be an
3702 -- indexed component rather than a function call.
3703
3704 --------------------------------
3705 -- Find_Component_In_Instance --
3706 --------------------------------
3707
3708 procedure Find_Component_In_Instance (Rec : Entity_Id) is
3709 Comp : Entity_Id;
3710
3711 begin
3712 Comp := First_Component (Rec);
3713 while Present (Comp) loop
3714 if Chars (Comp) = Chars (Sel) then
3715 Set_Entity_With_Style_Check (Sel, Comp);
3716 Set_Etype (Sel, Etype (Comp));
3717 Set_Etype (N, Etype (Comp));
3718 return;
3719 end if;
3720
3721 Next_Component (Comp);
3722 end loop;
3723
3724 -- This must succeed because code was legal in the generic
3725
3726 raise Program_Error;
3727 end Find_Component_In_Instance;
3728
3729 ------------------------------
3730 -- Has_Mode_Conformant_Spec --
3731 ------------------------------
3732
3733 function Has_Mode_Conformant_Spec (Comp : Entity_Id) return Boolean is
3734 Comp_Param : Entity_Id;
3735 Param : Node_Id;
3736 Param_Typ : Entity_Id;
3737
3738 begin
3739 Comp_Param := First_Formal (Comp);
3740
3741 if Nkind (Parent (N)) = N_Indexed_Component then
3742 Param := First (Expressions (Parent (N)));
3743 else
3744 Param := First (Parameter_Associations (Parent (N)));
3745 end if;
3746
3747 while Present (Comp_Param)
3748 and then Present (Param)
3749 loop
3750 Param_Typ := Find_Parameter_Type (Param);
3751
3752 if Present (Param_Typ)
3753 and then
3754 not Conforming_Types
3755 (Etype (Comp_Param), Param_Typ, Mode_Conformant)
3756 then
3757 return False;
3758 end if;
3759
3760 Next_Formal (Comp_Param);
3761 Next (Param);
3762 end loop;
3763
3764 -- One of the specs has additional formals
3765
3766 if Present (Comp_Param) or else Present (Param) then
3767 return False;
3768 end if;
3769
3770 return True;
3771 end Has_Mode_Conformant_Spec;
3772
3773 -- Start of processing for Analyze_Selected_Component
3774
3775 begin
3776 Set_Etype (N, Any_Type);
3777
3778 if Is_Overloaded (Name) then
3779 Analyze_Overloaded_Selected_Component (N);
3780 return;
3781
3782 elsif Etype (Name) = Any_Type then
3783 Set_Entity (Sel, Any_Id);
3784 Set_Etype (Sel, Any_Type);
3785 return;
3786
3787 else
3788 Prefix_Type := Etype (Name);
3789 end if;
3790
3791 if Is_Access_Type (Prefix_Type) then
3792
3793 -- A RACW object can never be used as prefix of a selected component
3794 -- since that means it is dereferenced without being a controlling
3795 -- operand of a dispatching operation (RM E.2.2(16/1)). Before
3796 -- reporting an error, we must check whether this is actually a
3797 -- dispatching call in prefix form.
3798
3799 if Is_Remote_Access_To_Class_Wide_Type (Prefix_Type)
3800 and then Comes_From_Source (N)
3801 then
3802 if Try_Object_Operation (N) then
3803 return;
3804 else
3805 Error_Msg_N
3806 ("invalid dereference of a remote access-to-class-wide value",
3807 N);
3808 end if;
3809
3810 -- Normal case of selected component applied to access type
3811
3812 else
3813 Error_Msg_NW (Warn_On_Dereference, "?implicit dereference", N);
3814
3815 if Is_Entity_Name (Name) then
3816 Pent := Entity (Name);
3817 elsif Nkind (Name) = N_Selected_Component
3818 and then Is_Entity_Name (Selector_Name (Name))
3819 then
3820 Pent := Entity (Selector_Name (Name));
3821 end if;
3822
3823 Prefix_Type := Process_Implicit_Dereference_Prefix (Pent, Name);
3824 end if;
3825
3826 -- If we have an explicit dereference of a remote access-to-class-wide
3827 -- value, then issue an error (see RM-E.2.2(16/1)). However we first
3828 -- have to check for the case of a prefix that is a controlling operand
3829 -- of a prefixed dispatching call, as the dereference is legal in that
3830 -- case. Normally this condition is checked in Validate_Remote_Access_
3831 -- To_Class_Wide_Type, but we have to defer the checking for selected
3832 -- component prefixes because of the prefixed dispatching call case.
3833 -- Note that implicit dereferences are checked for this just above.
3834
3835 elsif Nkind (Name) = N_Explicit_Dereference
3836 and then Is_Remote_Access_To_Class_Wide_Type (Etype (Prefix (Name)))
3837 and then Comes_From_Source (N)
3838 then
3839 if Try_Object_Operation (N) then
3840 return;
3841 else
3842 Error_Msg_N
3843 ("invalid dereference of a remote access-to-class-wide value",
3844 N);
3845 end if;
3846 end if;
3847
3848 -- (Ada 2005): if the prefix is the limited view of a type, and
3849 -- the context already includes the full view, use the full view
3850 -- in what follows, either to retrieve a component of to find
3851 -- a primitive operation. If the prefix is an explicit dereference,
3852 -- set the type of the prefix to reflect this transformation.
3853 -- If the non-limited view is itself an incomplete type, get the
3854 -- full view if available.
3855
3856 if Is_Incomplete_Type (Prefix_Type)
3857 and then From_With_Type (Prefix_Type)
3858 and then Present (Non_Limited_View (Prefix_Type))
3859 then
3860 Prefix_Type := Get_Full_View (Non_Limited_View (Prefix_Type));
3861
3862 if Nkind (N) = N_Explicit_Dereference then
3863 Set_Etype (Prefix (N), Prefix_Type);
3864 end if;
3865
3866 elsif Ekind (Prefix_Type) = E_Class_Wide_Type
3867 and then From_With_Type (Prefix_Type)
3868 and then Present (Non_Limited_View (Etype (Prefix_Type)))
3869 then
3870 Prefix_Type :=
3871 Class_Wide_Type (Non_Limited_View (Etype (Prefix_Type)));
3872
3873 if Nkind (N) = N_Explicit_Dereference then
3874 Set_Etype (Prefix (N), Prefix_Type);
3875 end if;
3876 end if;
3877
3878 if Ekind (Prefix_Type) = E_Private_Subtype then
3879 Prefix_Type := Base_Type (Prefix_Type);
3880 end if;
3881
3882 Type_To_Use := Prefix_Type;
3883
3884 -- For class-wide types, use the entity list of the root type. This
3885 -- indirection is specially important for private extensions because
3886 -- only the root type get switched (not the class-wide type).
3887
3888 if Is_Class_Wide_Type (Prefix_Type) then
3889 Type_To_Use := Root_Type (Prefix_Type);
3890 end if;
3891
3892 -- If the prefix is a single concurrent object, use its name in error
3893 -- messages, rather than that of its anonymous type.
3894
3895 Is_Single_Concurrent_Object :=
3896 Is_Concurrent_Type (Prefix_Type)
3897 and then Is_Internal_Name (Chars (Prefix_Type))
3898 and then not Is_Derived_Type (Prefix_Type)
3899 and then Is_Entity_Name (Name);
3900
3901 Comp := First_Entity (Type_To_Use);
3902
3903 -- If the selector has an original discriminant, the node appears in
3904 -- an instance. Replace the discriminant with the corresponding one
3905 -- in the current discriminated type. For nested generics, this must
3906 -- be done transitively, so note the new original discriminant.
3907
3908 if Nkind (Sel) = N_Identifier
3909 and then In_Instance
3910 and then Present (Original_Discriminant (Sel))
3911 then
3912 Comp := Find_Corresponding_Discriminant (Sel, Prefix_Type);
3913
3914 -- Mark entity before rewriting, for completeness and because
3915 -- subsequent semantic checks might examine the original node.
3916
3917 Set_Entity (Sel, Comp);
3918 Rewrite (Selector_Name (N), New_Occurrence_Of (Comp, Sloc (N)));
3919 Set_Original_Discriminant (Selector_Name (N), Comp);
3920 Set_Etype (N, Etype (Comp));
3921 Check_Implicit_Dereference (N, Etype (Comp));
3922
3923 if Is_Access_Type (Etype (Name)) then
3924 Insert_Explicit_Dereference (Name);
3925 Error_Msg_NW (Warn_On_Dereference, "?implicit dereference", N);
3926 end if;
3927
3928 elsif Is_Record_Type (Prefix_Type) then
3929
3930 -- Find component with given name. In an instance, if the node is
3931 -- known as a prefixed call, do not examine components whose
3932 -- visibility may be accidental.
3933
3934 while Present (Comp) and then not Is_Prefixed_Call (N) loop
3935 if Chars (Comp) = Chars (Sel)
3936 and then Is_Visible_Component (Comp, N)
3937 then
3938 Set_Entity_With_Style_Check (Sel, Comp);
3939 Set_Etype (Sel, Etype (Comp));
3940
3941 if Ekind (Comp) = E_Discriminant then
3942 if Is_Unchecked_Union (Base_Type (Prefix_Type)) then
3943 Error_Msg_N
3944 ("cannot reference discriminant of unchecked union",
3945 Sel);
3946 end if;
3947
3948 if Is_Generic_Type (Prefix_Type)
3949 or else
3950 Is_Generic_Type (Root_Type (Prefix_Type))
3951 then
3952 Set_Original_Discriminant (Sel, Comp);
3953 end if;
3954 end if;
3955
3956 -- Resolve the prefix early otherwise it is not possible to
3957 -- build the actual subtype of the component: it may need
3958 -- to duplicate this prefix and duplication is only allowed
3959 -- on fully resolved expressions.
3960
3961 Resolve (Name);
3962
3963 -- Ada 2005 (AI-50217): Check wrong use of incomplete types or
3964 -- subtypes in a package specification.
3965 -- Example:
3966
3967 -- limited with Pkg;
3968 -- package Pkg is
3969 -- type Acc_Inc is access Pkg.T;
3970 -- X : Acc_Inc;
3971 -- N : Natural := X.all.Comp; -- ERROR, limited view
3972 -- end Pkg; -- Comp is not visible
3973
3974 if Nkind (Name) = N_Explicit_Dereference
3975 and then From_With_Type (Etype (Prefix (Name)))
3976 and then not Is_Potentially_Use_Visible (Etype (Name))
3977 and then Nkind (Parent (Cunit_Entity (Current_Sem_Unit))) =
3978 N_Package_Specification
3979 then
3980 Error_Msg_NE
3981 ("premature usage of incomplete}", Prefix (Name),
3982 Etype (Prefix (Name)));
3983 end if;
3984
3985 -- We never need an actual subtype for the case of a selection
3986 -- for a indexed component of a non-packed array, since in
3987 -- this case gigi generates all the checks and can find the
3988 -- necessary bounds information.
3989
3990 -- We also do not need an actual subtype for the case of a
3991 -- first, last, length, or range attribute applied to a
3992 -- non-packed array, since gigi can again get the bounds in
3993 -- these cases (gigi cannot handle the packed case, since it
3994 -- has the bounds of the packed array type, not the original
3995 -- bounds of the type). However, if the prefix is itself a
3996 -- selected component, as in a.b.c (i), gigi may regard a.b.c
3997 -- as a dynamic-sized temporary, so we do generate an actual
3998 -- subtype for this case.
3999
4000 Parent_N := Parent (N);
4001
4002 if not Is_Packed (Etype (Comp))
4003 and then
4004 ((Nkind (Parent_N) = N_Indexed_Component
4005 and then Nkind (Name) /= N_Selected_Component)
4006 or else
4007 (Nkind (Parent_N) = N_Attribute_Reference
4008 and then (Attribute_Name (Parent_N) = Name_First
4009 or else
4010 Attribute_Name (Parent_N) = Name_Last
4011 or else
4012 Attribute_Name (Parent_N) = Name_Length
4013 or else
4014 Attribute_Name (Parent_N) = Name_Range)))
4015 then
4016 Set_Etype (N, Etype (Comp));
4017
4018 -- If full analysis is not enabled, we do not generate an
4019 -- actual subtype, because in the absence of expansion
4020 -- reference to a formal of a protected type, for example,
4021 -- will not be properly transformed, and will lead to
4022 -- out-of-scope references in gigi.
4023
4024 -- In all other cases, we currently build an actual subtype.
4025 -- It seems likely that many of these cases can be avoided,
4026 -- but right now, the front end makes direct references to the
4027 -- bounds (e.g. in generating a length check), and if we do
4028 -- not make an actual subtype, we end up getting a direct
4029 -- reference to a discriminant, which will not do.
4030
4031 elsif Full_Analysis then
4032 Act_Decl :=
4033 Build_Actual_Subtype_Of_Component (Etype (Comp), N);
4034 Insert_Action (N, Act_Decl);
4035
4036 if No (Act_Decl) then
4037 Set_Etype (N, Etype (Comp));
4038
4039 else
4040 -- Component type depends on discriminants. Enter the
4041 -- main attributes of the subtype.
4042
4043 declare
4044 Subt : constant Entity_Id :=
4045 Defining_Identifier (Act_Decl);
4046
4047 begin
4048 Set_Etype (Subt, Base_Type (Etype (Comp)));
4049 Set_Ekind (Subt, Ekind (Etype (Comp)));
4050 Set_Etype (N, Subt);
4051 end;
4052 end if;
4053
4054 -- If Full_Analysis not enabled, just set the Etype
4055
4056 else
4057 Set_Etype (N, Etype (Comp));
4058 end if;
4059
4060 Check_Implicit_Dereference (N, Etype (N));
4061 return;
4062 end if;
4063
4064 -- If the prefix is a private extension, check only the visible
4065 -- components of the partial view. This must include the tag,
4066 -- which can appear in expanded code in a tag check.
4067
4068 if Ekind (Type_To_Use) = E_Record_Type_With_Private
4069 and then Chars (Selector_Name (N)) /= Name_uTag
4070 then
4071 exit when Comp = Last_Entity (Type_To_Use);
4072 end if;
4073
4074 Next_Entity (Comp);
4075 end loop;
4076
4077 -- Ada 2005 (AI-252): The selected component can be interpreted as
4078 -- a prefixed view of a subprogram. Depending on the context, this is
4079 -- either a name that can appear in a renaming declaration, or part
4080 -- of an enclosing call given in prefix form.
4081
4082 -- Ada 2005 (AI05-0030): In the case of dispatching requeue, the
4083 -- selected component should resolve to a name.
4084
4085 if Ada_Version >= Ada_2005
4086 and then Is_Tagged_Type (Prefix_Type)
4087 and then not Is_Concurrent_Type (Prefix_Type)
4088 then
4089 if Nkind (Parent (N)) = N_Generic_Association
4090 or else Nkind (Parent (N)) = N_Requeue_Statement
4091 or else Nkind (Parent (N)) = N_Subprogram_Renaming_Declaration
4092 then
4093 if Find_Primitive_Operation (N) then
4094 return;
4095 end if;
4096
4097 elsif Try_Object_Operation (N) then
4098 return;
4099 end if;
4100
4101 -- If the transformation fails, it will be necessary to redo the
4102 -- analysis with all errors enabled, to indicate candidate
4103 -- interpretations and reasons for each failure ???
4104
4105 end if;
4106
4107 elsif Is_Private_Type (Prefix_Type) then
4108
4109 -- Allow access only to discriminants of the type. If the type has
4110 -- no full view, gigi uses the parent type for the components, so we
4111 -- do the same here.
4112
4113 if No (Full_View (Prefix_Type)) then
4114 Type_To_Use := Root_Type (Base_Type (Prefix_Type));
4115 Comp := First_Entity (Type_To_Use);
4116 end if;
4117
4118 while Present (Comp) loop
4119 if Chars (Comp) = Chars (Sel) then
4120 if Ekind (Comp) = E_Discriminant then
4121 Set_Entity_With_Style_Check (Sel, Comp);
4122 Generate_Reference (Comp, Sel);
4123
4124 Set_Etype (Sel, Etype (Comp));
4125 Set_Etype (N, Etype (Comp));
4126 Check_Implicit_Dereference (N, Etype (N));
4127
4128 if Is_Generic_Type (Prefix_Type)
4129 or else Is_Generic_Type (Root_Type (Prefix_Type))
4130 then
4131 Set_Original_Discriminant (Sel, Comp);
4132 end if;
4133
4134 -- Before declaring an error, check whether this is tagged
4135 -- private type and a call to a primitive operation.
4136
4137 elsif Ada_Version >= Ada_2005
4138 and then Is_Tagged_Type (Prefix_Type)
4139 and then Try_Object_Operation (N)
4140 then
4141 return;
4142
4143 else
4144 Error_Msg_Node_2 := First_Subtype (Prefix_Type);
4145 Error_Msg_NE ("invisible selector& for }", N, Sel);
4146 Set_Entity (Sel, Any_Id);
4147 Set_Etype (N, Any_Type);
4148 end if;
4149
4150 return;
4151 end if;
4152
4153 Next_Entity (Comp);
4154 end loop;
4155
4156 elsif Is_Concurrent_Type (Prefix_Type) then
4157
4158 -- Find visible operation with given name. For a protected type,
4159 -- the possible candidates are discriminants, entries or protected
4160 -- procedures. For a task type, the set can only include entries or
4161 -- discriminants if the task type is not an enclosing scope. If it
4162 -- is an enclosing scope (e.g. in an inner task) then all entities
4163 -- are visible, but the prefix must denote the enclosing scope, i.e.
4164 -- can only be a direct name or an expanded name.
4165
4166 Set_Etype (Sel, Any_Type);
4167 In_Scope := In_Open_Scopes (Prefix_Type);
4168
4169 while Present (Comp) loop
4170 if Chars (Comp) = Chars (Sel) then
4171 if Is_Overloadable (Comp) then
4172 Add_One_Interp (Sel, Comp, Etype (Comp));
4173
4174 -- If the prefix is tagged, the correct interpretation may
4175 -- lie in the primitive or class-wide operations of the
4176 -- type. Perform a simple conformance check to determine
4177 -- whether Try_Object_Operation should be invoked even if
4178 -- a visible entity is found.
4179
4180 if Is_Tagged_Type (Prefix_Type)
4181 and then
4182 Nkind_In (Parent (N), N_Procedure_Call_Statement,
4183 N_Function_Call,
4184 N_Indexed_Component)
4185 and then Has_Mode_Conformant_Spec (Comp)
4186 then
4187 Has_Candidate := True;
4188 end if;
4189
4190 -- Note: a selected component may not denote a component of a
4191 -- protected type (4.1.3(7)).
4192
4193 elsif Ekind_In (Comp, E_Discriminant, E_Entry_Family)
4194 or else (In_Scope
4195 and then not Is_Protected_Type (Prefix_Type)
4196 and then Is_Entity_Name (Name))
4197 then
4198 Set_Entity_With_Style_Check (Sel, Comp);
4199 Generate_Reference (Comp, Sel);
4200
4201 -- The selector is not overloadable, so we have a candidate
4202 -- interpretation.
4203
4204 Has_Candidate := True;
4205
4206 else
4207 goto Next_Comp;
4208 end if;
4209
4210 Set_Etype (Sel, Etype (Comp));
4211 Set_Etype (N, Etype (Comp));
4212
4213 if Ekind (Comp) = E_Discriminant then
4214 Set_Original_Discriminant (Sel, Comp);
4215 end if;
4216
4217 -- For access type case, introduce explicit dereference for
4218 -- more uniform treatment of entry calls.
4219
4220 if Is_Access_Type (Etype (Name)) then
4221 Insert_Explicit_Dereference (Name);
4222 Error_Msg_NW
4223 (Warn_On_Dereference, "?implicit dereference", N);
4224 end if;
4225 end if;
4226
4227 <<Next_Comp>>
4228 Next_Entity (Comp);
4229 exit when not In_Scope
4230 and then
4231 Comp = First_Private_Entity (Base_Type (Prefix_Type));
4232 end loop;
4233
4234 -- If there is no visible entity with the given name or none of the
4235 -- visible entities are plausible interpretations, check whether
4236 -- there is some other primitive operation with that name.
4237
4238 if Ada_Version >= Ada_2005
4239 and then Is_Tagged_Type (Prefix_Type)
4240 then
4241 if (Etype (N) = Any_Type
4242 or else not Has_Candidate)
4243 and then Try_Object_Operation (N)
4244 then
4245 return;
4246
4247 -- If the context is not syntactically a procedure call, it
4248 -- may be a call to a primitive function declared outside of
4249 -- the synchronized type.
4250
4251 -- If the context is a procedure call, there might still be
4252 -- an overloading between an entry and a primitive procedure
4253 -- declared outside of the synchronized type, called in prefix
4254 -- notation. This is harder to disambiguate because in one case
4255 -- the controlling formal is implicit ???
4256
4257 elsif Nkind (Parent (N)) /= N_Procedure_Call_Statement
4258 and then Nkind (Parent (N)) /= N_Indexed_Component
4259 and then Try_Object_Operation (N)
4260 then
4261 return;
4262 end if;
4263
4264 -- Ada 2012 (AI05-0090-1): If we found a candidate of a call to an
4265 -- entry or procedure of a tagged concurrent type we must check
4266 -- if there are class-wide subprograms covering the primitive. If
4267 -- true then Try_Object_Operation reports the error.
4268
4269 if Has_Candidate
4270 and then Is_Concurrent_Type (Prefix_Type)
4271 and then Nkind (Parent (N)) = N_Procedure_Call_Statement
4272
4273 -- Duplicate the call. This is required to avoid problems with
4274 -- the tree transformations performed by Try_Object_Operation.
4275 -- Set properly the parent of the copied call, because it is
4276 -- about to be reanalyzed.
4277
4278 then
4279 declare
4280 Par : constant Node_Id := New_Copy_Tree (Parent (N));
4281
4282 begin
4283 Set_Parent (Par, Parent (Parent (N)));
4284
4285 if Try_Object_Operation
4286 (Sinfo.Name (Par), CW_Test_Only => True)
4287 then
4288 return;
4289 end if;
4290 end;
4291 end if;
4292 end if;
4293
4294 if Etype (N) = Any_Type and then Is_Protected_Type (Prefix_Type) then
4295
4296 -- Case of a prefix of a protected type: selector might denote
4297 -- an invisible private component.
4298
4299 Comp := First_Private_Entity (Base_Type (Prefix_Type));
4300 while Present (Comp) and then Chars (Comp) /= Chars (Sel) loop
4301 Next_Entity (Comp);
4302 end loop;
4303
4304 if Present (Comp) then
4305 if Is_Single_Concurrent_Object then
4306 Error_Msg_Node_2 := Entity (Name);
4307 Error_Msg_NE ("invisible selector& for &", N, Sel);
4308
4309 else
4310 Error_Msg_Node_2 := First_Subtype (Prefix_Type);
4311 Error_Msg_NE ("invisible selector& for }", N, Sel);
4312 end if;
4313 return;
4314 end if;
4315 end if;
4316
4317 Set_Is_Overloaded (N, Is_Overloaded (Sel));
4318
4319 else
4320 -- Invalid prefix
4321
4322 Error_Msg_NE ("invalid prefix in selected component&", N, Sel);
4323 end if;
4324
4325 -- If N still has no type, the component is not defined in the prefix
4326
4327 if Etype (N) = Any_Type then
4328
4329 if Is_Single_Concurrent_Object then
4330 Error_Msg_Node_2 := Entity (Name);
4331 Error_Msg_NE ("no selector& for&", N, Sel);
4332
4333 Check_Misspelled_Selector (Type_To_Use, Sel);
4334
4335 elsif Is_Generic_Type (Prefix_Type)
4336 and then Ekind (Prefix_Type) = E_Record_Type_With_Private
4337 and then Prefix_Type /= Etype (Prefix_Type)
4338 and then Is_Record_Type (Etype (Prefix_Type))
4339 then
4340 -- If this is a derived formal type, the parent may have
4341 -- different visibility at this point. Try for an inherited
4342 -- component before reporting an error.
4343
4344 Set_Etype (Prefix (N), Etype (Prefix_Type));
4345 Analyze_Selected_Component (N);
4346 return;
4347
4348 -- Similarly, if this is the actual for a formal derived type, the
4349 -- component inherited from the generic parent may not be visible
4350 -- in the actual, but the selected component is legal.
4351
4352 elsif Ekind (Prefix_Type) = E_Record_Subtype_With_Private
4353 and then Is_Generic_Actual_Type (Prefix_Type)
4354 and then Present (Full_View (Prefix_Type))
4355 then
4356
4357 Find_Component_In_Instance
4358 (Generic_Parent_Type (Parent (Prefix_Type)));
4359 return;
4360
4361 -- Finally, the formal and the actual may be private extensions,
4362 -- but the generic is declared in a child unit of the parent, and
4363 -- an additional step is needed to retrieve the proper scope.
4364
4365 elsif In_Instance
4366 and then Present (Parent_Subtype (Etype (Base_Type (Prefix_Type))))
4367 then
4368 Find_Component_In_Instance
4369 (Parent_Subtype (Etype (Base_Type (Prefix_Type))));
4370 return;
4371
4372 -- Component not found, specialize error message when appropriate
4373
4374 else
4375 if Ekind (Prefix_Type) = E_Record_Subtype then
4376
4377 -- Check whether this is a component of the base type which
4378 -- is absent from a statically constrained subtype. This will
4379 -- raise constraint error at run time, but is not a compile-
4380 -- time error. When the selector is illegal for base type as
4381 -- well fall through and generate a compilation error anyway.
4382
4383 Comp := First_Component (Base_Type (Prefix_Type));
4384 while Present (Comp) loop
4385 if Chars (Comp) = Chars (Sel)
4386 and then Is_Visible_Component (Comp)
4387 then
4388 Set_Entity_With_Style_Check (Sel, Comp);
4389 Generate_Reference (Comp, Sel);
4390 Set_Etype (Sel, Etype (Comp));
4391 Set_Etype (N, Etype (Comp));
4392
4393 -- Emit appropriate message. Gigi will replace the
4394 -- node subsequently with the appropriate Raise.
4395
4396 -- In Alfa mode, this is made into an error to simplify
4397 -- the processing of the formal verification backend.
4398
4399 if Alfa_Mode then
4400 Apply_Compile_Time_Constraint_Error
4401 (N, "component not present in }",
4402 CE_Discriminant_Check_Failed,
4403 Ent => Prefix_Type, Rep => False);
4404 else
4405 Apply_Compile_Time_Constraint_Error
4406 (N, "component not present in }?",
4407 CE_Discriminant_Check_Failed,
4408 Ent => Prefix_Type, Rep => False);
4409 end if;
4410
4411 Set_Raises_Constraint_Error (N);
4412 return;
4413 end if;
4414
4415 Next_Component (Comp);
4416 end loop;
4417
4418 end if;
4419
4420 Error_Msg_Node_2 := First_Subtype (Prefix_Type);
4421 Error_Msg_NE ("no selector& for}", N, Sel);
4422
4423 -- Add information in the case of an incomplete prefix
4424
4425 if Is_Incomplete_Type (Type_To_Use) then
4426 declare
4427 Inc : constant Entity_Id := First_Subtype (Type_To_Use);
4428
4429 begin
4430 if From_With_Type (Scope (Type_To_Use)) then
4431 Error_Msg_NE
4432 ("\limited view of& has no components", N, Inc);
4433
4434 else
4435 Error_Msg_NE
4436 ("\premature usage of incomplete type&", N, Inc);
4437
4438 if Nkind (Parent (Inc)) =
4439 N_Incomplete_Type_Declaration
4440 then
4441 -- Record location of premature use in entity so that
4442 -- a continuation message is generated when the
4443 -- completion is seen.
4444
4445 Set_Premature_Use (Parent (Inc), N);
4446 end if;
4447 end if;
4448 end;
4449 end if;
4450
4451 Check_Misspelled_Selector (Type_To_Use, Sel);
4452 end if;
4453
4454 Set_Entity (Sel, Any_Id);
4455 Set_Etype (Sel, Any_Type);
4456 end if;
4457 end Analyze_Selected_Component;
4458
4459 ---------------------------
4460 -- Analyze_Short_Circuit --
4461 ---------------------------
4462
4463 procedure Analyze_Short_Circuit (N : Node_Id) is
4464 L : constant Node_Id := Left_Opnd (N);
4465 R : constant Node_Id := Right_Opnd (N);
4466 Ind : Interp_Index;
4467 It : Interp;
4468
4469 begin
4470 Analyze_Expression (L);
4471 Analyze_Expression (R);
4472 Set_Etype (N, Any_Type);
4473
4474 if not Is_Overloaded (L) then
4475 if Root_Type (Etype (L)) = Standard_Boolean
4476 and then Has_Compatible_Type (R, Etype (L))
4477 then
4478 Add_One_Interp (N, Etype (L), Etype (L));
4479 end if;
4480
4481 else
4482 Get_First_Interp (L, Ind, It);
4483 while Present (It.Typ) loop
4484 if Root_Type (It.Typ) = Standard_Boolean
4485 and then Has_Compatible_Type (R, It.Typ)
4486 then
4487 Add_One_Interp (N, It.Typ, It.Typ);
4488 end if;
4489
4490 Get_Next_Interp (Ind, It);
4491 end loop;
4492 end if;
4493
4494 -- Here we have failed to find an interpretation. Clearly we know that
4495 -- it is not the case that both operands can have an interpretation of
4496 -- Boolean, but this is by far the most likely intended interpretation.
4497 -- So we simply resolve both operands as Booleans, and at least one of
4498 -- these resolutions will generate an error message, and we do not need
4499 -- to give another error message on the short circuit operation itself.
4500
4501 if Etype (N) = Any_Type then
4502 Resolve (L, Standard_Boolean);
4503 Resolve (R, Standard_Boolean);
4504 Set_Etype (N, Standard_Boolean);
4505 end if;
4506 end Analyze_Short_Circuit;
4507
4508 -------------------
4509 -- Analyze_Slice --
4510 -------------------
4511
4512 procedure Analyze_Slice (N : Node_Id) is
4513 D : constant Node_Id := Discrete_Range (N);
4514 P : constant Node_Id := Prefix (N);
4515 Array_Type : Entity_Id;
4516 Index_Type : Entity_Id;
4517
4518 procedure Analyze_Overloaded_Slice;
4519 -- If the prefix is overloaded, select those interpretations that
4520 -- yield a one-dimensional array type.
4521
4522 ------------------------------
4523 -- Analyze_Overloaded_Slice --
4524 ------------------------------
4525
4526 procedure Analyze_Overloaded_Slice is
4527 I : Interp_Index;
4528 It : Interp;
4529 Typ : Entity_Id;
4530
4531 begin
4532 Set_Etype (N, Any_Type);
4533
4534 Get_First_Interp (P, I, It);
4535 while Present (It.Nam) loop
4536 Typ := It.Typ;
4537
4538 if Is_Access_Type (Typ) then
4539 Typ := Designated_Type (Typ);
4540 Error_Msg_NW (Warn_On_Dereference, "?implicit dereference", N);
4541 end if;
4542
4543 if Is_Array_Type (Typ)
4544 and then Number_Dimensions (Typ) = 1
4545 and then Has_Compatible_Type (D, Etype (First_Index (Typ)))
4546 then
4547 Add_One_Interp (N, Typ, Typ);
4548 end if;
4549
4550 Get_Next_Interp (I, It);
4551 end loop;
4552
4553 if Etype (N) = Any_Type then
4554 Error_Msg_N ("expect array type in prefix of slice", N);
4555 end if;
4556 end Analyze_Overloaded_Slice;
4557
4558 -- Start of processing for Analyze_Slice
4559
4560 begin
4561 if Comes_From_Source (N) then
4562 Check_SPARK_Restriction ("slice is not allowed", N);
4563 end if;
4564
4565 Analyze (P);
4566 Analyze (D);
4567
4568 if Is_Overloaded (P) then
4569 Analyze_Overloaded_Slice;
4570
4571 else
4572 Array_Type := Etype (P);
4573 Set_Etype (N, Any_Type);
4574
4575 if Is_Access_Type (Array_Type) then
4576 Array_Type := Designated_Type (Array_Type);
4577 Error_Msg_NW (Warn_On_Dereference, "?implicit dereference", N);
4578 end if;
4579
4580 if not Is_Array_Type (Array_Type) then
4581 Wrong_Type (P, Any_Array);
4582
4583 elsif Number_Dimensions (Array_Type) > 1 then
4584 Error_Msg_N
4585 ("type is not one-dimensional array in slice prefix", N);
4586
4587 else
4588 if Ekind (Array_Type) = E_String_Literal_Subtype then
4589 Index_Type := Etype (String_Literal_Low_Bound (Array_Type));
4590 else
4591 Index_Type := Etype (First_Index (Array_Type));
4592 end if;
4593
4594 if not Has_Compatible_Type (D, Index_Type) then
4595 Wrong_Type (D, Index_Type);
4596 else
4597 Set_Etype (N, Array_Type);
4598 end if;
4599 end if;
4600 end if;
4601 end Analyze_Slice;
4602
4603 -----------------------------
4604 -- Analyze_Type_Conversion --
4605 -----------------------------
4606
4607 procedure Analyze_Type_Conversion (N : Node_Id) is
4608 Expr : constant Node_Id := Expression (N);
4609 T : Entity_Id;
4610
4611 begin
4612 -- If Conversion_OK is set, then the Etype is already set, and the
4613 -- only processing required is to analyze the expression. This is
4614 -- used to construct certain "illegal" conversions which are not
4615 -- allowed by Ada semantics, but can be handled OK by Gigi, see
4616 -- Sinfo for further details.
4617
4618 if Conversion_OK (N) then
4619 Analyze (Expr);
4620 return;
4621 end if;
4622
4623 -- Otherwise full type analysis is required, as well as some semantic
4624 -- checks to make sure the argument of the conversion is appropriate.
4625
4626 Find_Type (Subtype_Mark (N));
4627 T := Entity (Subtype_Mark (N));
4628 Set_Etype (N, T);
4629 Check_Fully_Declared (T, N);
4630 Analyze_Expression (Expr);
4631 Validate_Remote_Type_Type_Conversion (N);
4632
4633 -- Only remaining step is validity checks on the argument. These
4634 -- are skipped if the conversion does not come from the source.
4635
4636 if not Comes_From_Source (N) then
4637 return;
4638
4639 -- If there was an error in a generic unit, no need to replicate the
4640 -- error message. Conversely, constant-folding in the generic may
4641 -- transform the argument of a conversion into a string literal, which
4642 -- is legal. Therefore the following tests are not performed in an
4643 -- instance.
4644
4645 elsif In_Instance then
4646 return;
4647
4648 elsif Nkind (Expr) = N_Null then
4649 Error_Msg_N ("argument of conversion cannot be null", N);
4650 Error_Msg_N ("\use qualified expression instead", N);
4651 Set_Etype (N, Any_Type);
4652
4653 elsif Nkind (Expr) = N_Aggregate then
4654 Error_Msg_N ("argument of conversion cannot be aggregate", N);
4655 Error_Msg_N ("\use qualified expression instead", N);
4656
4657 elsif Nkind (Expr) = N_Allocator then
4658 Error_Msg_N ("argument of conversion cannot be an allocator", N);
4659 Error_Msg_N ("\use qualified expression instead", N);
4660
4661 elsif Nkind (Expr) = N_String_Literal then
4662 Error_Msg_N ("argument of conversion cannot be string literal", N);
4663 Error_Msg_N ("\use qualified expression instead", N);
4664
4665 elsif Nkind (Expr) = N_Character_Literal then
4666 if Ada_Version = Ada_83 then
4667 Resolve (Expr, T);
4668 else
4669 Error_Msg_N ("argument of conversion cannot be character literal",
4670 N);
4671 Error_Msg_N ("\use qualified expression instead", N);
4672 end if;
4673
4674 elsif Nkind (Expr) = N_Attribute_Reference
4675 and then
4676 (Attribute_Name (Expr) = Name_Access or else
4677 Attribute_Name (Expr) = Name_Unchecked_Access or else
4678 Attribute_Name (Expr) = Name_Unrestricted_Access)
4679 then
4680 Error_Msg_N ("argument of conversion cannot be access", N);
4681 Error_Msg_N ("\use qualified expression instead", N);
4682 end if;
4683 end Analyze_Type_Conversion;
4684
4685 ----------------------
4686 -- Analyze_Unary_Op --
4687 ----------------------
4688
4689 procedure Analyze_Unary_Op (N : Node_Id) is
4690 R : constant Node_Id := Right_Opnd (N);
4691 Op_Id : Entity_Id := Entity (N);
4692
4693 begin
4694 Set_Etype (N, Any_Type);
4695 Candidate_Type := Empty;
4696
4697 Analyze_Expression (R);
4698
4699 if Present (Op_Id) then
4700 if Ekind (Op_Id) = E_Operator then
4701 Find_Unary_Types (R, Op_Id, N);
4702 else
4703 Add_One_Interp (N, Op_Id, Etype (Op_Id));
4704 end if;
4705
4706 else
4707 Op_Id := Get_Name_Entity_Id (Chars (N));
4708 while Present (Op_Id) loop
4709 if Ekind (Op_Id) = E_Operator then
4710 if No (Next_Entity (First_Entity (Op_Id))) then
4711 Find_Unary_Types (R, Op_Id, N);
4712 end if;
4713
4714 elsif Is_Overloadable (Op_Id) then
4715 Analyze_User_Defined_Unary_Op (N, Op_Id);
4716 end if;
4717
4718 Op_Id := Homonym (Op_Id);
4719 end loop;
4720 end if;
4721
4722 Operator_Check (N);
4723 end Analyze_Unary_Op;
4724
4725 ----------------------------------
4726 -- Analyze_Unchecked_Expression --
4727 ----------------------------------
4728
4729 procedure Analyze_Unchecked_Expression (N : Node_Id) is
4730 begin
4731 Analyze (Expression (N), Suppress => All_Checks);
4732 Set_Etype (N, Etype (Expression (N)));
4733 Save_Interps (Expression (N), N);
4734 end Analyze_Unchecked_Expression;
4735
4736 ---------------------------------------
4737 -- Analyze_Unchecked_Type_Conversion --
4738 ---------------------------------------
4739
4740 procedure Analyze_Unchecked_Type_Conversion (N : Node_Id) is
4741 begin
4742 Find_Type (Subtype_Mark (N));
4743 Analyze_Expression (Expression (N));
4744 Set_Etype (N, Entity (Subtype_Mark (N)));
4745 end Analyze_Unchecked_Type_Conversion;
4746
4747 ------------------------------------
4748 -- Analyze_User_Defined_Binary_Op --
4749 ------------------------------------
4750
4751 procedure Analyze_User_Defined_Binary_Op
4752 (N : Node_Id;
4753 Op_Id : Entity_Id)
4754 is
4755 begin
4756 -- Only do analysis if the operator Comes_From_Source, since otherwise
4757 -- the operator was generated by the expander, and all such operators
4758 -- always refer to the operators in package Standard.
4759
4760 if Comes_From_Source (N) then
4761 declare
4762 F1 : constant Entity_Id := First_Formal (Op_Id);
4763 F2 : constant Entity_Id := Next_Formal (F1);
4764
4765 begin
4766 -- Verify that Op_Id is a visible binary function. Note that since
4767 -- we know Op_Id is overloaded, potentially use visible means use
4768 -- visible for sure (RM 9.4(11)).
4769
4770 if Ekind (Op_Id) = E_Function
4771 and then Present (F2)
4772 and then (Is_Immediately_Visible (Op_Id)
4773 or else Is_Potentially_Use_Visible (Op_Id))
4774 and then Has_Compatible_Type (Left_Opnd (N), Etype (F1))
4775 and then Has_Compatible_Type (Right_Opnd (N), Etype (F2))
4776 then
4777 Add_One_Interp (N, Op_Id, Etype (Op_Id));
4778
4779 -- If the left operand is overloaded, indicate that the
4780 -- current type is a viable candidate. This is redundant
4781 -- in most cases, but for equality and comparison operators
4782 -- where the context does not impose a type on the operands,
4783 -- setting the proper type is necessary to avoid subsequent
4784 -- ambiguities during resolution, when both user-defined and
4785 -- predefined operators may be candidates.
4786
4787 if Is_Overloaded (Left_Opnd (N)) then
4788 Set_Etype (Left_Opnd (N), Etype (F1));
4789 end if;
4790
4791 if Debug_Flag_E then
4792 Write_Str ("user defined operator ");
4793 Write_Name (Chars (Op_Id));
4794 Write_Str (" on node ");
4795 Write_Int (Int (N));
4796 Write_Eol;
4797 end if;
4798 end if;
4799 end;
4800 end if;
4801 end Analyze_User_Defined_Binary_Op;
4802
4803 -----------------------------------
4804 -- Analyze_User_Defined_Unary_Op --
4805 -----------------------------------
4806
4807 procedure Analyze_User_Defined_Unary_Op
4808 (N : Node_Id;
4809 Op_Id : Entity_Id)
4810 is
4811 begin
4812 -- Only do analysis if the operator Comes_From_Source, since otherwise
4813 -- the operator was generated by the expander, and all such operators
4814 -- always refer to the operators in package Standard.
4815
4816 if Comes_From_Source (N) then
4817 declare
4818 F : constant Entity_Id := First_Formal (Op_Id);
4819
4820 begin
4821 -- Verify that Op_Id is a visible unary function. Note that since
4822 -- we know Op_Id is overloaded, potentially use visible means use
4823 -- visible for sure (RM 9.4(11)).
4824
4825 if Ekind (Op_Id) = E_Function
4826 and then No (Next_Formal (F))
4827 and then (Is_Immediately_Visible (Op_Id)
4828 or else Is_Potentially_Use_Visible (Op_Id))
4829 and then Has_Compatible_Type (Right_Opnd (N), Etype (F))
4830 then
4831 Add_One_Interp (N, Op_Id, Etype (Op_Id));
4832 end if;
4833 end;
4834 end if;
4835 end Analyze_User_Defined_Unary_Op;
4836
4837 ---------------------------
4838 -- Check_Arithmetic_Pair --
4839 ---------------------------
4840
4841 procedure Check_Arithmetic_Pair
4842 (T1, T2 : Entity_Id;
4843 Op_Id : Entity_Id;
4844 N : Node_Id)
4845 is
4846 Op_Name : constant Name_Id := Chars (Op_Id);
4847
4848 function Has_Fixed_Op (Typ : Entity_Id; Op : Entity_Id) return Boolean;
4849 -- Check whether the fixed-point type Typ has a user-defined operator
4850 -- (multiplication or division) that should hide the corresponding
4851 -- predefined operator. Used to implement Ada 2005 AI-264, to make
4852 -- such operators more visible and therefore useful.
4853
4854 -- If the name of the operation is an expanded name with prefix
4855 -- Standard, the predefined universal fixed operator is available,
4856 -- as specified by AI-420 (RM 4.5.5 (19.1/2)).
4857
4858 function Specific_Type (T1, T2 : Entity_Id) return Entity_Id;
4859 -- Get specific type (i.e. non-universal type if there is one)
4860
4861 ------------------
4862 -- Has_Fixed_Op --
4863 ------------------
4864
4865 function Has_Fixed_Op (Typ : Entity_Id; Op : Entity_Id) return Boolean is
4866 Bas : constant Entity_Id := Base_Type (Typ);
4867 Ent : Entity_Id;
4868 F1 : Entity_Id;
4869 F2 : Entity_Id;
4870
4871 begin
4872 -- If the universal_fixed operation is given explicitly the rule
4873 -- concerning primitive operations of the type do not apply.
4874
4875 if Nkind (N) = N_Function_Call
4876 and then Nkind (Name (N)) = N_Expanded_Name
4877 and then Entity (Prefix (Name (N))) = Standard_Standard
4878 then
4879 return False;
4880 end if;
4881
4882 -- The operation is treated as primitive if it is declared in the
4883 -- same scope as the type, and therefore on the same entity chain.
4884
4885 Ent := Next_Entity (Typ);
4886 while Present (Ent) loop
4887 if Chars (Ent) = Chars (Op) then
4888 F1 := First_Formal (Ent);
4889 F2 := Next_Formal (F1);
4890
4891 -- The operation counts as primitive if either operand or
4892 -- result are of the given base type, and both operands are
4893 -- fixed point types.
4894
4895 if (Base_Type (Etype (F1)) = Bas
4896 and then Is_Fixed_Point_Type (Etype (F2)))
4897
4898 or else
4899 (Base_Type (Etype (F2)) = Bas
4900 and then Is_Fixed_Point_Type (Etype (F1)))
4901
4902 or else
4903 (Base_Type (Etype (Ent)) = Bas
4904 and then Is_Fixed_Point_Type (Etype (F1))
4905 and then Is_Fixed_Point_Type (Etype (F2)))
4906 then
4907 return True;
4908 end if;
4909 end if;
4910
4911 Next_Entity (Ent);
4912 end loop;
4913
4914 return False;
4915 end Has_Fixed_Op;
4916
4917 -------------------
4918 -- Specific_Type --
4919 -------------------
4920
4921 function Specific_Type (T1, T2 : Entity_Id) return Entity_Id is
4922 begin
4923 if T1 = Universal_Integer or else T1 = Universal_Real then
4924 return Base_Type (T2);
4925 else
4926 return Base_Type (T1);
4927 end if;
4928 end Specific_Type;
4929
4930 -- Start of processing for Check_Arithmetic_Pair
4931
4932 begin
4933 if Op_Name = Name_Op_Add or else Op_Name = Name_Op_Subtract then
4934
4935 if Is_Numeric_Type (T1)
4936 and then Is_Numeric_Type (T2)
4937 and then (Covers (T1 => T1, T2 => T2)
4938 or else
4939 Covers (T1 => T2, T2 => T1))
4940 then
4941 Add_One_Interp (N, Op_Id, Specific_Type (T1, T2));
4942 end if;
4943
4944 elsif Op_Name = Name_Op_Multiply or else Op_Name = Name_Op_Divide then
4945
4946 if Is_Fixed_Point_Type (T1)
4947 and then (Is_Fixed_Point_Type (T2)
4948 or else T2 = Universal_Real)
4949 then
4950 -- If Treat_Fixed_As_Integer is set then the Etype is already set
4951 -- and no further processing is required (this is the case of an
4952 -- operator constructed by Exp_Fixd for a fixed point operation)
4953 -- Otherwise add one interpretation with universal fixed result
4954 -- If the operator is given in functional notation, it comes
4955 -- from source and Fixed_As_Integer cannot apply.
4956
4957 if (Nkind (N) not in N_Op
4958 or else not Treat_Fixed_As_Integer (N))
4959 and then
4960 (not Has_Fixed_Op (T1, Op_Id)
4961 or else Nkind (Parent (N)) = N_Type_Conversion)
4962 then
4963 Add_One_Interp (N, Op_Id, Universal_Fixed);
4964 end if;
4965
4966 elsif Is_Fixed_Point_Type (T2)
4967 and then (Nkind (N) not in N_Op
4968 or else not Treat_Fixed_As_Integer (N))
4969 and then T1 = Universal_Real
4970 and then
4971 (not Has_Fixed_Op (T1, Op_Id)
4972 or else Nkind (Parent (N)) = N_Type_Conversion)
4973 then
4974 Add_One_Interp (N, Op_Id, Universal_Fixed);
4975
4976 elsif Is_Numeric_Type (T1)
4977 and then Is_Numeric_Type (T2)
4978 and then (Covers (T1 => T1, T2 => T2)
4979 or else
4980 Covers (T1 => T2, T2 => T1))
4981 then
4982 Add_One_Interp (N, Op_Id, Specific_Type (T1, T2));
4983
4984 elsif Is_Fixed_Point_Type (T1)
4985 and then (Base_Type (T2) = Base_Type (Standard_Integer)
4986 or else T2 = Universal_Integer)
4987 then
4988 Add_One_Interp (N, Op_Id, T1);
4989
4990 elsif T2 = Universal_Real
4991 and then Base_Type (T1) = Base_Type (Standard_Integer)
4992 and then Op_Name = Name_Op_Multiply
4993 then
4994 Add_One_Interp (N, Op_Id, Any_Fixed);
4995
4996 elsif T1 = Universal_Real
4997 and then Base_Type (T2) = Base_Type (Standard_Integer)
4998 then
4999 Add_One_Interp (N, Op_Id, Any_Fixed);
5000
5001 elsif Is_Fixed_Point_Type (T2)
5002 and then (Base_Type (T1) = Base_Type (Standard_Integer)
5003 or else T1 = Universal_Integer)
5004 and then Op_Name = Name_Op_Multiply
5005 then
5006 Add_One_Interp (N, Op_Id, T2);
5007
5008 elsif T1 = Universal_Real and then T2 = Universal_Integer then
5009 Add_One_Interp (N, Op_Id, T1);
5010
5011 elsif T2 = Universal_Real
5012 and then T1 = Universal_Integer
5013 and then Op_Name = Name_Op_Multiply
5014 then
5015 Add_One_Interp (N, Op_Id, T2);
5016 end if;
5017
5018 elsif Op_Name = Name_Op_Mod or else Op_Name = Name_Op_Rem then
5019
5020 -- Note: The fixed-point operands case with Treat_Fixed_As_Integer
5021 -- set does not require any special processing, since the Etype is
5022 -- already set (case of operation constructed by Exp_Fixed).
5023
5024 if Is_Integer_Type (T1)
5025 and then (Covers (T1 => T1, T2 => T2)
5026 or else
5027 Covers (T1 => T2, T2 => T1))
5028 then
5029 Add_One_Interp (N, Op_Id, Specific_Type (T1, T2));
5030 end if;
5031
5032 elsif Op_Name = Name_Op_Expon then
5033 if Is_Numeric_Type (T1)
5034 and then not Is_Fixed_Point_Type (T1)
5035 and then (Base_Type (T2) = Base_Type (Standard_Integer)
5036 or else T2 = Universal_Integer)
5037 then
5038 Add_One_Interp (N, Op_Id, Base_Type (T1));
5039 end if;
5040
5041 else pragma Assert (Nkind (N) in N_Op_Shift);
5042
5043 -- If not one of the predefined operators, the node may be one
5044 -- of the intrinsic functions. Its kind is always specific, and
5045 -- we can use it directly, rather than the name of the operation.
5046
5047 if Is_Integer_Type (T1)
5048 and then (Base_Type (T2) = Base_Type (Standard_Integer)
5049 or else T2 = Universal_Integer)
5050 then
5051 Add_One_Interp (N, Op_Id, Base_Type (T1));
5052 end if;
5053 end if;
5054 end Check_Arithmetic_Pair;
5055
5056 -------------------------------
5057 -- Check_Misspelled_Selector --
5058 -------------------------------
5059
5060 procedure Check_Misspelled_Selector
5061 (Prefix : Entity_Id;
5062 Sel : Node_Id)
5063 is
5064 Max_Suggestions : constant := 2;
5065 Nr_Of_Suggestions : Natural := 0;
5066
5067 Suggestion_1 : Entity_Id := Empty;
5068 Suggestion_2 : Entity_Id := Empty;
5069
5070 Comp : Entity_Id;
5071
5072 begin
5073 -- All the components of the prefix of selector Sel are matched
5074 -- against Sel and a count is maintained of possible misspellings.
5075 -- When at the end of the analysis there are one or two (not more!)
5076 -- possible misspellings, these misspellings will be suggested as
5077 -- possible correction.
5078
5079 if not (Is_Private_Type (Prefix) or else Is_Record_Type (Prefix)) then
5080
5081 -- Concurrent types should be handled as well ???
5082
5083 return;
5084 end if;
5085
5086 Comp := First_Entity (Prefix);
5087 while Nr_Of_Suggestions <= Max_Suggestions and then Present (Comp) loop
5088 if Is_Visible_Component (Comp) then
5089 if Is_Bad_Spelling_Of (Chars (Comp), Chars (Sel)) then
5090 Nr_Of_Suggestions := Nr_Of_Suggestions + 1;
5091
5092 case Nr_Of_Suggestions is
5093 when 1 => Suggestion_1 := Comp;
5094 when 2 => Suggestion_2 := Comp;
5095 when others => exit;
5096 end case;
5097 end if;
5098 end if;
5099
5100 Comp := Next_Entity (Comp);
5101 end loop;
5102
5103 -- Report at most two suggestions
5104
5105 if Nr_Of_Suggestions = 1 then
5106 Error_Msg_NE -- CODEFIX
5107 ("\possible misspelling of&", Sel, Suggestion_1);
5108
5109 elsif Nr_Of_Suggestions = 2 then
5110 Error_Msg_Node_2 := Suggestion_2;
5111 Error_Msg_NE -- CODEFIX
5112 ("\possible misspelling of& or&", Sel, Suggestion_1);
5113 end if;
5114 end Check_Misspelled_Selector;
5115
5116 ----------------------
5117 -- Defined_In_Scope --
5118 ----------------------
5119
5120 function Defined_In_Scope (T : Entity_Id; S : Entity_Id) return Boolean
5121 is
5122 S1 : constant Entity_Id := Scope (Base_Type (T));
5123 begin
5124 return S1 = S
5125 or else (S1 = System_Aux_Id and then S = Scope (S1));
5126 end Defined_In_Scope;
5127
5128 -------------------
5129 -- Diagnose_Call --
5130 -------------------
5131
5132 procedure Diagnose_Call (N : Node_Id; Nam : Node_Id) is
5133 Actual : Node_Id;
5134 X : Interp_Index;
5135 It : Interp;
5136 Err_Mode : Boolean;
5137 New_Nam : Node_Id;
5138 Void_Interp_Seen : Boolean := False;
5139
5140 Success : Boolean;
5141 pragma Warnings (Off, Boolean);
5142
5143 begin
5144 if Ada_Version >= Ada_2005 then
5145 Actual := First_Actual (N);
5146 while Present (Actual) loop
5147
5148 -- Ada 2005 (AI-50217): Post an error in case of premature
5149 -- usage of an entity from the limited view.
5150
5151 if not Analyzed (Etype (Actual))
5152 and then From_With_Type (Etype (Actual))
5153 then
5154 Error_Msg_Qual_Level := 1;
5155 Error_Msg_NE
5156 ("missing with_clause for scope of imported type&",
5157 Actual, Etype (Actual));
5158 Error_Msg_Qual_Level := 0;
5159 end if;
5160
5161 Next_Actual (Actual);
5162 end loop;
5163 end if;
5164
5165 -- Analyze each candidate call again, with full error reporting
5166 -- for each.
5167
5168 Error_Msg_N
5169 ("no candidate interpretations match the actuals:!", Nam);
5170 Err_Mode := All_Errors_Mode;
5171 All_Errors_Mode := True;
5172
5173 -- If this is a call to an operation of a concurrent type,
5174 -- the failed interpretations have been removed from the
5175 -- name. Recover them to provide full diagnostics.
5176
5177 if Nkind (Parent (Nam)) = N_Selected_Component then
5178 Set_Entity (Nam, Empty);
5179 New_Nam := New_Copy_Tree (Parent (Nam));
5180 Set_Is_Overloaded (New_Nam, False);
5181 Set_Is_Overloaded (Selector_Name (New_Nam), False);
5182 Set_Parent (New_Nam, Parent (Parent (Nam)));
5183 Analyze_Selected_Component (New_Nam);
5184 Get_First_Interp (Selector_Name (New_Nam), X, It);
5185 else
5186 Get_First_Interp (Nam, X, It);
5187 end if;
5188
5189 while Present (It.Nam) loop
5190 if Etype (It.Nam) = Standard_Void_Type then
5191 Void_Interp_Seen := True;
5192 end if;
5193
5194 Analyze_One_Call (N, It.Nam, True, Success);
5195 Get_Next_Interp (X, It);
5196 end loop;
5197
5198 if Nkind (N) = N_Function_Call then
5199 Get_First_Interp (Nam, X, It);
5200 while Present (It.Nam) loop
5201 if Ekind_In (It.Nam, E_Function, E_Operator) then
5202 return;
5203 else
5204 Get_Next_Interp (X, It);
5205 end if;
5206 end loop;
5207
5208 -- If all interpretations are procedures, this deserves a
5209 -- more precise message. Ditto if this appears as the prefix
5210 -- of a selected component, which may be a lexical error.
5211
5212 Error_Msg_N
5213 ("\context requires function call, found procedure name", Nam);
5214
5215 if Nkind (Parent (N)) = N_Selected_Component
5216 and then N = Prefix (Parent (N))
5217 then
5218 Error_Msg_N -- CODEFIX
5219 ("\period should probably be semicolon", Parent (N));
5220 end if;
5221
5222 elsif Nkind (N) = N_Procedure_Call_Statement
5223 and then not Void_Interp_Seen
5224 then
5225 Error_Msg_N (
5226 "\function name found in procedure call", Nam);
5227 end if;
5228
5229 All_Errors_Mode := Err_Mode;
5230 end Diagnose_Call;
5231
5232 ---------------------------
5233 -- Find_Arithmetic_Types --
5234 ---------------------------
5235
5236 procedure Find_Arithmetic_Types
5237 (L, R : Node_Id;
5238 Op_Id : Entity_Id;
5239 N : Node_Id)
5240 is
5241 Index1 : Interp_Index;
5242 Index2 : Interp_Index;
5243 It1 : Interp;
5244 It2 : Interp;
5245
5246 procedure Check_Right_Argument (T : Entity_Id);
5247 -- Check right operand of operator
5248
5249 --------------------------
5250 -- Check_Right_Argument --
5251 --------------------------
5252
5253 procedure Check_Right_Argument (T : Entity_Id) is
5254 begin
5255 if not Is_Overloaded (R) then
5256 Check_Arithmetic_Pair (T, Etype (R), Op_Id, N);
5257 else
5258 Get_First_Interp (R, Index2, It2);
5259 while Present (It2.Typ) loop
5260 Check_Arithmetic_Pair (T, It2.Typ, Op_Id, N);
5261 Get_Next_Interp (Index2, It2);
5262 end loop;
5263 end if;
5264 end Check_Right_Argument;
5265
5266 -- Start of processing for Find_Arithmetic_Types
5267
5268 begin
5269 if not Is_Overloaded (L) then
5270 Check_Right_Argument (Etype (L));
5271
5272 else
5273 Get_First_Interp (L, Index1, It1);
5274 while Present (It1.Typ) loop
5275 Check_Right_Argument (It1.Typ);
5276 Get_Next_Interp (Index1, It1);
5277 end loop;
5278 end if;
5279
5280 end Find_Arithmetic_Types;
5281
5282 ------------------------
5283 -- Find_Boolean_Types --
5284 ------------------------
5285
5286 procedure Find_Boolean_Types
5287 (L, R : Node_Id;
5288 Op_Id : Entity_Id;
5289 N : Node_Id)
5290 is
5291 Index : Interp_Index;
5292 It : Interp;
5293
5294 procedure Check_Numeric_Argument (T : Entity_Id);
5295 -- Special case for logical operations one of whose operands is an
5296 -- integer literal. If both are literal the result is any modular type.
5297
5298 ----------------------------
5299 -- Check_Numeric_Argument --
5300 ----------------------------
5301
5302 procedure Check_Numeric_Argument (T : Entity_Id) is
5303 begin
5304 if T = Universal_Integer then
5305 Add_One_Interp (N, Op_Id, Any_Modular);
5306
5307 elsif Is_Modular_Integer_Type (T) then
5308 Add_One_Interp (N, Op_Id, T);
5309 end if;
5310 end Check_Numeric_Argument;
5311
5312 -- Start of processing for Find_Boolean_Types
5313
5314 begin
5315 if not Is_Overloaded (L) then
5316 if Etype (L) = Universal_Integer
5317 or else Etype (L) = Any_Modular
5318 then
5319 if not Is_Overloaded (R) then
5320 Check_Numeric_Argument (Etype (R));
5321
5322 else
5323 Get_First_Interp (R, Index, It);
5324 while Present (It.Typ) loop
5325 Check_Numeric_Argument (It.Typ);
5326 Get_Next_Interp (Index, It);
5327 end loop;
5328 end if;
5329
5330 -- If operands are aggregates, we must assume that they may be
5331 -- boolean arrays, and leave disambiguation for the second pass.
5332 -- If only one is an aggregate, verify that the other one has an
5333 -- interpretation as a boolean array
5334
5335 elsif Nkind (L) = N_Aggregate then
5336 if Nkind (R) = N_Aggregate then
5337 Add_One_Interp (N, Op_Id, Etype (L));
5338
5339 elsif not Is_Overloaded (R) then
5340 if Valid_Boolean_Arg (Etype (R)) then
5341 Add_One_Interp (N, Op_Id, Etype (R));
5342 end if;
5343
5344 else
5345 Get_First_Interp (R, Index, It);
5346 while Present (It.Typ) loop
5347 if Valid_Boolean_Arg (It.Typ) then
5348 Add_One_Interp (N, Op_Id, It.Typ);
5349 end if;
5350
5351 Get_Next_Interp (Index, It);
5352 end loop;
5353 end if;
5354
5355 elsif Valid_Boolean_Arg (Etype (L))
5356 and then Has_Compatible_Type (R, Etype (L))
5357 then
5358 Add_One_Interp (N, Op_Id, Etype (L));
5359 end if;
5360
5361 else
5362 Get_First_Interp (L, Index, It);
5363 while Present (It.Typ) loop
5364 if Valid_Boolean_Arg (It.Typ)
5365 and then Has_Compatible_Type (R, It.Typ)
5366 then
5367 Add_One_Interp (N, Op_Id, It.Typ);
5368 end if;
5369
5370 Get_Next_Interp (Index, It);
5371 end loop;
5372 end if;
5373 end Find_Boolean_Types;
5374
5375 ---------------------------
5376 -- Find_Comparison_Types --
5377 ---------------------------
5378
5379 procedure Find_Comparison_Types
5380 (L, R : Node_Id;
5381 Op_Id : Entity_Id;
5382 N : Node_Id)
5383 is
5384 Index : Interp_Index;
5385 It : Interp;
5386 Found : Boolean := False;
5387 I_F : Interp_Index;
5388 T_F : Entity_Id;
5389 Scop : Entity_Id := Empty;
5390
5391 procedure Try_One_Interp (T1 : Entity_Id);
5392 -- Routine to try one proposed interpretation. Note that the context
5393 -- of the operator plays no role in resolving the arguments, so that
5394 -- if there is more than one interpretation of the operands that is
5395 -- compatible with comparison, the operation is ambiguous.
5396
5397 --------------------
5398 -- Try_One_Interp --
5399 --------------------
5400
5401 procedure Try_One_Interp (T1 : Entity_Id) is
5402 begin
5403
5404 -- If the operator is an expanded name, then the type of the operand
5405 -- must be defined in the corresponding scope. If the type is
5406 -- universal, the context will impose the correct type.
5407
5408 if Present (Scop)
5409 and then not Defined_In_Scope (T1, Scop)
5410 and then T1 /= Universal_Integer
5411 and then T1 /= Universal_Real
5412 and then T1 /= Any_String
5413 and then T1 /= Any_Composite
5414 then
5415 return;
5416 end if;
5417
5418 if Valid_Comparison_Arg (T1)
5419 and then Has_Compatible_Type (R, T1)
5420 then
5421 if Found
5422 and then Base_Type (T1) /= Base_Type (T_F)
5423 then
5424 It := Disambiguate (L, I_F, Index, Any_Type);
5425
5426 if It = No_Interp then
5427 Ambiguous_Operands (N);
5428 Set_Etype (L, Any_Type);
5429 return;
5430
5431 else
5432 T_F := It.Typ;
5433 end if;
5434
5435 else
5436 Found := True;
5437 T_F := T1;
5438 I_F := Index;
5439 end if;
5440
5441 Set_Etype (L, T_F);
5442 Find_Non_Universal_Interpretations (N, R, Op_Id, T1);
5443
5444 end if;
5445 end Try_One_Interp;
5446
5447 -- Start of processing for Find_Comparison_Types
5448
5449 begin
5450 -- If left operand is aggregate, the right operand has to
5451 -- provide a usable type for it.
5452
5453 if Nkind (L) = N_Aggregate
5454 and then Nkind (R) /= N_Aggregate
5455 then
5456 Find_Comparison_Types (L => R, R => L, Op_Id => Op_Id, N => N);
5457 return;
5458 end if;
5459
5460 if Nkind (N) = N_Function_Call
5461 and then Nkind (Name (N)) = N_Expanded_Name
5462 then
5463 Scop := Entity (Prefix (Name (N)));
5464
5465 -- The prefix may be a package renaming, and the subsequent test
5466 -- requires the original package.
5467
5468 if Ekind (Scop) = E_Package
5469 and then Present (Renamed_Entity (Scop))
5470 then
5471 Scop := Renamed_Entity (Scop);
5472 Set_Entity (Prefix (Name (N)), Scop);
5473 end if;
5474 end if;
5475
5476 if not Is_Overloaded (L) then
5477 Try_One_Interp (Etype (L));
5478
5479 else
5480 Get_First_Interp (L, Index, It);
5481 while Present (It.Typ) loop
5482 Try_One_Interp (It.Typ);
5483 Get_Next_Interp (Index, It);
5484 end loop;
5485 end if;
5486 end Find_Comparison_Types;
5487
5488 ----------------------------------------
5489 -- Find_Non_Universal_Interpretations --
5490 ----------------------------------------
5491
5492 procedure Find_Non_Universal_Interpretations
5493 (N : Node_Id;
5494 R : Node_Id;
5495 Op_Id : Entity_Id;
5496 T1 : Entity_Id)
5497 is
5498 Index : Interp_Index;
5499 It : Interp;
5500
5501 begin
5502 if T1 = Universal_Integer
5503 or else T1 = Universal_Real
5504
5505 -- If the left operand of an equality operator is null, the visibility
5506 -- of the operator must be determined from the interpretation of the
5507 -- right operand. This processing must be done for Any_Access, which
5508 -- is the internal representation of the type of the literal null.
5509
5510 or else T1 = Any_Access
5511 then
5512 if not Is_Overloaded (R) then
5513 Add_One_Interp
5514 (N, Op_Id, Standard_Boolean, Base_Type (Etype (R)));
5515 else
5516 Get_First_Interp (R, Index, It);
5517 while Present (It.Typ) loop
5518 if Covers (It.Typ, T1) then
5519 Add_One_Interp
5520 (N, Op_Id, Standard_Boolean, Base_Type (It.Typ));
5521 end if;
5522
5523 Get_Next_Interp (Index, It);
5524 end loop;
5525 end if;
5526 else
5527 Add_One_Interp (N, Op_Id, Standard_Boolean, Base_Type (T1));
5528 end if;
5529 end Find_Non_Universal_Interpretations;
5530
5531 ------------------------------
5532 -- Find_Concatenation_Types --
5533 ------------------------------
5534
5535 procedure Find_Concatenation_Types
5536 (L, R : Node_Id;
5537 Op_Id : Entity_Id;
5538 N : Node_Id)
5539 is
5540 Op_Type : constant Entity_Id := Etype (Op_Id);
5541
5542 begin
5543 if Is_Array_Type (Op_Type)
5544 and then not Is_Limited_Type (Op_Type)
5545
5546 and then (Has_Compatible_Type (L, Op_Type)
5547 or else
5548 Has_Compatible_Type (L, Component_Type (Op_Type)))
5549
5550 and then (Has_Compatible_Type (R, Op_Type)
5551 or else
5552 Has_Compatible_Type (R, Component_Type (Op_Type)))
5553 then
5554 Add_One_Interp (N, Op_Id, Op_Type);
5555 end if;
5556 end Find_Concatenation_Types;
5557
5558 -------------------------
5559 -- Find_Equality_Types --
5560 -------------------------
5561
5562 procedure Find_Equality_Types
5563 (L, R : Node_Id;
5564 Op_Id : Entity_Id;
5565 N : Node_Id)
5566 is
5567 Index : Interp_Index;
5568 It : Interp;
5569 Found : Boolean := False;
5570 I_F : Interp_Index;
5571 T_F : Entity_Id;
5572 Scop : Entity_Id := Empty;
5573
5574 procedure Try_One_Interp (T1 : Entity_Id);
5575 -- The context of the equality operator plays no role in resolving the
5576 -- arguments, so that if there is more than one interpretation of the
5577 -- operands that is compatible with equality, the construct is ambiguous
5578 -- and an error can be emitted now, after trying to disambiguate, i.e.
5579 -- applying preference rules.
5580
5581 --------------------
5582 -- Try_One_Interp --
5583 --------------------
5584
5585 procedure Try_One_Interp (T1 : Entity_Id) is
5586 Bas : constant Entity_Id := Base_Type (T1);
5587
5588 begin
5589 -- If the operator is an expanded name, then the type of the operand
5590 -- must be defined in the corresponding scope. If the type is
5591 -- universal, the context will impose the correct type. An anonymous
5592 -- type for a 'Access reference is also universal in this sense, as
5593 -- the actual type is obtained from context.
5594 -- In Ada 2005, the equality operator for anonymous access types
5595 -- is declared in Standard, and preference rules apply to it.
5596
5597 if Present (Scop) then
5598 if Defined_In_Scope (T1, Scop)
5599 or else T1 = Universal_Integer
5600 or else T1 = Universal_Real
5601 or else T1 = Any_Access
5602 or else T1 = Any_String
5603 or else T1 = Any_Composite
5604 or else (Ekind (T1) = E_Access_Subprogram_Type
5605 and then not Comes_From_Source (T1))
5606 then
5607 null;
5608
5609 elsif Ekind (T1) = E_Anonymous_Access_Type
5610 and then Scop = Standard_Standard
5611 then
5612 null;
5613
5614 else
5615 -- The scope does not contain an operator for the type
5616
5617 return;
5618 end if;
5619
5620 -- If we have infix notation, the operator must be usable. Within
5621 -- an instance, if the type is already established we know it is
5622 -- correct. If an operand is universal it is compatible with any
5623 -- numeric type.
5624
5625 -- In Ada 2005, the equality on anonymous access types is declared
5626 -- in Standard, and is always visible.
5627
5628 elsif In_Open_Scopes (Scope (Bas))
5629 or else Is_Potentially_Use_Visible (Bas)
5630 or else In_Use (Bas)
5631 or else (In_Use (Scope (Bas)) and then not Is_Hidden (Bas))
5632 or else (In_Instance
5633 and then
5634 (First_Subtype (T1) = First_Subtype (Etype (R))
5635 or else
5636 (Is_Numeric_Type (T1)
5637 and then Is_Universal_Numeric_Type (Etype (R)))))
5638 or else Ekind (T1) = E_Anonymous_Access_Type
5639 then
5640 null;
5641
5642 else
5643 -- Save candidate type for subsequent error message, if any
5644
5645 if not Is_Limited_Type (T1) then
5646 Candidate_Type := T1;
5647 end if;
5648
5649 return;
5650 end if;
5651
5652 -- Ada 2005 (AI-230): Keep restriction imposed by Ada 83 and 95:
5653 -- Do not allow anonymous access types in equality operators.
5654
5655 if Ada_Version < Ada_2005
5656 and then Ekind (T1) = E_Anonymous_Access_Type
5657 then
5658 return;
5659 end if;
5660
5661 -- If the right operand has a type compatible with T1, check for an
5662 -- acceptable interpretation, unless T1 is limited (no predefined
5663 -- equality available), or this is use of a "/=" for a tagged type.
5664 -- In the latter case, possible interpretations of equality need to
5665 -- be considered, we don't want the default inequality declared in
5666 -- Standard to be chosen, and the "/=" will be rewritten as a
5667 -- negation of "=" (see the end of Analyze_Equality_Op). This ensures
5668 -- that that rewriting happens during analysis rather than being
5669 -- delayed until expansion (this is needed for ASIS, which only sees
5670 -- the unexpanded tree). Note that if the node is N_Op_Ne, but Op_Id
5671 -- is Name_Op_Eq then we still proceed with the interpretation,
5672 -- because that indicates the potential rewriting case where the
5673 -- interpretation to consider is actually "=" and the node may be
5674 -- about to be rewritten by Analyze_Equality_Op.
5675
5676 if T1 /= Standard_Void_Type
5677 and then Has_Compatible_Type (R, T1)
5678
5679 and then
5680 ((not Is_Limited_Type (T1)
5681 and then not Is_Limited_Composite (T1))
5682
5683 or else
5684 (Is_Array_Type (T1)
5685 and then not Is_Limited_Type (Component_Type (T1))
5686 and then Available_Full_View_Of_Component (T1)))
5687
5688 and then
5689 (Nkind (N) /= N_Op_Ne
5690 or else not Is_Tagged_Type (T1)
5691 or else Chars (Op_Id) = Name_Op_Eq)
5692 then
5693 if Found
5694 and then Base_Type (T1) /= Base_Type (T_F)
5695 then
5696 It := Disambiguate (L, I_F, Index, Any_Type);
5697
5698 if It = No_Interp then
5699 Ambiguous_Operands (N);
5700 Set_Etype (L, Any_Type);
5701 return;
5702
5703 else
5704 T_F := It.Typ;
5705 end if;
5706
5707 else
5708 Found := True;
5709 T_F := T1;
5710 I_F := Index;
5711 end if;
5712
5713 if not Analyzed (L) then
5714 Set_Etype (L, T_F);
5715 end if;
5716
5717 Find_Non_Universal_Interpretations (N, R, Op_Id, T1);
5718
5719 -- Case of operator was not visible, Etype still set to Any_Type
5720
5721 if Etype (N) = Any_Type then
5722 Found := False;
5723 end if;
5724
5725 elsif Scop = Standard_Standard
5726 and then Ekind (T1) = E_Anonymous_Access_Type
5727 then
5728 Found := True;
5729 end if;
5730 end Try_One_Interp;
5731
5732 -- Start of processing for Find_Equality_Types
5733
5734 begin
5735 -- If left operand is aggregate, the right operand has to
5736 -- provide a usable type for it.
5737
5738 if Nkind (L) = N_Aggregate
5739 and then Nkind (R) /= N_Aggregate
5740 then
5741 Find_Equality_Types (L => R, R => L, Op_Id => Op_Id, N => N);
5742 return;
5743 end if;
5744
5745 if Nkind (N) = N_Function_Call
5746 and then Nkind (Name (N)) = N_Expanded_Name
5747 then
5748 Scop := Entity (Prefix (Name (N)));
5749
5750 -- The prefix may be a package renaming, and the subsequent test
5751 -- requires the original package.
5752
5753 if Ekind (Scop) = E_Package
5754 and then Present (Renamed_Entity (Scop))
5755 then
5756 Scop := Renamed_Entity (Scop);
5757 Set_Entity (Prefix (Name (N)), Scop);
5758 end if;
5759 end if;
5760
5761 if not Is_Overloaded (L) then
5762 Try_One_Interp (Etype (L));
5763
5764 else
5765 Get_First_Interp (L, Index, It);
5766 while Present (It.Typ) loop
5767 Try_One_Interp (It.Typ);
5768 Get_Next_Interp (Index, It);
5769 end loop;
5770 end if;
5771 end Find_Equality_Types;
5772
5773 -------------------------
5774 -- Find_Negation_Types --
5775 -------------------------
5776
5777 procedure Find_Negation_Types
5778 (R : Node_Id;
5779 Op_Id : Entity_Id;
5780 N : Node_Id)
5781 is
5782 Index : Interp_Index;
5783 It : Interp;
5784
5785 begin
5786 if not Is_Overloaded (R) then
5787 if Etype (R) = Universal_Integer then
5788 Add_One_Interp (N, Op_Id, Any_Modular);
5789 elsif Valid_Boolean_Arg (Etype (R)) then
5790 Add_One_Interp (N, Op_Id, Etype (R));
5791 end if;
5792
5793 else
5794 Get_First_Interp (R, Index, It);
5795 while Present (It.Typ) loop
5796 if Valid_Boolean_Arg (It.Typ) then
5797 Add_One_Interp (N, Op_Id, It.Typ);
5798 end if;
5799
5800 Get_Next_Interp (Index, It);
5801 end loop;
5802 end if;
5803 end Find_Negation_Types;
5804
5805 ------------------------------
5806 -- Find_Primitive_Operation --
5807 ------------------------------
5808
5809 function Find_Primitive_Operation (N : Node_Id) return Boolean is
5810 Obj : constant Node_Id := Prefix (N);
5811 Op : constant Node_Id := Selector_Name (N);
5812
5813 Prim : Elmt_Id;
5814 Prims : Elist_Id;
5815 Typ : Entity_Id;
5816
5817 begin
5818 Set_Etype (Op, Any_Type);
5819
5820 if Is_Access_Type (Etype (Obj)) then
5821 Typ := Designated_Type (Etype (Obj));
5822 else
5823 Typ := Etype (Obj);
5824 end if;
5825
5826 if Is_Class_Wide_Type (Typ) then
5827 Typ := Root_Type (Typ);
5828 end if;
5829
5830 Prims := Primitive_Operations (Typ);
5831
5832 Prim := First_Elmt (Prims);
5833 while Present (Prim) loop
5834 if Chars (Node (Prim)) = Chars (Op) then
5835 Add_One_Interp (Op, Node (Prim), Etype (Node (Prim)));
5836 Set_Etype (N, Etype (Node (Prim)));
5837 end if;
5838
5839 Next_Elmt (Prim);
5840 end loop;
5841
5842 -- Now look for class-wide operations of the type or any of its
5843 -- ancestors by iterating over the homonyms of the selector.
5844
5845 declare
5846 Cls_Type : constant Entity_Id := Class_Wide_Type (Typ);
5847 Hom : Entity_Id;
5848
5849 begin
5850 Hom := Current_Entity (Op);
5851 while Present (Hom) loop
5852 if (Ekind (Hom) = E_Procedure
5853 or else
5854 Ekind (Hom) = E_Function)
5855 and then Scope (Hom) = Scope (Typ)
5856 and then Present (First_Formal (Hom))
5857 and then
5858 (Base_Type (Etype (First_Formal (Hom))) = Cls_Type
5859 or else
5860 (Is_Access_Type (Etype (First_Formal (Hom)))
5861 and then
5862 Ekind (Etype (First_Formal (Hom))) =
5863 E_Anonymous_Access_Type
5864 and then
5865 Base_Type
5866 (Designated_Type (Etype (First_Formal (Hom)))) =
5867 Cls_Type))
5868 then
5869 Add_One_Interp (Op, Hom, Etype (Hom));
5870 Set_Etype (N, Etype (Hom));
5871 end if;
5872
5873 Hom := Homonym (Hom);
5874 end loop;
5875 end;
5876
5877 return Etype (Op) /= Any_Type;
5878 end Find_Primitive_Operation;
5879
5880 ----------------------
5881 -- Find_Unary_Types --
5882 ----------------------
5883
5884 procedure Find_Unary_Types
5885 (R : Node_Id;
5886 Op_Id : Entity_Id;
5887 N : Node_Id)
5888 is
5889 Index : Interp_Index;
5890 It : Interp;
5891
5892 begin
5893 if not Is_Overloaded (R) then
5894 if Is_Numeric_Type (Etype (R)) then
5895
5896 -- In an instance a generic actual may be a numeric type even if
5897 -- the formal in the generic unit was not. In that case, the
5898 -- predefined operator was not a possible interpretation in the
5899 -- generic, and cannot be one in the instance.
5900
5901 if In_Instance
5902 and then
5903 not Is_Numeric_Type (Corresponding_Generic_Type (Etype (R)))
5904 then
5905 null;
5906 else
5907 Add_One_Interp (N, Op_Id, Base_Type (Etype (R)));
5908 end if;
5909 end if;
5910
5911 else
5912 Get_First_Interp (R, Index, It);
5913 while Present (It.Typ) loop
5914 if Is_Numeric_Type (It.Typ) then
5915 if In_Instance
5916 and then
5917 not Is_Numeric_Type
5918 (Corresponding_Generic_Type (Etype (It.Typ)))
5919 then
5920 null;
5921
5922 else
5923 Add_One_Interp (N, Op_Id, Base_Type (It.Typ));
5924 end if;
5925 end if;
5926
5927 Get_Next_Interp (Index, It);
5928 end loop;
5929 end if;
5930 end Find_Unary_Types;
5931
5932 ------------------
5933 -- Junk_Operand --
5934 ------------------
5935
5936 function Junk_Operand (N : Node_Id) return Boolean is
5937 Enode : Node_Id;
5938
5939 begin
5940 if Error_Posted (N) then
5941 return False;
5942 end if;
5943
5944 -- Get entity to be tested
5945
5946 if Is_Entity_Name (N)
5947 and then Present (Entity (N))
5948 then
5949 Enode := N;
5950
5951 -- An odd case, a procedure name gets converted to a very peculiar
5952 -- function call, and here is where we detect this happening.
5953
5954 elsif Nkind (N) = N_Function_Call
5955 and then Is_Entity_Name (Name (N))
5956 and then Present (Entity (Name (N)))
5957 then
5958 Enode := Name (N);
5959
5960 -- Another odd case, there are at least some cases of selected
5961 -- components where the selected component is not marked as having
5962 -- an entity, even though the selector does have an entity
5963
5964 elsif Nkind (N) = N_Selected_Component
5965 and then Present (Entity (Selector_Name (N)))
5966 then
5967 Enode := Selector_Name (N);
5968
5969 else
5970 return False;
5971 end if;
5972
5973 -- Now test the entity we got to see if it is a bad case
5974
5975 case Ekind (Entity (Enode)) is
5976
5977 when E_Package =>
5978 Error_Msg_N
5979 ("package name cannot be used as operand", Enode);
5980
5981 when Generic_Unit_Kind =>
5982 Error_Msg_N
5983 ("generic unit name cannot be used as operand", Enode);
5984
5985 when Type_Kind =>
5986 Error_Msg_N
5987 ("subtype name cannot be used as operand", Enode);
5988
5989 when Entry_Kind =>
5990 Error_Msg_N
5991 ("entry name cannot be used as operand", Enode);
5992
5993 when E_Procedure =>
5994 Error_Msg_N
5995 ("procedure name cannot be used as operand", Enode);
5996
5997 when E_Exception =>
5998 Error_Msg_N
5999 ("exception name cannot be used as operand", Enode);
6000
6001 when E_Block | E_Label | E_Loop =>
6002 Error_Msg_N
6003 ("label name cannot be used as operand", Enode);
6004
6005 when others =>
6006 return False;
6007
6008 end case;
6009
6010 return True;
6011 end Junk_Operand;
6012
6013 --------------------
6014 -- Operator_Check --
6015 --------------------
6016
6017 procedure Operator_Check (N : Node_Id) is
6018 begin
6019 Remove_Abstract_Operations (N);
6020
6021 -- Test for case of no interpretation found for operator
6022
6023 if Etype (N) = Any_Type then
6024 declare
6025 L : Node_Id;
6026 R : Node_Id;
6027 Op_Id : Entity_Id := Empty;
6028
6029 begin
6030 R := Right_Opnd (N);
6031
6032 if Nkind (N) in N_Binary_Op then
6033 L := Left_Opnd (N);
6034 else
6035 L := Empty;
6036 end if;
6037
6038 -- If either operand has no type, then don't complain further,
6039 -- since this simply means that we have a propagated error.
6040
6041 if R = Error
6042 or else Etype (R) = Any_Type
6043 or else (Nkind (N) in N_Binary_Op and then Etype (L) = Any_Type)
6044 then
6045 return;
6046
6047 -- We explicitly check for the case of concatenation of component
6048 -- with component to avoid reporting spurious matching array types
6049 -- that might happen to be lurking in distant packages (such as
6050 -- run-time packages). This also prevents inconsistencies in the
6051 -- messages for certain ACVC B tests, which can vary depending on
6052 -- types declared in run-time interfaces. Another improvement when
6053 -- aggregates are present is to look for a well-typed operand.
6054
6055 elsif Present (Candidate_Type)
6056 and then (Nkind (N) /= N_Op_Concat
6057 or else Is_Array_Type (Etype (L))
6058 or else Is_Array_Type (Etype (R)))
6059 then
6060 if Nkind (N) = N_Op_Concat then
6061 if Etype (L) /= Any_Composite
6062 and then Is_Array_Type (Etype (L))
6063 then
6064 Candidate_Type := Etype (L);
6065
6066 elsif Etype (R) /= Any_Composite
6067 and then Is_Array_Type (Etype (R))
6068 then
6069 Candidate_Type := Etype (R);
6070 end if;
6071 end if;
6072
6073 Error_Msg_NE -- CODEFIX
6074 ("operator for} is not directly visible!",
6075 N, First_Subtype (Candidate_Type));
6076
6077 declare
6078 U : constant Node_Id :=
6079 Cunit (Get_Source_Unit (Candidate_Type));
6080 begin
6081 if Unit_Is_Visible (U) then
6082 Error_Msg_N -- CODEFIX
6083 ("use clause would make operation legal!", N);
6084 else
6085 Error_Msg_NE -- CODEFIX
6086 ("add with_clause and use_clause for&!",
6087 N, Defining_Entity (Unit (U)));
6088 end if;
6089 end;
6090 return;
6091
6092 -- If either operand is a junk operand (e.g. package name), then
6093 -- post appropriate error messages, but do not complain further.
6094
6095 -- Note that the use of OR in this test instead of OR ELSE is
6096 -- quite deliberate, we may as well check both operands in the
6097 -- binary operator case.
6098
6099 elsif Junk_Operand (R)
6100 or (Nkind (N) in N_Binary_Op and then Junk_Operand (L))
6101 then
6102 return;
6103
6104 -- If we have a logical operator, one of whose operands is
6105 -- Boolean, then we know that the other operand cannot resolve to
6106 -- Boolean (since we got no interpretations), but in that case we
6107 -- pretty much know that the other operand should be Boolean, so
6108 -- resolve it that way (generating an error)
6109
6110 elsif Nkind_In (N, N_Op_And, N_Op_Or, N_Op_Xor) then
6111 if Etype (L) = Standard_Boolean then
6112 Resolve (R, Standard_Boolean);
6113 return;
6114 elsif Etype (R) = Standard_Boolean then
6115 Resolve (L, Standard_Boolean);
6116 return;
6117 end if;
6118
6119 -- For an arithmetic operator or comparison operator, if one
6120 -- of the operands is numeric, then we know the other operand
6121 -- is not the same numeric type. If it is a non-numeric type,
6122 -- then probably it is intended to match the other operand.
6123
6124 elsif Nkind_In (N, N_Op_Add,
6125 N_Op_Divide,
6126 N_Op_Ge,
6127 N_Op_Gt,
6128 N_Op_Le)
6129 or else
6130 Nkind_In (N, N_Op_Lt,
6131 N_Op_Mod,
6132 N_Op_Multiply,
6133 N_Op_Rem,
6134 N_Op_Subtract)
6135 then
6136 if Is_Numeric_Type (Etype (L))
6137 and then not Is_Numeric_Type (Etype (R))
6138 then
6139 Resolve (R, Etype (L));
6140 return;
6141
6142 elsif Is_Numeric_Type (Etype (R))
6143 and then not Is_Numeric_Type (Etype (L))
6144 then
6145 Resolve (L, Etype (R));
6146 return;
6147 end if;
6148
6149 -- Comparisons on A'Access are common enough to deserve a
6150 -- special message.
6151
6152 elsif Nkind_In (N, N_Op_Eq, N_Op_Ne)
6153 and then Ekind (Etype (L)) = E_Access_Attribute_Type
6154 and then Ekind (Etype (R)) = E_Access_Attribute_Type
6155 then
6156 Error_Msg_N
6157 ("two access attributes cannot be compared directly", N);
6158 Error_Msg_N
6159 ("\use qualified expression for one of the operands",
6160 N);
6161 return;
6162
6163 -- Another one for C programmers
6164
6165 elsif Nkind (N) = N_Op_Concat
6166 and then Valid_Boolean_Arg (Etype (L))
6167 and then Valid_Boolean_Arg (Etype (R))
6168 then
6169 Error_Msg_N ("invalid operands for concatenation", N);
6170 Error_Msg_N -- CODEFIX
6171 ("\maybe AND was meant", N);
6172 return;
6173
6174 -- A special case for comparison of access parameter with null
6175
6176 elsif Nkind (N) = N_Op_Eq
6177 and then Is_Entity_Name (L)
6178 and then Nkind (Parent (Entity (L))) = N_Parameter_Specification
6179 and then Nkind (Parameter_Type (Parent (Entity (L)))) =
6180 N_Access_Definition
6181 and then Nkind (R) = N_Null
6182 then
6183 Error_Msg_N ("access parameter is not allowed to be null", L);
6184 Error_Msg_N ("\(call would raise Constraint_Error)", L);
6185 return;
6186
6187 -- Another special case for exponentiation, where the right
6188 -- operand must be Natural, independently of the base.
6189
6190 elsif Nkind (N) = N_Op_Expon
6191 and then Is_Numeric_Type (Etype (L))
6192 and then not Is_Overloaded (R)
6193 and then
6194 First_Subtype (Base_Type (Etype (R))) /= Standard_Integer
6195 and then Base_Type (Etype (R)) /= Universal_Integer
6196 then
6197 if Ada_Version >= Ada_2012
6198 and then Has_Dimension_System (Etype (L))
6199 then
6200 Error_Msg_NE
6201 ("exponent for dimensioned type must be a rational" &
6202 ", found}", R, Etype (R));
6203 else
6204 Error_Msg_NE
6205 ("exponent must be of type Natural, found}", R, Etype (R));
6206 end if;
6207
6208 return;
6209 end if;
6210
6211 -- If we fall through then just give general message. Note that in
6212 -- the following messages, if the operand is overloaded we choose
6213 -- an arbitrary type to complain about, but that is probably more
6214 -- useful than not giving a type at all.
6215
6216 if Nkind (N) in N_Unary_Op then
6217 Error_Msg_Node_2 := Etype (R);
6218 Error_Msg_N ("operator& not defined for}", N);
6219 return;
6220
6221 else
6222 if Nkind (N) in N_Binary_Op then
6223 if not Is_Overloaded (L)
6224 and then not Is_Overloaded (R)
6225 and then Base_Type (Etype (L)) = Base_Type (Etype (R))
6226 then
6227 Error_Msg_Node_2 := First_Subtype (Etype (R));
6228 Error_Msg_N ("there is no applicable operator& for}", N);
6229
6230 else
6231 -- Another attempt to find a fix: one of the candidate
6232 -- interpretations may not be use-visible. This has
6233 -- already been checked for predefined operators, so
6234 -- we examine only user-defined functions.
6235
6236 Op_Id := Get_Name_Entity_Id (Chars (N));
6237
6238 while Present (Op_Id) loop
6239 if Ekind (Op_Id) /= E_Operator
6240 and then Is_Overloadable (Op_Id)
6241 then
6242 if not Is_Immediately_Visible (Op_Id)
6243 and then not In_Use (Scope (Op_Id))
6244 and then not Is_Abstract_Subprogram (Op_Id)
6245 and then not Is_Hidden (Op_Id)
6246 and then Ekind (Scope (Op_Id)) = E_Package
6247 and then
6248 Has_Compatible_Type
6249 (L, Etype (First_Formal (Op_Id)))
6250 and then Present
6251 (Next_Formal (First_Formal (Op_Id)))
6252 and then
6253 Has_Compatible_Type
6254 (R,
6255 Etype (Next_Formal (First_Formal (Op_Id))))
6256 then
6257 Error_Msg_N
6258 ("No legal interpretation for operator&", N);
6259 Error_Msg_NE
6260 ("\use clause on& would make operation legal",
6261 N, Scope (Op_Id));
6262 exit;
6263 end if;
6264 end if;
6265
6266 Op_Id := Homonym (Op_Id);
6267 end loop;
6268
6269 if No (Op_Id) then
6270 Error_Msg_N ("invalid operand types for operator&", N);
6271
6272 if Nkind (N) /= N_Op_Concat then
6273 Error_Msg_NE ("\left operand has}!", N, Etype (L));
6274 Error_Msg_NE ("\right operand has}!", N, Etype (R));
6275 end if;
6276 end if;
6277 end if;
6278 end if;
6279 end if;
6280 end;
6281 end if;
6282 end Operator_Check;
6283
6284 -----------------------------------------
6285 -- Process_Implicit_Dereference_Prefix --
6286 -----------------------------------------
6287
6288 function Process_Implicit_Dereference_Prefix
6289 (E : Entity_Id;
6290 P : Entity_Id) return Entity_Id
6291 is
6292 Ref : Node_Id;
6293 Typ : constant Entity_Id := Designated_Type (Etype (P));
6294
6295 begin
6296 if Present (E)
6297 and then (Operating_Mode = Check_Semantics or else not Expander_Active)
6298 then
6299 -- We create a dummy reference to E to ensure that the reference
6300 -- is not considered as part of an assignment (an implicit
6301 -- dereference can never assign to its prefix). The Comes_From_Source
6302 -- attribute needs to be propagated for accurate warnings.
6303
6304 Ref := New_Reference_To (E, Sloc (P));
6305 Set_Comes_From_Source (Ref, Comes_From_Source (P));
6306 Generate_Reference (E, Ref);
6307 end if;
6308
6309 -- An implicit dereference is a legal occurrence of an
6310 -- incomplete type imported through a limited_with clause,
6311 -- if the full view is visible.
6312
6313 if From_With_Type (Typ)
6314 and then not From_With_Type (Scope (Typ))
6315 and then
6316 (Is_Immediately_Visible (Scope (Typ))
6317 or else
6318 (Is_Child_Unit (Scope (Typ))
6319 and then Is_Visible_Child_Unit (Scope (Typ))))
6320 then
6321 return Available_View (Typ);
6322 else
6323 return Typ;
6324 end if;
6325
6326 end Process_Implicit_Dereference_Prefix;
6327
6328 --------------------------------
6329 -- Remove_Abstract_Operations --
6330 --------------------------------
6331
6332 procedure Remove_Abstract_Operations (N : Node_Id) is
6333 Abstract_Op : Entity_Id := Empty;
6334 Address_Kludge : Boolean := False;
6335 I : Interp_Index;
6336 It : Interp;
6337
6338 -- AI-310: If overloaded, remove abstract non-dispatching operations. We
6339 -- activate this if either extensions are enabled, or if the abstract
6340 -- operation in question comes from a predefined file. This latter test
6341 -- allows us to use abstract to make operations invisible to users. In
6342 -- particular, if type Address is non-private and abstract subprograms
6343 -- are used to hide its operators, they will be truly hidden.
6344
6345 type Operand_Position is (First_Op, Second_Op);
6346 Univ_Type : constant Entity_Id := Universal_Interpretation (N);
6347
6348 procedure Remove_Address_Interpretations (Op : Operand_Position);
6349 -- Ambiguities may arise when the operands are literal and the address
6350 -- operations in s-auxdec are visible. In that case, remove the
6351 -- interpretation of a literal as Address, to retain the semantics of
6352 -- Address as a private type.
6353
6354 ------------------------------------
6355 -- Remove_Address_Interpretations --
6356 ------------------------------------
6357
6358 procedure Remove_Address_Interpretations (Op : Operand_Position) is
6359 Formal : Entity_Id;
6360
6361 begin
6362 if Is_Overloaded (N) then
6363 Get_First_Interp (N, I, It);
6364 while Present (It.Nam) loop
6365 Formal := First_Entity (It.Nam);
6366
6367 if Op = Second_Op then
6368 Formal := Next_Entity (Formal);
6369 end if;
6370
6371 if Is_Descendent_Of_Address (Etype (Formal)) then
6372 Address_Kludge := True;
6373 Remove_Interp (I);
6374 end if;
6375
6376 Get_Next_Interp (I, It);
6377 end loop;
6378 end if;
6379 end Remove_Address_Interpretations;
6380
6381 -- Start of processing for Remove_Abstract_Operations
6382
6383 begin
6384 if Is_Overloaded (N) then
6385 if Debug_Flag_V then
6386 Write_Str ("Remove_Abstract_Operations: ");
6387 Write_Overloads (N);
6388 end if;
6389
6390 Get_First_Interp (N, I, It);
6391
6392 while Present (It.Nam) loop
6393 if Is_Overloadable (It.Nam)
6394 and then Is_Abstract_Subprogram (It.Nam)
6395 and then not Is_Dispatching_Operation (It.Nam)
6396 then
6397 Abstract_Op := It.Nam;
6398
6399 if Is_Descendent_Of_Address (It.Typ) then
6400 Address_Kludge := True;
6401 Remove_Interp (I);
6402 exit;
6403
6404 -- In Ada 2005, this operation does not participate in overload
6405 -- resolution. If the operation is defined in a predefined
6406 -- unit, it is one of the operations declared abstract in some
6407 -- variants of System, and it must be removed as well.
6408
6409 elsif Ada_Version >= Ada_2005
6410 or else Is_Predefined_File_Name
6411 (Unit_File_Name (Get_Source_Unit (It.Nam)))
6412 then
6413 Remove_Interp (I);
6414 exit;
6415 end if;
6416 end if;
6417
6418 Get_Next_Interp (I, It);
6419 end loop;
6420
6421 if No (Abstract_Op) then
6422
6423 -- If some interpretation yields an integer type, it is still
6424 -- possible that there are address interpretations. Remove them
6425 -- if one operand is a literal, to avoid spurious ambiguities
6426 -- on systems where Address is a visible integer type.
6427
6428 if Is_Overloaded (N)
6429 and then Nkind (N) in N_Op
6430 and then Is_Integer_Type (Etype (N))
6431 then
6432 if Nkind (N) in N_Binary_Op then
6433 if Nkind (Right_Opnd (N)) = N_Integer_Literal then
6434 Remove_Address_Interpretations (Second_Op);
6435
6436 elsif Nkind (Right_Opnd (N)) = N_Integer_Literal then
6437 Remove_Address_Interpretations (First_Op);
6438 end if;
6439 end if;
6440 end if;
6441
6442 elsif Nkind (N) in N_Op then
6443
6444 -- Remove interpretations that treat literals as addresses. This
6445 -- is never appropriate, even when Address is defined as a visible
6446 -- Integer type. The reason is that we would really prefer Address
6447 -- to behave as a private type, even in this case, which is there
6448 -- only to accommodate oddities of VMS address sizes. If Address
6449 -- is a visible integer type, we get lots of overload ambiguities.
6450
6451 if Nkind (N) in N_Binary_Op then
6452 declare
6453 U1 : constant Boolean :=
6454 Present (Universal_Interpretation (Right_Opnd (N)));
6455 U2 : constant Boolean :=
6456 Present (Universal_Interpretation (Left_Opnd (N)));
6457
6458 begin
6459 if U1 then
6460 Remove_Address_Interpretations (Second_Op);
6461 end if;
6462
6463 if U2 then
6464 Remove_Address_Interpretations (First_Op);
6465 end if;
6466
6467 if not (U1 and U2) then
6468
6469 -- Remove corresponding predefined operator, which is
6470 -- always added to the overload set.
6471
6472 Get_First_Interp (N, I, It);
6473 while Present (It.Nam) loop
6474 if Scope (It.Nam) = Standard_Standard
6475 and then Base_Type (It.Typ) =
6476 Base_Type (Etype (Abstract_Op))
6477 then
6478 Remove_Interp (I);
6479 end if;
6480
6481 Get_Next_Interp (I, It);
6482 end loop;
6483
6484 elsif Is_Overloaded (N)
6485 and then Present (Univ_Type)
6486 then
6487 -- If both operands have a universal interpretation,
6488 -- it is still necessary to remove interpretations that
6489 -- yield Address. Any remaining ambiguities will be
6490 -- removed in Disambiguate.
6491
6492 Get_First_Interp (N, I, It);
6493 while Present (It.Nam) loop
6494 if Is_Descendent_Of_Address (It.Typ) then
6495 Remove_Interp (I);
6496
6497 elsif not Is_Type (It.Nam) then
6498 Set_Entity (N, It.Nam);
6499 end if;
6500
6501 Get_Next_Interp (I, It);
6502 end loop;
6503 end if;
6504 end;
6505 end if;
6506
6507 elsif Nkind (N) = N_Function_Call
6508 and then
6509 (Nkind (Name (N)) = N_Operator_Symbol
6510 or else
6511 (Nkind (Name (N)) = N_Expanded_Name
6512 and then
6513 Nkind (Selector_Name (Name (N))) = N_Operator_Symbol))
6514 then
6515
6516 declare
6517 Arg1 : constant Node_Id := First (Parameter_Associations (N));
6518 U1 : constant Boolean :=
6519 Present (Universal_Interpretation (Arg1));
6520 U2 : constant Boolean :=
6521 Present (Next (Arg1)) and then
6522 Present (Universal_Interpretation (Next (Arg1)));
6523
6524 begin
6525 if U1 then
6526 Remove_Address_Interpretations (First_Op);
6527 end if;
6528
6529 if U2 then
6530 Remove_Address_Interpretations (Second_Op);
6531 end if;
6532
6533 if not (U1 and U2) then
6534 Get_First_Interp (N, I, It);
6535 while Present (It.Nam) loop
6536 if Scope (It.Nam) = Standard_Standard
6537 and then It.Typ = Base_Type (Etype (Abstract_Op))
6538 then
6539 Remove_Interp (I);
6540 end if;
6541
6542 Get_Next_Interp (I, It);
6543 end loop;
6544 end if;
6545 end;
6546 end if;
6547
6548 -- If the removal has left no valid interpretations, emit an error
6549 -- message now and label node as illegal.
6550
6551 if Present (Abstract_Op) then
6552 Get_First_Interp (N, I, It);
6553
6554 if No (It.Nam) then
6555
6556 -- Removal of abstract operation left no viable candidate
6557
6558 Set_Etype (N, Any_Type);
6559 Error_Msg_Sloc := Sloc (Abstract_Op);
6560 Error_Msg_NE
6561 ("cannot call abstract operation& declared#", N, Abstract_Op);
6562
6563 -- In Ada 2005, an abstract operation may disable predefined
6564 -- operators. Since the context is not yet known, we mark the
6565 -- predefined operators as potentially hidden. Do not include
6566 -- predefined operators when addresses are involved since this
6567 -- case is handled separately.
6568
6569 elsif Ada_Version >= Ada_2005
6570 and then not Address_Kludge
6571 then
6572 while Present (It.Nam) loop
6573 if Is_Numeric_Type (It.Typ)
6574 and then Scope (It.Typ) = Standard_Standard
6575 then
6576 Set_Abstract_Op (I, Abstract_Op);
6577 end if;
6578
6579 Get_Next_Interp (I, It);
6580 end loop;
6581 end if;
6582 end if;
6583
6584 if Debug_Flag_V then
6585 Write_Str ("Remove_Abstract_Operations done: ");
6586 Write_Overloads (N);
6587 end if;
6588 end if;
6589 end Remove_Abstract_Operations;
6590
6591 ----------------------------
6592 -- Try_Container_Indexing --
6593 ----------------------------
6594
6595 function Try_Container_Indexing
6596 (N : Node_Id;
6597 Prefix : Node_Id;
6598 Exprs : List_Id) return Boolean
6599 is
6600 Loc : constant Source_Ptr := Sloc (N);
6601 Assoc : List_Id;
6602 Disc : Entity_Id;
6603 Func : Entity_Id;
6604 Func_Name : Node_Id;
6605 Indexing : Node_Id;
6606
6607 begin
6608
6609 -- Check whether type has a specified indexing aspect
6610
6611 Func_Name := Empty;
6612
6613 if Is_Variable (Prefix) then
6614 Func_Name := Find_Aspect (Etype (Prefix), Aspect_Variable_Indexing);
6615 end if;
6616
6617 if No (Func_Name) then
6618 Func_Name := Find_Aspect (Etype (Prefix), Aspect_Constant_Indexing);
6619 end if;
6620
6621 -- If aspect does not exist the expression is illegal. Error is
6622 -- diagnosed in caller.
6623
6624 if No (Func_Name) then
6625
6626 -- The prefix itself may be an indexing of a container
6627 -- rewrite as such and re-analyze.
6628
6629 if Has_Implicit_Dereference (Etype (Prefix)) then
6630 Build_Explicit_Dereference
6631 (Prefix, First_Discriminant (Etype (Prefix)));
6632 return Try_Container_Indexing (N, Prefix, Exprs);
6633
6634 else
6635 return False;
6636 end if;
6637 end if;
6638
6639 Assoc := New_List (Relocate_Node (Prefix));
6640
6641 -- A generalized iterator may have nore than one index expression, so
6642 -- transfer all of them to the argument list to be used in the call.
6643
6644 declare
6645 Arg : Node_Id;
6646 begin
6647 Arg := First (Exprs);
6648 while Present (Arg) loop
6649 Append (Relocate_Node (Arg), Assoc);
6650 Next (Arg);
6651 end loop;
6652 end;
6653
6654 if not Is_Overloaded (Func_Name) then
6655 Func := Entity (Func_Name);
6656 Indexing :=
6657 Make_Function_Call (Loc,
6658 Name => New_Occurrence_Of (Func, Loc),
6659 Parameter_Associations => Assoc);
6660 Rewrite (N, Indexing);
6661 Analyze (N);
6662
6663 -- If the return type of the indexing function is a reference type,
6664 -- add the dereference as a possible interpretation. Note that the
6665 -- indexing aspect may be a function that returns the element type
6666 -- with no intervening implicit dereference.
6667
6668 if Has_Discriminants (Etype (Func)) then
6669 Disc := First_Discriminant (Etype (Func));
6670 while Present (Disc) loop
6671 if Has_Implicit_Dereference (Disc) then
6672 Add_One_Interp (N, Disc, Designated_Type (Etype (Disc)));
6673 exit;
6674 end if;
6675
6676 Next_Discriminant (Disc);
6677 end loop;
6678 end if;
6679
6680 else
6681 Indexing := Make_Function_Call (Loc,
6682 Name => Make_Identifier (Loc, Chars (Func_Name)),
6683 Parameter_Associations => Assoc);
6684
6685 Rewrite (N, Indexing);
6686
6687 declare
6688 I : Interp_Index;
6689 It : Interp;
6690 Success : Boolean;
6691
6692 begin
6693 Get_First_Interp (Func_Name, I, It);
6694 Set_Etype (N, Any_Type);
6695 while Present (It.Nam) loop
6696 Analyze_One_Call (N, It.Nam, False, Success);
6697 if Success then
6698 Set_Etype (Name (N), It.Typ);
6699 Set_Entity (Name (N), It.Nam);
6700
6701 -- Add implicit dereference interpretation
6702
6703 if Has_Discriminants (Etype (It.Nam)) then
6704 Disc := First_Discriminant (Etype (It.Nam));
6705 while Present (Disc) loop
6706 if Has_Implicit_Dereference (Disc) then
6707 Add_One_Interp
6708 (N, Disc, Designated_Type (Etype (Disc)));
6709 exit;
6710 end if;
6711
6712 Next_Discriminant (Disc);
6713 end loop;
6714 end if;
6715
6716 exit;
6717 end if;
6718 Get_Next_Interp (I, It);
6719 end loop;
6720 end;
6721 end if;
6722
6723 if Etype (N) = Any_Type then
6724 Error_Msg_NE
6725 ("container cannot be indexed with&", N, Etype (First (Exprs)));
6726 Rewrite (N, New_Occurrence_Of (Any_Id, Loc));
6727 else
6728 Analyze (N);
6729 end if;
6730
6731 return True;
6732 end Try_Container_Indexing;
6733
6734 -----------------------
6735 -- Try_Indirect_Call --
6736 -----------------------
6737
6738 function Try_Indirect_Call
6739 (N : Node_Id;
6740 Nam : Entity_Id;
6741 Typ : Entity_Id) return Boolean
6742 is
6743 Actual : Node_Id;
6744 Formal : Entity_Id;
6745
6746 Call_OK : Boolean;
6747 pragma Warnings (Off, Call_OK);
6748
6749 begin
6750 Normalize_Actuals (N, Designated_Type (Typ), False, Call_OK);
6751
6752 Actual := First_Actual (N);
6753 Formal := First_Formal (Designated_Type (Typ));
6754 while Present (Actual) and then Present (Formal) loop
6755 if not Has_Compatible_Type (Actual, Etype (Formal)) then
6756 return False;
6757 end if;
6758
6759 Next (Actual);
6760 Next_Formal (Formal);
6761 end loop;
6762
6763 if No (Actual) and then No (Formal) then
6764 Add_One_Interp (N, Nam, Etype (Designated_Type (Typ)));
6765
6766 -- Nam is a candidate interpretation for the name in the call,
6767 -- if it is not an indirect call.
6768
6769 if not Is_Type (Nam)
6770 and then Is_Entity_Name (Name (N))
6771 then
6772 Set_Entity (Name (N), Nam);
6773 end if;
6774
6775 return True;
6776 else
6777 return False;
6778 end if;
6779 end Try_Indirect_Call;
6780
6781 ----------------------
6782 -- Try_Indexed_Call --
6783 ----------------------
6784
6785 function Try_Indexed_Call
6786 (N : Node_Id;
6787 Nam : Entity_Id;
6788 Typ : Entity_Id;
6789 Skip_First : Boolean) return Boolean
6790 is
6791 Loc : constant Source_Ptr := Sloc (N);
6792 Actuals : constant List_Id := Parameter_Associations (N);
6793 Actual : Node_Id;
6794 Index : Entity_Id;
6795
6796 begin
6797 Actual := First (Actuals);
6798
6799 -- If the call was originally written in prefix form, skip the first
6800 -- actual, which is obviously not defaulted.
6801
6802 if Skip_First then
6803 Next (Actual);
6804 end if;
6805
6806 Index := First_Index (Typ);
6807 while Present (Actual) and then Present (Index) loop
6808
6809 -- If the parameter list has a named association, the expression
6810 -- is definitely a call and not an indexed component.
6811
6812 if Nkind (Actual) = N_Parameter_Association then
6813 return False;
6814 end if;
6815
6816 if Is_Entity_Name (Actual)
6817 and then Is_Type (Entity (Actual))
6818 and then No (Next (Actual))
6819 then
6820 -- A single actual that is a type name indicates a slice if the
6821 -- type is discrete, and an error otherwise.
6822
6823 if Is_Discrete_Type (Entity (Actual)) then
6824 Rewrite (N,
6825 Make_Slice (Loc,
6826 Prefix =>
6827 Make_Function_Call (Loc,
6828 Name => Relocate_Node (Name (N))),
6829 Discrete_Range =>
6830 New_Occurrence_Of (Entity (Actual), Sloc (Actual))));
6831
6832 Analyze (N);
6833
6834 else
6835 Error_Msg_N ("invalid use of type in expression", Actual);
6836 Set_Etype (N, Any_Type);
6837 end if;
6838
6839 return True;
6840
6841 elsif not Has_Compatible_Type (Actual, Etype (Index)) then
6842 return False;
6843 end if;
6844
6845 Next (Actual);
6846 Next_Index (Index);
6847 end loop;
6848
6849 if No (Actual) and then No (Index) then
6850 Add_One_Interp (N, Nam, Component_Type (Typ));
6851
6852 -- Nam is a candidate interpretation for the name in the call,
6853 -- if it is not an indirect call.
6854
6855 if not Is_Type (Nam)
6856 and then Is_Entity_Name (Name (N))
6857 then
6858 Set_Entity (Name (N), Nam);
6859 end if;
6860
6861 return True;
6862 else
6863 return False;
6864 end if;
6865 end Try_Indexed_Call;
6866
6867 --------------------------
6868 -- Try_Object_Operation --
6869 --------------------------
6870
6871 function Try_Object_Operation
6872 (N : Node_Id; CW_Test_Only : Boolean := False) return Boolean
6873 is
6874 K : constant Node_Kind := Nkind (Parent (N));
6875 Is_Subprg_Call : constant Boolean := K in N_Subprogram_Call;
6876 Loc : constant Source_Ptr := Sloc (N);
6877 Obj : constant Node_Id := Prefix (N);
6878
6879 Subprog : constant Node_Id :=
6880 Make_Identifier (Sloc (Selector_Name (N)),
6881 Chars => Chars (Selector_Name (N)));
6882 -- Identifier on which possible interpretations will be collected
6883
6884 Report_Error : Boolean := False;
6885 -- If no candidate interpretation matches the context, redo the
6886 -- analysis with error enabled to provide additional information.
6887
6888 Actual : Node_Id;
6889 Candidate : Entity_Id := Empty;
6890 New_Call_Node : Node_Id := Empty;
6891 Node_To_Replace : Node_Id;
6892 Obj_Type : Entity_Id := Etype (Obj);
6893 Success : Boolean := False;
6894
6895 function Valid_Candidate
6896 (Success : Boolean;
6897 Call : Node_Id;
6898 Subp : Entity_Id) return Entity_Id;
6899 -- If the subprogram is a valid interpretation, record it, and add
6900 -- to the list of interpretations of Subprog. Otherwise return Empty.
6901
6902 procedure Complete_Object_Operation
6903 (Call_Node : Node_Id;
6904 Node_To_Replace : Node_Id);
6905 -- Make Subprog the name of Call_Node, replace Node_To_Replace with
6906 -- Call_Node, insert the object (or its dereference) as the first actual
6907 -- in the call, and complete the analysis of the call.
6908
6909 procedure Report_Ambiguity (Op : Entity_Id);
6910 -- If a prefixed procedure call is ambiguous, indicate whether the
6911 -- call includes an implicit dereference or an implicit 'Access.
6912
6913 procedure Transform_Object_Operation
6914 (Call_Node : out Node_Id;
6915 Node_To_Replace : out Node_Id);
6916 -- Transform Obj.Operation (X, Y,,) into Operation (Obj, X, Y ..)
6917 -- Call_Node is the resulting subprogram call, Node_To_Replace is
6918 -- either N or the parent of N, and Subprog is a reference to the
6919 -- subprogram we are trying to match.
6920
6921 function Try_Class_Wide_Operation
6922 (Call_Node : Node_Id;
6923 Node_To_Replace : Node_Id) return Boolean;
6924 -- Traverse all ancestor types looking for a class-wide subprogram
6925 -- for which the current operation is a valid non-dispatching call.
6926
6927 procedure Try_One_Prefix_Interpretation (T : Entity_Id);
6928 -- If prefix is overloaded, its interpretation may include different
6929 -- tagged types, and we must examine the primitive operations and
6930 -- the class-wide operations of each in order to find candidate
6931 -- interpretations for the call as a whole.
6932
6933 function Try_Primitive_Operation
6934 (Call_Node : Node_Id;
6935 Node_To_Replace : Node_Id) return Boolean;
6936 -- Traverse the list of primitive subprograms looking for a dispatching
6937 -- operation for which the current node is a valid call .
6938
6939 ---------------------
6940 -- Valid_Candidate --
6941 ---------------------
6942
6943 function Valid_Candidate
6944 (Success : Boolean;
6945 Call : Node_Id;
6946 Subp : Entity_Id) return Entity_Id
6947 is
6948 Arr_Type : Entity_Id;
6949 Comp_Type : Entity_Id;
6950
6951 begin
6952 -- If the subprogram is a valid interpretation, record it in global
6953 -- variable Subprog, to collect all possible overloadings.
6954
6955 if Success then
6956 if Subp /= Entity (Subprog) then
6957 Add_One_Interp (Subprog, Subp, Etype (Subp));
6958 end if;
6959 end if;
6960
6961 -- If the call may be an indexed call, retrieve component type of
6962 -- resulting expression, and add possible interpretation.
6963
6964 Arr_Type := Empty;
6965 Comp_Type := Empty;
6966
6967 if Nkind (Call) = N_Function_Call
6968 and then Nkind (Parent (N)) = N_Indexed_Component
6969 and then Needs_One_Actual (Subp)
6970 then
6971 if Is_Array_Type (Etype (Subp)) then
6972 Arr_Type := Etype (Subp);
6973
6974 elsif Is_Access_Type (Etype (Subp))
6975 and then Is_Array_Type (Designated_Type (Etype (Subp)))
6976 then
6977 Arr_Type := Designated_Type (Etype (Subp));
6978 end if;
6979 end if;
6980
6981 if Present (Arr_Type) then
6982
6983 -- Verify that the actuals (excluding the object) match the types
6984 -- of the indexes.
6985
6986 declare
6987 Actual : Node_Id;
6988 Index : Node_Id;
6989
6990 begin
6991 Actual := Next (First_Actual (Call));
6992 Index := First_Index (Arr_Type);
6993 while Present (Actual) and then Present (Index) loop
6994 if not Has_Compatible_Type (Actual, Etype (Index)) then
6995 Arr_Type := Empty;
6996 exit;
6997 end if;
6998
6999 Next_Actual (Actual);
7000 Next_Index (Index);
7001 end loop;
7002
7003 if No (Actual)
7004 and then No (Index)
7005 and then Present (Arr_Type)
7006 then
7007 Comp_Type := Component_Type (Arr_Type);
7008 end if;
7009 end;
7010
7011 if Present (Comp_Type)
7012 and then Etype (Subprog) /= Comp_Type
7013 then
7014 Add_One_Interp (Subprog, Subp, Comp_Type);
7015 end if;
7016 end if;
7017
7018 if Etype (Call) /= Any_Type then
7019 return Subp;
7020 else
7021 return Empty;
7022 end if;
7023 end Valid_Candidate;
7024
7025 -------------------------------
7026 -- Complete_Object_Operation --
7027 -------------------------------
7028
7029 procedure Complete_Object_Operation
7030 (Call_Node : Node_Id;
7031 Node_To_Replace : Node_Id)
7032 is
7033 Control : constant Entity_Id := First_Formal (Entity (Subprog));
7034 Formal_Type : constant Entity_Id := Etype (Control);
7035 First_Actual : Node_Id;
7036
7037 begin
7038 -- Place the name of the operation, with its interpretations,
7039 -- on the rewritten call.
7040
7041 Set_Name (Call_Node, Subprog);
7042
7043 First_Actual := First (Parameter_Associations (Call_Node));
7044
7045 -- For cross-reference purposes, treat the new node as being in
7046 -- the source if the original one is. Set entity and type, even
7047 -- though they may be overwritten during resolution if overloaded.
7048
7049 Set_Comes_From_Source (Subprog, Comes_From_Source (N));
7050 Set_Comes_From_Source (Call_Node, Comes_From_Source (N));
7051
7052 if Nkind (N) = N_Selected_Component
7053 and then not Inside_A_Generic
7054 then
7055 Set_Entity (Selector_Name (N), Entity (Subprog));
7056 Set_Etype (Selector_Name (N), Etype (Entity (Subprog)));
7057 end if;
7058
7059 -- If need be, rewrite first actual as an explicit dereference
7060 -- If the call is overloaded, the rewriting can only be done
7061 -- once the primitive operation is identified.
7062
7063 if Is_Overloaded (Subprog) then
7064
7065 -- The prefix itself may be overloaded, and its interpretations
7066 -- must be propagated to the new actual in the call.
7067
7068 if Is_Overloaded (Obj) then
7069 Save_Interps (Obj, First_Actual);
7070 end if;
7071
7072 Rewrite (First_Actual, Obj);
7073
7074 elsif not Is_Access_Type (Formal_Type)
7075 and then Is_Access_Type (Etype (Obj))
7076 then
7077 Rewrite (First_Actual,
7078 Make_Explicit_Dereference (Sloc (Obj), Obj));
7079 Analyze (First_Actual);
7080
7081 -- If we need to introduce an explicit dereference, verify that
7082 -- the resulting actual is compatible with the mode of the formal.
7083
7084 if Ekind (First_Formal (Entity (Subprog))) /= E_In_Parameter
7085 and then Is_Access_Constant (Etype (Obj))
7086 then
7087 Error_Msg_NE
7088 ("expect variable in call to&", Prefix (N), Entity (Subprog));
7089 end if;
7090
7091 -- Conversely, if the formal is an access parameter and the object
7092 -- is not, replace the actual with a 'Access reference. Its analysis
7093 -- will check that the object is aliased.
7094
7095 elsif Is_Access_Type (Formal_Type)
7096 and then not Is_Access_Type (Etype (Obj))
7097 then
7098 -- A special case: A.all'access is illegal if A is an access to a
7099 -- constant and the context requires an access to a variable.
7100
7101 if not Is_Access_Constant (Formal_Type) then
7102 if (Nkind (Obj) = N_Explicit_Dereference
7103 and then Is_Access_Constant (Etype (Prefix (Obj))))
7104 or else not Is_Variable (Obj)
7105 then
7106 Error_Msg_NE
7107 ("actual for& must be a variable", Obj, Control);
7108 end if;
7109 end if;
7110
7111 Rewrite (First_Actual,
7112 Make_Attribute_Reference (Loc,
7113 Attribute_Name => Name_Access,
7114 Prefix => Relocate_Node (Obj)));
7115
7116 if not Is_Aliased_View (Obj) then
7117 Error_Msg_NE
7118 ("object in prefixed call to& must be aliased"
7119 & " (RM-2005 4.3.1 (13))",
7120 Prefix (First_Actual), Subprog);
7121 end if;
7122
7123 Analyze (First_Actual);
7124
7125 else
7126 if Is_Overloaded (Obj) then
7127 Save_Interps (Obj, First_Actual);
7128 end if;
7129
7130 Rewrite (First_Actual, Obj);
7131 end if;
7132
7133 Rewrite (Node_To_Replace, Call_Node);
7134
7135 -- Propagate the interpretations collected in subprog to the new
7136 -- function call node, to be resolved from context.
7137
7138 if Is_Overloaded (Subprog) then
7139 Save_Interps (Subprog, Node_To_Replace);
7140
7141 else
7142 Analyze (Node_To_Replace);
7143
7144 -- If the operation has been rewritten into a call, which may get
7145 -- subsequently an explicit dereference, preserve the type on the
7146 -- original node (selected component or indexed component) for
7147 -- subsequent legality tests, e.g. Is_Variable. which examines
7148 -- the original node.
7149
7150 if Nkind (Node_To_Replace) = N_Function_Call then
7151 Set_Etype
7152 (Original_Node (Node_To_Replace), Etype (Node_To_Replace));
7153 end if;
7154 end if;
7155 end Complete_Object_Operation;
7156
7157 ----------------------
7158 -- Report_Ambiguity --
7159 ----------------------
7160
7161 procedure Report_Ambiguity (Op : Entity_Id) is
7162 Access_Actual : constant Boolean :=
7163 Is_Access_Type (Etype (Prefix (N)));
7164 Access_Formal : Boolean := False;
7165
7166 begin
7167 Error_Msg_Sloc := Sloc (Op);
7168
7169 if Present (First_Formal (Op)) then
7170 Access_Formal := Is_Access_Type (Etype (First_Formal (Op)));
7171 end if;
7172
7173 if Access_Formal and then not Access_Actual then
7174 if Nkind (Parent (Op)) = N_Full_Type_Declaration then
7175 Error_Msg_N
7176 ("\possible interpretation"
7177 & " (inherited, with implicit 'Access) #", N);
7178 else
7179 Error_Msg_N
7180 ("\possible interpretation (with implicit 'Access) #", N);
7181 end if;
7182
7183 elsif not Access_Formal and then Access_Actual then
7184 if Nkind (Parent (Op)) = N_Full_Type_Declaration then
7185 Error_Msg_N
7186 ("\possible interpretation"
7187 & " ( inherited, with implicit dereference) #", N);
7188 else
7189 Error_Msg_N
7190 ("\possible interpretation (with implicit dereference) #", N);
7191 end if;
7192
7193 else
7194 if Nkind (Parent (Op)) = N_Full_Type_Declaration then
7195 Error_Msg_N ("\possible interpretation (inherited)#", N);
7196 else
7197 Error_Msg_N -- CODEFIX
7198 ("\possible interpretation#", N);
7199 end if;
7200 end if;
7201 end Report_Ambiguity;
7202
7203 --------------------------------
7204 -- Transform_Object_Operation --
7205 --------------------------------
7206
7207 procedure Transform_Object_Operation
7208 (Call_Node : out Node_Id;
7209 Node_To_Replace : out Node_Id)
7210 is
7211 Dummy : constant Node_Id := New_Copy (Obj);
7212 -- Placeholder used as a first parameter in the call, replaced
7213 -- eventually by the proper object.
7214
7215 Parent_Node : constant Node_Id := Parent (N);
7216
7217 Actual : Node_Id;
7218 Actuals : List_Id;
7219
7220 begin
7221 -- Common case covering 1) Call to a procedure and 2) Call to a
7222 -- function that has some additional actuals.
7223
7224 if Nkind (Parent_Node) in N_Subprogram_Call
7225
7226 -- N is a selected component node containing the name of the
7227 -- subprogram. If N is not the name of the parent node we must
7228 -- not replace the parent node by the new construct. This case
7229 -- occurs when N is a parameterless call to a subprogram that
7230 -- is an actual parameter of a call to another subprogram. For
7231 -- example:
7232 -- Some_Subprogram (..., Obj.Operation, ...)
7233
7234 and then Name (Parent_Node) = N
7235 then
7236 Node_To_Replace := Parent_Node;
7237
7238 Actuals := Parameter_Associations (Parent_Node);
7239
7240 if Present (Actuals) then
7241 Prepend (Dummy, Actuals);
7242 else
7243 Actuals := New_List (Dummy);
7244 end if;
7245
7246 if Nkind (Parent_Node) = N_Procedure_Call_Statement then
7247 Call_Node :=
7248 Make_Procedure_Call_Statement (Loc,
7249 Name => New_Copy (Subprog),
7250 Parameter_Associations => Actuals);
7251
7252 else
7253 Call_Node :=
7254 Make_Function_Call (Loc,
7255 Name => New_Copy (Subprog),
7256 Parameter_Associations => Actuals);
7257
7258 end if;
7259
7260 -- Before analysis, a function call appears as an indexed component
7261 -- if there are no named associations.
7262
7263 elsif Nkind (Parent_Node) = N_Indexed_Component
7264 and then N = Prefix (Parent_Node)
7265 then
7266 Node_To_Replace := Parent_Node;
7267 Actuals := Expressions (Parent_Node);
7268
7269 Actual := First (Actuals);
7270 while Present (Actual) loop
7271 Analyze (Actual);
7272 Next (Actual);
7273 end loop;
7274
7275 Prepend (Dummy, Actuals);
7276
7277 Call_Node :=
7278 Make_Function_Call (Loc,
7279 Name => New_Copy (Subprog),
7280 Parameter_Associations => Actuals);
7281
7282 -- Parameterless call: Obj.F is rewritten as F (Obj)
7283
7284 else
7285 Node_To_Replace := N;
7286
7287 Call_Node :=
7288 Make_Function_Call (Loc,
7289 Name => New_Copy (Subprog),
7290 Parameter_Associations => New_List (Dummy));
7291 end if;
7292 end Transform_Object_Operation;
7293
7294 ------------------------------
7295 -- Try_Class_Wide_Operation --
7296 ------------------------------
7297
7298 function Try_Class_Wide_Operation
7299 (Call_Node : Node_Id;
7300 Node_To_Replace : Node_Id) return Boolean
7301 is
7302 Anc_Type : Entity_Id;
7303 Matching_Op : Entity_Id := Empty;
7304 Error : Boolean;
7305
7306 procedure Traverse_Homonyms
7307 (Anc_Type : Entity_Id;
7308 Error : out Boolean);
7309 -- Traverse the homonym chain of the subprogram searching for those
7310 -- homonyms whose first formal has the Anc_Type's class-wide type,
7311 -- or an anonymous access type designating the class-wide type. If
7312 -- an ambiguity is detected, then Error is set to True.
7313
7314 procedure Traverse_Interfaces
7315 (Anc_Type : Entity_Id;
7316 Error : out Boolean);
7317 -- Traverse the list of interfaces, if any, associated with Anc_Type
7318 -- and search for acceptable class-wide homonyms associated with each
7319 -- interface. If an ambiguity is detected, then Error is set to True.
7320
7321 -----------------------
7322 -- Traverse_Homonyms --
7323 -----------------------
7324
7325 procedure Traverse_Homonyms
7326 (Anc_Type : Entity_Id;
7327 Error : out Boolean)
7328 is
7329 Cls_Type : Entity_Id;
7330 Hom : Entity_Id;
7331 Hom_Ref : Node_Id;
7332 Success : Boolean;
7333
7334 begin
7335 Error := False;
7336
7337 Cls_Type := Class_Wide_Type (Anc_Type);
7338
7339 Hom := Current_Entity (Subprog);
7340
7341 -- Find a non-hidden operation whose first parameter is of the
7342 -- class-wide type, a subtype thereof, or an anonymous access
7343 -- to same. If in an instance, the operation can be considered
7344 -- even if hidden (it may be hidden because the instantiation is
7345 -- expanded after the containing package has been analyzed).
7346
7347 while Present (Hom) loop
7348 if Ekind_In (Hom, E_Procedure, E_Function)
7349 and then (not Is_Hidden (Hom) or else In_Instance)
7350 and then Scope (Hom) = Scope (Anc_Type)
7351 and then Present (First_Formal (Hom))
7352 and then
7353 (Base_Type (Etype (First_Formal (Hom))) = Cls_Type
7354 or else
7355 (Is_Access_Type (Etype (First_Formal (Hom)))
7356 and then
7357 Ekind (Etype (First_Formal (Hom))) =
7358 E_Anonymous_Access_Type
7359 and then
7360 Base_Type
7361 (Designated_Type (Etype (First_Formal (Hom)))) =
7362 Cls_Type))
7363 then
7364 -- If the context is a procedure call, ignore functions
7365 -- in the name of the call.
7366
7367 if Ekind (Hom) = E_Function
7368 and then Nkind (Parent (N)) = N_Procedure_Call_Statement
7369 and then N = Name (Parent (N))
7370 then
7371 goto Next_Hom;
7372
7373 -- If the context is a function call, ignore procedures
7374 -- in the name of the call.
7375
7376 elsif Ekind (Hom) = E_Procedure
7377 and then Nkind (Parent (N)) /= N_Procedure_Call_Statement
7378 then
7379 goto Next_Hom;
7380 end if;
7381
7382 Set_Etype (Call_Node, Any_Type);
7383 Set_Is_Overloaded (Call_Node, False);
7384 Success := False;
7385
7386 if No (Matching_Op) then
7387 Hom_Ref := New_Reference_To (Hom, Sloc (Subprog));
7388 Set_Etype (Call_Node, Any_Type);
7389 Set_Parent (Call_Node, Parent (Node_To_Replace));
7390
7391 Set_Name (Call_Node, Hom_Ref);
7392
7393 Analyze_One_Call
7394 (N => Call_Node,
7395 Nam => Hom,
7396 Report => Report_Error,
7397 Success => Success,
7398 Skip_First => True);
7399
7400 Matching_Op :=
7401 Valid_Candidate (Success, Call_Node, Hom);
7402
7403 else
7404 Analyze_One_Call
7405 (N => Call_Node,
7406 Nam => Hom,
7407 Report => Report_Error,
7408 Success => Success,
7409 Skip_First => True);
7410
7411 if Present (Valid_Candidate (Success, Call_Node, Hom))
7412 and then Nkind (Call_Node) /= N_Function_Call
7413 then
7414 Error_Msg_NE ("ambiguous call to&", N, Hom);
7415 Report_Ambiguity (Matching_Op);
7416 Report_Ambiguity (Hom);
7417 Error := True;
7418 return;
7419 end if;
7420 end if;
7421 end if;
7422
7423 <<Next_Hom>>
7424 Hom := Homonym (Hom);
7425 end loop;
7426 end Traverse_Homonyms;
7427
7428 -------------------------
7429 -- Traverse_Interfaces --
7430 -------------------------
7431
7432 procedure Traverse_Interfaces
7433 (Anc_Type : Entity_Id;
7434 Error : out Boolean)
7435 is
7436 Intface_List : constant List_Id :=
7437 Abstract_Interface_List (Anc_Type);
7438 Intface : Node_Id;
7439
7440 begin
7441 Error := False;
7442
7443 if Is_Non_Empty_List (Intface_List) then
7444 Intface := First (Intface_List);
7445 while Present (Intface) loop
7446
7447 -- Look for acceptable class-wide homonyms associated with
7448 -- the interface.
7449
7450 Traverse_Homonyms (Etype (Intface), Error);
7451
7452 if Error then
7453 return;
7454 end if;
7455
7456 -- Continue the search by looking at each of the interface's
7457 -- associated interface ancestors.
7458
7459 Traverse_Interfaces (Etype (Intface), Error);
7460
7461 if Error then
7462 return;
7463 end if;
7464
7465 Next (Intface);
7466 end loop;
7467 end if;
7468 end Traverse_Interfaces;
7469
7470 -- Start of processing for Try_Class_Wide_Operation
7471
7472 begin
7473 -- If we are searching only for conflicting class-wide subprograms
7474 -- then initialize directly Matching_Op with the target entity.
7475
7476 if CW_Test_Only then
7477 Matching_Op := Entity (Selector_Name (N));
7478 end if;
7479
7480 -- Loop through ancestor types (including interfaces), traversing
7481 -- the homonym chain of the subprogram, trying out those homonyms
7482 -- whose first formal has the class-wide type of the ancestor, or
7483 -- an anonymous access type designating the class-wide type.
7484
7485 Anc_Type := Obj_Type;
7486 loop
7487 -- Look for a match among homonyms associated with the ancestor
7488
7489 Traverse_Homonyms (Anc_Type, Error);
7490
7491 if Error then
7492 return True;
7493 end if;
7494
7495 -- Continue the search for matches among homonyms associated with
7496 -- any interfaces implemented by the ancestor.
7497
7498 Traverse_Interfaces (Anc_Type, Error);
7499
7500 if Error then
7501 return True;
7502 end if;
7503
7504 exit when Etype (Anc_Type) = Anc_Type;
7505 Anc_Type := Etype (Anc_Type);
7506 end loop;
7507
7508 if Present (Matching_Op) then
7509 Set_Etype (Call_Node, Etype (Matching_Op));
7510 end if;
7511
7512 return Present (Matching_Op);
7513 end Try_Class_Wide_Operation;
7514
7515 -----------------------------------
7516 -- Try_One_Prefix_Interpretation --
7517 -----------------------------------
7518
7519 procedure Try_One_Prefix_Interpretation (T : Entity_Id) is
7520 begin
7521 Obj_Type := T;
7522
7523 if Is_Access_Type (Obj_Type) then
7524 Obj_Type := Designated_Type (Obj_Type);
7525 end if;
7526
7527 if Ekind (Obj_Type) = E_Private_Subtype then
7528 Obj_Type := Base_Type (Obj_Type);
7529 end if;
7530
7531 if Is_Class_Wide_Type (Obj_Type) then
7532 Obj_Type := Etype (Class_Wide_Type (Obj_Type));
7533 end if;
7534
7535 -- The type may have be obtained through a limited_with clause,
7536 -- in which case the primitive operations are available on its
7537 -- non-limited view. If still incomplete, retrieve full view.
7538
7539 if Ekind (Obj_Type) = E_Incomplete_Type
7540 and then From_With_Type (Obj_Type)
7541 then
7542 Obj_Type := Get_Full_View (Non_Limited_View (Obj_Type));
7543 end if;
7544
7545 -- If the object is not tagged, or the type is still an incomplete
7546 -- type, this is not a prefixed call.
7547
7548 if not Is_Tagged_Type (Obj_Type)
7549 or else Is_Incomplete_Type (Obj_Type)
7550 then
7551 return;
7552 end if;
7553
7554 declare
7555 Dup_Call_Node : constant Node_Id := New_Copy (New_Call_Node);
7556 CW_Result : Boolean;
7557 Prim_Result : Boolean;
7558 pragma Unreferenced (CW_Result);
7559
7560 begin
7561 if not CW_Test_Only then
7562 Prim_Result :=
7563 Try_Primitive_Operation
7564 (Call_Node => New_Call_Node,
7565 Node_To_Replace => Node_To_Replace);
7566 end if;
7567
7568 -- Check if there is a class-wide subprogram covering the
7569 -- primitive. This check must be done even if a candidate
7570 -- was found in order to report ambiguous calls.
7571
7572 if not (Prim_Result) then
7573 CW_Result :=
7574 Try_Class_Wide_Operation
7575 (Call_Node => New_Call_Node,
7576 Node_To_Replace => Node_To_Replace);
7577
7578 -- If we found a primitive we search for class-wide subprograms
7579 -- using a duplicate of the call node (done to avoid missing its
7580 -- decoration if there is no ambiguity).
7581
7582 else
7583 CW_Result :=
7584 Try_Class_Wide_Operation
7585 (Call_Node => Dup_Call_Node,
7586 Node_To_Replace => Node_To_Replace);
7587 end if;
7588 end;
7589 end Try_One_Prefix_Interpretation;
7590
7591 -----------------------------
7592 -- Try_Primitive_Operation --
7593 -----------------------------
7594
7595 function Try_Primitive_Operation
7596 (Call_Node : Node_Id;
7597 Node_To_Replace : Node_Id) return Boolean
7598 is
7599 Elmt : Elmt_Id;
7600 Prim_Op : Entity_Id;
7601 Matching_Op : Entity_Id := Empty;
7602 Prim_Op_Ref : Node_Id := Empty;
7603
7604 Corr_Type : Entity_Id := Empty;
7605 -- If the prefix is a synchronized type, the controlling type of
7606 -- the primitive operation is the corresponding record type, else
7607 -- this is the object type itself.
7608
7609 Success : Boolean := False;
7610
7611 function Collect_Generic_Type_Ops (T : Entity_Id) return Elist_Id;
7612 -- For tagged types the candidate interpretations are found in
7613 -- the list of primitive operations of the type and its ancestors.
7614 -- For formal tagged types we have to find the operations declared
7615 -- in the same scope as the type (including in the generic formal
7616 -- part) because the type itself carries no primitive operations,
7617 -- except for formal derived types that inherit the operations of
7618 -- the parent and progenitors.
7619 -- If the context is a generic subprogram body, the generic formals
7620 -- are visible by name, but are not in the entity list of the
7621 -- subprogram because that list starts with the subprogram formals.
7622 -- We retrieve the candidate operations from the generic declaration.
7623
7624 function Is_Private_Overriding (Op : Entity_Id) return Boolean;
7625 -- An operation that overrides an inherited operation in the private
7626 -- part of its package may be hidden, but if the inherited operation
7627 -- is visible a direct call to it will dispatch to the private one,
7628 -- which is therefore a valid candidate.
7629
7630 function Valid_First_Argument_Of (Op : Entity_Id) return Boolean;
7631 -- Verify that the prefix, dereferenced if need be, is a valid
7632 -- controlling argument in a call to Op. The remaining actuals
7633 -- are checked in the subsequent call to Analyze_One_Call.
7634
7635 ------------------------------
7636 -- Collect_Generic_Type_Ops --
7637 ------------------------------
7638
7639 function Collect_Generic_Type_Ops (T : Entity_Id) return Elist_Id is
7640 Bas : constant Entity_Id := Base_Type (T);
7641 Candidates : constant Elist_Id := New_Elmt_List;
7642 Subp : Entity_Id;
7643 Formal : Entity_Id;
7644
7645 procedure Check_Candidate;
7646 -- The operation is a candidate if its first parameter is a
7647 -- controlling operand of the desired type.
7648
7649 -----------------------
7650 -- Check_Candidate; --
7651 -----------------------
7652
7653 procedure Check_Candidate is
7654 begin
7655 Formal := First_Formal (Subp);
7656
7657 if Present (Formal)
7658 and then Is_Controlling_Formal (Formal)
7659 and then
7660 (Base_Type (Etype (Formal)) = Bas
7661 or else
7662 (Is_Access_Type (Etype (Formal))
7663 and then Designated_Type (Etype (Formal)) = Bas))
7664 then
7665 Append_Elmt (Subp, Candidates);
7666 end if;
7667 end Check_Candidate;
7668
7669 -- Start of processing for Collect_Generic_Type_Ops
7670
7671 begin
7672 if Is_Derived_Type (T) then
7673 return Primitive_Operations (T);
7674
7675 elsif Ekind_In (Scope (T), E_Procedure, E_Function) then
7676
7677 -- Scan the list of generic formals to find subprograms
7678 -- that may have a first controlling formal of the type.
7679
7680 if Nkind (Unit_Declaration_Node (Scope (T)))
7681 = N_Generic_Subprogram_Declaration
7682 then
7683 declare
7684 Decl : Node_Id;
7685
7686 begin
7687 Decl :=
7688 First (Generic_Formal_Declarations
7689 (Unit_Declaration_Node (Scope (T))));
7690 while Present (Decl) loop
7691 if Nkind (Decl) in N_Formal_Subprogram_Declaration then
7692 Subp := Defining_Entity (Decl);
7693 Check_Candidate;
7694 end if;
7695
7696 Next (Decl);
7697 end loop;
7698 end;
7699 end if;
7700 return Candidates;
7701
7702 else
7703 -- Scan the list of entities declared in the same scope as
7704 -- the type. In general this will be an open scope, given that
7705 -- the call we are analyzing can only appear within a generic
7706 -- declaration or body (either the one that declares T, or a
7707 -- child unit).
7708
7709 -- For a subtype representing a generic actual type, go to the
7710 -- base type.
7711
7712 if Is_Generic_Actual_Type (T) then
7713 Subp := First_Entity (Scope (Base_Type (T)));
7714 else
7715 Subp := First_Entity (Scope (T));
7716 end if;
7717
7718 while Present (Subp) loop
7719 if Is_Overloadable (Subp) then
7720 Check_Candidate;
7721 end if;
7722
7723 Next_Entity (Subp);
7724 end loop;
7725
7726 return Candidates;
7727 end if;
7728 end Collect_Generic_Type_Ops;
7729
7730 ---------------------------
7731 -- Is_Private_Overriding --
7732 ---------------------------
7733
7734 function Is_Private_Overriding (Op : Entity_Id) return Boolean is
7735 Visible_Op : constant Entity_Id := Homonym (Op);
7736
7737 begin
7738 return Present (Visible_Op)
7739 and then Scope (Op) = Scope (Visible_Op)
7740 and then not Comes_From_Source (Visible_Op)
7741 and then Alias (Visible_Op) = Op
7742 and then not Is_Hidden (Visible_Op);
7743 end Is_Private_Overriding;
7744
7745 -----------------------------
7746 -- Valid_First_Argument_Of --
7747 -----------------------------
7748
7749 function Valid_First_Argument_Of (Op : Entity_Id) return Boolean is
7750 Typ : Entity_Id := Etype (First_Formal (Op));
7751
7752 begin
7753 if Is_Concurrent_Type (Typ)
7754 and then Present (Corresponding_Record_Type (Typ))
7755 then
7756 Typ := Corresponding_Record_Type (Typ);
7757 end if;
7758
7759 -- Simple case. Object may be a subtype of the tagged type or
7760 -- may be the corresponding record of a synchronized type.
7761
7762 return Obj_Type = Typ
7763 or else Base_Type (Obj_Type) = Typ
7764 or else Corr_Type = Typ
7765
7766 -- Prefix can be dereferenced
7767
7768 or else
7769 (Is_Access_Type (Corr_Type)
7770 and then Designated_Type (Corr_Type) = Typ)
7771
7772 -- Formal is an access parameter, for which the object
7773 -- can provide an access.
7774
7775 or else
7776 (Ekind (Typ) = E_Anonymous_Access_Type
7777 and then
7778 Base_Type (Designated_Type (Typ)) = Base_Type (Corr_Type));
7779 end Valid_First_Argument_Of;
7780
7781 -- Start of processing for Try_Primitive_Operation
7782
7783 begin
7784 -- Look for subprograms in the list of primitive operations. The name
7785 -- must be identical, and the kind of call indicates the expected
7786 -- kind of operation (function or procedure). If the type is a
7787 -- (tagged) synchronized type, the primitive ops are attached to the
7788 -- corresponding record (base) type.
7789
7790 if Is_Concurrent_Type (Obj_Type) then
7791 if Present (Corresponding_Record_Type (Obj_Type)) then
7792 Corr_Type := Base_Type (Corresponding_Record_Type (Obj_Type));
7793 Elmt := First_Elmt (Primitive_Operations (Corr_Type));
7794 else
7795 Corr_Type := Obj_Type;
7796 Elmt := First_Elmt (Collect_Generic_Type_Ops (Obj_Type));
7797 end if;
7798
7799 elsif not Is_Generic_Type (Obj_Type) then
7800 Corr_Type := Obj_Type;
7801 Elmt := First_Elmt (Primitive_Operations (Obj_Type));
7802
7803 else
7804 Corr_Type := Obj_Type;
7805 Elmt := First_Elmt (Collect_Generic_Type_Ops (Obj_Type));
7806 end if;
7807
7808 while Present (Elmt) loop
7809 Prim_Op := Node (Elmt);
7810
7811 if Chars (Prim_Op) = Chars (Subprog)
7812 and then Present (First_Formal (Prim_Op))
7813 and then Valid_First_Argument_Of (Prim_Op)
7814 and then
7815 (Nkind (Call_Node) = N_Function_Call)
7816 = (Ekind (Prim_Op) = E_Function)
7817 then
7818 -- Ada 2005 (AI-251): If this primitive operation corresponds
7819 -- with an immediate ancestor interface there is no need to add
7820 -- it to the list of interpretations; the corresponding aliased
7821 -- primitive is also in this list of primitive operations and
7822 -- will be used instead.
7823
7824 if (Present (Interface_Alias (Prim_Op))
7825 and then Is_Ancestor (Find_Dispatching_Type
7826 (Alias (Prim_Op)), Corr_Type))
7827
7828 -- Do not consider hidden primitives unless the type is in an
7829 -- open scope or we are within an instance, where visibility
7830 -- is known to be correct, or else if this is an overriding
7831 -- operation in the private part for an inherited operation.
7832
7833 or else (Is_Hidden (Prim_Op)
7834 and then not Is_Immediately_Visible (Obj_Type)
7835 and then not In_Instance
7836 and then not Is_Private_Overriding (Prim_Op))
7837 then
7838 goto Continue;
7839 end if;
7840
7841 Set_Etype (Call_Node, Any_Type);
7842 Set_Is_Overloaded (Call_Node, False);
7843
7844 if No (Matching_Op) then
7845 Prim_Op_Ref := New_Reference_To (Prim_Op, Sloc (Subprog));
7846 Candidate := Prim_Op;
7847
7848 Set_Parent (Call_Node, Parent (Node_To_Replace));
7849
7850 Set_Name (Call_Node, Prim_Op_Ref);
7851 Success := False;
7852
7853 Analyze_One_Call
7854 (N => Call_Node,
7855 Nam => Prim_Op,
7856 Report => Report_Error,
7857 Success => Success,
7858 Skip_First => True);
7859
7860 Matching_Op := Valid_Candidate (Success, Call_Node, Prim_Op);
7861
7862 -- More than one interpretation, collect for subsequent
7863 -- disambiguation. If this is a procedure call and there
7864 -- is another match, report ambiguity now.
7865
7866 else
7867 Analyze_One_Call
7868 (N => Call_Node,
7869 Nam => Prim_Op,
7870 Report => Report_Error,
7871 Success => Success,
7872 Skip_First => True);
7873
7874 if Present (Valid_Candidate (Success, Call_Node, Prim_Op))
7875 and then Nkind (Call_Node) /= N_Function_Call
7876 then
7877 Error_Msg_NE ("ambiguous call to&", N, Prim_Op);
7878 Report_Ambiguity (Matching_Op);
7879 Report_Ambiguity (Prim_Op);
7880 return True;
7881 end if;
7882 end if;
7883 end if;
7884
7885 <<Continue>>
7886 Next_Elmt (Elmt);
7887 end loop;
7888
7889 if Present (Matching_Op) then
7890 Set_Etype (Call_Node, Etype (Matching_Op));
7891 end if;
7892
7893 return Present (Matching_Op);
7894 end Try_Primitive_Operation;
7895
7896 -- Start of processing for Try_Object_Operation
7897
7898 begin
7899 Analyze_Expression (Obj);
7900
7901 -- Analyze the actuals if node is known to be a subprogram call
7902
7903 if Is_Subprg_Call and then N = Name (Parent (N)) then
7904 Actual := First (Parameter_Associations (Parent (N)));
7905 while Present (Actual) loop
7906 Analyze_Expression (Actual);
7907 Next (Actual);
7908 end loop;
7909 end if;
7910
7911 -- Build a subprogram call node, using a copy of Obj as its first
7912 -- actual. This is a placeholder, to be replaced by an explicit
7913 -- dereference when needed.
7914
7915 Transform_Object_Operation
7916 (Call_Node => New_Call_Node,
7917 Node_To_Replace => Node_To_Replace);
7918
7919 Set_Etype (New_Call_Node, Any_Type);
7920 Set_Etype (Subprog, Any_Type);
7921 Set_Parent (New_Call_Node, Parent (Node_To_Replace));
7922
7923 if not Is_Overloaded (Obj) then
7924 Try_One_Prefix_Interpretation (Obj_Type);
7925
7926 else
7927 declare
7928 I : Interp_Index;
7929 It : Interp;
7930 begin
7931 Get_First_Interp (Obj, I, It);
7932 while Present (It.Nam) loop
7933 Try_One_Prefix_Interpretation (It.Typ);
7934 Get_Next_Interp (I, It);
7935 end loop;
7936 end;
7937 end if;
7938
7939 if Etype (New_Call_Node) /= Any_Type then
7940
7941 -- No need to complete the tree transformations if we are only
7942 -- searching for conflicting class-wide subprograms
7943
7944 if CW_Test_Only then
7945 return False;
7946 else
7947 Complete_Object_Operation
7948 (Call_Node => New_Call_Node,
7949 Node_To_Replace => Node_To_Replace);
7950 return True;
7951 end if;
7952
7953 elsif Present (Candidate) then
7954
7955 -- The argument list is not type correct. Re-analyze with error
7956 -- reporting enabled, and use one of the possible candidates.
7957 -- In All_Errors_Mode, re-analyze all failed interpretations.
7958
7959 if All_Errors_Mode then
7960 Report_Error := True;
7961 if Try_Primitive_Operation
7962 (Call_Node => New_Call_Node,
7963 Node_To_Replace => Node_To_Replace)
7964
7965 or else
7966 Try_Class_Wide_Operation
7967 (Call_Node => New_Call_Node,
7968 Node_To_Replace => Node_To_Replace)
7969 then
7970 null;
7971 end if;
7972
7973 else
7974 Analyze_One_Call
7975 (N => New_Call_Node,
7976 Nam => Candidate,
7977 Report => True,
7978 Success => Success,
7979 Skip_First => True);
7980 end if;
7981
7982 -- No need for further errors
7983
7984 return True;
7985
7986 else
7987 -- There was no candidate operation, so report it as an error
7988 -- in the caller: Analyze_Selected_Component.
7989
7990 return False;
7991 end if;
7992 end Try_Object_Operation;
7993
7994 ---------
7995 -- wpo --
7996 ---------
7997
7998 procedure wpo (T : Entity_Id) is
7999 Op : Entity_Id;
8000 E : Elmt_Id;
8001
8002 begin
8003 if not Is_Tagged_Type (T) then
8004 return;
8005 end if;
8006
8007 E := First_Elmt (Primitive_Operations (Base_Type (T)));
8008 while Present (E) loop
8009 Op := Node (E);
8010 Write_Int (Int (Op));
8011 Write_Str (" === ");
8012 Write_Name (Chars (Op));
8013 Write_Str (" in ");
8014 Write_Name (Chars (Scope (Op)));
8015 Next_Elmt (E);
8016 Write_Eol;
8017 end loop;
8018 end wpo;
8019
8020 end Sem_Ch4;