[NDS32] new attribute no_prologue and new option -mret-in-naked-func.
[official-gcc.git] / gcc / ada / sem_ch4.adb
blobf17741758dd0a5e00e867dbb638d35511aa41c22
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-2018, Free Software Foundation, Inc. --
10 -- --
11 -- GNAT is free software; you can redistribute it and/or modify it under --
12 -- terms of the GNU General Public License as published by the Free Soft- --
13 -- ware Foundation; either version 3, or (at your option) any later ver- --
14 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
17 -- for more details. You should have received a copy of the GNU General --
18 -- Public License distributed with GNAT; see file COPYING3. If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license. --
20 -- --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
23 -- --
24 ------------------------------------------------------------------------------
26 with 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 Itypes; use Itypes;
34 with Lib; use Lib;
35 with Lib.Xref; use Lib.Xref;
36 with Namet; use Namet;
37 with Namet.Sp; use Namet.Sp;
38 with Nlists; use Nlists;
39 with Nmake; use Nmake;
40 with Opt; use Opt;
41 with Output; use Output;
42 with Restrict; use Restrict;
43 with Rident; use Rident;
44 with Sem; use Sem;
45 with Sem_Aux; use Sem_Aux;
46 with Sem_Case; use Sem_Case;
47 with Sem_Cat; use Sem_Cat;
48 with Sem_Ch3; use Sem_Ch3;
49 with Sem_Ch6; use Sem_Ch6;
50 with Sem_Ch8; use Sem_Ch8;
51 with Sem_Dim; use Sem_Dim;
52 with Sem_Disp; use Sem_Disp;
53 with Sem_Dist; use Sem_Dist;
54 with Sem_Eval; use Sem_Eval;
55 with Sem_Res; use Sem_Res;
56 with Sem_Type; use Sem_Type;
57 with Sem_Util; use Sem_Util;
58 with Sem_Warn; use Sem_Warn;
59 with Stand; use Stand;
60 with Sinfo; use Sinfo;
61 with Snames; use Snames;
62 with Tbuild; use Tbuild;
63 with Uintp; use Uintp;
65 package body Sem_Ch4 is
67 -- Tables which speed up the identification of dangerous calls to Ada 2012
68 -- functions with writable actuals (AI05-0144).
70 -- The following table enumerates the Ada constructs which may evaluate in
71 -- arbitrary order. It does not cover all the language constructs which can
72 -- be evaluated in arbitrary order but the subset needed for AI05-0144.
74 Has_Arbitrary_Evaluation_Order : constant array (Node_Kind) of Boolean :=
75 (N_Aggregate => True,
76 N_Assignment_Statement => True,
77 N_Entry_Call_Statement => True,
78 N_Extension_Aggregate => True,
79 N_Full_Type_Declaration => True,
80 N_Indexed_Component => True,
81 N_Object_Declaration => True,
82 N_Pragma => True,
83 N_Range => True,
84 N_Slice => True,
85 N_Array_Type_Definition => True,
86 N_Membership_Test => True,
87 N_Binary_Op => True,
88 N_Subprogram_Call => True,
89 others => False);
91 -- The following table enumerates the nodes on which we stop climbing when
92 -- locating the outermost Ada construct that can be evaluated in arbitrary
93 -- order.
95 Stop_Subtree_Climbing : constant array (Node_Kind) of Boolean :=
96 (N_Aggregate => True,
97 N_Assignment_Statement => True,
98 N_Entry_Call_Statement => True,
99 N_Extended_Return_Statement => True,
100 N_Extension_Aggregate => True,
101 N_Full_Type_Declaration => True,
102 N_Object_Declaration => True,
103 N_Object_Renaming_Declaration => True,
104 N_Package_Specification => True,
105 N_Pragma => True,
106 N_Procedure_Call_Statement => True,
107 N_Simple_Return_Statement => True,
108 N_Has_Condition => True,
109 others => False);
111 -----------------------
112 -- Local Subprograms --
113 -----------------------
115 procedure Analyze_Concatenation_Rest (N : Node_Id);
116 -- Does the "rest" of the work of Analyze_Concatenation, after the left
117 -- operand has been analyzed. See Analyze_Concatenation for details.
119 procedure Analyze_Expression (N : Node_Id);
120 -- For expressions that are not names, this is just a call to analyze. If
121 -- the expression is a name, it may be a call to a parameterless function,
122 -- and if so must be converted into an explicit call node and analyzed as
123 -- such. This deproceduring must be done during the first pass of overload
124 -- resolution, because otherwise a procedure call with overloaded actuals
125 -- may fail to resolve.
127 procedure Analyze_Operator_Call (N : Node_Id; Op_Id : Entity_Id);
128 -- Analyze a call of the form "+"(x, y), etc. The prefix of the call is an
129 -- operator name or an expanded name whose selector is an operator name,
130 -- and one possible interpretation is as a predefined operator.
132 procedure Analyze_Overloaded_Selected_Component (N : Node_Id);
133 -- If the prefix of a selected_component is overloaded, the proper
134 -- interpretation that yields a record type with the proper selector
135 -- name must be selected.
137 procedure Analyze_User_Defined_Binary_Op (N : Node_Id; Op_Id : Entity_Id);
138 -- Procedure to analyze a user defined binary operator, which is resolved
139 -- like a function, but instead of a list of actuals it is presented
140 -- with the left and right operands of an operator node.
142 procedure Analyze_User_Defined_Unary_Op (N : Node_Id; Op_Id : Entity_Id);
143 -- Procedure to analyze a user defined unary operator, which is resolved
144 -- like a function, but instead of a list of actuals, it is presented with
145 -- the operand of the operator node.
147 procedure Ambiguous_Operands (N : Node_Id);
148 -- For equality, membership, and comparison operators with overloaded
149 -- arguments, list possible interpretations.
151 procedure Analyze_One_Call
152 (N : Node_Id;
153 Nam : Entity_Id;
154 Report : Boolean;
155 Success : out Boolean;
156 Skip_First : Boolean := False);
157 -- Check one interpretation of an overloaded subprogram name for
158 -- compatibility with the types of the actuals in a call. If there is a
159 -- single interpretation which does not match, post error if Report is
160 -- set to True.
162 -- Nam is the entity that provides the formals against which the actuals
163 -- are checked. Nam is either the name of a subprogram, or the internal
164 -- subprogram type constructed for an access_to_subprogram. If the actuals
165 -- are compatible with Nam, then Nam is added to the list of candidate
166 -- interpretations for N, and Success is set to True.
168 -- The flag Skip_First is used when analyzing a call that was rewritten
169 -- from object notation. In this case the first actual may have to receive
170 -- an explicit dereference, depending on the first formal of the operation
171 -- being called. The caller will have verified that the object is legal
172 -- for the call. If the remaining parameters match, the first parameter
173 -- will rewritten as a dereference if needed, prior to completing analysis.
175 procedure Check_Misspelled_Selector
176 (Prefix : Entity_Id;
177 Sel : Node_Id);
178 -- Give possible misspelling message if Sel seems likely to be a mis-
179 -- spelling of one of the selectors of the Prefix. This is called by
180 -- Analyze_Selected_Component after producing an invalid selector error
181 -- message.
183 function Defined_In_Scope (T : Entity_Id; S : Entity_Id) return Boolean;
184 -- Verify that type T is declared in scope S. Used to find interpretations
185 -- for operators given by expanded names. This is abstracted as a separate
186 -- function to handle extensions to System, where S is System, but T is
187 -- declared in the extension.
189 procedure Find_Arithmetic_Types
190 (L, R : Node_Id;
191 Op_Id : Entity_Id;
192 N : Node_Id);
193 -- L and R are the operands of an arithmetic operator. Find consistent
194 -- pairs of interpretations for L and R that have a numeric type consistent
195 -- with the semantics of the operator.
197 procedure Find_Comparison_Types
198 (L, R : Node_Id;
199 Op_Id : Entity_Id;
200 N : Node_Id);
201 -- L and R are operands of a comparison operator. Find consistent pairs of
202 -- interpretations for L and R.
204 procedure Find_Concatenation_Types
205 (L, R : Node_Id;
206 Op_Id : Entity_Id;
207 N : Node_Id);
208 -- For the four varieties of concatenation
210 procedure Find_Equality_Types
211 (L, R : Node_Id;
212 Op_Id : Entity_Id;
213 N : Node_Id);
214 -- Ditto for equality operators
216 procedure Find_Boolean_Types
217 (L, R : Node_Id;
218 Op_Id : Entity_Id;
219 N : Node_Id);
220 -- Ditto for binary logical operations
222 procedure Find_Negation_Types
223 (R : Node_Id;
224 Op_Id : Entity_Id;
225 N : Node_Id);
226 -- Find consistent interpretation for operand of negation operator
228 procedure Find_Non_Universal_Interpretations
229 (N : Node_Id;
230 R : Node_Id;
231 Op_Id : Entity_Id;
232 T1 : Entity_Id);
233 -- For equality and comparison operators, the result is always boolean, and
234 -- the legality of the operation is determined from the visibility of the
235 -- operand types. If one of the operands has a universal interpretation,
236 -- the legality check uses some compatible non-universal interpretation of
237 -- the other operand. N can be an operator node, or a function call whose
238 -- name is an operator designator. Any_Access, which is the initial type of
239 -- the literal NULL, is a universal type for the purpose of this routine.
241 function Find_Primitive_Operation (N : Node_Id) return Boolean;
242 -- Find candidate interpretations for the name Obj.Proc when it appears in
243 -- a subprogram renaming declaration.
245 procedure Find_Unary_Types
246 (R : Node_Id;
247 Op_Id : Entity_Id;
248 N : Node_Id);
249 -- Unary arithmetic types: plus, minus, abs
251 procedure Check_Arithmetic_Pair
252 (T1, T2 : Entity_Id;
253 Op_Id : Entity_Id;
254 N : Node_Id);
255 -- Subsidiary procedure to Find_Arithmetic_Types. T1 and T2 are valid types
256 -- for left and right operand. Determine whether they constitute a valid
257 -- pair for the given operator, and record the corresponding interpretation
258 -- of the operator node. The node N may be an operator node (the usual
259 -- case) or a function call whose prefix is an operator designator. In
260 -- both cases Op_Id is the operator name itself.
262 procedure Diagnose_Call (N : Node_Id; Nam : Node_Id);
263 -- Give detailed information on overloaded call where none of the
264 -- interpretations match. N is the call node, Nam the designator for
265 -- the overloaded entity being called.
267 function Junk_Operand (N : Node_Id) return Boolean;
268 -- Test for an operand that is an inappropriate entity (e.g. a package
269 -- name or a label). If so, issue an error message and return True. If
270 -- the operand is not an inappropriate entity kind, return False.
272 procedure Operator_Check (N : Node_Id);
273 -- Verify that an operator has received some valid interpretation. If none
274 -- was found, determine whether a use clause would make the operation
275 -- legal. The variable Candidate_Type (defined in Sem_Type) is set for
276 -- every type compatible with the operator, even if the operator for the
277 -- type is not directly visible. The routine uses this type to emit a more
278 -- informative message.
280 function Process_Implicit_Dereference_Prefix
281 (E : Entity_Id;
282 P : Node_Id) return Entity_Id;
283 -- Called when P is the prefix of an implicit dereference, denoting an
284 -- object E. The function returns the designated type of the prefix, taking
285 -- into account that the designated type of an anonymous access type may be
286 -- a limited view, when the nonlimited view is visible.
288 -- If in semantics only mode (-gnatc or generic), the function also records
289 -- that the prefix is a reference to E, if any. Normally, such a reference
290 -- is generated only when the implicit dereference is expanded into an
291 -- explicit one, but for consistency we must generate the reference when
292 -- expansion is disabled as well.
294 procedure Remove_Abstract_Operations (N : Node_Id);
295 -- Ada 2005: implementation of AI-310. An abstract non-dispatching
296 -- operation is not a candidate interpretation.
298 function Try_Container_Indexing
299 (N : Node_Id;
300 Prefix : Node_Id;
301 Exprs : List_Id) return Boolean;
302 -- AI05-0139: Generalized indexing to support iterators over containers
304 function Try_Indexed_Call
305 (N : Node_Id;
306 Nam : Entity_Id;
307 Typ : Entity_Id;
308 Skip_First : Boolean) return Boolean;
309 -- If a function has defaults for all its actuals, a call to it may in fact
310 -- be an indexing on the result of the call. Try_Indexed_Call attempts the
311 -- interpretation as an indexing, prior to analysis as a call. If both are
312 -- possible, the node is overloaded with both interpretations (same symbol
313 -- but two different types). If the call is written in prefix form, the
314 -- prefix becomes the first parameter in the call, and only the remaining
315 -- actuals must be checked for the presence of defaults.
317 function Try_Indirect_Call
318 (N : Node_Id;
319 Nam : Entity_Id;
320 Typ : Entity_Id) return Boolean;
321 -- Similarly, a function F that needs no actuals can return an access to a
322 -- subprogram, and the call F (X) interpreted as F.all (X). In this case
323 -- the call may be overloaded with both interpretations.
325 procedure wpo (T : Entity_Id);
326 pragma Warnings (Off, wpo);
327 -- Used for debugging: obtain list of primitive operations even if
328 -- type is not frozen and dispatch table is not built yet.
330 ------------------------
331 -- Ambiguous_Operands --
332 ------------------------
334 procedure Ambiguous_Operands (N : Node_Id) is
335 procedure List_Operand_Interps (Opnd : Node_Id);
337 --------------------------
338 -- List_Operand_Interps --
339 --------------------------
341 procedure List_Operand_Interps (Opnd : Node_Id) is
342 Nam : Node_Id := Empty;
343 Err : Node_Id := N;
345 begin
346 if Is_Overloaded (Opnd) then
347 if Nkind (Opnd) in N_Op then
348 Nam := Opnd;
350 elsif Nkind (Opnd) = N_Function_Call then
351 Nam := Name (Opnd);
353 elsif Ada_Version >= Ada_2012 then
354 declare
355 It : Interp;
356 I : Interp_Index;
358 begin
359 Get_First_Interp (Opnd, I, It);
360 while Present (It.Nam) loop
361 if Has_Implicit_Dereference (It.Typ) then
362 Error_Msg_N
363 ("can be interpreted as implicit dereference", Opnd);
364 return;
365 end if;
367 Get_Next_Interp (I, It);
368 end loop;
369 end;
371 return;
372 end if;
374 else
375 return;
376 end if;
378 if Opnd = Left_Opnd (N) then
379 Error_Msg_N
380 ("\left operand has the following interpretations", N);
381 else
382 Error_Msg_N
383 ("\right operand has the following interpretations", N);
384 Err := Opnd;
385 end if;
387 List_Interps (Nam, Err);
388 end List_Operand_Interps;
390 -- Start of processing for Ambiguous_Operands
392 begin
393 if Nkind (N) in N_Membership_Test then
394 Error_Msg_N ("ambiguous operands for membership", N);
396 elsif Nkind_In (N, N_Op_Eq, N_Op_Ne) then
397 Error_Msg_N ("ambiguous operands for equality", N);
399 else
400 Error_Msg_N ("ambiguous operands for comparison", N);
401 end if;
403 if All_Errors_Mode then
404 List_Operand_Interps (Left_Opnd (N));
405 List_Operand_Interps (Right_Opnd (N));
406 else
407 Error_Msg_N ("\use -gnatf switch for details", N);
408 end if;
409 end Ambiguous_Operands;
411 -----------------------
412 -- Analyze_Aggregate --
413 -----------------------
415 -- Most of the analysis of Aggregates requires that the type be known, and
416 -- is therefore put off until resolution of the context. Delta aggregates
417 -- have a base component that determines the enclosing aggregate type so
418 -- its type can be ascertained earlier. This also allows delta aggregates
419 -- to appear in the context of a record type with a private extension, as
420 -- per the latest update of AI12-0127.
422 procedure Analyze_Aggregate (N : Node_Id) is
423 begin
424 if No (Etype (N)) then
425 if Nkind (N) = N_Delta_Aggregate then
426 declare
427 Base : constant Node_Id := Expression (N);
429 I : Interp_Index;
430 It : Interp;
432 begin
433 Analyze (Base);
435 -- If the base is overloaded, propagate interpretations to the
436 -- enclosing aggregate.
438 if Is_Overloaded (Base) then
439 Get_First_Interp (Base, I, It);
440 Set_Etype (N, Any_Type);
442 while Present (It.Nam) loop
443 Add_One_Interp (N, It.Typ, It.Typ);
444 Get_Next_Interp (I, It);
445 end loop;
447 else
448 Set_Etype (N, Etype (Base));
449 end if;
450 end;
452 else
453 Set_Etype (N, Any_Composite);
454 end if;
455 end if;
456 end Analyze_Aggregate;
458 -----------------------
459 -- Analyze_Allocator --
460 -----------------------
462 procedure Analyze_Allocator (N : Node_Id) is
463 Loc : constant Source_Ptr := Sloc (N);
464 Sav_Errs : constant Nat := Serious_Errors_Detected;
465 E : Node_Id := Expression (N);
466 Acc_Type : Entity_Id;
467 Type_Id : Entity_Id;
468 P : Node_Id;
469 C : Node_Id;
470 Onode : Node_Id;
472 begin
473 Check_SPARK_05_Restriction ("allocator is not allowed", N);
475 -- Deal with allocator restrictions
477 -- In accordance with H.4(7), the No_Allocators restriction only applies
478 -- to user-written allocators. The same consideration applies to the
479 -- No_Standard_Allocators_Before_Elaboration restriction.
481 if Comes_From_Source (N) then
482 Check_Restriction (No_Allocators, N);
484 -- Processing for No_Standard_Allocators_After_Elaboration, loop to
485 -- look at enclosing context, checking task/main subprogram case.
487 C := N;
488 P := Parent (C);
489 while Present (P) loop
491 -- For the task case we need a handled sequence of statements,
492 -- where the occurrence of the allocator is within the statements
493 -- and the parent is a task body
495 if Nkind (P) = N_Handled_Sequence_Of_Statements
496 and then Is_List_Member (C)
497 and then List_Containing (C) = Statements (P)
498 then
499 Onode := Original_Node (Parent (P));
501 -- Check for allocator within task body, this is a definite
502 -- violation of No_Allocators_After_Elaboration we can detect
503 -- at compile time.
505 if Nkind (Onode) = N_Task_Body then
506 Check_Restriction
507 (No_Standard_Allocators_After_Elaboration, N);
508 exit;
509 end if;
510 end if;
512 -- The other case is appearance in a subprogram body. This is
513 -- a violation if this is a library level subprogram with no
514 -- parameters. Note that this is now a static error even if the
515 -- subprogram is not the main program (this is a change, in an
516 -- earlier version only the main program was affected, and the
517 -- check had to be done in the binder.
519 if Nkind (P) = N_Subprogram_Body
520 and then Nkind (Parent (P)) = N_Compilation_Unit
521 and then No (Parameter_Specifications (Specification (P)))
522 then
523 Check_Restriction
524 (No_Standard_Allocators_After_Elaboration, N);
525 end if;
527 C := P;
528 P := Parent (C);
529 end loop;
530 end if;
532 -- Ada 2012 (AI05-0111-3): Analyze the subpool_specification, if
533 -- any. The expected type for the name is any type. A non-overloading
534 -- rule then requires it to be of a type descended from
535 -- System.Storage_Pools.Subpools.Subpool_Handle.
537 -- This isn't exactly what the AI says, but it seems to be the right
538 -- rule. The AI should be fixed.???
540 declare
541 Subpool : constant Node_Id := Subpool_Handle_Name (N);
543 begin
544 if Present (Subpool) then
545 Analyze (Subpool);
547 if Is_Overloaded (Subpool) then
548 Error_Msg_N ("ambiguous subpool handle", Subpool);
549 end if;
551 -- Check that Etype (Subpool) is descended from Subpool_Handle
553 Resolve (Subpool);
554 end if;
555 end;
557 -- Analyze the qualified expression or subtype indication
559 if Nkind (E) = N_Qualified_Expression then
560 Acc_Type := Create_Itype (E_Allocator_Type, N);
561 Set_Etype (Acc_Type, Acc_Type);
562 Find_Type (Subtype_Mark (E));
564 -- Analyze the qualified expression, and apply the name resolution
565 -- rule given in 4.7(3).
567 Analyze (E);
568 Type_Id := Etype (E);
569 Set_Directly_Designated_Type (Acc_Type, Type_Id);
571 -- A qualified expression requires an exact match of the type,
572 -- class-wide matching is not allowed.
574 -- if Is_Class_Wide_Type (Type_Id)
575 -- and then Base_Type
576 -- (Etype (Expression (E))) /= Base_Type (Type_Id)
577 -- then
578 -- Wrong_Type (Expression (E), Type_Id);
579 -- end if;
581 -- We don't analyze the qualified expression itself because it's
582 -- part of the allocator. It is fully analyzed and resolved when
583 -- the allocator is resolved with the context type.
585 Set_Etype (E, Type_Id);
587 -- Case where allocator has a subtype indication
589 else
590 declare
591 Def_Id : Entity_Id;
592 Base_Typ : Entity_Id;
594 begin
595 -- If the allocator includes a N_Subtype_Indication then a
596 -- constraint is present, otherwise the node is a subtype mark.
597 -- Introduce an explicit subtype declaration into the tree
598 -- defining some anonymous subtype and rewrite the allocator to
599 -- use this subtype rather than the subtype indication.
601 -- It is important to introduce the explicit subtype declaration
602 -- so that the bounds of the subtype indication are attached to
603 -- the tree in case the allocator is inside a generic unit.
605 -- Finally, if there is no subtype indication and the type is
606 -- a tagged unconstrained type with discriminants, the designated
607 -- object is constrained by their default values, and it is
608 -- simplest to introduce an explicit constraint now. In some cases
609 -- this is done during expansion, but freeze actions are certain
610 -- to be emitted in the proper order if constraint is explicit.
612 if Is_Entity_Name (E) and then Expander_Active then
613 Find_Type (E);
614 Type_Id := Entity (E);
616 if Is_Tagged_Type (Type_Id)
617 and then Has_Discriminants (Type_Id)
618 and then not Is_Constrained (Type_Id)
619 and then
620 Present
621 (Discriminant_Default_Value
622 (First_Discriminant (Type_Id)))
623 then
624 declare
625 Constr : constant List_Id := New_List;
626 Loc : constant Source_Ptr := Sloc (E);
627 Discr : Entity_Id := First_Discriminant (Type_Id);
629 begin
630 if Present (Discriminant_Default_Value (Discr)) then
631 while Present (Discr) loop
632 Append (Discriminant_Default_Value (Discr), Constr);
633 Next_Discriminant (Discr);
634 end loop;
636 Rewrite (E,
637 Make_Subtype_Indication (Loc,
638 Subtype_Mark => New_Occurrence_Of (Type_Id, Loc),
639 Constraint =>
640 Make_Index_Or_Discriminant_Constraint (Loc,
641 Constraints => Constr)));
642 end if;
643 end;
644 end if;
645 end if;
647 if Nkind (E) = N_Subtype_Indication then
649 -- A constraint is only allowed for a composite type in Ada
650 -- 95. In Ada 83, a constraint is also allowed for an
651 -- access-to-composite type, but the constraint is ignored.
653 Find_Type (Subtype_Mark (E));
654 Base_Typ := Entity (Subtype_Mark (E));
656 if Is_Elementary_Type (Base_Typ) then
657 if not (Ada_Version = Ada_83
658 and then Is_Access_Type (Base_Typ))
659 then
660 Error_Msg_N ("constraint not allowed here", E);
662 if Nkind (Constraint (E)) =
663 N_Index_Or_Discriminant_Constraint
664 then
665 Error_Msg_N -- CODEFIX
666 ("\if qualified expression was meant, " &
667 "use apostrophe", Constraint (E));
668 end if;
669 end if;
671 -- Get rid of the bogus constraint:
673 Rewrite (E, New_Copy_Tree (Subtype_Mark (E)));
674 Analyze_Allocator (N);
675 return;
676 end if;
678 if Expander_Active then
679 Def_Id := Make_Temporary (Loc, 'S');
681 Insert_Action (E,
682 Make_Subtype_Declaration (Loc,
683 Defining_Identifier => Def_Id,
684 Subtype_Indication => Relocate_Node (E)));
686 if Sav_Errs /= Serious_Errors_Detected
687 and then Nkind (Constraint (E)) =
688 N_Index_Or_Discriminant_Constraint
689 then
690 Error_Msg_N -- CODEFIX
691 ("if qualified expression was meant, "
692 & "use apostrophe!", Constraint (E));
693 end if;
695 E := New_Occurrence_Of (Def_Id, Loc);
696 Rewrite (Expression (N), E);
697 end if;
698 end if;
700 Type_Id := Process_Subtype (E, N);
701 Acc_Type := Create_Itype (E_Allocator_Type, N);
702 Set_Etype (Acc_Type, Acc_Type);
703 Set_Directly_Designated_Type (Acc_Type, Type_Id);
704 Check_Fully_Declared (Type_Id, N);
706 -- Ada 2005 (AI-231): If the designated type is itself an access
707 -- type that excludes null, its default initialization will
708 -- be a null object, and we can insert an unconditional raise
709 -- before the allocator.
711 -- Ada 2012 (AI-104): A not null indication here is altogether
712 -- illegal.
714 if Can_Never_Be_Null (Type_Id) then
715 declare
716 Not_Null_Check : constant Node_Id :=
717 Make_Raise_Constraint_Error (Sloc (E),
718 Reason => CE_Null_Not_Allowed);
720 begin
721 if Expander_Active then
722 Insert_Action (N, Not_Null_Check);
723 Analyze (Not_Null_Check);
725 elsif Warn_On_Ada_2012_Compatibility then
726 Error_Msg_N
727 ("null value not allowed here in Ada 2012?y?", E);
728 end if;
729 end;
730 end if;
732 -- Check for missing initialization. Skip this check if we already
733 -- had errors on analyzing the allocator, since in that case these
734 -- are probably cascaded errors.
736 if not Is_Definite_Subtype (Type_Id)
737 and then Serious_Errors_Detected = Sav_Errs
738 then
739 -- The build-in-place machinery may produce an allocator when
740 -- the designated type is indefinite but the underlying type is
741 -- not. In this case the unknown discriminants are meaningless
742 -- and should not trigger error messages. Check the parent node
743 -- because the allocator is marked as coming from source.
745 if Present (Underlying_Type (Type_Id))
746 and then Is_Definite_Subtype (Underlying_Type (Type_Id))
747 and then not Comes_From_Source (Parent (N))
748 then
749 null;
751 -- An unusual case arises when the parent of a derived type is
752 -- a limited record extension with unknown discriminants, and
753 -- its full view has no discriminants.
755 -- A more general fix might be to create the proper underlying
756 -- type for such a derived type, but it is a record type with
757 -- no private attributes, so this required extending the
758 -- meaning of this attribute. ???
760 elsif Ekind (Etype (Type_Id)) = E_Record_Type_With_Private
761 and then Present (Underlying_Type (Etype (Type_Id)))
762 and then
763 not Has_Discriminants (Underlying_Type (Etype (Type_Id)))
764 and then not Comes_From_Source (Parent (N))
765 then
766 null;
768 elsif Is_Class_Wide_Type (Type_Id) then
769 Error_Msg_N
770 ("initialization required in class-wide allocation", N);
772 else
773 if Ada_Version < Ada_2005
774 and then Is_Limited_Type (Type_Id)
775 then
776 Error_Msg_N ("unconstrained allocation not allowed", N);
778 if Is_Array_Type (Type_Id) then
779 Error_Msg_N
780 ("\constraint with array bounds required", N);
782 elsif Has_Unknown_Discriminants (Type_Id) then
783 null;
785 else pragma Assert (Has_Discriminants (Type_Id));
786 Error_Msg_N
787 ("\constraint with discriminant values required", N);
788 end if;
790 -- Limited Ada 2005 and general nonlimited case
792 else
793 Error_Msg_N
794 ("uninitialized unconstrained allocation not "
795 & "allowed", N);
797 if Is_Array_Type (Type_Id) then
798 Error_Msg_N
799 ("\qualified expression or constraint with "
800 & "array bounds required", N);
802 elsif Has_Unknown_Discriminants (Type_Id) then
803 Error_Msg_N ("\qualified expression required", N);
805 else pragma Assert (Has_Discriminants (Type_Id));
806 Error_Msg_N
807 ("\qualified expression or constraint with "
808 & "discriminant values required", N);
809 end if;
810 end if;
811 end if;
812 end if;
813 end;
814 end if;
816 if Is_Abstract_Type (Type_Id) then
817 Error_Msg_N ("cannot allocate abstract object", E);
818 end if;
820 if Has_Task (Designated_Type (Acc_Type)) then
821 Check_Restriction (No_Tasking, N);
822 Check_Restriction (Max_Tasks, N);
823 Check_Restriction (No_Task_Allocators, N);
824 end if;
826 -- Check restriction against dynamically allocated protected objects
828 if Has_Protected (Designated_Type (Acc_Type)) then
829 Check_Restriction (No_Protected_Type_Allocators, N);
830 end if;
832 -- AI05-0013-1: No_Nested_Finalization forbids allocators if the access
833 -- type is nested, and the designated type needs finalization. The rule
834 -- is conservative in that class-wide types need finalization.
836 if Needs_Finalization (Designated_Type (Acc_Type))
837 and then not Is_Library_Level_Entity (Acc_Type)
838 then
839 Check_Restriction (No_Nested_Finalization, N);
840 end if;
842 -- Check that an allocator of a nested access type doesn't create a
843 -- protected object when restriction No_Local_Protected_Objects applies.
845 if Has_Protected (Designated_Type (Acc_Type))
846 and then not Is_Library_Level_Entity (Acc_Type)
847 then
848 Check_Restriction (No_Local_Protected_Objects, N);
849 end if;
851 -- Likewise for No_Local_Timing_Events
853 if Has_Timing_Event (Designated_Type (Acc_Type))
854 and then not Is_Library_Level_Entity (Acc_Type)
855 then
856 Check_Restriction (No_Local_Timing_Events, N);
857 end if;
859 -- If the No_Streams restriction is set, check that the type of the
860 -- object is not, and does not contain, any subtype derived from
861 -- Ada.Streams.Root_Stream_Type. Note that we guard the call to
862 -- Has_Stream just for efficiency reasons. There is no point in
863 -- spending time on a Has_Stream check if the restriction is not set.
865 if Restriction_Check_Required (No_Streams) then
866 if Has_Stream (Designated_Type (Acc_Type)) then
867 Check_Restriction (No_Streams, N);
868 end if;
869 end if;
871 Set_Etype (N, Acc_Type);
873 if not Is_Library_Level_Entity (Acc_Type) then
874 Check_Restriction (No_Local_Allocators, N);
875 end if;
877 if Serious_Errors_Detected > Sav_Errs then
878 Set_Error_Posted (N);
879 Set_Etype (N, Any_Type);
880 end if;
881 end Analyze_Allocator;
883 ---------------------------
884 -- Analyze_Arithmetic_Op --
885 ---------------------------
887 procedure Analyze_Arithmetic_Op (N : Node_Id) is
888 L : constant Node_Id := Left_Opnd (N);
889 R : constant Node_Id := Right_Opnd (N);
890 Op_Id : Entity_Id;
892 begin
893 Candidate_Type := Empty;
894 Analyze_Expression (L);
895 Analyze_Expression (R);
897 -- If the entity is already set, the node is the instantiation of a
898 -- generic node with a non-local reference, or was manufactured by a
899 -- call to Make_Op_xxx. In either case the entity is known to be valid,
900 -- and we do not need to collect interpretations, instead we just get
901 -- the single possible interpretation.
903 Op_Id := Entity (N);
905 if Present (Op_Id) then
906 if Ekind (Op_Id) = E_Operator then
908 if Nkind_In (N, N_Op_Divide, N_Op_Mod, N_Op_Multiply, N_Op_Rem)
909 and then Treat_Fixed_As_Integer (N)
910 then
911 null;
912 else
913 Set_Etype (N, Any_Type);
914 Find_Arithmetic_Types (L, R, Op_Id, N);
915 end if;
917 else
918 Set_Etype (N, Any_Type);
919 Add_One_Interp (N, Op_Id, Etype (Op_Id));
920 end if;
922 -- Entity is not already set, so we do need to collect interpretations
924 else
925 Set_Etype (N, Any_Type);
927 Op_Id := Get_Name_Entity_Id (Chars (N));
928 while Present (Op_Id) loop
929 if Ekind (Op_Id) = E_Operator
930 and then Present (Next_Entity (First_Entity (Op_Id)))
931 then
932 Find_Arithmetic_Types (L, R, Op_Id, N);
934 -- The following may seem superfluous, because an operator cannot
935 -- be generic, but this ignores the cleverness of the author of
936 -- ACVC bc1013a.
938 elsif Is_Overloadable (Op_Id) then
939 Analyze_User_Defined_Binary_Op (N, Op_Id);
940 end if;
942 Op_Id := Homonym (Op_Id);
943 end loop;
944 end if;
946 Operator_Check (N);
947 Check_Function_Writable_Actuals (N);
948 end Analyze_Arithmetic_Op;
950 ------------------
951 -- Analyze_Call --
952 ------------------
954 -- Function, procedure, and entry calls are checked here. The Name in
955 -- the call may be overloaded. The actuals have been analyzed and may
956 -- themselves be overloaded. On exit from this procedure, the node N
957 -- may have zero, one or more interpretations. In the first case an
958 -- error message is produced. In the last case, the node is flagged
959 -- as overloaded and the interpretations are collected in All_Interp.
961 -- If the name is an Access_To_Subprogram, it cannot be overloaded, but
962 -- the type-checking is similar to that of other calls.
964 procedure Analyze_Call (N : Node_Id) is
965 Actuals : constant List_Id := Parameter_Associations (N);
966 Loc : constant Source_Ptr := Sloc (N);
967 Nam : Node_Id;
968 X : Interp_Index;
969 It : Interp;
970 Nam_Ent : Entity_Id;
971 Success : Boolean := False;
973 Deref : Boolean := False;
974 -- Flag indicates whether an interpretation of the prefix is a
975 -- parameterless call that returns an access_to_subprogram.
977 procedure Check_Mixed_Parameter_And_Named_Associations;
978 -- Check that parameter and named associations are not mixed. This is
979 -- a restriction in SPARK mode.
981 procedure Check_Writable_Actuals (N : Node_Id);
982 -- If the call has out or in-out parameters then mark its outermost
983 -- enclosing construct as a node on which the writable actuals check
984 -- must be performed.
986 function Name_Denotes_Function return Boolean;
987 -- If the type of the name is an access to subprogram, this may be the
988 -- type of a name, or the return type of the function being called. If
989 -- the name is not an entity then it can denote a protected function.
990 -- Until we distinguish Etype from Return_Type, we must use this routine
991 -- to resolve the meaning of the name in the call.
993 procedure No_Interpretation;
994 -- Output error message when no valid interpretation exists
996 --------------------------------------------------
997 -- Check_Mixed_Parameter_And_Named_Associations --
998 --------------------------------------------------
1000 procedure Check_Mixed_Parameter_And_Named_Associations is
1001 Actual : Node_Id;
1002 Named_Seen : Boolean;
1004 begin
1005 Named_Seen := False;
1007 Actual := First (Actuals);
1008 while Present (Actual) loop
1009 case Nkind (Actual) is
1010 when N_Parameter_Association =>
1011 if Named_Seen then
1012 Check_SPARK_05_Restriction
1013 ("named association cannot follow positional one",
1014 Actual);
1015 exit;
1016 end if;
1018 when others =>
1019 Named_Seen := True;
1020 end case;
1022 Next (Actual);
1023 end loop;
1024 end Check_Mixed_Parameter_And_Named_Associations;
1026 ----------------------------
1027 -- Check_Writable_Actuals --
1028 ----------------------------
1030 -- The identification of conflicts in calls to functions with writable
1031 -- actuals is performed in the analysis phase of the front end to ensure
1032 -- that it reports exactly the same errors compiling with and without
1033 -- expansion enabled. It is performed in two stages:
1035 -- 1) When a call to a function with out-mode parameters is found,
1036 -- we climb to the outermost enclosing construct that can be
1037 -- evaluated in arbitrary order and we mark it with the flag
1038 -- Check_Actuals.
1040 -- 2) When the analysis of the marked node is complete, we traverse
1041 -- its decorated subtree searching for conflicts (see function
1042 -- Sem_Util.Check_Function_Writable_Actuals).
1044 -- The unique exception to this general rule is for aggregates, since
1045 -- their analysis is performed by the front end in the resolution
1046 -- phase. For aggregates we do not climb to their enclosing construct:
1047 -- we restrict the analysis to the subexpressions initializing the
1048 -- aggregate components.
1050 -- This implies that the analysis of expressions containing aggregates
1051 -- is not complete, since there may be conflicts on writable actuals
1052 -- involving subexpressions of the enclosing logical or arithmetic
1053 -- expressions. However, we cannot wait and perform the analysis when
1054 -- the whole subtree is resolved, since the subtrees may be transformed,
1055 -- thus adding extra complexity and computation cost to identify and
1056 -- report exactly the same errors compiling with and without expansion
1057 -- enabled.
1059 procedure Check_Writable_Actuals (N : Node_Id) is
1060 begin
1061 if Comes_From_Source (N)
1062 and then Present (Get_Subprogram_Entity (N))
1063 and then Has_Out_Or_In_Out_Parameter (Get_Subprogram_Entity (N))
1064 then
1065 -- For procedures and entries there is no need to climb since
1066 -- we only need to check if the actuals of this call invoke
1067 -- functions whose out-mode parameters overlap.
1069 if Nkind (N) /= N_Function_Call then
1070 Set_Check_Actuals (N);
1072 -- For calls to functions we climb to the outermost enclosing
1073 -- construct where the out-mode actuals of this function may
1074 -- introduce conflicts.
1076 else
1077 declare
1078 Outermost : Node_Id := Empty; -- init to avoid warning
1079 P : Node_Id := N;
1081 begin
1082 while Present (P) loop
1083 -- For object declarations we can climb to the node from
1084 -- its object definition branch or from its initializing
1085 -- expression. We prefer to mark the child node as the
1086 -- outermost construct to avoid adding further complexity
1087 -- to the routine that will later take care of
1088 -- performing the writable actuals check.
1090 if Has_Arbitrary_Evaluation_Order (Nkind (P))
1091 and then not Nkind_In (P, N_Assignment_Statement,
1092 N_Object_Declaration)
1093 then
1094 Outermost := P;
1095 end if;
1097 -- Avoid climbing more than needed
1099 exit when Stop_Subtree_Climbing (Nkind (P))
1100 or else (Nkind (P) = N_Range
1101 and then not
1102 Nkind_In (Parent (P), N_In, N_Not_In));
1104 P := Parent (P);
1105 end loop;
1107 Set_Check_Actuals (Outermost);
1108 end;
1109 end if;
1110 end if;
1111 end Check_Writable_Actuals;
1113 ---------------------------
1114 -- Name_Denotes_Function --
1115 ---------------------------
1117 function Name_Denotes_Function return Boolean is
1118 begin
1119 if Is_Entity_Name (Nam) then
1120 return Ekind (Entity (Nam)) = E_Function;
1121 elsif Nkind (Nam) = N_Selected_Component then
1122 return Ekind (Entity (Selector_Name (Nam))) = E_Function;
1123 else
1124 return False;
1125 end if;
1126 end Name_Denotes_Function;
1128 -----------------------
1129 -- No_Interpretation --
1130 -----------------------
1132 procedure No_Interpretation is
1133 L : constant Boolean := Is_List_Member (N);
1134 K : constant Node_Kind := Nkind (Parent (N));
1136 begin
1137 -- If the node is in a list whose parent is not an expression then it
1138 -- must be an attempted procedure call.
1140 if L and then K not in N_Subexpr then
1141 if Ekind (Entity (Nam)) = E_Generic_Procedure then
1142 Error_Msg_NE
1143 ("must instantiate generic procedure& before call",
1144 Nam, Entity (Nam));
1145 else
1146 Error_Msg_N ("procedure or entry name expected", Nam);
1147 end if;
1149 -- Check for tasking cases where only an entry call will do
1151 elsif not L
1152 and then Nkind_In (K, N_Entry_Call_Alternative,
1153 N_Triggering_Alternative)
1154 then
1155 Error_Msg_N ("entry name expected", Nam);
1157 -- Otherwise give general error message
1159 else
1160 Error_Msg_N ("invalid prefix in call", Nam);
1161 end if;
1162 end No_Interpretation;
1164 -- Start of processing for Analyze_Call
1166 begin
1167 if Restriction_Check_Required (SPARK_05) then
1168 Check_Mixed_Parameter_And_Named_Associations;
1169 end if;
1171 -- Initialize the type of the result of the call to the error type,
1172 -- which will be reset if the type is successfully resolved.
1174 Set_Etype (N, Any_Type);
1176 Nam := Name (N);
1178 if not Is_Overloaded (Nam) then
1180 -- Only one interpretation to check
1182 if Ekind (Etype (Nam)) = E_Subprogram_Type then
1183 Nam_Ent := Etype (Nam);
1185 -- If the prefix is an access_to_subprogram, this may be an indirect
1186 -- call. This is the case if the name in the call is not an entity
1187 -- name, or if it is a function name in the context of a procedure
1188 -- call. In this latter case, we have a call to a parameterless
1189 -- function that returns a pointer_to_procedure which is the entity
1190 -- being called. Finally, F (X) may be a call to a parameterless
1191 -- function that returns a pointer to a function with parameters.
1192 -- Note that if F returns an access-to-subprogram whose designated
1193 -- type is an array, F (X) cannot be interpreted as an indirect call
1194 -- through the result of the call to F.
1196 elsif Is_Access_Type (Etype (Nam))
1197 and then Ekind (Designated_Type (Etype (Nam))) = E_Subprogram_Type
1198 and then
1199 (not Name_Denotes_Function
1200 or else Nkind (N) = N_Procedure_Call_Statement
1201 or else
1202 (Nkind (Parent (N)) /= N_Explicit_Dereference
1203 and then Is_Entity_Name (Nam)
1204 and then No (First_Formal (Entity (Nam)))
1205 and then not
1206 Is_Array_Type (Etype (Designated_Type (Etype (Nam))))
1207 and then Present (Actuals)))
1208 then
1209 Nam_Ent := Designated_Type (Etype (Nam));
1210 Insert_Explicit_Dereference (Nam);
1212 -- Selected component case. Simple entry or protected operation,
1213 -- where the entry name is given by the selector name.
1215 elsif Nkind (Nam) = N_Selected_Component then
1216 Nam_Ent := Entity (Selector_Name (Nam));
1218 if not Ekind_In (Nam_Ent, E_Entry,
1219 E_Entry_Family,
1220 E_Function,
1221 E_Procedure)
1222 then
1223 Error_Msg_N ("name in call is not a callable entity", Nam);
1224 Set_Etype (N, Any_Type);
1225 return;
1226 end if;
1228 -- If the name is an Indexed component, it can be a call to a member
1229 -- of an entry family. The prefix must be a selected component whose
1230 -- selector is the entry. Analyze_Procedure_Call normalizes several
1231 -- kinds of call into this form.
1233 elsif Nkind (Nam) = N_Indexed_Component then
1234 if Nkind (Prefix (Nam)) = N_Selected_Component then
1235 Nam_Ent := Entity (Selector_Name (Prefix (Nam)));
1236 else
1237 Error_Msg_N ("name in call is not a callable entity", Nam);
1238 Set_Etype (N, Any_Type);
1239 return;
1240 end if;
1242 elsif not Is_Entity_Name (Nam) then
1243 Error_Msg_N ("name in call is not a callable entity", Nam);
1244 Set_Etype (N, Any_Type);
1245 return;
1247 else
1248 Nam_Ent := Entity (Nam);
1250 -- If not overloadable, this may be a generalized indexing
1251 -- operation with named associations. Rewrite again as an
1252 -- indexed component and analyze as container indexing.
1254 if not Is_Overloadable (Nam_Ent) then
1255 if Present
1256 (Find_Value_Of_Aspect
1257 (Etype (Nam_Ent), Aspect_Constant_Indexing))
1258 then
1259 Replace (N,
1260 Make_Indexed_Component (Sloc (N),
1261 Prefix => Nam,
1262 Expressions => Parameter_Associations (N)));
1264 if Try_Container_Indexing (N, Nam, Expressions (N)) then
1265 return;
1266 else
1267 No_Interpretation;
1268 end if;
1270 else
1271 No_Interpretation;
1272 end if;
1274 return;
1275 end if;
1276 end if;
1278 -- Operations generated for RACW stub types are called only through
1279 -- dispatching, and can never be the static interpretation of a call.
1281 if Is_RACW_Stub_Type_Operation (Nam_Ent) then
1282 No_Interpretation;
1283 return;
1284 end if;
1286 Analyze_One_Call (N, Nam_Ent, True, Success);
1288 -- If this is an indirect call, the return type of the access_to
1289 -- subprogram may be an incomplete type. At the point of the call,
1290 -- use the full type if available, and at the same time update the
1291 -- return type of the access_to_subprogram.
1293 if Success
1294 and then Nkind (Nam) = N_Explicit_Dereference
1295 and then Ekind (Etype (N)) = E_Incomplete_Type
1296 and then Present (Full_View (Etype (N)))
1297 then
1298 Set_Etype (N, Full_View (Etype (N)));
1299 Set_Etype (Nam_Ent, Etype (N));
1300 end if;
1302 -- Overloaded call
1304 else
1305 -- An overloaded selected component must denote overloaded operations
1306 -- of a concurrent type. The interpretations are attached to the
1307 -- simple name of those operations.
1309 if Nkind (Nam) = N_Selected_Component then
1310 Nam := Selector_Name (Nam);
1311 end if;
1313 Get_First_Interp (Nam, X, It);
1314 while Present (It.Nam) loop
1315 Nam_Ent := It.Nam;
1316 Deref := False;
1318 -- Name may be call that returns an access to subprogram, or more
1319 -- generally an overloaded expression one of whose interpretations
1320 -- yields an access to subprogram. If the name is an entity, we do
1321 -- not dereference, because the node is a call that returns the
1322 -- access type: note difference between f(x), where the call may
1323 -- return an access subprogram type, and f(x)(y), where the type
1324 -- returned by the call to f is implicitly dereferenced to analyze
1325 -- the outer call.
1327 if Is_Access_Type (Nam_Ent) then
1328 Nam_Ent := Designated_Type (Nam_Ent);
1330 elsif Is_Access_Type (Etype (Nam_Ent))
1331 and then
1332 (not Is_Entity_Name (Nam)
1333 or else Nkind (N) = N_Procedure_Call_Statement)
1334 and then Ekind (Designated_Type (Etype (Nam_Ent)))
1335 = E_Subprogram_Type
1336 then
1337 Nam_Ent := Designated_Type (Etype (Nam_Ent));
1339 if Is_Entity_Name (Nam) then
1340 Deref := True;
1341 end if;
1342 end if;
1344 -- If the call has been rewritten from a prefixed call, the first
1345 -- parameter has been analyzed, but may need a subsequent
1346 -- dereference, so skip its analysis now.
1348 if N /= Original_Node (N)
1349 and then Nkind (Original_Node (N)) = Nkind (N)
1350 and then Nkind (Name (N)) /= Nkind (Name (Original_Node (N)))
1351 and then Present (Parameter_Associations (N))
1352 and then Present (Etype (First (Parameter_Associations (N))))
1353 then
1354 Analyze_One_Call
1355 (N, Nam_Ent, False, Success, Skip_First => True);
1356 else
1357 Analyze_One_Call (N, Nam_Ent, False, Success);
1358 end if;
1360 -- If the interpretation succeeds, mark the proper type of the
1361 -- prefix (any valid candidate will do). If not, remove the
1362 -- candidate interpretation. If this is a parameterless call
1363 -- on an anonymous access to subprogram, X is a variable with
1364 -- an access discriminant D, the entity in the interpretation is
1365 -- D, so rewrite X as X.D.all.
1367 if Success then
1368 if Deref
1369 and then Nkind (Parent (N)) /= N_Explicit_Dereference
1370 then
1371 if Ekind (It.Nam) = E_Discriminant
1372 and then Has_Implicit_Dereference (It.Nam)
1373 then
1374 Rewrite (Name (N),
1375 Make_Explicit_Dereference (Loc,
1376 Prefix =>
1377 Make_Selected_Component (Loc,
1378 Prefix =>
1379 New_Occurrence_Of (Entity (Nam), Loc),
1380 Selector_Name =>
1381 New_Occurrence_Of (It.Nam, Loc))));
1383 Analyze (N);
1384 return;
1386 else
1387 Set_Entity (Nam, It.Nam);
1388 Insert_Explicit_Dereference (Nam);
1389 Set_Etype (Nam, Nam_Ent);
1390 end if;
1392 else
1393 Set_Etype (Nam, It.Typ);
1394 end if;
1396 elsif Nkind_In (Name (N), N_Function_Call, N_Selected_Component)
1397 then
1398 Remove_Interp (X);
1399 end if;
1401 Get_Next_Interp (X, It);
1402 end loop;
1404 -- If the name is the result of a function call, it can only be a
1405 -- call to a function returning an access to subprogram. Insert
1406 -- explicit dereference.
1408 if Nkind (Nam) = N_Function_Call then
1409 Insert_Explicit_Dereference (Nam);
1410 end if;
1412 if Etype (N) = Any_Type then
1414 -- None of the interpretations is compatible with the actuals
1416 Diagnose_Call (N, Nam);
1418 -- Special checks for uninstantiated put routines
1420 if Nkind (N) = N_Procedure_Call_Statement
1421 and then Is_Entity_Name (Nam)
1422 and then Chars (Nam) = Name_Put
1423 and then List_Length (Actuals) = 1
1424 then
1425 declare
1426 Arg : constant Node_Id := First (Actuals);
1427 Typ : Entity_Id;
1429 begin
1430 if Nkind (Arg) = N_Parameter_Association then
1431 Typ := Etype (Explicit_Actual_Parameter (Arg));
1432 else
1433 Typ := Etype (Arg);
1434 end if;
1436 if Is_Signed_Integer_Type (Typ) then
1437 Error_Msg_N
1438 ("possible missing instantiation of "
1439 & "'Text_'I'O.'Integer_'I'O!", Nam);
1441 elsif Is_Modular_Integer_Type (Typ) then
1442 Error_Msg_N
1443 ("possible missing instantiation of "
1444 & "'Text_'I'O.'Modular_'I'O!", Nam);
1446 elsif Is_Floating_Point_Type (Typ) then
1447 Error_Msg_N
1448 ("possible missing instantiation of "
1449 & "'Text_'I'O.'Float_'I'O!", Nam);
1451 elsif Is_Ordinary_Fixed_Point_Type (Typ) then
1452 Error_Msg_N
1453 ("possible missing instantiation of "
1454 & "'Text_'I'O.'Fixed_'I'O!", Nam);
1456 elsif Is_Decimal_Fixed_Point_Type (Typ) then
1457 Error_Msg_N
1458 ("possible missing instantiation of "
1459 & "'Text_'I'O.'Decimal_'I'O!", Nam);
1461 elsif Is_Enumeration_Type (Typ) then
1462 Error_Msg_N
1463 ("possible missing instantiation of "
1464 & "'Text_'I'O.'Enumeration_'I'O!", Nam);
1465 end if;
1466 end;
1467 end if;
1469 elsif not Is_Overloaded (N)
1470 and then Is_Entity_Name (Nam)
1471 then
1472 -- Resolution yields a single interpretation. Verify that the
1473 -- reference has capitalization consistent with the declaration.
1475 Set_Entity_With_Checks (Nam, Entity (Nam));
1476 Generate_Reference (Entity (Nam), Nam);
1478 Set_Etype (Nam, Etype (Entity (Nam)));
1479 else
1480 Remove_Abstract_Operations (N);
1481 end if;
1483 End_Interp_List;
1484 end if;
1486 if Ada_Version >= Ada_2012 then
1488 -- Check if the call contains a function with writable actuals
1490 Check_Writable_Actuals (N);
1492 -- If found and the outermost construct that can be evaluated in
1493 -- an arbitrary order is precisely this call, then check all its
1494 -- actuals.
1496 Check_Function_Writable_Actuals (N);
1498 -- The return type of the function may be incomplete. This can be
1499 -- the case if the type is a generic formal, or a limited view. It
1500 -- can also happen when the function declaration appears before the
1501 -- full view of the type (which is legal in Ada 2012) and the call
1502 -- appears in a different unit, in which case the incomplete view
1503 -- must be replaced with the full view (or the nonlimited view)
1504 -- to prevent subsequent type errors. Note that the usual install/
1505 -- removal of limited_with clauses is not sufficient to handle this
1506 -- case, because the limited view may have been captured in another
1507 -- compilation unit that defines the current function.
1509 if Is_Incomplete_Type (Etype (N)) then
1510 if Present (Full_View (Etype (N))) then
1511 if Is_Entity_Name (Nam) then
1512 Set_Etype (Nam, Full_View (Etype (N)));
1513 Set_Etype (Entity (Nam), Full_View (Etype (N)));
1514 end if;
1516 Set_Etype (N, Full_View (Etype (N)));
1518 elsif From_Limited_With (Etype (N))
1519 and then Present (Non_Limited_View (Etype (N)))
1520 then
1521 Set_Etype (N, Non_Limited_View (Etype (N)));
1523 -- If there is no completion for the type, this may be because
1524 -- there is only a limited view of it and there is nothing in
1525 -- the context of the current unit that has required a regular
1526 -- compilation of the unit containing the type. We recognize
1527 -- this unusual case by the fact that that unit is not analyzed.
1528 -- Note that the call being analyzed is in a different unit from
1529 -- the function declaration, and nothing indicates that the type
1530 -- is a limited view.
1532 elsif Ekind (Scope (Etype (N))) = E_Package
1533 and then Present (Limited_View (Scope (Etype (N))))
1534 and then not Analyzed (Unit_Declaration_Node (Scope (Etype (N))))
1535 then
1536 Error_Msg_NE
1537 ("cannot call function that returns limited view of}",
1538 N, Etype (N));
1540 Error_Msg_NE
1541 ("\there must be a regular with_clause for package & in the "
1542 & "current unit, or in some unit in its context",
1543 N, Scope (Etype (N)));
1545 Set_Etype (N, Any_Type);
1546 end if;
1547 end if;
1548 end if;
1549 end Analyze_Call;
1551 -----------------------------
1552 -- Analyze_Case_Expression --
1553 -----------------------------
1555 procedure Analyze_Case_Expression (N : Node_Id) is
1556 procedure Non_Static_Choice_Error (Choice : Node_Id);
1557 -- Error routine invoked by the generic instantiation below when
1558 -- the case expression has a non static choice.
1560 package Case_Choices_Analysis is new
1561 Generic_Analyze_Choices
1562 (Process_Associated_Node => No_OP);
1563 use Case_Choices_Analysis;
1565 package Case_Choices_Checking is new
1566 Generic_Check_Choices
1567 (Process_Empty_Choice => No_OP,
1568 Process_Non_Static_Choice => Non_Static_Choice_Error,
1569 Process_Associated_Node => No_OP);
1570 use Case_Choices_Checking;
1572 -----------------------------
1573 -- Non_Static_Choice_Error --
1574 -----------------------------
1576 procedure Non_Static_Choice_Error (Choice : Node_Id) is
1577 begin
1578 Flag_Non_Static_Expr
1579 ("choice given in case expression is not static!", Choice);
1580 end Non_Static_Choice_Error;
1582 -- Local variables
1584 Expr : constant Node_Id := Expression (N);
1585 Alt : Node_Id;
1586 Exp_Type : Entity_Id;
1587 Exp_Btype : Entity_Id;
1589 FirstX : Node_Id := Empty;
1590 -- First expression in the case for which there is some type information
1591 -- available, i.e. it is not Any_Type, which can happen because of some
1592 -- error, or from the use of e.g. raise Constraint_Error.
1594 Others_Present : Boolean;
1595 -- Indicates if Others was present
1597 Wrong_Alt : Node_Id := Empty;
1598 -- For error reporting
1600 -- Start of processing for Analyze_Case_Expression
1602 begin
1603 if Comes_From_Source (N) then
1604 Check_Compiler_Unit ("case expression", N);
1605 end if;
1607 Analyze_And_Resolve (Expr, Any_Discrete);
1608 Check_Unset_Reference (Expr);
1609 Exp_Type := Etype (Expr);
1610 Exp_Btype := Base_Type (Exp_Type);
1612 Alt := First (Alternatives (N));
1613 while Present (Alt) loop
1614 if Error_Posted (Expression (Alt)) then
1615 return;
1616 end if;
1618 Analyze (Expression (Alt));
1620 if No (FirstX) and then Etype (Expression (Alt)) /= Any_Type then
1621 FirstX := Expression (Alt);
1622 end if;
1624 Next (Alt);
1625 end loop;
1627 -- Get our initial type from the first expression for which we got some
1628 -- useful type information from the expression.
1630 if No (FirstX) then
1631 return;
1632 end if;
1634 if not Is_Overloaded (FirstX) then
1635 Set_Etype (N, Etype (FirstX));
1637 else
1638 declare
1639 I : Interp_Index;
1640 It : Interp;
1642 begin
1643 Set_Etype (N, Any_Type);
1645 Get_First_Interp (FirstX, I, It);
1646 while Present (It.Nam) loop
1648 -- For each interpretation of the first expression, we only
1649 -- add the interpretation if every other expression in the
1650 -- case expression alternatives has a compatible type.
1652 Alt := Next (First (Alternatives (N)));
1653 while Present (Alt) loop
1654 exit when not Has_Compatible_Type (Expression (Alt), It.Typ);
1655 Next (Alt);
1656 end loop;
1658 if No (Alt) then
1659 Add_One_Interp (N, It.Typ, It.Typ);
1660 else
1661 Wrong_Alt := Alt;
1662 end if;
1664 Get_Next_Interp (I, It);
1665 end loop;
1666 end;
1667 end if;
1669 Exp_Btype := Base_Type (Exp_Type);
1671 -- The expression must be of a discrete type which must be determinable
1672 -- independently of the context in which the expression occurs, but
1673 -- using the fact that the expression must be of a discrete type.
1674 -- Moreover, the type this expression must not be a character literal
1675 -- (which is always ambiguous).
1677 -- If error already reported by Resolve, nothing more to do
1679 if Exp_Btype = Any_Discrete or else Exp_Btype = Any_Type then
1680 return;
1682 -- Special casee message for character literal
1684 elsif Exp_Btype = Any_Character then
1685 Error_Msg_N
1686 ("character literal as case expression is ambiguous", Expr);
1687 return;
1688 end if;
1690 if Etype (N) = Any_Type and then Present (Wrong_Alt) then
1691 Error_Msg_N
1692 ("type incompatible with that of previous alternatives",
1693 Expression (Wrong_Alt));
1694 return;
1695 end if;
1697 -- If the case expression is a formal object of mode in out, then
1698 -- treat it as having a nonstatic subtype by forcing use of the base
1699 -- type (which has to get passed to Check_Case_Choices below). Also
1700 -- use base type when the case expression is parenthesized.
1702 if Paren_Count (Expr) > 0
1703 or else (Is_Entity_Name (Expr)
1704 and then Ekind (Entity (Expr)) = E_Generic_In_Out_Parameter)
1705 then
1706 Exp_Type := Exp_Btype;
1707 end if;
1709 -- The case expression alternatives cover the range of a static subtype
1710 -- subject to aspect Static_Predicate. Do not check the choices when the
1711 -- case expression has not been fully analyzed yet because this may lead
1712 -- to bogus errors.
1714 if Is_OK_Static_Subtype (Exp_Type)
1715 and then Has_Static_Predicate_Aspect (Exp_Type)
1716 and then In_Spec_Expression
1717 then
1718 null;
1720 -- Call Analyze_Choices and Check_Choices to do the rest of the work
1722 else
1723 Analyze_Choices (Alternatives (N), Exp_Type);
1724 Check_Choices (N, Alternatives (N), Exp_Type, Others_Present);
1726 if Exp_Type = Universal_Integer and then not Others_Present then
1727 Error_Msg_N
1728 ("case on universal integer requires OTHERS choice", Expr);
1729 end if;
1730 end if;
1731 end Analyze_Case_Expression;
1733 ---------------------------
1734 -- Analyze_Comparison_Op --
1735 ---------------------------
1737 procedure Analyze_Comparison_Op (N : Node_Id) is
1738 L : constant Node_Id := Left_Opnd (N);
1739 R : constant Node_Id := Right_Opnd (N);
1740 Op_Id : Entity_Id := Entity (N);
1742 begin
1743 Set_Etype (N, Any_Type);
1744 Candidate_Type := Empty;
1746 Analyze_Expression (L);
1747 Analyze_Expression (R);
1749 if Present (Op_Id) then
1750 if Ekind (Op_Id) = E_Operator then
1751 Find_Comparison_Types (L, R, Op_Id, N);
1752 else
1753 Add_One_Interp (N, Op_Id, Etype (Op_Id));
1754 end if;
1756 if Is_Overloaded (L) then
1757 Set_Etype (L, Intersect_Types (L, R));
1758 end if;
1760 else
1761 Op_Id := Get_Name_Entity_Id (Chars (N));
1762 while Present (Op_Id) loop
1763 if Ekind (Op_Id) = E_Operator then
1764 Find_Comparison_Types (L, R, Op_Id, N);
1765 else
1766 Analyze_User_Defined_Binary_Op (N, Op_Id);
1767 end if;
1769 Op_Id := Homonym (Op_Id);
1770 end loop;
1771 end if;
1773 Operator_Check (N);
1774 Check_Function_Writable_Actuals (N);
1775 end Analyze_Comparison_Op;
1777 ---------------------------
1778 -- Analyze_Concatenation --
1779 ---------------------------
1781 procedure Analyze_Concatenation (N : Node_Id) is
1783 -- We wish to avoid deep recursion, because concatenations are often
1784 -- deeply nested, as in A&B&...&Z. Therefore, we walk down the left
1785 -- operands nonrecursively until we find something that is not a
1786 -- concatenation (A in this case), or has already been analyzed. We
1787 -- analyze that, and then walk back up the tree following Parent
1788 -- pointers, calling Analyze_Concatenation_Rest to do the rest of the
1789 -- work at each level. The Parent pointers allow us to avoid recursion,
1790 -- and thus avoid running out of memory.
1792 NN : Node_Id := N;
1793 L : Node_Id;
1795 begin
1796 Candidate_Type := Empty;
1798 -- The following code is equivalent to:
1800 -- Set_Etype (N, Any_Type);
1801 -- Analyze_Expression (Left_Opnd (N));
1802 -- Analyze_Concatenation_Rest (N);
1804 -- where the Analyze_Expression call recurses back here if the left
1805 -- operand is a concatenation.
1807 -- Walk down left operands
1809 loop
1810 Set_Etype (NN, Any_Type);
1811 L := Left_Opnd (NN);
1812 exit when Nkind (L) /= N_Op_Concat or else Analyzed (L);
1813 NN := L;
1814 end loop;
1816 -- Now (given the above example) NN is A&B and L is A
1818 -- First analyze L ...
1820 Analyze_Expression (L);
1822 -- ... then walk NN back up until we reach N (where we started), calling
1823 -- Analyze_Concatenation_Rest along the way.
1825 loop
1826 Analyze_Concatenation_Rest (NN);
1827 exit when NN = N;
1828 NN := Parent (NN);
1829 end loop;
1830 end Analyze_Concatenation;
1832 --------------------------------
1833 -- Analyze_Concatenation_Rest --
1834 --------------------------------
1836 -- If the only one-dimensional array type in scope is String,
1837 -- this is the resulting type of the operation. Otherwise there
1838 -- will be a concatenation operation defined for each user-defined
1839 -- one-dimensional array.
1841 procedure Analyze_Concatenation_Rest (N : Node_Id) is
1842 L : constant Node_Id := Left_Opnd (N);
1843 R : constant Node_Id := Right_Opnd (N);
1844 Op_Id : Entity_Id := Entity (N);
1845 LT : Entity_Id;
1846 RT : Entity_Id;
1848 begin
1849 Analyze_Expression (R);
1851 -- If the entity is present, the node appears in an instance, and
1852 -- denotes a predefined concatenation operation. The resulting type is
1853 -- obtained from the arguments when possible. If the arguments are
1854 -- aggregates, the array type and the concatenation type must be
1855 -- visible.
1857 if Present (Op_Id) then
1858 if Ekind (Op_Id) = E_Operator then
1859 LT := Base_Type (Etype (L));
1860 RT := Base_Type (Etype (R));
1862 if Is_Array_Type (LT)
1863 and then (RT = LT or else RT = Base_Type (Component_Type (LT)))
1864 then
1865 Add_One_Interp (N, Op_Id, LT);
1867 elsif Is_Array_Type (RT)
1868 and then LT = Base_Type (Component_Type (RT))
1869 then
1870 Add_One_Interp (N, Op_Id, RT);
1872 -- If one operand is a string type or a user-defined array type,
1873 -- and the other is a literal, result is of the specific type.
1875 elsif
1876 (Root_Type (LT) = Standard_String
1877 or else Scope (LT) /= Standard_Standard)
1878 and then Etype (R) = Any_String
1879 then
1880 Add_One_Interp (N, Op_Id, LT);
1882 elsif
1883 (Root_Type (RT) = Standard_String
1884 or else Scope (RT) /= Standard_Standard)
1885 and then Etype (L) = Any_String
1886 then
1887 Add_One_Interp (N, Op_Id, RT);
1889 elsif not Is_Generic_Type (Etype (Op_Id)) then
1890 Add_One_Interp (N, Op_Id, Etype (Op_Id));
1892 else
1893 -- Type and its operations must be visible
1895 Set_Entity (N, Empty);
1896 Analyze_Concatenation (N);
1897 end if;
1899 else
1900 Add_One_Interp (N, Op_Id, Etype (Op_Id));
1901 end if;
1903 else
1904 Op_Id := Get_Name_Entity_Id (Name_Op_Concat);
1905 while Present (Op_Id) loop
1906 if Ekind (Op_Id) = E_Operator then
1908 -- Do not consider operators declared in dead code, they can
1909 -- not be part of the resolution.
1911 if Is_Eliminated (Op_Id) then
1912 null;
1913 else
1914 Find_Concatenation_Types (L, R, Op_Id, N);
1915 end if;
1917 else
1918 Analyze_User_Defined_Binary_Op (N, Op_Id);
1919 end if;
1921 Op_Id := Homonym (Op_Id);
1922 end loop;
1923 end if;
1925 Operator_Check (N);
1926 end Analyze_Concatenation_Rest;
1928 -------------------------
1929 -- Analyze_Equality_Op --
1930 -------------------------
1932 procedure Analyze_Equality_Op (N : Node_Id) is
1933 Loc : constant Source_Ptr := Sloc (N);
1934 L : constant Node_Id := Left_Opnd (N);
1935 R : constant Node_Id := Right_Opnd (N);
1936 Op_Id : Entity_Id;
1938 begin
1939 Set_Etype (N, Any_Type);
1940 Candidate_Type := Empty;
1942 Analyze_Expression (L);
1943 Analyze_Expression (R);
1945 -- If the entity is set, the node is a generic instance with a non-local
1946 -- reference to the predefined operator or to a user-defined function.
1947 -- It can also be an inequality that is expanded into the negation of a
1948 -- call to a user-defined equality operator.
1950 -- For the predefined case, the result is Boolean, regardless of the
1951 -- type of the operands. The operands may even be limited, if they are
1952 -- generic actuals. If they are overloaded, label the left argument with
1953 -- the common type that must be present, or with the type of the formal
1954 -- of the user-defined function.
1956 if Present (Entity (N)) then
1957 Op_Id := Entity (N);
1959 if Ekind (Op_Id) = E_Operator then
1960 Add_One_Interp (N, Op_Id, Standard_Boolean);
1961 else
1962 Add_One_Interp (N, Op_Id, Etype (Op_Id));
1963 end if;
1965 if Is_Overloaded (L) then
1966 if Ekind (Op_Id) = E_Operator then
1967 Set_Etype (L, Intersect_Types (L, R));
1968 else
1969 Set_Etype (L, Etype (First_Formal (Op_Id)));
1970 end if;
1971 end if;
1973 else
1974 Op_Id := Get_Name_Entity_Id (Chars (N));
1975 while Present (Op_Id) loop
1976 if Ekind (Op_Id) = E_Operator then
1977 Find_Equality_Types (L, R, Op_Id, N);
1978 else
1979 Analyze_User_Defined_Binary_Op (N, Op_Id);
1980 end if;
1982 Op_Id := Homonym (Op_Id);
1983 end loop;
1984 end if;
1986 -- If there was no match, and the operator is inequality, this may be
1987 -- a case where inequality has not been made explicit, as for tagged
1988 -- types. Analyze the node as the negation of an equality operation.
1989 -- This cannot be done earlier, because before analysis we cannot rule
1990 -- out the presence of an explicit inequality.
1992 if Etype (N) = Any_Type
1993 and then Nkind (N) = N_Op_Ne
1994 then
1995 Op_Id := Get_Name_Entity_Id (Name_Op_Eq);
1996 while Present (Op_Id) loop
1997 if Ekind (Op_Id) = E_Operator then
1998 Find_Equality_Types (L, R, Op_Id, N);
1999 else
2000 Analyze_User_Defined_Binary_Op (N, Op_Id);
2001 end if;
2003 Op_Id := Homonym (Op_Id);
2004 end loop;
2006 if Etype (N) /= Any_Type then
2007 Op_Id := Entity (N);
2009 Rewrite (N,
2010 Make_Op_Not (Loc,
2011 Right_Opnd =>
2012 Make_Op_Eq (Loc,
2013 Left_Opnd => Left_Opnd (N),
2014 Right_Opnd => Right_Opnd (N))));
2016 Set_Entity (Right_Opnd (N), Op_Id);
2017 Analyze (N);
2018 end if;
2019 end if;
2021 Operator_Check (N);
2022 Check_Function_Writable_Actuals (N);
2023 end Analyze_Equality_Op;
2025 ----------------------------------
2026 -- Analyze_Explicit_Dereference --
2027 ----------------------------------
2029 procedure Analyze_Explicit_Dereference (N : Node_Id) is
2030 Loc : constant Source_Ptr := Sloc (N);
2031 P : constant Node_Id := Prefix (N);
2032 T : Entity_Id;
2033 I : Interp_Index;
2034 It : Interp;
2035 New_N : Node_Id;
2037 function Is_Function_Type return Boolean;
2038 -- Check whether node may be interpreted as an implicit function call
2040 ----------------------
2041 -- Is_Function_Type --
2042 ----------------------
2044 function Is_Function_Type return Boolean is
2045 I : Interp_Index;
2046 It : Interp;
2048 begin
2049 if not Is_Overloaded (N) then
2050 return Ekind (Base_Type (Etype (N))) = E_Subprogram_Type
2051 and then Etype (Base_Type (Etype (N))) /= Standard_Void_Type;
2053 else
2054 Get_First_Interp (N, I, It);
2055 while Present (It.Nam) loop
2056 if Ekind (Base_Type (It.Typ)) /= E_Subprogram_Type
2057 or else Etype (Base_Type (It.Typ)) = Standard_Void_Type
2058 then
2059 return False;
2060 end if;
2062 Get_Next_Interp (I, It);
2063 end loop;
2065 return True;
2066 end if;
2067 end Is_Function_Type;
2069 -- Start of processing for Analyze_Explicit_Dereference
2071 begin
2072 -- If source node, check SPARK restriction. We guard this with the
2073 -- source node check, because ???
2075 if Comes_From_Source (N) then
2076 Check_SPARK_05_Restriction ("explicit dereference is not allowed", N);
2077 end if;
2079 -- In formal verification mode, keep track of all reads and writes
2080 -- through explicit dereferences.
2082 if GNATprove_Mode then
2083 SPARK_Specific.Generate_Dereference (N);
2084 end if;
2086 Analyze (P);
2087 Set_Etype (N, Any_Type);
2089 -- Test for remote access to subprogram type, and if so return
2090 -- after rewriting the original tree.
2092 if Remote_AST_E_Dereference (P) then
2093 return;
2094 end if;
2096 -- Normal processing for other than remote access to subprogram type
2098 if not Is_Overloaded (P) then
2099 if Is_Access_Type (Etype (P)) then
2101 -- Set the Etype. We need to go through Is_For_Access_Subtypes to
2102 -- avoid other problems caused by the Private_Subtype and it is
2103 -- safe to go to the Base_Type because this is the same as
2104 -- converting the access value to its Base_Type.
2106 declare
2107 DT : Entity_Id := Designated_Type (Etype (P));
2109 begin
2110 if Ekind (DT) = E_Private_Subtype
2111 and then Is_For_Access_Subtype (DT)
2112 then
2113 DT := Base_Type (DT);
2114 end if;
2116 -- An explicit dereference is a legal occurrence of an
2117 -- incomplete type imported through a limited_with clause, if
2118 -- the full view is visible, or if we are within an instance
2119 -- body, where the enclosing body has a regular with_clause
2120 -- on the unit.
2122 if From_Limited_With (DT)
2123 and then not From_Limited_With (Scope (DT))
2124 and then
2125 (Is_Immediately_Visible (Scope (DT))
2126 or else
2127 (Is_Child_Unit (Scope (DT))
2128 and then Is_Visible_Lib_Unit (Scope (DT)))
2129 or else In_Instance_Body)
2130 then
2131 Set_Etype (N, Available_View (DT));
2133 else
2134 Set_Etype (N, DT);
2135 end if;
2136 end;
2138 elsif Etype (P) /= Any_Type then
2139 Error_Msg_N ("prefix of dereference must be an access type", N);
2140 return;
2141 end if;
2143 else
2144 Get_First_Interp (P, I, It);
2145 while Present (It.Nam) loop
2146 T := It.Typ;
2148 if Is_Access_Type (T) then
2149 Add_One_Interp (N, Designated_Type (T), Designated_Type (T));
2150 end if;
2152 Get_Next_Interp (I, It);
2153 end loop;
2155 -- Error if no interpretation of the prefix has an access type
2157 if Etype (N) = Any_Type then
2158 Error_Msg_N
2159 ("access type required in prefix of explicit dereference", P);
2160 Set_Etype (N, Any_Type);
2161 return;
2162 end if;
2163 end if;
2165 if Is_Function_Type
2166 and then Nkind (Parent (N)) /= N_Indexed_Component
2168 and then (Nkind (Parent (N)) /= N_Function_Call
2169 or else N /= Name (Parent (N)))
2171 and then (Nkind (Parent (N)) /= N_Procedure_Call_Statement
2172 or else N /= Name (Parent (N)))
2174 and then Nkind (Parent (N)) /= N_Subprogram_Renaming_Declaration
2175 and then (Nkind (Parent (N)) /= N_Attribute_Reference
2176 or else
2177 (Attribute_Name (Parent (N)) /= Name_Address
2178 and then
2179 Attribute_Name (Parent (N)) /= Name_Access))
2180 then
2181 -- Name is a function call with no actuals, in a context that
2182 -- requires deproceduring (including as an actual in an enclosing
2183 -- function or procedure call). There are some pathological cases
2184 -- where the prefix might include functions that return access to
2185 -- subprograms and others that return a regular type. Disambiguation
2186 -- of those has to take place in Resolve.
2188 New_N :=
2189 Make_Function_Call (Loc,
2190 Name => Make_Explicit_Dereference (Loc, P),
2191 Parameter_Associations => New_List);
2193 -- If the prefix is overloaded, remove operations that have formals,
2194 -- we know that this is a parameterless call.
2196 if Is_Overloaded (P) then
2197 Get_First_Interp (P, I, It);
2198 while Present (It.Nam) loop
2199 T := It.Typ;
2201 if No (First_Formal (Base_Type (Designated_Type (T)))) then
2202 Set_Etype (P, T);
2203 else
2204 Remove_Interp (I);
2205 end if;
2207 Get_Next_Interp (I, It);
2208 end loop;
2209 end if;
2211 Rewrite (N, New_N);
2212 Analyze (N);
2214 elsif not Is_Function_Type
2215 and then Is_Overloaded (N)
2216 then
2217 -- The prefix may include access to subprograms and other access
2218 -- types. If the context selects the interpretation that is a
2219 -- function call (not a procedure call) we cannot rewrite the node
2220 -- yet, but we include the result of the call interpretation.
2222 Get_First_Interp (N, I, It);
2223 while Present (It.Nam) loop
2224 if Ekind (Base_Type (It.Typ)) = E_Subprogram_Type
2225 and then Etype (Base_Type (It.Typ)) /= Standard_Void_Type
2226 and then Nkind (Parent (N)) /= N_Procedure_Call_Statement
2227 then
2228 Add_One_Interp (N, Etype (It.Typ), Etype (It.Typ));
2229 end if;
2231 Get_Next_Interp (I, It);
2232 end loop;
2233 end if;
2235 -- A value of remote access-to-class-wide must not be dereferenced
2236 -- (RM E.2.2(16)).
2238 Validate_Remote_Access_To_Class_Wide_Type (N);
2239 end Analyze_Explicit_Dereference;
2241 ------------------------
2242 -- Analyze_Expression --
2243 ------------------------
2245 procedure Analyze_Expression (N : Node_Id) is
2246 begin
2248 -- If the expression is an indexed component that will be rewritten
2249 -- as a container indexing, it has already been analyzed.
2251 if Nkind (N) = N_Indexed_Component
2252 and then Present (Generalized_Indexing (N))
2253 then
2254 null;
2256 else
2257 Analyze (N);
2258 Check_Parameterless_Call (N);
2259 end if;
2260 end Analyze_Expression;
2262 -------------------------------------
2263 -- Analyze_Expression_With_Actions --
2264 -------------------------------------
2266 procedure Analyze_Expression_With_Actions (N : Node_Id) is
2267 A : Node_Id;
2269 begin
2270 A := First (Actions (N));
2271 while Present (A) loop
2272 Analyze (A);
2273 Next (A);
2274 end loop;
2276 Analyze_Expression (Expression (N));
2277 Set_Etype (N, Etype (Expression (N)));
2278 end Analyze_Expression_With_Actions;
2280 ---------------------------
2281 -- Analyze_If_Expression --
2282 ---------------------------
2284 procedure Analyze_If_Expression (N : Node_Id) is
2285 Condition : constant Node_Id := First (Expressions (N));
2286 Then_Expr : Node_Id;
2287 Else_Expr : Node_Id;
2289 begin
2290 -- Defend against error of missing expressions from previous error
2292 if No (Condition) then
2293 Check_Error_Detected;
2294 return;
2295 end if;
2297 Then_Expr := Next (Condition);
2299 if No (Then_Expr) then
2300 Check_Error_Detected;
2301 return;
2302 end if;
2304 Else_Expr := Next (Then_Expr);
2306 if Comes_From_Source (N) then
2307 Check_SPARK_05_Restriction ("if expression is not allowed", N);
2308 end if;
2310 if Comes_From_Source (N) then
2311 Check_Compiler_Unit ("if expression", N);
2312 end if;
2314 -- Analyze and resolve the condition. We need to resolve this now so
2315 -- that it gets folded to True/False if possible, before we analyze
2316 -- the THEN/ELSE branches, because when analyzing these branches, we
2317 -- may call Is_Statically_Unevaluated, which expects the condition of
2318 -- an enclosing IF to have been analyze/resolved/evaluated.
2320 Analyze_Expression (Condition);
2321 Resolve (Condition, Any_Boolean);
2323 -- Analyze THEN expression and (if present) ELSE expression. For those
2324 -- we delay resolution in the normal manner, because of overloading etc.
2326 Analyze_Expression (Then_Expr);
2328 if Present (Else_Expr) then
2329 Analyze_Expression (Else_Expr);
2330 end if;
2332 -- If then expression not overloaded, then that decides the type
2334 if not Is_Overloaded (Then_Expr) then
2335 Set_Etype (N, Etype (Then_Expr));
2337 -- Case where then expression is overloaded
2339 else
2340 declare
2341 I : Interp_Index;
2342 It : Interp;
2344 begin
2345 Set_Etype (N, Any_Type);
2347 -- Loop through interpretations of Then_Expr
2349 Get_First_Interp (Then_Expr, I, It);
2350 while Present (It.Nam) loop
2352 -- Add possible interpretation of Then_Expr if no Else_Expr, or
2353 -- Else_Expr is present and has a compatible type.
2355 if No (Else_Expr)
2356 or else Has_Compatible_Type (Else_Expr, It.Typ)
2357 then
2358 Add_One_Interp (N, It.Typ, It.Typ);
2359 end if;
2361 Get_Next_Interp (I, It);
2362 end loop;
2364 -- If no valid interpretation has been found, then the type of the
2365 -- ELSE expression does not match any interpretation of the THEN
2366 -- expression.
2368 if Etype (N) = Any_Type then
2369 Error_Msg_N
2370 ("type incompatible with that of `THEN` expression",
2371 Else_Expr);
2372 return;
2373 end if;
2374 end;
2375 end if;
2376 end Analyze_If_Expression;
2378 ------------------------------------
2379 -- Analyze_Indexed_Component_Form --
2380 ------------------------------------
2382 procedure Analyze_Indexed_Component_Form (N : Node_Id) is
2383 P : constant Node_Id := Prefix (N);
2384 Exprs : constant List_Id := Expressions (N);
2385 Exp : Node_Id;
2386 P_T : Entity_Id;
2387 E : Node_Id;
2388 U_N : Entity_Id;
2390 procedure Process_Function_Call;
2391 -- Prefix in indexed component form is an overloadable entity, so the
2392 -- node is a function call. Reformat it as such.
2394 procedure Process_Indexed_Component;
2395 -- Prefix in indexed component form is actually an indexed component.
2396 -- This routine processes it, knowing that the prefix is already
2397 -- resolved.
2399 procedure Process_Indexed_Component_Or_Slice;
2400 -- An indexed component with a single index may designate a slice if
2401 -- the index is a subtype mark. This routine disambiguates these two
2402 -- cases by resolving the prefix to see if it is a subtype mark.
2404 procedure Process_Overloaded_Indexed_Component;
2405 -- If the prefix of an indexed component is overloaded, the proper
2406 -- interpretation is selected by the index types and the context.
2408 ---------------------------
2409 -- Process_Function_Call --
2410 ---------------------------
2412 procedure Process_Function_Call is
2413 Loc : constant Source_Ptr := Sloc (N);
2414 Actual : Node_Id;
2416 begin
2417 Change_Node (N, N_Function_Call);
2418 Set_Name (N, P);
2419 Set_Parameter_Associations (N, Exprs);
2421 -- Analyze actuals prior to analyzing the call itself
2423 Actual := First (Parameter_Associations (N));
2424 while Present (Actual) loop
2425 Analyze (Actual);
2426 Check_Parameterless_Call (Actual);
2428 -- Move to next actual. Note that we use Next, not Next_Actual
2429 -- here. The reason for this is a bit subtle. If a function call
2430 -- includes named associations, the parser recognizes the node
2431 -- as a call, and it is analyzed as such. If all associations are
2432 -- positional, the parser builds an indexed_component node, and
2433 -- it is only after analysis of the prefix that the construct
2434 -- is recognized as a call, in which case Process_Function_Call
2435 -- rewrites the node and analyzes the actuals. If the list of
2436 -- actuals is malformed, the parser may leave the node as an
2437 -- indexed component (despite the presence of named associations).
2438 -- The iterator Next_Actual is equivalent to Next if the list is
2439 -- positional, but follows the normalized chain of actuals when
2440 -- named associations are present. In this case normalization has
2441 -- not taken place, and actuals remain unanalyzed, which leads to
2442 -- subsequent crashes or loops if there is an attempt to continue
2443 -- analysis of the program.
2445 -- IF there is a single actual and it is a type name, the node
2446 -- can only be interpreted as a slice of a parameterless call.
2447 -- Rebuild the node as such and analyze.
2449 if No (Next (Actual))
2450 and then Is_Entity_Name (Actual)
2451 and then Is_Type (Entity (Actual))
2452 and then Is_Discrete_Type (Entity (Actual))
2453 then
2454 Replace (N,
2455 Make_Slice (Loc,
2456 Prefix => P,
2457 Discrete_Range =>
2458 New_Occurrence_Of (Entity (Actual), Loc)));
2459 Analyze (N);
2460 return;
2462 else
2463 Next (Actual);
2464 end if;
2465 end loop;
2467 Analyze_Call (N);
2468 end Process_Function_Call;
2470 -------------------------------
2471 -- Process_Indexed_Component --
2472 -------------------------------
2474 procedure Process_Indexed_Component is
2475 Exp : Node_Id;
2476 Array_Type : Entity_Id;
2477 Index : Node_Id;
2478 Pent : Entity_Id := Empty;
2480 begin
2481 Exp := First (Exprs);
2483 if Is_Overloaded (P) then
2484 Process_Overloaded_Indexed_Component;
2486 else
2487 Array_Type := Etype (P);
2489 if Is_Entity_Name (P) then
2490 Pent := Entity (P);
2491 elsif Nkind (P) = N_Selected_Component
2492 and then Is_Entity_Name (Selector_Name (P))
2493 then
2494 Pent := Entity (Selector_Name (P));
2495 end if;
2497 -- Prefix must be appropriate for an array type, taking into
2498 -- account a possible implicit dereference.
2500 if Is_Access_Type (Array_Type) then
2501 Error_Msg_NW
2502 (Warn_On_Dereference, "?d?implicit dereference", N);
2503 Array_Type := Process_Implicit_Dereference_Prefix (Pent, P);
2504 end if;
2506 if Is_Array_Type (Array_Type) then
2508 -- In order to correctly access First_Index component later,
2509 -- replace string literal subtype by its parent type.
2511 if Ekind (Array_Type) = E_String_Literal_Subtype then
2512 Array_Type := Etype (Array_Type);
2513 end if;
2515 elsif Present (Pent) and then Ekind (Pent) = E_Entry_Family then
2516 Analyze (Exp);
2517 Set_Etype (N, Any_Type);
2519 if not Has_Compatible_Type (Exp, Entry_Index_Type (Pent)) then
2520 Error_Msg_N ("invalid index type in entry name", N);
2522 elsif Present (Next (Exp)) then
2523 Error_Msg_N ("too many subscripts in entry reference", N);
2525 else
2526 Set_Etype (N, Etype (P));
2527 end if;
2529 return;
2531 elsif Is_Record_Type (Array_Type)
2532 and then Remote_AST_I_Dereference (P)
2533 then
2534 return;
2536 elsif Try_Container_Indexing (N, P, Exprs) then
2537 return;
2539 elsif Array_Type = Any_Type then
2540 Set_Etype (N, Any_Type);
2542 -- In most cases the analysis of the prefix will have emitted
2543 -- an error already, but if the prefix may be interpreted as a
2544 -- call in prefixed notation, the report is left to the caller.
2545 -- To prevent cascaded errors, report only if no previous ones.
2547 if Serious_Errors_Detected = 0 then
2548 Error_Msg_N ("invalid prefix in indexed component", P);
2550 if Nkind (P) = N_Expanded_Name then
2551 Error_Msg_NE ("\& is not visible", P, Selector_Name (P));
2552 end if;
2553 end if;
2555 return;
2557 -- Here we definitely have a bad indexing
2559 else
2560 if Nkind (Parent (N)) = N_Requeue_Statement
2561 and then Present (Pent) and then Ekind (Pent) = E_Entry
2562 then
2563 Error_Msg_N
2564 ("REQUEUE does not permit parameters", First (Exprs));
2566 elsif Is_Entity_Name (P)
2567 and then Etype (P) = Standard_Void_Type
2568 then
2569 Error_Msg_NE ("incorrect use of &", P, Entity (P));
2571 else
2572 Error_Msg_N ("array type required in indexed component", P);
2573 end if;
2575 Set_Etype (N, Any_Type);
2576 return;
2577 end if;
2579 Index := First_Index (Array_Type);
2580 while Present (Index) and then Present (Exp) loop
2581 if not Has_Compatible_Type (Exp, Etype (Index)) then
2582 Wrong_Type (Exp, Etype (Index));
2583 Set_Etype (N, Any_Type);
2584 return;
2585 end if;
2587 Next_Index (Index);
2588 Next (Exp);
2589 end loop;
2591 Set_Etype (N, Component_Type (Array_Type));
2592 Check_Implicit_Dereference (N, Etype (N));
2594 if Present (Index) then
2595 Error_Msg_N
2596 ("too few subscripts in array reference", First (Exprs));
2598 elsif Present (Exp) then
2599 Error_Msg_N ("too many subscripts in array reference", Exp);
2600 end if;
2601 end if;
2602 end Process_Indexed_Component;
2604 ----------------------------------------
2605 -- Process_Indexed_Component_Or_Slice --
2606 ----------------------------------------
2608 procedure Process_Indexed_Component_Or_Slice is
2609 begin
2610 Exp := First (Exprs);
2611 while Present (Exp) loop
2612 Analyze_Expression (Exp);
2613 Next (Exp);
2614 end loop;
2616 Exp := First (Exprs);
2618 -- If one index is present, and it is a subtype name, then the node
2619 -- denotes a slice (note that the case of an explicit range for a
2620 -- slice was already built as an N_Slice node in the first place,
2621 -- so that case is not handled here).
2623 -- We use a replace rather than a rewrite here because this is one
2624 -- of the cases in which the tree built by the parser is plain wrong.
2626 if No (Next (Exp))
2627 and then Is_Entity_Name (Exp)
2628 and then Is_Type (Entity (Exp))
2629 then
2630 Replace (N,
2631 Make_Slice (Sloc (N),
2632 Prefix => P,
2633 Discrete_Range => New_Copy (Exp)));
2634 Analyze (N);
2636 -- Otherwise (more than one index present, or single index is not
2637 -- a subtype name), then we have the indexed component case.
2639 else
2640 Process_Indexed_Component;
2641 end if;
2642 end Process_Indexed_Component_Or_Slice;
2644 ------------------------------------------
2645 -- Process_Overloaded_Indexed_Component --
2646 ------------------------------------------
2648 procedure Process_Overloaded_Indexed_Component is
2649 Exp : Node_Id;
2650 I : Interp_Index;
2651 It : Interp;
2652 Typ : Entity_Id;
2653 Index : Node_Id;
2654 Found : Boolean;
2656 begin
2657 Set_Etype (N, Any_Type);
2659 Get_First_Interp (P, I, It);
2660 while Present (It.Nam) loop
2661 Typ := It.Typ;
2663 if Is_Access_Type (Typ) then
2664 Typ := Designated_Type (Typ);
2665 Error_Msg_NW
2666 (Warn_On_Dereference, "?d?implicit dereference", N);
2667 end if;
2669 if Is_Array_Type (Typ) then
2671 -- Got a candidate: verify that index types are compatible
2673 Index := First_Index (Typ);
2674 Found := True;
2675 Exp := First (Exprs);
2676 while Present (Index) and then Present (Exp) loop
2677 if Has_Compatible_Type (Exp, Etype (Index)) then
2678 null;
2679 else
2680 Found := False;
2681 Remove_Interp (I);
2682 exit;
2683 end if;
2685 Next_Index (Index);
2686 Next (Exp);
2687 end loop;
2689 if Found and then No (Index) and then No (Exp) then
2690 declare
2691 CT : constant Entity_Id :=
2692 Base_Type (Component_Type (Typ));
2693 begin
2694 Add_One_Interp (N, CT, CT);
2695 Check_Implicit_Dereference (N, CT);
2696 end;
2697 end if;
2699 elsif Try_Container_Indexing (N, P, Exprs) then
2700 return;
2702 end if;
2704 Get_Next_Interp (I, It);
2705 end loop;
2707 if Etype (N) = Any_Type then
2708 Error_Msg_N ("no legal interpretation for indexed component", N);
2709 Set_Is_Overloaded (N, False);
2710 end if;
2712 End_Interp_List;
2713 end Process_Overloaded_Indexed_Component;
2715 -- Start of processing for Analyze_Indexed_Component_Form
2717 begin
2718 -- Get name of array, function or type
2720 Analyze (P);
2722 -- If P is an explicit dereference whose prefix is of a remote access-
2723 -- to-subprogram type, then N has already been rewritten as a subprogram
2724 -- call and analyzed.
2726 if Nkind (N) in N_Subprogram_Call then
2727 return;
2729 -- When the prefix is attribute 'Loop_Entry and the sole expression of
2730 -- the indexed component denotes a loop name, the indexed form is turned
2731 -- into an attribute reference.
2733 elsif Nkind (N) = N_Attribute_Reference
2734 and then Attribute_Name (N) = Name_Loop_Entry
2735 then
2736 return;
2737 end if;
2739 pragma Assert (Nkind (N) = N_Indexed_Component);
2741 P_T := Base_Type (Etype (P));
2743 if Is_Entity_Name (P) and then Present (Entity (P)) then
2744 U_N := Entity (P);
2746 if Is_Type (U_N) then
2748 -- Reformat node as a type conversion
2750 E := Remove_Head (Exprs);
2752 if Present (First (Exprs)) then
2753 Error_Msg_N
2754 ("argument of type conversion must be single expression", N);
2755 end if;
2757 Change_Node (N, N_Type_Conversion);
2758 Set_Subtype_Mark (N, P);
2759 Set_Etype (N, U_N);
2760 Set_Expression (N, E);
2762 -- After changing the node, call for the specific Analysis
2763 -- routine directly, to avoid a double call to the expander.
2765 Analyze_Type_Conversion (N);
2766 return;
2767 end if;
2769 if Is_Overloadable (U_N) then
2770 Process_Function_Call;
2772 elsif Ekind (Etype (P)) = E_Subprogram_Type
2773 or else (Is_Access_Type (Etype (P))
2774 and then
2775 Ekind (Designated_Type (Etype (P))) =
2776 E_Subprogram_Type)
2777 then
2778 -- Call to access_to-subprogram with possible implicit dereference
2780 Process_Function_Call;
2782 elsif Is_Generic_Subprogram (U_N) then
2784 -- A common beginner's (or C++ templates fan) error
2786 Error_Msg_N ("generic subprogram cannot be called", N);
2787 Set_Etype (N, Any_Type);
2788 return;
2790 else
2791 Process_Indexed_Component_Or_Slice;
2792 end if;
2794 -- If not an entity name, prefix is an expression that may denote
2795 -- an array or an access-to-subprogram.
2797 else
2798 if Ekind (P_T) = E_Subprogram_Type
2799 or else (Is_Access_Type (P_T)
2800 and then
2801 Ekind (Designated_Type (P_T)) = E_Subprogram_Type)
2802 then
2803 Process_Function_Call;
2805 elsif Nkind (P) = N_Selected_Component
2806 and then Present (Entity (Selector_Name (P)))
2807 and then Is_Overloadable (Entity (Selector_Name (P)))
2808 then
2809 Process_Function_Call;
2811 -- In ASIS mode within a generic, a prefixed call is analyzed and
2812 -- partially rewritten but the original indexed component has not
2813 -- yet been rewritten as a call. Perform the replacement now.
2815 elsif Nkind (P) = N_Selected_Component
2816 and then Nkind (Parent (P)) = N_Function_Call
2817 and then ASIS_Mode
2818 then
2819 Rewrite (N, Parent (P));
2820 Analyze (N);
2822 else
2823 -- Indexed component, slice, or a call to a member of a family
2824 -- entry, which will be converted to an entry call later.
2826 Process_Indexed_Component_Or_Slice;
2827 end if;
2828 end if;
2830 Analyze_Dimension (N);
2831 end Analyze_Indexed_Component_Form;
2833 ------------------------
2834 -- Analyze_Logical_Op --
2835 ------------------------
2837 procedure Analyze_Logical_Op (N : Node_Id) is
2838 L : constant Node_Id := Left_Opnd (N);
2839 R : constant Node_Id := Right_Opnd (N);
2840 Op_Id : Entity_Id := Entity (N);
2842 begin
2843 Set_Etype (N, Any_Type);
2844 Candidate_Type := Empty;
2846 Analyze_Expression (L);
2847 Analyze_Expression (R);
2849 if Present (Op_Id) then
2851 if Ekind (Op_Id) = E_Operator then
2852 Find_Boolean_Types (L, R, Op_Id, N);
2853 else
2854 Add_One_Interp (N, Op_Id, Etype (Op_Id));
2855 end if;
2857 else
2858 Op_Id := Get_Name_Entity_Id (Chars (N));
2859 while Present (Op_Id) loop
2860 if Ekind (Op_Id) = E_Operator then
2861 Find_Boolean_Types (L, R, Op_Id, N);
2862 else
2863 Analyze_User_Defined_Binary_Op (N, Op_Id);
2864 end if;
2866 Op_Id := Homonym (Op_Id);
2867 end loop;
2868 end if;
2870 Operator_Check (N);
2871 Check_Function_Writable_Actuals (N);
2872 end Analyze_Logical_Op;
2874 ---------------------------
2875 -- Analyze_Membership_Op --
2876 ---------------------------
2878 procedure Analyze_Membership_Op (N : Node_Id) is
2879 Loc : constant Source_Ptr := Sloc (N);
2880 L : constant Node_Id := Left_Opnd (N);
2881 R : constant Node_Id := Right_Opnd (N);
2883 Index : Interp_Index;
2884 It : Interp;
2885 Found : Boolean := False;
2886 I_F : Interp_Index;
2887 T_F : Entity_Id;
2889 procedure Try_One_Interp (T1 : Entity_Id);
2890 -- Routine to try one proposed interpretation. Note that the context
2891 -- of the operation plays no role in resolving the arguments, so that
2892 -- if there is more than one interpretation of the operands that is
2893 -- compatible with a membership test, the operation is ambiguous.
2895 --------------------
2896 -- Try_One_Interp --
2897 --------------------
2899 procedure Try_One_Interp (T1 : Entity_Id) is
2900 begin
2901 if Has_Compatible_Type (R, T1) then
2902 if Found
2903 and then Base_Type (T1) /= Base_Type (T_F)
2904 then
2905 It := Disambiguate (L, I_F, Index, Any_Type);
2907 if It = No_Interp then
2908 Ambiguous_Operands (N);
2909 Set_Etype (L, Any_Type);
2910 return;
2912 else
2913 T_F := It.Typ;
2914 end if;
2916 else
2917 Found := True;
2918 T_F := T1;
2919 I_F := Index;
2920 end if;
2922 Set_Etype (L, T_F);
2923 end if;
2924 end Try_One_Interp;
2926 procedure Analyze_Set_Membership;
2927 -- If a set of alternatives is present, analyze each and find the
2928 -- common type to which they must all resolve.
2930 ----------------------------
2931 -- Analyze_Set_Membership --
2932 ----------------------------
2934 procedure Analyze_Set_Membership is
2935 Alt : Node_Id;
2936 Index : Interp_Index;
2937 It : Interp;
2938 Candidate_Interps : Node_Id;
2939 Common_Type : Entity_Id := Empty;
2941 begin
2942 if Comes_From_Source (N) then
2943 Check_Compiler_Unit ("set membership", N);
2944 end if;
2946 Analyze (L);
2947 Candidate_Interps := L;
2949 if not Is_Overloaded (L) then
2950 Common_Type := Etype (L);
2952 Alt := First (Alternatives (N));
2953 while Present (Alt) loop
2954 Analyze (Alt);
2956 if not Has_Compatible_Type (Alt, Common_Type) then
2957 Wrong_Type (Alt, Common_Type);
2958 end if;
2960 Next (Alt);
2961 end loop;
2963 else
2964 Alt := First (Alternatives (N));
2965 while Present (Alt) loop
2966 Analyze (Alt);
2967 if not Is_Overloaded (Alt) then
2968 Common_Type := Etype (Alt);
2970 else
2971 Get_First_Interp (Alt, Index, It);
2972 while Present (It.Typ) loop
2973 if not
2974 Has_Compatible_Type (Candidate_Interps, It.Typ)
2975 then
2976 Remove_Interp (Index);
2977 end if;
2979 Get_Next_Interp (Index, It);
2980 end loop;
2982 Get_First_Interp (Alt, Index, It);
2984 if No (It.Typ) then
2985 Error_Msg_N ("alternative has no legal type", Alt);
2986 return;
2987 end if;
2989 -- If alternative is not overloaded, we have a unique type
2990 -- for all of them.
2992 Set_Etype (Alt, It.Typ);
2994 -- If the alternative is an enumeration literal, use the one
2995 -- for this interpretation.
2997 if Is_Entity_Name (Alt) then
2998 Set_Entity (Alt, It.Nam);
2999 end if;
3001 Get_Next_Interp (Index, It);
3003 if No (It.Typ) then
3004 Set_Is_Overloaded (Alt, False);
3005 Common_Type := Etype (Alt);
3006 end if;
3008 Candidate_Interps := Alt;
3009 end if;
3011 Next (Alt);
3012 end loop;
3013 end if;
3015 Set_Etype (N, Standard_Boolean);
3017 if Present (Common_Type) then
3018 Set_Etype (L, Common_Type);
3020 -- The left operand may still be overloaded, to be resolved using
3021 -- the Common_Type.
3023 else
3024 Error_Msg_N ("cannot resolve membership operation", N);
3025 end if;
3026 end Analyze_Set_Membership;
3028 -- Start of processing for Analyze_Membership_Op
3030 begin
3031 Analyze_Expression (L);
3033 if No (R) then
3034 if Ada_Version >= Ada_2012 then
3035 Analyze_Set_Membership;
3036 Check_Function_Writable_Actuals (N);
3037 else
3038 Error_Msg_N
3039 ("multiple choices in membership tests only allowed in Ada 2012",
3041 end if;
3043 return;
3044 end if;
3046 if Nkind (R) = N_Range
3047 or else (Nkind (R) = N_Attribute_Reference
3048 and then Attribute_Name (R) = Name_Range)
3049 then
3050 Analyze (R);
3052 if not Is_Overloaded (L) then
3053 Try_One_Interp (Etype (L));
3055 else
3056 Get_First_Interp (L, Index, It);
3057 while Present (It.Typ) loop
3058 Try_One_Interp (It.Typ);
3059 Get_Next_Interp (Index, It);
3060 end loop;
3061 end if;
3063 -- If not a range, it can be a subtype mark, or else it is a degenerate
3064 -- membership test with a singleton value, i.e. a test for equality,
3065 -- if the types are compatible.
3067 else
3068 Analyze (R);
3070 if Is_Entity_Name (R)
3071 and then Is_Type (Entity (R))
3072 then
3073 Find_Type (R);
3074 Check_Fully_Declared (Entity (R), R);
3076 elsif Ada_Version >= Ada_2012
3077 and then Has_Compatible_Type (R, Etype (L))
3078 then
3079 if Nkind (N) = N_In then
3080 Rewrite (N,
3081 Make_Op_Eq (Loc,
3082 Left_Opnd => L,
3083 Right_Opnd => R));
3084 else
3085 Rewrite (N,
3086 Make_Op_Ne (Loc,
3087 Left_Opnd => L,
3088 Right_Opnd => R));
3089 end if;
3091 Analyze (N);
3092 return;
3094 else
3095 -- In all versions of the language, if we reach this point there
3096 -- is a previous error that will be diagnosed below.
3098 Find_Type (R);
3099 end if;
3100 end if;
3102 -- Compatibility between expression and subtype mark or range is
3103 -- checked during resolution. The result of the operation is Boolean
3104 -- in any case.
3106 Set_Etype (N, Standard_Boolean);
3108 if Comes_From_Source (N)
3109 and then Present (Right_Opnd (N))
3110 and then Is_CPP_Class (Etype (Etype (Right_Opnd (N))))
3111 then
3112 Error_Msg_N ("membership test not applicable to cpp-class types", N);
3113 end if;
3115 Check_Function_Writable_Actuals (N);
3116 end Analyze_Membership_Op;
3118 -----------------
3119 -- Analyze_Mod --
3120 -----------------
3122 procedure Analyze_Mod (N : Node_Id) is
3123 begin
3124 -- A special warning check, if we have an expression of the form:
3125 -- expr mod 2 * literal
3126 -- where literal is 64 or less, then probably what was meant was
3127 -- expr mod 2 ** literal
3128 -- so issue an appropriate warning.
3130 if Warn_On_Suspicious_Modulus_Value
3131 and then Nkind (Right_Opnd (N)) = N_Integer_Literal
3132 and then Intval (Right_Opnd (N)) = Uint_2
3133 and then Nkind (Parent (N)) = N_Op_Multiply
3134 and then Nkind (Right_Opnd (Parent (N))) = N_Integer_Literal
3135 and then Intval (Right_Opnd (Parent (N))) <= Uint_64
3136 then
3137 Error_Msg_N
3138 ("suspicious MOD value, was '*'* intended'??M?", Parent (N));
3139 end if;
3141 -- Remaining processing is same as for other arithmetic operators
3143 Analyze_Arithmetic_Op (N);
3144 end Analyze_Mod;
3146 ----------------------
3147 -- Analyze_Negation --
3148 ----------------------
3150 procedure Analyze_Negation (N : Node_Id) is
3151 R : constant Node_Id := Right_Opnd (N);
3152 Op_Id : Entity_Id := Entity (N);
3154 begin
3155 Set_Etype (N, Any_Type);
3156 Candidate_Type := Empty;
3158 Analyze_Expression (R);
3160 if Present (Op_Id) then
3161 if Ekind (Op_Id) = E_Operator then
3162 Find_Negation_Types (R, Op_Id, N);
3163 else
3164 Add_One_Interp (N, Op_Id, Etype (Op_Id));
3165 end if;
3167 else
3168 Op_Id := Get_Name_Entity_Id (Chars (N));
3169 while Present (Op_Id) loop
3170 if Ekind (Op_Id) = E_Operator then
3171 Find_Negation_Types (R, Op_Id, N);
3172 else
3173 Analyze_User_Defined_Unary_Op (N, Op_Id);
3174 end if;
3176 Op_Id := Homonym (Op_Id);
3177 end loop;
3178 end if;
3180 Operator_Check (N);
3181 end Analyze_Negation;
3183 ------------------
3184 -- Analyze_Null --
3185 ------------------
3187 procedure Analyze_Null (N : Node_Id) is
3188 begin
3189 Check_SPARK_05_Restriction ("null is not allowed", N);
3191 Set_Etype (N, Any_Access);
3192 end Analyze_Null;
3194 ----------------------
3195 -- Analyze_One_Call --
3196 ----------------------
3198 procedure Analyze_One_Call
3199 (N : Node_Id;
3200 Nam : Entity_Id;
3201 Report : Boolean;
3202 Success : out Boolean;
3203 Skip_First : Boolean := False)
3205 Actuals : constant List_Id := Parameter_Associations (N);
3206 Prev_T : constant Entity_Id := Etype (N);
3208 -- Recognize cases of prefixed calls that have been rewritten in
3209 -- various ways. The simplest case is a rewritten selected component,
3210 -- but it can also be an already-examined indexed component, or a
3211 -- prefix that is itself a rewritten prefixed call that is in turn
3212 -- an indexed call (the syntactic ambiguity involving the indexing of
3213 -- a function with defaulted parameters that returns an array).
3214 -- A flag Maybe_Indexed_Call might be useful here ???
3216 Must_Skip : constant Boolean := Skip_First
3217 or else Nkind (Original_Node (N)) = N_Selected_Component
3218 or else
3219 (Nkind (Original_Node (N)) = N_Indexed_Component
3220 and then Nkind (Prefix (Original_Node (N))) =
3221 N_Selected_Component)
3222 or else
3223 (Nkind (Parent (N)) = N_Function_Call
3224 and then Is_Array_Type (Etype (Name (N)))
3225 and then Etype (Original_Node (N)) =
3226 Component_Type (Etype (Name (N)))
3227 and then Nkind (Original_Node (Parent (N))) =
3228 N_Selected_Component);
3230 -- The first formal must be omitted from the match when trying to find
3231 -- a primitive operation that is a possible interpretation, and also
3232 -- after the call has been rewritten, because the corresponding actual
3233 -- is already known to be compatible, and because this may be an
3234 -- indexing of a call with default parameters.
3236 Formal : Entity_Id;
3237 Actual : Node_Id;
3238 Is_Indexed : Boolean := False;
3239 Is_Indirect : Boolean := False;
3240 Subp_Type : constant Entity_Id := Etype (Nam);
3241 Norm_OK : Boolean;
3243 function Compatible_Types_In_Predicate
3244 (T1 : Entity_Id;
3245 T2 : Entity_Id) return Boolean;
3246 -- For an Ada 2012 predicate or invariant, a call may mention an
3247 -- incomplete type, while resolution of the corresponding predicate
3248 -- function may see the full view, as a consequence of the delayed
3249 -- resolution of the corresponding expressions. This may occur in
3250 -- the body of a predicate function, or in a call to such. Anomalies
3251 -- involving private and full views can also happen. In each case,
3252 -- rewrite node or add conversions to remove spurious type errors.
3254 procedure Indicate_Name_And_Type;
3255 -- If candidate interpretation matches, indicate name and type of result
3256 -- on call node.
3258 function Operator_Hidden_By (Fun : Entity_Id) return Boolean;
3259 -- There may be a user-defined operator that hides the current
3260 -- interpretation. We must check for this independently of the
3261 -- analysis of the call with the user-defined operation, because
3262 -- the parameter names may be wrong and yet the hiding takes place.
3263 -- This fixes a problem with ACATS test B34014O.
3265 -- When the type Address is a visible integer type, and the DEC
3266 -- system extension is visible, the predefined operator may be
3267 -- hidden as well, by one of the address operations in auxdec.
3268 -- Finally, The abstract operations on address do not hide the
3269 -- predefined operator (this is the purpose of making them abstract).
3271 -----------------------------------
3272 -- Compatible_Types_In_Predicate --
3273 -----------------------------------
3275 function Compatible_Types_In_Predicate
3276 (T1 : Entity_Id;
3277 T2 : Entity_Id) return Boolean
3279 function Common_Type (T : Entity_Id) return Entity_Id;
3280 -- Find non-private full view if any, without going to ancestor type
3281 -- (as opposed to Underlying_Type).
3283 -----------------
3284 -- Common_Type --
3285 -----------------
3287 function Common_Type (T : Entity_Id) return Entity_Id is
3288 begin
3289 if Is_Private_Type (T) and then Present (Full_View (T)) then
3290 return Base_Type (Full_View (T));
3291 else
3292 return Base_Type (T);
3293 end if;
3294 end Common_Type;
3296 -- Start of processing for Compatible_Types_In_Predicate
3298 begin
3299 if (Ekind (Current_Scope) = E_Function
3300 and then Is_Predicate_Function (Current_Scope))
3301 or else
3302 (Ekind (Nam) = E_Function
3303 and then Is_Predicate_Function (Nam))
3304 then
3305 if Is_Incomplete_Type (T1)
3306 and then Present (Full_View (T1))
3307 and then Full_View (T1) = T2
3308 then
3309 Set_Etype (Formal, Etype (Actual));
3310 return True;
3312 elsif Common_Type (T1) = Common_Type (T2) then
3313 Rewrite (Actual, Unchecked_Convert_To (Etype (Formal), Actual));
3314 return True;
3316 else
3317 return False;
3318 end if;
3320 else
3321 return False;
3322 end if;
3323 end Compatible_Types_In_Predicate;
3325 ----------------------------
3326 -- Indicate_Name_And_Type --
3327 ----------------------------
3329 procedure Indicate_Name_And_Type is
3330 begin
3331 Add_One_Interp (N, Nam, Etype (Nam));
3332 Check_Implicit_Dereference (N, Etype (Nam));
3333 Success := True;
3335 -- If the prefix of the call is a name, indicate the entity
3336 -- being called. If it is not a name, it is an expression that
3337 -- denotes an access to subprogram or else an entry or family. In
3338 -- the latter case, the name is a selected component, and the entity
3339 -- being called is noted on the selector.
3341 if not Is_Type (Nam) then
3342 if Is_Entity_Name (Name (N)) then
3343 Set_Entity (Name (N), Nam);
3344 Set_Etype (Name (N), Etype (Nam));
3346 elsif Nkind (Name (N)) = N_Selected_Component then
3347 Set_Entity (Selector_Name (Name (N)), Nam);
3348 end if;
3349 end if;
3351 if Debug_Flag_E and not Report then
3352 Write_Str (" Overloaded call ");
3353 Write_Int (Int (N));
3354 Write_Str (" compatible with ");
3355 Write_Int (Int (Nam));
3356 Write_Eol;
3357 end if;
3358 end Indicate_Name_And_Type;
3360 ------------------------
3361 -- Operator_Hidden_By --
3362 ------------------------
3364 function Operator_Hidden_By (Fun : Entity_Id) return Boolean is
3365 Act1 : constant Node_Id := First_Actual (N);
3366 Act2 : constant Node_Id := Next_Actual (Act1);
3367 Form1 : constant Entity_Id := First_Formal (Fun);
3368 Form2 : constant Entity_Id := Next_Formal (Form1);
3370 begin
3371 if Ekind (Fun) /= E_Function or else Is_Abstract_Subprogram (Fun) then
3372 return False;
3374 elsif not Has_Compatible_Type (Act1, Etype (Form1)) then
3375 return False;
3377 elsif Present (Form2) then
3378 if No (Act2)
3379 or else not Has_Compatible_Type (Act2, Etype (Form2))
3380 then
3381 return False;
3382 end if;
3384 elsif Present (Act2) then
3385 return False;
3386 end if;
3388 -- Now we know that the arity of the operator matches the function,
3389 -- and the function call is a valid interpretation. The function
3390 -- hides the operator if it has the right signature, or if one of
3391 -- its operands is a non-abstract operation on Address when this is
3392 -- a visible integer type.
3394 return Hides_Op (Fun, Nam)
3395 or else Is_Descendant_Of_Address (Etype (Form1))
3396 or else
3397 (Present (Form2)
3398 and then Is_Descendant_Of_Address (Etype (Form2)));
3399 end Operator_Hidden_By;
3401 -- Start of processing for Analyze_One_Call
3403 begin
3404 Success := False;
3406 -- If the subprogram has no formals or if all the formals have defaults,
3407 -- and the return type is an array type, the node may denote an indexing
3408 -- of the result of a parameterless call. In Ada 2005, the subprogram
3409 -- may have one non-defaulted formal, and the call may have been written
3410 -- in prefix notation, so that the rebuilt parameter list has more than
3411 -- one actual.
3413 if not Is_Overloadable (Nam)
3414 and then Ekind (Nam) /= E_Subprogram_Type
3415 and then Ekind (Nam) /= E_Entry_Family
3416 then
3417 return;
3418 end if;
3420 -- An indexing requires at least one actual. The name of the call cannot
3421 -- be an implicit indirect call, so it cannot be a generated explicit
3422 -- dereference.
3424 if not Is_Empty_List (Actuals)
3425 and then
3426 (Needs_No_Actuals (Nam)
3427 or else
3428 (Needs_One_Actual (Nam)
3429 and then Present (Next_Actual (First (Actuals)))))
3430 then
3431 if Is_Array_Type (Subp_Type)
3432 and then
3433 (Nkind (Name (N)) /= N_Explicit_Dereference
3434 or else Comes_From_Source (Name (N)))
3435 then
3436 Is_Indexed := Try_Indexed_Call (N, Nam, Subp_Type, Must_Skip);
3438 elsif Is_Access_Type (Subp_Type)
3439 and then Is_Array_Type (Designated_Type (Subp_Type))
3440 then
3441 Is_Indexed :=
3442 Try_Indexed_Call
3443 (N, Nam, Designated_Type (Subp_Type), Must_Skip);
3445 -- The prefix can also be a parameterless function that returns an
3446 -- access to subprogram, in which case this is an indirect call.
3447 -- If this succeeds, an explicit dereference is added later on,
3448 -- in Analyze_Call or Resolve_Call.
3450 elsif Is_Access_Type (Subp_Type)
3451 and then Ekind (Designated_Type (Subp_Type)) = E_Subprogram_Type
3452 then
3453 Is_Indirect := Try_Indirect_Call (N, Nam, Subp_Type);
3454 end if;
3456 end if;
3458 -- If the call has been transformed into a slice, it is of the form
3459 -- F (Subtype) where F is parameterless. The node has been rewritten in
3460 -- Try_Indexed_Call and there is nothing else to do.
3462 if Is_Indexed
3463 and then Nkind (N) = N_Slice
3464 then
3465 return;
3466 end if;
3468 Normalize_Actuals
3469 (N, Nam, (Report and not Is_Indexed and not Is_Indirect), Norm_OK);
3471 if not Norm_OK then
3473 -- If an indirect call is a possible interpretation, indicate
3474 -- success to the caller. This may be an indexing of an explicit
3475 -- dereference of a call that returns an access type (see above).
3477 if Is_Indirect
3478 or else (Is_Indexed
3479 and then Nkind (Name (N)) = N_Explicit_Dereference
3480 and then Comes_From_Source (Name (N)))
3481 then
3482 Success := True;
3483 return;
3485 -- Mismatch in number or names of parameters
3487 elsif Debug_Flag_E then
3488 Write_Str (" normalization fails in call ");
3489 Write_Int (Int (N));
3490 Write_Str (" with subprogram ");
3491 Write_Int (Int (Nam));
3492 Write_Eol;
3493 end if;
3495 -- If the context expects a function call, discard any interpretation
3496 -- that is a procedure. If the node is not overloaded, leave as is for
3497 -- better error reporting when type mismatch is found.
3499 elsif Nkind (N) = N_Function_Call
3500 and then Is_Overloaded (Name (N))
3501 and then Ekind (Nam) = E_Procedure
3502 then
3503 return;
3505 -- Ditto for function calls in a procedure context
3507 elsif Nkind (N) = N_Procedure_Call_Statement
3508 and then Is_Overloaded (Name (N))
3509 and then Etype (Nam) /= Standard_Void_Type
3510 then
3511 return;
3513 elsif No (Actuals) then
3515 -- If Normalize succeeds, then there are default parameters for
3516 -- all formals.
3518 Indicate_Name_And_Type;
3520 elsif Ekind (Nam) = E_Operator then
3521 if Nkind (N) = N_Procedure_Call_Statement then
3522 return;
3523 end if;
3525 -- This can occur when the prefix of the call is an operator
3526 -- name or an expanded name whose selector is an operator name.
3528 Analyze_Operator_Call (N, Nam);
3530 if Etype (N) /= Prev_T then
3532 -- Check that operator is not hidden by a function interpretation
3534 if Is_Overloaded (Name (N)) then
3535 declare
3536 I : Interp_Index;
3537 It : Interp;
3539 begin
3540 Get_First_Interp (Name (N), I, It);
3541 while Present (It.Nam) loop
3542 if Operator_Hidden_By (It.Nam) then
3543 Set_Etype (N, Prev_T);
3544 return;
3545 end if;
3547 Get_Next_Interp (I, It);
3548 end loop;
3549 end;
3550 end if;
3552 -- If operator matches formals, record its name on the call.
3553 -- If the operator is overloaded, Resolve will select the
3554 -- correct one from the list of interpretations. The call
3555 -- node itself carries the first candidate.
3557 Set_Entity (Name (N), Nam);
3558 Success := True;
3560 elsif Report and then Etype (N) = Any_Type then
3561 Error_Msg_N ("incompatible arguments for operator", N);
3562 end if;
3564 else
3565 -- Normalize_Actuals has chained the named associations in the
3566 -- correct order of the formals.
3568 Actual := First_Actual (N);
3569 Formal := First_Formal (Nam);
3571 -- If we are analyzing a call rewritten from object notation, skip
3572 -- first actual, which may be rewritten later as an explicit
3573 -- dereference.
3575 if Must_Skip then
3576 Next_Actual (Actual);
3577 Next_Formal (Formal);
3578 end if;
3580 while Present (Actual) and then Present (Formal) loop
3581 if Nkind (Parent (Actual)) /= N_Parameter_Association
3582 or else Chars (Selector_Name (Parent (Actual))) = Chars (Formal)
3583 then
3584 -- The actual can be compatible with the formal, but we must
3585 -- also check that the context is not an address type that is
3586 -- visibly an integer type. In this case the use of literals is
3587 -- illegal, except in the body of descendants of system, where
3588 -- arithmetic operations on address are of course used.
3590 if Has_Compatible_Type (Actual, Etype (Formal))
3591 and then
3592 (Etype (Actual) /= Universal_Integer
3593 or else not Is_Descendant_Of_Address (Etype (Formal))
3594 or else In_Predefined_Unit (N))
3595 then
3596 Next_Actual (Actual);
3597 Next_Formal (Formal);
3599 -- In Allow_Integer_Address mode, we allow an actual integer to
3600 -- match a formal address type and vice versa. We only do this
3601 -- if we are certain that an error will otherwise be issued
3603 elsif Address_Integer_Convert_OK
3604 (Etype (Actual), Etype (Formal))
3605 and then (Report and not Is_Indexed and not Is_Indirect)
3606 then
3607 -- Handle this case by introducing an unchecked conversion
3609 Rewrite (Actual,
3610 Unchecked_Convert_To (Etype (Formal),
3611 Relocate_Node (Actual)));
3612 Analyze_And_Resolve (Actual, Etype (Formal));
3613 Next_Actual (Actual);
3614 Next_Formal (Formal);
3616 -- Under relaxed RM semantics silently replace occurrences of
3617 -- null by System.Address_Null. We only do this if we know that
3618 -- an error will otherwise be issued.
3620 elsif Null_To_Null_Address_Convert_OK (Actual, Etype (Formal))
3621 and then (Report and not Is_Indexed and not Is_Indirect)
3622 then
3623 Replace_Null_By_Null_Address (Actual);
3624 Analyze_And_Resolve (Actual, Etype (Formal));
3625 Next_Actual (Actual);
3626 Next_Formal (Formal);
3628 elsif Compatible_Types_In_Predicate
3629 (Etype (Formal), Etype (Actual))
3630 then
3631 Next_Actual (Actual);
3632 Next_Formal (Formal);
3634 -- In a complex case where an enclosing generic and a nested
3635 -- generic package, both declared with partially parameterized
3636 -- formal subprograms with the same names, are instantiated
3637 -- with the same type, the types of the actual parameter and
3638 -- that of the formal may appear incompatible at first sight.
3640 -- generic
3641 -- type Outer_T is private;
3642 -- with function Func (Formal : Outer_T)
3643 -- return ... is <>;
3645 -- package Outer_Gen is
3646 -- generic
3647 -- type Inner_T is private;
3648 -- with function Func (Formal : Inner_T) -- (1)
3649 -- return ... is <>;
3651 -- package Inner_Gen is
3652 -- function Inner_Func (Formal : Inner_T) -- (2)
3653 -- return ... is (Func (Formal));
3654 -- end Inner_Gen;
3655 -- end Outer_Generic;
3657 -- package Outer_Inst is new Outer_Gen (Actual_T);
3658 -- package Inner_Inst is new Outer_Inst.Inner_Gen (Actual_T);
3660 -- In the example above, the type of parameter
3661 -- Inner_Func.Formal at (2) is incompatible with the type of
3662 -- Func.Formal at (1) in the context of instantiations
3663 -- Outer_Inst and Inner_Inst. In reality both types are generic
3664 -- actual subtypes renaming base type Actual_T as part of the
3665 -- generic prologues for the instantiations.
3667 -- Recognize this case and add a type conversion to allow this
3668 -- kind of generic actual subtype conformance. Note that this
3669 -- is done only when the call is non-overloaded because the
3670 -- resolution mechanism already has the means to disambiguate
3671 -- similar cases.
3673 elsif not Is_Overloaded (Name (N))
3674 and then Is_Type (Etype (Actual))
3675 and then Is_Type (Etype (Formal))
3676 and then Is_Generic_Actual_Type (Etype (Actual))
3677 and then Is_Generic_Actual_Type (Etype (Formal))
3678 and then Base_Type (Etype (Actual)) =
3679 Base_Type (Etype (Formal))
3680 then
3681 Rewrite (Actual,
3682 Convert_To (Etype (Formal), Relocate_Node (Actual)));
3683 Analyze_And_Resolve (Actual, Etype (Formal));
3684 Next_Actual (Actual);
3685 Next_Formal (Formal);
3687 -- Handle failed type check
3689 else
3690 if Debug_Flag_E then
3691 Write_Str (" type checking fails in call ");
3692 Write_Int (Int (N));
3693 Write_Str (" with formal ");
3694 Write_Int (Int (Formal));
3695 Write_Str (" in subprogram ");
3696 Write_Int (Int (Nam));
3697 Write_Eol;
3698 end if;
3700 -- Comment needed on the following test???
3702 if Report and not Is_Indexed and not Is_Indirect then
3704 -- Ada 2005 (AI-251): Complete the error notification
3705 -- to help new Ada 2005 users.
3707 if Is_Class_Wide_Type (Etype (Formal))
3708 and then Is_Interface (Etype (Etype (Formal)))
3709 and then not Interface_Present_In_Ancestor
3710 (Typ => Etype (Actual),
3711 Iface => Etype (Etype (Formal)))
3712 then
3713 Error_Msg_NE
3714 ("(Ada 2005) does not implement interface }",
3715 Actual, Etype (Etype (Formal)));
3716 end if;
3718 Wrong_Type (Actual, Etype (Formal));
3720 if Nkind (Actual) = N_Op_Eq
3721 and then Nkind (Left_Opnd (Actual)) = N_Identifier
3722 then
3723 Formal := First_Formal (Nam);
3724 while Present (Formal) loop
3725 if Chars (Left_Opnd (Actual)) = Chars (Formal) then
3726 Error_Msg_N -- CODEFIX
3727 ("possible misspelling of `='>`!", Actual);
3728 exit;
3729 end if;
3731 Next_Formal (Formal);
3732 end loop;
3733 end if;
3735 if All_Errors_Mode then
3736 Error_Msg_Sloc := Sloc (Nam);
3738 if Etype (Formal) = Any_Type then
3739 Error_Msg_N
3740 ("there is no legal actual parameter", Actual);
3741 end if;
3743 if Is_Overloadable (Nam)
3744 and then Present (Alias (Nam))
3745 and then not Comes_From_Source (Nam)
3746 then
3747 Error_Msg_NE
3748 ("\\ =='> in call to inherited operation & #!",
3749 Actual, Nam);
3751 elsif Ekind (Nam) = E_Subprogram_Type then
3752 declare
3753 Access_To_Subprogram_Typ :
3754 constant Entity_Id :=
3755 Defining_Identifier
3756 (Associated_Node_For_Itype (Nam));
3757 begin
3758 Error_Msg_NE
3759 ("\\ =='> in call to dereference of &#!",
3760 Actual, Access_To_Subprogram_Typ);
3761 end;
3763 else
3764 Error_Msg_NE
3765 ("\\ =='> in call to &#!", Actual, Nam);
3767 end if;
3768 end if;
3769 end if;
3771 return;
3772 end if;
3774 else
3775 -- Normalize_Actuals has verified that a default value exists
3776 -- for this formal. Current actual names a subsequent formal.
3778 Next_Formal (Formal);
3779 end if;
3780 end loop;
3782 -- On exit, all actuals match
3784 Indicate_Name_And_Type;
3785 end if;
3786 end Analyze_One_Call;
3788 ---------------------------
3789 -- Analyze_Operator_Call --
3790 ---------------------------
3792 procedure Analyze_Operator_Call (N : Node_Id; Op_Id : Entity_Id) is
3793 Op_Name : constant Name_Id := Chars (Op_Id);
3794 Act1 : constant Node_Id := First_Actual (N);
3795 Act2 : constant Node_Id := Next_Actual (Act1);
3797 begin
3798 -- Binary operator case
3800 if Present (Act2) then
3802 -- If more than two operands, then not binary operator after all
3804 if Present (Next_Actual (Act2)) then
3805 return;
3806 end if;
3808 -- Otherwise action depends on operator
3810 case Op_Name is
3811 when Name_Op_Add
3812 | Name_Op_Divide
3813 | Name_Op_Expon
3814 | Name_Op_Mod
3815 | Name_Op_Multiply
3816 | Name_Op_Rem
3817 | Name_Op_Subtract
3819 Find_Arithmetic_Types (Act1, Act2, Op_Id, N);
3821 when Name_Op_And
3822 | Name_Op_Or
3823 | Name_Op_Xor
3825 Find_Boolean_Types (Act1, Act2, Op_Id, N);
3827 when Name_Op_Ge
3828 | Name_Op_Gt
3829 | Name_Op_Le
3830 | Name_Op_Lt
3832 Find_Comparison_Types (Act1, Act2, Op_Id, N);
3834 when Name_Op_Eq
3835 | Name_Op_Ne
3837 Find_Equality_Types (Act1, Act2, Op_Id, N);
3839 when Name_Op_Concat =>
3840 Find_Concatenation_Types (Act1, Act2, Op_Id, N);
3842 -- Is this when others, or should it be an abort???
3844 when others =>
3845 null;
3846 end case;
3848 -- Unary operator case
3850 else
3851 case Op_Name is
3852 when Name_Op_Abs
3853 | Name_Op_Add
3854 | Name_Op_Subtract
3856 Find_Unary_Types (Act1, Op_Id, N);
3858 when Name_Op_Not =>
3859 Find_Negation_Types (Act1, Op_Id, N);
3861 -- Is this when others correct, or should it be an abort???
3863 when others =>
3864 null;
3865 end case;
3866 end if;
3867 end Analyze_Operator_Call;
3869 -------------------------------------------
3870 -- Analyze_Overloaded_Selected_Component --
3871 -------------------------------------------
3873 procedure Analyze_Overloaded_Selected_Component (N : Node_Id) is
3874 Nam : constant Node_Id := Prefix (N);
3875 Sel : constant Node_Id := Selector_Name (N);
3876 Comp : Entity_Id;
3877 I : Interp_Index;
3878 It : Interp;
3879 T : Entity_Id;
3881 begin
3882 Set_Etype (Sel, Any_Type);
3884 Get_First_Interp (Nam, I, It);
3885 while Present (It.Typ) loop
3886 if Is_Access_Type (It.Typ) then
3887 T := Designated_Type (It.Typ);
3888 Error_Msg_NW (Warn_On_Dereference, "?d?implicit dereference", N);
3889 else
3890 T := It.Typ;
3891 end if;
3893 -- Locate the component. For a private prefix the selector can denote
3894 -- a discriminant.
3896 if Is_Record_Type (T) or else Is_Private_Type (T) then
3898 -- If the prefix is a class-wide type, the visible components are
3899 -- those of the base type.
3901 if Is_Class_Wide_Type (T) then
3902 T := Etype (T);
3903 end if;
3905 Comp := First_Entity (T);
3906 while Present (Comp) loop
3907 if Chars (Comp) = Chars (Sel)
3908 and then Is_Visible_Component (Comp, Sel)
3909 then
3911 -- AI05-105: if the context is an object renaming with
3912 -- an anonymous access type, the expected type of the
3913 -- object must be anonymous. This is a name resolution rule.
3915 if Nkind (Parent (N)) /= N_Object_Renaming_Declaration
3916 or else No (Access_Definition (Parent (N)))
3917 or else Ekind (Etype (Comp)) = E_Anonymous_Access_Type
3918 or else
3919 Ekind (Etype (Comp)) = E_Anonymous_Access_Subprogram_Type
3920 then
3921 Set_Entity (Sel, Comp);
3922 Set_Etype (Sel, Etype (Comp));
3923 Add_One_Interp (N, Etype (Comp), Etype (Comp));
3924 Check_Implicit_Dereference (N, Etype (Comp));
3926 -- This also specifies a candidate to resolve the name.
3927 -- Further overloading will be resolved from context.
3928 -- The selector name itself does not carry overloading
3929 -- information.
3931 Set_Etype (Nam, It.Typ);
3933 else
3934 -- Named access type in the context of a renaming
3935 -- declaration with an access definition. Remove
3936 -- inapplicable candidate.
3938 Remove_Interp (I);
3939 end if;
3940 end if;
3942 Next_Entity (Comp);
3943 end loop;
3945 elsif Is_Concurrent_Type (T) then
3946 Comp := First_Entity (T);
3947 while Present (Comp)
3948 and then Comp /= First_Private_Entity (T)
3949 loop
3950 if Chars (Comp) = Chars (Sel) then
3951 if Is_Overloadable (Comp) then
3952 Add_One_Interp (Sel, Comp, Etype (Comp));
3953 else
3954 Set_Entity_With_Checks (Sel, Comp);
3955 Generate_Reference (Comp, Sel);
3956 end if;
3958 Set_Etype (Sel, Etype (Comp));
3959 Set_Etype (N, Etype (Comp));
3960 Set_Etype (Nam, It.Typ);
3962 -- For access type case, introduce explicit dereference for
3963 -- more uniform treatment of entry calls. Do this only once
3964 -- if several interpretations yield an access type.
3966 if Is_Access_Type (Etype (Nam))
3967 and then Nkind (Nam) /= N_Explicit_Dereference
3968 then
3969 Insert_Explicit_Dereference (Nam);
3970 Error_Msg_NW
3971 (Warn_On_Dereference, "?d?implicit dereference", N);
3972 end if;
3973 end if;
3975 Next_Entity (Comp);
3976 end loop;
3978 Set_Is_Overloaded (N, Is_Overloaded (Sel));
3979 end if;
3981 Get_Next_Interp (I, It);
3982 end loop;
3984 if Etype (N) = Any_Type
3985 and then not Try_Object_Operation (N)
3986 then
3987 Error_Msg_NE ("undefined selector& for overloaded prefix", N, Sel);
3988 Set_Entity (Sel, Any_Id);
3989 Set_Etype (Sel, Any_Type);
3990 end if;
3991 end Analyze_Overloaded_Selected_Component;
3993 ----------------------------------
3994 -- Analyze_Qualified_Expression --
3995 ----------------------------------
3997 procedure Analyze_Qualified_Expression (N : Node_Id) is
3998 Mark : constant Entity_Id := Subtype_Mark (N);
3999 Expr : constant Node_Id := Expression (N);
4000 I : Interp_Index;
4001 It : Interp;
4002 T : Entity_Id;
4004 begin
4005 Analyze_Expression (Expr);
4007 Set_Etype (N, Any_Type);
4008 Find_Type (Mark);
4009 T := Entity (Mark);
4011 if Nkind_In (Enclosing_Declaration (N), N_Formal_Type_Declaration,
4012 N_Full_Type_Declaration,
4013 N_Incomplete_Type_Declaration,
4014 N_Protected_Type_Declaration,
4015 N_Private_Extension_Declaration,
4016 N_Private_Type_Declaration,
4017 N_Subtype_Declaration,
4018 N_Task_Type_Declaration)
4019 and then T = Defining_Identifier (Enclosing_Declaration (N))
4020 then
4021 Error_Msg_N ("current instance not allowed", Mark);
4022 T := Any_Type;
4023 end if;
4025 Set_Etype (N, T);
4027 if T = Any_Type then
4028 return;
4029 end if;
4031 Check_Fully_Declared (T, N);
4033 -- If expected type is class-wide, check for exact match before
4034 -- expansion, because if the expression is a dispatching call it
4035 -- may be rewritten as explicit dereference with class-wide result.
4036 -- If expression is overloaded, retain only interpretations that
4037 -- will yield exact matches.
4039 if Is_Class_Wide_Type (T) then
4040 if not Is_Overloaded (Expr) then
4041 if Base_Type (Etype (Expr)) /= Base_Type (T) then
4042 if Nkind (Expr) = N_Aggregate then
4043 Error_Msg_N ("type of aggregate cannot be class-wide", Expr);
4044 else
4045 Wrong_Type (Expr, T);
4046 end if;
4047 end if;
4049 else
4050 Get_First_Interp (Expr, I, It);
4052 while Present (It.Nam) loop
4053 if Base_Type (It.Typ) /= Base_Type (T) then
4054 Remove_Interp (I);
4055 end if;
4057 Get_Next_Interp (I, It);
4058 end loop;
4059 end if;
4060 end if;
4062 Set_Etype (N, T);
4063 end Analyze_Qualified_Expression;
4065 -----------------------------------
4066 -- Analyze_Quantified_Expression --
4067 -----------------------------------
4069 procedure Analyze_Quantified_Expression (N : Node_Id) is
4070 function Is_Empty_Range (Typ : Entity_Id) return Boolean;
4071 -- If the iterator is part of a quantified expression, and the range is
4072 -- known to be statically empty, emit a warning and replace expression
4073 -- with its static value. Returns True if the replacement occurs.
4075 function No_Else_Or_Trivial_True (If_Expr : Node_Id) return Boolean;
4076 -- Determine whether if expression If_Expr lacks an else part or if it
4077 -- has one, it evaluates to True.
4079 --------------------
4080 -- Is_Empty_Range --
4081 --------------------
4083 function Is_Empty_Range (Typ : Entity_Id) return Boolean is
4084 Loc : constant Source_Ptr := Sloc (N);
4086 begin
4087 if Is_Array_Type (Typ)
4088 and then Compile_Time_Known_Bounds (Typ)
4089 and then
4090 (Expr_Value (Type_Low_Bound (Etype (First_Index (Typ)))) >
4091 Expr_Value (Type_High_Bound (Etype (First_Index (Typ)))))
4092 then
4093 Preanalyze_And_Resolve (Condition (N), Standard_Boolean);
4095 if All_Present (N) then
4096 Error_Msg_N
4097 ("??quantified expression with ALL "
4098 & "over a null range has value True", N);
4099 Rewrite (N, New_Occurrence_Of (Standard_True, Loc));
4101 else
4102 Error_Msg_N
4103 ("??quantified expression with SOME "
4104 & "over a null range has value False", N);
4105 Rewrite (N, New_Occurrence_Of (Standard_False, Loc));
4106 end if;
4108 Analyze (N);
4109 return True;
4111 else
4112 return False;
4113 end if;
4114 end Is_Empty_Range;
4116 -----------------------------
4117 -- No_Else_Or_Trivial_True --
4118 -----------------------------
4120 function No_Else_Or_Trivial_True (If_Expr : Node_Id) return Boolean is
4121 Else_Expr : constant Node_Id :=
4122 Next (Next (First (Expressions (If_Expr))));
4123 begin
4124 return
4125 No (Else_Expr)
4126 or else (Compile_Time_Known_Value (Else_Expr)
4127 and then Is_True (Expr_Value (Else_Expr)));
4128 end No_Else_Or_Trivial_True;
4130 -- Local variables
4132 Cond : constant Node_Id := Condition (N);
4133 Loop_Id : Entity_Id;
4134 QE_Scop : Entity_Id;
4136 -- Start of processing for Analyze_Quantified_Expression
4138 begin
4139 Check_SPARK_05_Restriction ("quantified expression is not allowed", N);
4141 -- Create a scope to emulate the loop-like behavior of the quantified
4142 -- expression. The scope is needed to provide proper visibility of the
4143 -- loop variable.
4145 QE_Scop := New_Internal_Entity (E_Loop, Current_Scope, Sloc (N), 'L');
4146 Set_Etype (QE_Scop, Standard_Void_Type);
4147 Set_Scope (QE_Scop, Current_Scope);
4148 Set_Parent (QE_Scop, N);
4150 Push_Scope (QE_Scop);
4152 -- All constituents are preanalyzed and resolved to avoid untimely
4153 -- generation of various temporaries and types. Full analysis and
4154 -- expansion is carried out when the quantified expression is
4155 -- transformed into an expression with actions.
4157 if Present (Iterator_Specification (N)) then
4158 Preanalyze (Iterator_Specification (N));
4160 -- Do not proceed with the analysis when the range of iteration is
4161 -- empty. The appropriate error is issued by Is_Empty_Range.
4163 if Is_Entity_Name (Name (Iterator_Specification (N)))
4164 and then Is_Empty_Range (Etype (Name (Iterator_Specification (N))))
4165 then
4166 return;
4167 end if;
4169 else pragma Assert (Present (Loop_Parameter_Specification (N)));
4170 declare
4171 Loop_Par : constant Node_Id := Loop_Parameter_Specification (N);
4173 begin
4174 Preanalyze (Loop_Par);
4176 if Nkind (Discrete_Subtype_Definition (Loop_Par)) = N_Function_Call
4177 and then Parent (Loop_Par) /= N
4178 then
4179 -- The parser cannot distinguish between a loop specification
4180 -- and an iterator specification. If after preanalysis the
4181 -- proper form has been recognized, rewrite the expression to
4182 -- reflect the right kind. This is needed for proper ASIS
4183 -- navigation. If expansion is enabled, the transformation is
4184 -- performed when the expression is rewritten as a loop.
4186 Set_Iterator_Specification (N,
4187 New_Copy_Tree (Iterator_Specification (Parent (Loop_Par))));
4189 Set_Defining_Identifier (Iterator_Specification (N),
4190 Relocate_Node (Defining_Identifier (Loop_Par)));
4191 Set_Name (Iterator_Specification (N),
4192 Relocate_Node (Discrete_Subtype_Definition (Loop_Par)));
4193 Set_Comes_From_Source (Iterator_Specification (N),
4194 Comes_From_Source (Loop_Parameter_Specification (N)));
4195 Set_Loop_Parameter_Specification (N, Empty);
4196 end if;
4197 end;
4198 end if;
4200 Preanalyze_And_Resolve (Cond, Standard_Boolean);
4202 End_Scope;
4203 Set_Etype (N, Standard_Boolean);
4205 -- Verify that the loop variable is used within the condition of the
4206 -- quantified expression.
4208 if Present (Iterator_Specification (N)) then
4209 Loop_Id := Defining_Identifier (Iterator_Specification (N));
4210 else
4211 Loop_Id := Defining_Identifier (Loop_Parameter_Specification (N));
4212 end if;
4214 if Warn_On_Suspicious_Contract
4215 and then not Referenced (Loop_Id, Cond)
4216 then
4217 -- Generating C, this check causes spurious warnings on inlined
4218 -- postconditions; we can safely disable it because this check
4219 -- was previously performed when analyzing the internally built
4220 -- postconditions procedure.
4222 if Modify_Tree_For_C and then In_Inlined_Body then
4223 null;
4224 else
4225 Error_Msg_N ("?T?unused variable &", Loop_Id);
4226 end if;
4227 end if;
4229 -- Diagnose a possible misuse of the SOME existential quantifier. When
4230 -- we have a quantified expression of the form:
4232 -- for some X => (if P then Q [else True])
4234 -- any value for X that makes P False results in the if expression being
4235 -- trivially True, and so also results in the quantified expression
4236 -- being trivially True.
4238 if Warn_On_Suspicious_Contract
4239 and then not All_Present (N)
4240 and then Nkind (Cond) = N_If_Expression
4241 and then No_Else_Or_Trivial_True (Cond)
4242 then
4243 Error_Msg_N ("?T?suspicious expression", N);
4244 Error_Msg_N ("\\did you mean (for all X ='> (if P then Q))", N);
4245 Error_Msg_N ("\\or (for some X ='> P and then Q) instead'?", N);
4246 end if;
4247 end Analyze_Quantified_Expression;
4249 -------------------
4250 -- Analyze_Range --
4251 -------------------
4253 procedure Analyze_Range (N : Node_Id) is
4254 L : constant Node_Id := Low_Bound (N);
4255 H : constant Node_Id := High_Bound (N);
4256 I1, I2 : Interp_Index;
4257 It1, It2 : Interp;
4259 procedure Check_Common_Type (T1, T2 : Entity_Id);
4260 -- Verify the compatibility of two types, and choose the
4261 -- non universal one if the other is universal.
4263 procedure Check_High_Bound (T : Entity_Id);
4264 -- Test one interpretation of the low bound against all those
4265 -- of the high bound.
4267 procedure Check_Universal_Expression (N : Node_Id);
4268 -- In Ada 83, reject bounds of a universal range that are not literals
4269 -- or entity names.
4271 -----------------------
4272 -- Check_Common_Type --
4273 -----------------------
4275 procedure Check_Common_Type (T1, T2 : Entity_Id) is
4276 begin
4277 if Covers (T1 => T1, T2 => T2)
4278 or else
4279 Covers (T1 => T2, T2 => T1)
4280 then
4281 if T1 = Universal_Integer
4282 or else T1 = Universal_Real
4283 or else T1 = Any_Character
4284 then
4285 Add_One_Interp (N, Base_Type (T2), Base_Type (T2));
4287 elsif T1 = T2 then
4288 Add_One_Interp (N, T1, T1);
4290 else
4291 Add_One_Interp (N, Base_Type (T1), Base_Type (T1));
4292 end if;
4293 end if;
4294 end Check_Common_Type;
4296 ----------------------
4297 -- Check_High_Bound --
4298 ----------------------
4300 procedure Check_High_Bound (T : Entity_Id) is
4301 begin
4302 if not Is_Overloaded (H) then
4303 Check_Common_Type (T, Etype (H));
4304 else
4305 Get_First_Interp (H, I2, It2);
4306 while Present (It2.Typ) loop
4307 Check_Common_Type (T, It2.Typ);
4308 Get_Next_Interp (I2, It2);
4309 end loop;
4310 end if;
4311 end Check_High_Bound;
4313 --------------------------------
4314 -- Check_Universal_Expression --
4315 --------------------------------
4317 procedure Check_Universal_Expression (N : Node_Id) is
4318 begin
4319 if Etype (N) = Universal_Integer
4320 and then Nkind (N) /= N_Integer_Literal
4321 and then not Is_Entity_Name (N)
4322 and then Nkind (N) /= N_Attribute_Reference
4323 then
4324 Error_Msg_N ("illegal bound in discrete range", N);
4325 end if;
4326 end Check_Universal_Expression;
4328 -- Start of processing for Analyze_Range
4330 begin
4331 Set_Etype (N, Any_Type);
4332 Analyze_Expression (L);
4333 Analyze_Expression (H);
4335 if Etype (L) = Any_Type or else Etype (H) = Any_Type then
4336 return;
4338 else
4339 if not Is_Overloaded (L) then
4340 Check_High_Bound (Etype (L));
4341 else
4342 Get_First_Interp (L, I1, It1);
4343 while Present (It1.Typ) loop
4344 Check_High_Bound (It1.Typ);
4345 Get_Next_Interp (I1, It1);
4346 end loop;
4347 end if;
4349 -- If result is Any_Type, then we did not find a compatible pair
4351 if Etype (N) = Any_Type then
4352 Error_Msg_N ("incompatible types in range ", N);
4353 end if;
4354 end if;
4356 if Ada_Version = Ada_83
4357 and then
4358 (Nkind (Parent (N)) = N_Loop_Parameter_Specification
4359 or else Nkind (Parent (N)) = N_Constrained_Array_Definition)
4360 then
4361 Check_Universal_Expression (L);
4362 Check_Universal_Expression (H);
4363 end if;
4365 Check_Function_Writable_Actuals (N);
4366 end Analyze_Range;
4368 -----------------------
4369 -- Analyze_Reference --
4370 -----------------------
4372 procedure Analyze_Reference (N : Node_Id) is
4373 P : constant Node_Id := Prefix (N);
4374 E : Entity_Id;
4375 T : Entity_Id;
4376 Acc_Type : Entity_Id;
4378 begin
4379 Analyze (P);
4381 -- An interesting error check, if we take the 'Ref of an object for
4382 -- which a pragma Atomic or Volatile has been given, and the type of the
4383 -- object is not Atomic or Volatile, then we are in trouble. The problem
4384 -- is that no trace of the atomic/volatile status will remain for the
4385 -- backend to respect when it deals with the resulting pointer, since
4386 -- the pointer type will not be marked atomic (it is a pointer to the
4387 -- base type of the object).
4389 -- It is not clear if that can ever occur, but in case it does, we will
4390 -- generate an error message. Not clear if this message can ever be
4391 -- generated, and pretty clear that it represents a bug if it is, still
4392 -- seems worth checking, except in CodePeer mode where we do not really
4393 -- care and don't want to bother the user.
4395 T := Etype (P);
4397 if Is_Entity_Name (P)
4398 and then Is_Object_Reference (P)
4399 and then not CodePeer_Mode
4400 then
4401 E := Entity (P);
4402 T := Etype (P);
4404 if (Has_Atomic_Components (E)
4405 and then not Has_Atomic_Components (T))
4406 or else
4407 (Has_Volatile_Components (E)
4408 and then not Has_Volatile_Components (T))
4409 or else (Is_Atomic (E) and then not Is_Atomic (T))
4410 or else (Is_Volatile (E) and then not Is_Volatile (T))
4411 then
4412 Error_Msg_N ("cannot take reference to Atomic/Volatile object", N);
4413 end if;
4414 end if;
4416 -- Carry on with normal processing
4418 Acc_Type := Create_Itype (E_Allocator_Type, N);
4419 Set_Etype (Acc_Type, Acc_Type);
4420 Set_Directly_Designated_Type (Acc_Type, Etype (P));
4421 Set_Etype (N, Acc_Type);
4422 end Analyze_Reference;
4424 --------------------------------
4425 -- Analyze_Selected_Component --
4426 --------------------------------
4428 -- Prefix is a record type or a task or protected type. In the latter case,
4429 -- the selector must denote a visible entry.
4431 procedure Analyze_Selected_Component (N : Node_Id) is
4432 Name : constant Node_Id := Prefix (N);
4433 Sel : constant Node_Id := Selector_Name (N);
4434 Act_Decl : Node_Id;
4435 Comp : Entity_Id;
4436 Has_Candidate : Boolean := False;
4437 Hidden_Comp : Entity_Id;
4438 In_Scope : Boolean;
4439 Is_Private_Op : Boolean;
4440 Parent_N : Node_Id;
4441 Pent : Entity_Id := Empty;
4442 Prefix_Type : Entity_Id;
4444 Type_To_Use : Entity_Id;
4445 -- In most cases this is the Prefix_Type, but if the Prefix_Type is
4446 -- a class-wide type, we use its root type, whose components are
4447 -- present in the class-wide type.
4449 Is_Single_Concurrent_Object : Boolean;
4450 -- Set True if the prefix is a single task or a single protected object
4452 procedure Find_Component_In_Instance (Rec : Entity_Id);
4453 -- In an instance, a component of a private extension may not be visible
4454 -- while it was visible in the generic. Search candidate scope for a
4455 -- component with the proper identifier. This is only done if all other
4456 -- searches have failed. If a match is found, the Etype of both N and
4457 -- Sel are set from this component, and the entity of Sel is set to
4458 -- reference this component. If no match is found, Entity (Sel) remains
4459 -- unset. For a derived type that is an actual of the instance, the
4460 -- desired component may be found in any ancestor.
4462 function Has_Mode_Conformant_Spec (Comp : Entity_Id) return Boolean;
4463 -- It is known that the parent of N denotes a subprogram call. Comp
4464 -- is an overloadable component of the concurrent type of the prefix.
4465 -- Determine whether all formals of the parent of N and Comp are mode
4466 -- conformant. If the parent node is not analyzed yet it may be an
4467 -- indexed component rather than a function call.
4469 function Has_Dereference (Nod : Node_Id) return Boolean;
4470 -- Check whether prefix includes a dereference at any level.
4472 --------------------------------
4473 -- Find_Component_In_Instance --
4474 --------------------------------
4476 procedure Find_Component_In_Instance (Rec : Entity_Id) is
4477 Comp : Entity_Id;
4478 Typ : Entity_Id;
4480 begin
4481 Typ := Rec;
4482 while Present (Typ) loop
4483 Comp := First_Component (Typ);
4484 while Present (Comp) loop
4485 if Chars (Comp) = Chars (Sel) then
4486 Set_Entity_With_Checks (Sel, Comp);
4487 Set_Etype (Sel, Etype (Comp));
4488 Set_Etype (N, Etype (Comp));
4489 return;
4490 end if;
4492 Next_Component (Comp);
4493 end loop;
4495 -- If not found, the component may be declared in the parent
4496 -- type or its full view, if any.
4498 if Is_Derived_Type (Typ) then
4499 Typ := Etype (Typ);
4501 if Is_Private_Type (Typ) then
4502 Typ := Full_View (Typ);
4503 end if;
4505 else
4506 return;
4507 end if;
4508 end loop;
4510 -- If we fall through, no match, so no changes made
4512 return;
4513 end Find_Component_In_Instance;
4515 ------------------------------
4516 -- Has_Mode_Conformant_Spec --
4517 ------------------------------
4519 function Has_Mode_Conformant_Spec (Comp : Entity_Id) return Boolean is
4520 Comp_Param : Entity_Id;
4521 Param : Node_Id;
4522 Param_Typ : Entity_Id;
4524 begin
4525 Comp_Param := First_Formal (Comp);
4527 if Nkind (Parent (N)) = N_Indexed_Component then
4528 Param := First (Expressions (Parent (N)));
4529 else
4530 Param := First (Parameter_Associations (Parent (N)));
4531 end if;
4533 while Present (Comp_Param)
4534 and then Present (Param)
4535 loop
4536 Param_Typ := Find_Parameter_Type (Param);
4538 if Present (Param_Typ)
4539 and then
4540 not Conforming_Types
4541 (Etype (Comp_Param), Param_Typ, Mode_Conformant)
4542 then
4543 return False;
4544 end if;
4546 Next_Formal (Comp_Param);
4547 Next (Param);
4548 end loop;
4550 -- One of the specs has additional formals; there is no match, unless
4551 -- this may be an indexing of a parameterless call.
4553 -- Note that when expansion is disabled, the corresponding record
4554 -- type of synchronized types is not constructed, so that there is
4555 -- no point is attempting an interpretation as a prefixed call, as
4556 -- this is bound to fail because the primitive operations will not
4557 -- be properly located.
4559 if Present (Comp_Param) or else Present (Param) then
4560 if Needs_No_Actuals (Comp)
4561 and then Is_Array_Type (Etype (Comp))
4562 and then not Expander_Active
4563 then
4564 return True;
4565 else
4566 return False;
4567 end if;
4568 end if;
4570 return True;
4571 end Has_Mode_Conformant_Spec;
4573 ---------------------
4574 -- Has_Dereference --
4575 ---------------------
4577 function Has_Dereference (Nod : Node_Id) return Boolean is
4578 begin
4579 if Nkind (Nod) = N_Explicit_Dereference then
4580 return True;
4582 -- When expansion is disabled an explicit dereference may not have
4583 -- been inserted, but if this is an access type the indirection makes
4584 -- the call safe.
4586 elsif Is_Access_Type (Etype (Nod)) then
4587 return True;
4589 elsif Nkind_In (Nod, N_Indexed_Component, N_Selected_Component) then
4590 return Has_Dereference (Prefix (Nod));
4592 else
4593 return False;
4594 end if;
4595 end Has_Dereference;
4597 -- Start of processing for Analyze_Selected_Component
4599 begin
4600 Set_Etype (N, Any_Type);
4602 if Is_Overloaded (Name) then
4603 Analyze_Overloaded_Selected_Component (N);
4604 return;
4606 elsif Etype (Name) = Any_Type then
4607 Set_Entity (Sel, Any_Id);
4608 Set_Etype (Sel, Any_Type);
4609 return;
4611 else
4612 Prefix_Type := Etype (Name);
4613 end if;
4615 if Is_Access_Type (Prefix_Type) then
4617 -- A RACW object can never be used as prefix of a selected component
4618 -- since that means it is dereferenced without being a controlling
4619 -- operand of a dispatching operation (RM E.2.2(16/1)). Before
4620 -- reporting an error, we must check whether this is actually a
4621 -- dispatching call in prefix form.
4623 if Is_Remote_Access_To_Class_Wide_Type (Prefix_Type)
4624 and then Comes_From_Source (N)
4625 then
4626 if Try_Object_Operation (N) then
4627 return;
4628 else
4629 Error_Msg_N
4630 ("invalid dereference of a remote access-to-class-wide value",
4632 end if;
4634 -- Normal case of selected component applied to access type
4636 else
4637 Error_Msg_NW (Warn_On_Dereference, "?d?implicit dereference", N);
4639 if Is_Entity_Name (Name) then
4640 Pent := Entity (Name);
4641 elsif Nkind (Name) = N_Selected_Component
4642 and then Is_Entity_Name (Selector_Name (Name))
4643 then
4644 Pent := Entity (Selector_Name (Name));
4645 end if;
4647 Prefix_Type := Process_Implicit_Dereference_Prefix (Pent, Name);
4648 end if;
4650 -- If we have an explicit dereference of a remote access-to-class-wide
4651 -- value, then issue an error (see RM-E.2.2(16/1)). However we first
4652 -- have to check for the case of a prefix that is a controlling operand
4653 -- of a prefixed dispatching call, as the dereference is legal in that
4654 -- case. Normally this condition is checked in Validate_Remote_Access_
4655 -- To_Class_Wide_Type, but we have to defer the checking for selected
4656 -- component prefixes because of the prefixed dispatching call case.
4657 -- Note that implicit dereferences are checked for this just above.
4659 elsif Nkind (Name) = N_Explicit_Dereference
4660 and then Is_Remote_Access_To_Class_Wide_Type (Etype (Prefix (Name)))
4661 and then Comes_From_Source (N)
4662 then
4663 if Try_Object_Operation (N) then
4664 return;
4665 else
4666 Error_Msg_N
4667 ("invalid dereference of a remote access-to-class-wide value",
4669 end if;
4670 end if;
4672 -- (Ada 2005): if the prefix is the limited view of a type, and
4673 -- the context already includes the full view, use the full view
4674 -- in what follows, either to retrieve a component of to find
4675 -- a primitive operation. If the prefix is an explicit dereference,
4676 -- set the type of the prefix to reflect this transformation.
4677 -- If the nonlimited view is itself an incomplete type, get the
4678 -- full view if available.
4680 if From_Limited_With (Prefix_Type)
4681 and then Has_Non_Limited_View (Prefix_Type)
4682 then
4683 Prefix_Type := Get_Full_View (Non_Limited_View (Prefix_Type));
4685 if Nkind (N) = N_Explicit_Dereference then
4686 Set_Etype (Prefix (N), Prefix_Type);
4687 end if;
4688 end if;
4690 if Ekind (Prefix_Type) = E_Private_Subtype then
4691 Prefix_Type := Base_Type (Prefix_Type);
4692 end if;
4694 Type_To_Use := Prefix_Type;
4696 -- For class-wide types, use the entity list of the root type. This
4697 -- indirection is specially important for private extensions because
4698 -- only the root type get switched (not the class-wide type).
4700 if Is_Class_Wide_Type (Prefix_Type) then
4701 Type_To_Use := Root_Type (Prefix_Type);
4702 end if;
4704 -- If the prefix is a single concurrent object, use its name in error
4705 -- messages, rather than that of its anonymous type.
4707 Is_Single_Concurrent_Object :=
4708 Is_Concurrent_Type (Prefix_Type)
4709 and then Is_Internal_Name (Chars (Prefix_Type))
4710 and then not Is_Derived_Type (Prefix_Type)
4711 and then Is_Entity_Name (Name);
4713 Comp := First_Entity (Type_To_Use);
4715 -- If the selector has an original discriminant, the node appears in
4716 -- an instance. Replace the discriminant with the corresponding one
4717 -- in the current discriminated type. For nested generics, this must
4718 -- be done transitively, so note the new original discriminant.
4720 if Nkind (Sel) = N_Identifier
4721 and then In_Instance
4722 and then Present (Original_Discriminant (Sel))
4723 then
4724 Comp := Find_Corresponding_Discriminant (Sel, Prefix_Type);
4726 -- Mark entity before rewriting, for completeness and because
4727 -- subsequent semantic checks might examine the original node.
4729 Set_Entity (Sel, Comp);
4730 Rewrite (Selector_Name (N), New_Occurrence_Of (Comp, Sloc (N)));
4731 Set_Original_Discriminant (Selector_Name (N), Comp);
4732 Set_Etype (N, Etype (Comp));
4733 Check_Implicit_Dereference (N, Etype (Comp));
4735 if Is_Access_Type (Etype (Name)) then
4736 Insert_Explicit_Dereference (Name);
4737 Error_Msg_NW (Warn_On_Dereference, "?d?implicit dereference", N);
4738 end if;
4740 elsif Is_Record_Type (Prefix_Type) then
4742 -- Find component with given name. In an instance, if the node is
4743 -- known as a prefixed call, do not examine components whose
4744 -- visibility may be accidental.
4746 while Present (Comp) and then not Is_Prefixed_Call (N) loop
4747 if Chars (Comp) = Chars (Sel)
4748 and then Is_Visible_Component (Comp, N)
4749 then
4750 Set_Entity_With_Checks (Sel, Comp);
4751 Set_Etype (Sel, Etype (Comp));
4753 if Ekind (Comp) = E_Discriminant then
4754 if Is_Unchecked_Union (Base_Type (Prefix_Type)) then
4755 Error_Msg_N
4756 ("cannot reference discriminant of unchecked union",
4757 Sel);
4758 end if;
4760 if Is_Generic_Type (Prefix_Type)
4761 or else
4762 Is_Generic_Type (Root_Type (Prefix_Type))
4763 then
4764 Set_Original_Discriminant (Sel, Comp);
4765 end if;
4766 end if;
4768 -- Resolve the prefix early otherwise it is not possible to
4769 -- build the actual subtype of the component: it may need
4770 -- to duplicate this prefix and duplication is only allowed
4771 -- on fully resolved expressions.
4773 Resolve (Name);
4775 -- Ada 2005 (AI-50217): Check wrong use of incomplete types or
4776 -- subtypes in a package specification.
4777 -- Example:
4779 -- limited with Pkg;
4780 -- package Pkg is
4781 -- type Acc_Inc is access Pkg.T;
4782 -- X : Acc_Inc;
4783 -- N : Natural := X.all.Comp; -- ERROR, limited view
4784 -- end Pkg; -- Comp is not visible
4786 if Nkind (Name) = N_Explicit_Dereference
4787 and then From_Limited_With (Etype (Prefix (Name)))
4788 and then not Is_Potentially_Use_Visible (Etype (Name))
4789 and then Nkind (Parent (Cunit_Entity (Current_Sem_Unit))) =
4790 N_Package_Specification
4791 then
4792 Error_Msg_NE
4793 ("premature usage of incomplete}", Prefix (Name),
4794 Etype (Prefix (Name)));
4795 end if;
4797 -- We never need an actual subtype for the case of a selection
4798 -- for a indexed component of a non-packed array, since in
4799 -- this case gigi generates all the checks and can find the
4800 -- necessary bounds information.
4802 -- We also do not need an actual subtype for the case of a
4803 -- first, last, length, or range attribute applied to a
4804 -- non-packed array, since gigi can again get the bounds in
4805 -- these cases (gigi cannot handle the packed case, since it
4806 -- has the bounds of the packed array type, not the original
4807 -- bounds of the type). However, if the prefix is itself a
4808 -- selected component, as in a.b.c (i), gigi may regard a.b.c
4809 -- as a dynamic-sized temporary, so we do generate an actual
4810 -- subtype for this case.
4812 Parent_N := Parent (N);
4814 if not Is_Packed (Etype (Comp))
4815 and then
4816 ((Nkind (Parent_N) = N_Indexed_Component
4817 and then Nkind (Name) /= N_Selected_Component)
4818 or else
4819 (Nkind (Parent_N) = N_Attribute_Reference
4820 and then
4821 Nam_In (Attribute_Name (Parent_N), Name_First,
4822 Name_Last,
4823 Name_Length,
4824 Name_Range)))
4825 then
4826 Set_Etype (N, Etype (Comp));
4828 -- If full analysis is not enabled, we do not generate an
4829 -- actual subtype, because in the absence of expansion
4830 -- reference to a formal of a protected type, for example,
4831 -- will not be properly transformed, and will lead to
4832 -- out-of-scope references in gigi.
4834 -- In all other cases, we currently build an actual subtype.
4835 -- It seems likely that many of these cases can be avoided,
4836 -- but right now, the front end makes direct references to the
4837 -- bounds (e.g. in generating a length check), and if we do
4838 -- not make an actual subtype, we end up getting a direct
4839 -- reference to a discriminant, which will not do.
4841 elsif Full_Analysis then
4842 Act_Decl :=
4843 Build_Actual_Subtype_Of_Component (Etype (Comp), N);
4844 Insert_Action (N, Act_Decl);
4846 if No (Act_Decl) then
4847 Set_Etype (N, Etype (Comp));
4849 else
4850 -- Component type depends on discriminants. Enter the
4851 -- main attributes of the subtype.
4853 declare
4854 Subt : constant Entity_Id :=
4855 Defining_Identifier (Act_Decl);
4857 begin
4858 Set_Etype (Subt, Base_Type (Etype (Comp)));
4859 Set_Ekind (Subt, Ekind (Etype (Comp)));
4860 Set_Etype (N, Subt);
4861 end;
4862 end if;
4864 -- If Full_Analysis not enabled, just set the Etype
4866 else
4867 Set_Etype (N, Etype (Comp));
4868 end if;
4870 Check_Implicit_Dereference (N, Etype (N));
4871 return;
4872 end if;
4874 -- If the prefix is a private extension, check only the visible
4875 -- components of the partial view. This must include the tag,
4876 -- which can appear in expanded code in a tag check.
4878 if Ekind (Type_To_Use) = E_Record_Type_With_Private
4879 and then Chars (Selector_Name (N)) /= Name_uTag
4880 then
4881 exit when Comp = Last_Entity (Type_To_Use);
4882 end if;
4884 Next_Entity (Comp);
4885 end loop;
4887 -- Ada 2005 (AI-252): The selected component can be interpreted as
4888 -- a prefixed view of a subprogram. Depending on the context, this is
4889 -- either a name that can appear in a renaming declaration, or part
4890 -- of an enclosing call given in prefix form.
4892 -- Ada 2005 (AI05-0030): In the case of dispatching requeue, the
4893 -- selected component should resolve to a name.
4895 if Ada_Version >= Ada_2005
4896 and then Is_Tagged_Type (Prefix_Type)
4897 and then not Is_Concurrent_Type (Prefix_Type)
4898 then
4899 if Nkind (Parent (N)) = N_Generic_Association
4900 or else Nkind (Parent (N)) = N_Requeue_Statement
4901 or else Nkind (Parent (N)) = N_Subprogram_Renaming_Declaration
4902 then
4903 if Find_Primitive_Operation (N) then
4904 return;
4905 end if;
4907 elsif Try_Object_Operation (N) then
4908 return;
4909 end if;
4911 -- If the transformation fails, it will be necessary to redo the
4912 -- analysis with all errors enabled, to indicate candidate
4913 -- interpretations and reasons for each failure ???
4915 end if;
4917 elsif Is_Private_Type (Prefix_Type) then
4919 -- Allow access only to discriminants of the type. If the type has
4920 -- no full view, gigi uses the parent type for the components, so we
4921 -- do the same here.
4923 if No (Full_View (Prefix_Type)) then
4924 Type_To_Use := Root_Type (Base_Type (Prefix_Type));
4925 Comp := First_Entity (Type_To_Use);
4926 end if;
4928 while Present (Comp) loop
4929 if Chars (Comp) = Chars (Sel) then
4930 if Ekind (Comp) = E_Discriminant then
4931 Set_Entity_With_Checks (Sel, Comp);
4932 Generate_Reference (Comp, Sel);
4934 Set_Etype (Sel, Etype (Comp));
4935 Set_Etype (N, Etype (Comp));
4936 Check_Implicit_Dereference (N, Etype (N));
4938 if Is_Generic_Type (Prefix_Type)
4939 or else Is_Generic_Type (Root_Type (Prefix_Type))
4940 then
4941 Set_Original_Discriminant (Sel, Comp);
4942 end if;
4944 -- Before declaring an error, check whether this is tagged
4945 -- private type and a call to a primitive operation.
4947 elsif Ada_Version >= Ada_2005
4948 and then Is_Tagged_Type (Prefix_Type)
4949 and then Try_Object_Operation (N)
4950 then
4951 return;
4953 else
4954 Error_Msg_Node_2 := First_Subtype (Prefix_Type);
4955 Error_Msg_NE ("invisible selector& for }", N, Sel);
4956 Set_Entity (Sel, Any_Id);
4957 Set_Etype (N, Any_Type);
4958 end if;
4960 return;
4961 end if;
4963 Next_Entity (Comp);
4964 end loop;
4966 elsif Is_Concurrent_Type (Prefix_Type) then
4968 -- Find visible operation with given name. For a protected type,
4969 -- the possible candidates are discriminants, entries or protected
4970 -- subprograms. For a task type, the set can only include entries or
4971 -- discriminants if the task type is not an enclosing scope. If it
4972 -- is an enclosing scope (e.g. in an inner task) then all entities
4973 -- are visible, but the prefix must denote the enclosing scope, i.e.
4974 -- can only be a direct name or an expanded name.
4976 Set_Etype (Sel, Any_Type);
4977 Hidden_Comp := Empty;
4978 In_Scope := In_Open_Scopes (Prefix_Type);
4979 Is_Private_Op := False;
4981 while Present (Comp) loop
4983 -- Do not examine private operations of the type if not within
4984 -- its scope.
4986 if Chars (Comp) = Chars (Sel) then
4987 if Is_Overloadable (Comp)
4988 and then (In_Scope
4989 or else Comp /= First_Private_Entity (Type_To_Use))
4990 then
4991 Add_One_Interp (Sel, Comp, Etype (Comp));
4992 if Comp = First_Private_Entity (Type_To_Use) then
4993 Is_Private_Op := True;
4994 end if;
4996 -- If the prefix is tagged, the correct interpretation may
4997 -- lie in the primitive or class-wide operations of the
4998 -- type. Perform a simple conformance check to determine
4999 -- whether Try_Object_Operation should be invoked even if
5000 -- a visible entity is found.
5002 if Is_Tagged_Type (Prefix_Type)
5003 and then Nkind_In (Parent (N), N_Function_Call,
5004 N_Indexed_Component,
5005 N_Procedure_Call_Statement)
5006 and then Has_Mode_Conformant_Spec (Comp)
5007 then
5008 Has_Candidate := True;
5009 end if;
5011 -- Note: a selected component may not denote a component of a
5012 -- protected type (4.1.3(7)).
5014 elsif Ekind_In (Comp, E_Discriminant, E_Entry_Family)
5015 or else (In_Scope
5016 and then not Is_Protected_Type (Prefix_Type)
5017 and then Is_Entity_Name (Name))
5018 then
5019 Set_Entity_With_Checks (Sel, Comp);
5020 Generate_Reference (Comp, Sel);
5022 -- The selector is not overloadable, so we have a candidate
5023 -- interpretation.
5025 Has_Candidate := True;
5027 else
5028 if Ekind (Comp) = E_Component then
5029 Hidden_Comp := Comp;
5030 end if;
5032 goto Next_Comp;
5033 end if;
5035 Set_Etype (Sel, Etype (Comp));
5036 Set_Etype (N, Etype (Comp));
5038 if Ekind (Comp) = E_Discriminant then
5039 Set_Original_Discriminant (Sel, Comp);
5040 end if;
5042 -- For access type case, introduce explicit dereference for
5043 -- more uniform treatment of entry calls.
5045 if Is_Access_Type (Etype (Name)) then
5046 Insert_Explicit_Dereference (Name);
5047 Error_Msg_NW
5048 (Warn_On_Dereference, "?d?implicit dereference", N);
5049 end if;
5050 end if;
5052 <<Next_Comp>>
5053 if Comp = First_Private_Entity (Type_To_Use) then
5054 if Etype (Sel) /= Any_Type then
5056 -- We have a candiate
5058 exit;
5060 else
5061 -- Indicate that subsequent operations are private,
5062 -- for better error reporting.
5064 Is_Private_Op := True;
5065 end if;
5066 end if;
5068 -- Do not examine private operations if not within scope of
5069 -- the synchronized type.
5071 exit when not In_Scope
5072 and then
5073 Comp = First_Private_Entity (Base_Type (Prefix_Type));
5074 Next_Entity (Comp);
5075 end loop;
5077 -- If the scope is a current instance, the prefix cannot be an
5078 -- expression of the same type, unless the selector designates a
5079 -- public operation (otherwise that would represent an attempt to
5080 -- reach an internal entity of another synchronized object).
5082 -- This is legal if prefix is an access to such type and there is
5083 -- a dereference, or is a component with a dereferenced prefix.
5084 -- It is also legal if the prefix is a component of a task type,
5085 -- and the selector is one of the task operations.
5087 if In_Scope
5088 and then not Is_Entity_Name (Name)
5089 and then not Has_Dereference (Name)
5090 then
5091 if Is_Task_Type (Prefix_Type)
5092 and then Present (Entity (Sel))
5093 and then Ekind_In (Entity (Sel), E_Entry, E_Entry_Family)
5094 then
5095 null;
5097 elsif Is_Protected_Type (Prefix_Type)
5098 and then Is_Overloadable (Entity (Sel))
5099 and then not Is_Private_Op
5100 then
5101 null;
5103 else
5104 Error_Msg_NE
5105 ("invalid reference to internal operation of some object of "
5106 & "type &", N, Type_To_Use);
5107 Set_Entity (Sel, Any_Id);
5108 Set_Etype (Sel, Any_Type);
5109 return;
5110 end if;
5112 -- Another special case: the prefix may denote an object of the type
5113 -- (but not a type) in which case this is an external call and the
5114 -- operation must be public.
5116 elsif In_Scope
5117 and then Is_Object_Reference (Original_Node (Prefix (N)))
5118 and then Comes_From_Source (N)
5119 and then Is_Private_Op
5120 then
5121 if Present (Hidden_Comp) then
5122 Error_Msg_NE
5123 ("invalid reference to private component of object of type "
5124 & "&", N, Type_To_Use);
5126 else
5127 Error_Msg_NE
5128 ("invalid reference to private operation of some object of "
5129 & "type &", N, Type_To_Use);
5130 end if;
5132 Set_Entity (Sel, Any_Id);
5133 Set_Etype (Sel, Any_Type);
5134 return;
5135 end if;
5137 -- If there is no visible entity with the given name or none of the
5138 -- visible entities are plausible interpretations, check whether
5139 -- there is some other primitive operation with that name.
5141 if Ada_Version >= Ada_2005 and then Is_Tagged_Type (Prefix_Type) then
5142 if (Etype (N) = Any_Type
5143 or else not Has_Candidate)
5144 and then Try_Object_Operation (N)
5145 then
5146 return;
5148 -- If the context is not syntactically a procedure call, it
5149 -- may be a call to a primitive function declared outside of
5150 -- the synchronized type.
5152 -- If the context is a procedure call, there might still be
5153 -- an overloading between an entry and a primitive procedure
5154 -- declared outside of the synchronized type, called in prefix
5155 -- notation. This is harder to disambiguate because in one case
5156 -- the controlling formal is implicit ???
5158 elsif Nkind (Parent (N)) /= N_Procedure_Call_Statement
5159 and then Nkind (Parent (N)) /= N_Indexed_Component
5160 and then Try_Object_Operation (N)
5161 then
5162 return;
5163 end if;
5165 -- Ada 2012 (AI05-0090-1): If we found a candidate of a call to an
5166 -- entry or procedure of a tagged concurrent type we must check
5167 -- if there are class-wide subprograms covering the primitive. If
5168 -- true then Try_Object_Operation reports the error.
5170 if Has_Candidate
5171 and then Is_Concurrent_Type (Prefix_Type)
5172 and then Nkind (Parent (N)) = N_Procedure_Call_Statement
5173 then
5174 -- Duplicate the call. This is required to avoid problems with
5175 -- the tree transformations performed by Try_Object_Operation.
5176 -- Set properly the parent of the copied call, because it is
5177 -- about to be reanalyzed.
5179 declare
5180 Par : constant Node_Id := New_Copy_Tree (Parent (N));
5182 begin
5183 Set_Parent (Par, Parent (Parent (N)));
5185 if Try_Object_Operation
5186 (Sinfo.Name (Par), CW_Test_Only => True)
5187 then
5188 return;
5189 end if;
5190 end;
5191 end if;
5192 end if;
5194 if Etype (N) = Any_Type and then Is_Protected_Type (Prefix_Type) then
5196 -- Case of a prefix of a protected type: selector might denote
5197 -- an invisible private component.
5199 Comp := First_Private_Entity (Base_Type (Prefix_Type));
5200 while Present (Comp) and then Chars (Comp) /= Chars (Sel) loop
5201 Next_Entity (Comp);
5202 end loop;
5204 if Present (Comp) then
5205 if Is_Single_Concurrent_Object then
5206 Error_Msg_Node_2 := Entity (Name);
5207 Error_Msg_NE ("invisible selector& for &", N, Sel);
5209 else
5210 Error_Msg_Node_2 := First_Subtype (Prefix_Type);
5211 Error_Msg_NE ("invisible selector& for }", N, Sel);
5212 end if;
5213 return;
5214 end if;
5215 end if;
5217 Set_Is_Overloaded (N, Is_Overloaded (Sel));
5219 else
5220 -- Invalid prefix
5222 Error_Msg_NE ("invalid prefix in selected component&", N, Sel);
5223 end if;
5225 -- If N still has no type, the component is not defined in the prefix
5227 if Etype (N) = Any_Type then
5229 if Is_Single_Concurrent_Object then
5230 Error_Msg_Node_2 := Entity (Name);
5231 Error_Msg_NE ("no selector& for&", N, Sel);
5233 Check_Misspelled_Selector (Type_To_Use, Sel);
5235 -- If this is a derived formal type, the parent may have different
5236 -- visibility at this point. Try for an inherited component before
5237 -- reporting an error.
5239 elsif Is_Generic_Type (Prefix_Type)
5240 and then Ekind (Prefix_Type) = E_Record_Type_With_Private
5241 and then Prefix_Type /= Etype (Prefix_Type)
5242 and then Is_Record_Type (Etype (Prefix_Type))
5243 then
5244 Set_Etype (Prefix (N), Etype (Prefix_Type));
5245 Analyze_Selected_Component (N);
5246 return;
5248 -- Similarly, if this is the actual for a formal derived type, or
5249 -- a derived type thereof, the component inherited from the generic
5250 -- parent may not be visible in the actual, but the selected
5251 -- component is legal. Climb up the derivation chain of the generic
5252 -- parent type until we find the proper ancestor type.
5254 elsif In_Instance and then Is_Tagged_Type (Prefix_Type) then
5255 declare
5256 Par : Entity_Id := Prefix_Type;
5257 begin
5258 -- Climb up derivation chain to generic actual subtype
5260 while not Is_Generic_Actual_Type (Par) loop
5261 if Ekind (Par) = E_Record_Type then
5262 Par := Parent_Subtype (Par);
5263 exit when No (Par);
5264 else
5265 exit when Par = Etype (Par);
5266 Par := Etype (Par);
5267 end if;
5268 end loop;
5270 if Present (Par) and then Is_Generic_Actual_Type (Par) then
5272 -- Now look for component in ancestor types
5274 Par := Generic_Parent_Type (Declaration_Node (Par));
5275 loop
5276 Find_Component_In_Instance (Par);
5277 exit when Present (Entity (Sel))
5278 or else Par = Etype (Par);
5279 Par := Etype (Par);
5280 end loop;
5282 -- Another special case: the type is an extension of a private
5283 -- type T, is an actual in an instance, and we are in the body
5284 -- of the instance, so the generic body had a full view of the
5285 -- type declaration for T or of some ancestor that defines the
5286 -- component in question.
5288 elsif Is_Derived_Type (Type_To_Use)
5289 and then Used_As_Generic_Actual (Type_To_Use)
5290 and then In_Instance_Body
5291 then
5292 Find_Component_In_Instance (Parent_Subtype (Type_To_Use));
5294 -- In ASIS mode the generic parent type may be absent. Examine
5295 -- the parent type directly for a component that may have been
5296 -- visible in a parent generic unit.
5298 elsif Is_Derived_Type (Prefix_Type) then
5299 Par := Etype (Prefix_Type);
5300 Find_Component_In_Instance (Par);
5301 end if;
5302 end;
5304 -- The search above must have eventually succeeded, since the
5305 -- selected component was legal in the generic.
5307 if No (Entity (Sel)) then
5308 raise Program_Error;
5309 end if;
5311 return;
5313 -- Component not found, specialize error message when appropriate
5315 else
5316 if Ekind (Prefix_Type) = E_Record_Subtype then
5318 -- Check whether this is a component of the base type which
5319 -- is absent from a statically constrained subtype. This will
5320 -- raise constraint error at run time, but is not a compile-
5321 -- time error. When the selector is illegal for base type as
5322 -- well fall through and generate a compilation error anyway.
5324 Comp := First_Component (Base_Type (Prefix_Type));
5325 while Present (Comp) loop
5326 if Chars (Comp) = Chars (Sel)
5327 and then Is_Visible_Component (Comp, Sel)
5328 then
5329 Set_Entity_With_Checks (Sel, Comp);
5330 Generate_Reference (Comp, Sel);
5331 Set_Etype (Sel, Etype (Comp));
5332 Set_Etype (N, Etype (Comp));
5334 -- Emit appropriate message. The node will be replaced
5335 -- by an appropriate raise statement.
5337 -- Note that in SPARK mode, as with all calls to apply a
5338 -- compile time constraint error, this will be made into
5339 -- an error to simplify the processing of the formal
5340 -- verification backend.
5342 Apply_Compile_Time_Constraint_Error
5343 (N, "component not present in }??",
5344 CE_Discriminant_Check_Failed,
5345 Ent => Prefix_Type, Rep => False);
5347 Set_Raises_Constraint_Error (N);
5348 return;
5349 end if;
5351 Next_Component (Comp);
5352 end loop;
5354 end if;
5356 Error_Msg_Node_2 := First_Subtype (Prefix_Type);
5357 Error_Msg_NE ("no selector& for}", N, Sel);
5359 -- Add information in the case of an incomplete prefix
5361 if Is_Incomplete_Type (Type_To_Use) then
5362 declare
5363 Inc : constant Entity_Id := First_Subtype (Type_To_Use);
5365 begin
5366 if From_Limited_With (Scope (Type_To_Use)) then
5367 Error_Msg_NE
5368 ("\limited view of& has no components", N, Inc);
5370 else
5371 Error_Msg_NE
5372 ("\premature usage of incomplete type&", N, Inc);
5374 if Nkind (Parent (Inc)) =
5375 N_Incomplete_Type_Declaration
5376 then
5377 -- Record location of premature use in entity so that
5378 -- a continuation message is generated when the
5379 -- completion is seen.
5381 Set_Premature_Use (Parent (Inc), N);
5382 end if;
5383 end if;
5384 end;
5385 end if;
5387 Check_Misspelled_Selector (Type_To_Use, Sel);
5388 end if;
5390 Set_Entity (Sel, Any_Id);
5391 Set_Etype (Sel, Any_Type);
5392 end if;
5393 end Analyze_Selected_Component;
5395 ---------------------------
5396 -- Analyze_Short_Circuit --
5397 ---------------------------
5399 procedure Analyze_Short_Circuit (N : Node_Id) is
5400 L : constant Node_Id := Left_Opnd (N);
5401 R : constant Node_Id := Right_Opnd (N);
5402 Ind : Interp_Index;
5403 It : Interp;
5405 begin
5406 Analyze_Expression (L);
5407 Analyze_Expression (R);
5408 Set_Etype (N, Any_Type);
5410 if not Is_Overloaded (L) then
5411 if Root_Type (Etype (L)) = Standard_Boolean
5412 and then Has_Compatible_Type (R, Etype (L))
5413 then
5414 Add_One_Interp (N, Etype (L), Etype (L));
5415 end if;
5417 else
5418 Get_First_Interp (L, Ind, It);
5419 while Present (It.Typ) loop
5420 if Root_Type (It.Typ) = Standard_Boolean
5421 and then Has_Compatible_Type (R, It.Typ)
5422 then
5423 Add_One_Interp (N, It.Typ, It.Typ);
5424 end if;
5426 Get_Next_Interp (Ind, It);
5427 end loop;
5428 end if;
5430 -- Here we have failed to find an interpretation. Clearly we know that
5431 -- it is not the case that both operands can have an interpretation of
5432 -- Boolean, but this is by far the most likely intended interpretation.
5433 -- So we simply resolve both operands as Booleans, and at least one of
5434 -- these resolutions will generate an error message, and we do not need
5435 -- to give another error message on the short circuit operation itself.
5437 if Etype (N) = Any_Type then
5438 Resolve (L, Standard_Boolean);
5439 Resolve (R, Standard_Boolean);
5440 Set_Etype (N, Standard_Boolean);
5441 end if;
5442 end Analyze_Short_Circuit;
5444 -------------------
5445 -- Analyze_Slice --
5446 -------------------
5448 procedure Analyze_Slice (N : Node_Id) is
5449 D : constant Node_Id := Discrete_Range (N);
5450 P : constant Node_Id := Prefix (N);
5451 Array_Type : Entity_Id;
5452 Index_Type : Entity_Id;
5454 procedure Analyze_Overloaded_Slice;
5455 -- If the prefix is overloaded, select those interpretations that
5456 -- yield a one-dimensional array type.
5458 ------------------------------
5459 -- Analyze_Overloaded_Slice --
5460 ------------------------------
5462 procedure Analyze_Overloaded_Slice is
5463 I : Interp_Index;
5464 It : Interp;
5465 Typ : Entity_Id;
5467 begin
5468 Set_Etype (N, Any_Type);
5470 Get_First_Interp (P, I, It);
5471 while Present (It.Nam) loop
5472 Typ := It.Typ;
5474 if Is_Access_Type (Typ) then
5475 Typ := Designated_Type (Typ);
5476 Error_Msg_NW
5477 (Warn_On_Dereference, "?d?implicit dereference", N);
5478 end if;
5480 if Is_Array_Type (Typ)
5481 and then Number_Dimensions (Typ) = 1
5482 and then Has_Compatible_Type (D, Etype (First_Index (Typ)))
5483 then
5484 Add_One_Interp (N, Typ, Typ);
5485 end if;
5487 Get_Next_Interp (I, It);
5488 end loop;
5490 if Etype (N) = Any_Type then
5491 Error_Msg_N ("expect array type in prefix of slice", N);
5492 end if;
5493 end Analyze_Overloaded_Slice;
5495 -- Start of processing for Analyze_Slice
5497 begin
5498 if Comes_From_Source (N) then
5499 Check_SPARK_05_Restriction ("slice is not allowed", N);
5500 end if;
5502 Analyze (P);
5503 Analyze (D);
5505 if Is_Overloaded (P) then
5506 Analyze_Overloaded_Slice;
5508 else
5509 Array_Type := Etype (P);
5510 Set_Etype (N, Any_Type);
5512 if Is_Access_Type (Array_Type) then
5513 Array_Type := Designated_Type (Array_Type);
5514 Error_Msg_NW (Warn_On_Dereference, "?d?implicit dereference", N);
5515 end if;
5517 if not Is_Array_Type (Array_Type) then
5518 Wrong_Type (P, Any_Array);
5520 elsif Number_Dimensions (Array_Type) > 1 then
5521 Error_Msg_N
5522 ("type is not one-dimensional array in slice prefix", N);
5524 else
5525 if Ekind (Array_Type) = E_String_Literal_Subtype then
5526 Index_Type := Etype (String_Literal_Low_Bound (Array_Type));
5527 else
5528 Index_Type := Etype (First_Index (Array_Type));
5529 end if;
5531 if not Has_Compatible_Type (D, Index_Type) then
5532 Wrong_Type (D, Index_Type);
5533 else
5534 Set_Etype (N, Array_Type);
5535 end if;
5536 end if;
5537 end if;
5538 end Analyze_Slice;
5540 -----------------------------
5541 -- Analyze_Type_Conversion --
5542 -----------------------------
5544 procedure Analyze_Type_Conversion (N : Node_Id) is
5545 Expr : constant Node_Id := Expression (N);
5546 Typ : Entity_Id;
5548 begin
5549 -- If Conversion_OK is set, then the Etype is already set, and the only
5550 -- processing required is to analyze the expression. This is used to
5551 -- construct certain "illegal" conversions which are not allowed by Ada
5552 -- semantics, but can be handled by Gigi, see Sinfo for further details.
5554 if Conversion_OK (N) then
5555 Analyze (Expr);
5556 return;
5557 end if;
5559 -- Otherwise full type analysis is required, as well as some semantic
5560 -- checks to make sure the argument of the conversion is appropriate.
5562 Find_Type (Subtype_Mark (N));
5563 Typ := Entity (Subtype_Mark (N));
5564 Set_Etype (N, Typ);
5565 Check_Fully_Declared (Typ, N);
5566 Analyze_Expression (Expr);
5567 Validate_Remote_Type_Type_Conversion (N);
5569 -- Only remaining step is validity checks on the argument. These
5570 -- are skipped if the conversion does not come from the source.
5572 if not Comes_From_Source (N) then
5573 return;
5575 -- If there was an error in a generic unit, no need to replicate the
5576 -- error message. Conversely, constant-folding in the generic may
5577 -- transform the argument of a conversion into a string literal, which
5578 -- is legal. Therefore the following tests are not performed in an
5579 -- instance. The same applies to an inlined body.
5581 elsif In_Instance or In_Inlined_Body then
5582 return;
5584 elsif Nkind (Expr) = N_Null then
5585 Error_Msg_N ("argument of conversion cannot be null", N);
5586 Error_Msg_N ("\use qualified expression instead", N);
5587 Set_Etype (N, Any_Type);
5589 elsif Nkind (Expr) = N_Aggregate then
5590 Error_Msg_N ("argument of conversion cannot be aggregate", N);
5591 Error_Msg_N ("\use qualified expression instead", N);
5593 elsif Nkind (Expr) = N_Allocator then
5594 Error_Msg_N ("argument of conversion cannot be an allocator", N);
5595 Error_Msg_N ("\use qualified expression instead", N);
5597 elsif Nkind (Expr) = N_String_Literal then
5598 Error_Msg_N ("argument of conversion cannot be string literal", N);
5599 Error_Msg_N ("\use qualified expression instead", N);
5601 elsif Nkind (Expr) = N_Character_Literal then
5602 if Ada_Version = Ada_83 then
5603 Resolve (Expr, Typ);
5604 else
5605 Error_Msg_N ("argument of conversion cannot be character literal",
5607 Error_Msg_N ("\use qualified expression instead", N);
5608 end if;
5610 elsif Nkind (Expr) = N_Attribute_Reference
5611 and then Nam_In (Attribute_Name (Expr), Name_Access,
5612 Name_Unchecked_Access,
5613 Name_Unrestricted_Access)
5614 then
5615 Error_Msg_N ("argument of conversion cannot be access", N);
5616 Error_Msg_N ("\use qualified expression instead", N);
5617 end if;
5619 -- A formal parameter of a specific tagged type whose related subprogram
5620 -- is subject to pragma Extensions_Visible with value "False" cannot
5621 -- appear in a class-wide conversion (SPARK RM 6.1.7(3)). Do not check
5622 -- internally generated expressions.
5624 if Is_Class_Wide_Type (Typ)
5625 and then Comes_From_Source (Expr)
5626 and then Is_EVF_Expression (Expr)
5627 then
5628 Error_Msg_N
5629 ("formal parameter cannot be converted to class-wide type when "
5630 & "Extensions_Visible is False", Expr);
5631 end if;
5632 end Analyze_Type_Conversion;
5634 ----------------------
5635 -- Analyze_Unary_Op --
5636 ----------------------
5638 procedure Analyze_Unary_Op (N : Node_Id) is
5639 R : constant Node_Id := Right_Opnd (N);
5640 Op_Id : Entity_Id := Entity (N);
5642 begin
5643 Set_Etype (N, Any_Type);
5644 Candidate_Type := Empty;
5646 Analyze_Expression (R);
5648 if Present (Op_Id) then
5649 if Ekind (Op_Id) = E_Operator then
5650 Find_Unary_Types (R, Op_Id, N);
5651 else
5652 Add_One_Interp (N, Op_Id, Etype (Op_Id));
5653 end if;
5655 else
5656 Op_Id := Get_Name_Entity_Id (Chars (N));
5657 while Present (Op_Id) loop
5658 if Ekind (Op_Id) = E_Operator then
5659 if No (Next_Entity (First_Entity (Op_Id))) then
5660 Find_Unary_Types (R, Op_Id, N);
5661 end if;
5663 elsif Is_Overloadable (Op_Id) then
5664 Analyze_User_Defined_Unary_Op (N, Op_Id);
5665 end if;
5667 Op_Id := Homonym (Op_Id);
5668 end loop;
5669 end if;
5671 Operator_Check (N);
5672 end Analyze_Unary_Op;
5674 ----------------------------------
5675 -- Analyze_Unchecked_Expression --
5676 ----------------------------------
5678 procedure Analyze_Unchecked_Expression (N : Node_Id) is
5679 begin
5680 Analyze (Expression (N), Suppress => All_Checks);
5681 Set_Etype (N, Etype (Expression (N)));
5682 Save_Interps (Expression (N), N);
5683 end Analyze_Unchecked_Expression;
5685 ---------------------------------------
5686 -- Analyze_Unchecked_Type_Conversion --
5687 ---------------------------------------
5689 procedure Analyze_Unchecked_Type_Conversion (N : Node_Id) is
5690 begin
5691 Find_Type (Subtype_Mark (N));
5692 Analyze_Expression (Expression (N));
5693 Set_Etype (N, Entity (Subtype_Mark (N)));
5694 end Analyze_Unchecked_Type_Conversion;
5696 ------------------------------------
5697 -- Analyze_User_Defined_Binary_Op --
5698 ------------------------------------
5700 procedure Analyze_User_Defined_Binary_Op
5701 (N : Node_Id;
5702 Op_Id : Entity_Id)
5704 begin
5705 -- Only do analysis if the operator Comes_From_Source, since otherwise
5706 -- the operator was generated by the expander, and all such operators
5707 -- always refer to the operators in package Standard.
5709 if Comes_From_Source (N) then
5710 declare
5711 F1 : constant Entity_Id := First_Formal (Op_Id);
5712 F2 : constant Entity_Id := Next_Formal (F1);
5714 begin
5715 -- Verify that Op_Id is a visible binary function. Note that since
5716 -- we know Op_Id is overloaded, potentially use visible means use
5717 -- visible for sure (RM 9.4(11)).
5719 if Ekind (Op_Id) = E_Function
5720 and then Present (F2)
5721 and then (Is_Immediately_Visible (Op_Id)
5722 or else Is_Potentially_Use_Visible (Op_Id))
5723 and then Has_Compatible_Type (Left_Opnd (N), Etype (F1))
5724 and then Has_Compatible_Type (Right_Opnd (N), Etype (F2))
5725 then
5726 Add_One_Interp (N, Op_Id, Etype (Op_Id));
5728 -- If the left operand is overloaded, indicate that the current
5729 -- type is a viable candidate. This is redundant in most cases,
5730 -- but for equality and comparison operators where the context
5731 -- does not impose a type on the operands, setting the proper
5732 -- type is necessary to avoid subsequent ambiguities during
5733 -- resolution, when both user-defined and predefined operators
5734 -- may be candidates.
5736 if Is_Overloaded (Left_Opnd (N)) then
5737 Set_Etype (Left_Opnd (N), Etype (F1));
5738 end if;
5740 if Debug_Flag_E then
5741 Write_Str ("user defined operator ");
5742 Write_Name (Chars (Op_Id));
5743 Write_Str (" on node ");
5744 Write_Int (Int (N));
5745 Write_Eol;
5746 end if;
5747 end if;
5748 end;
5749 end if;
5750 end Analyze_User_Defined_Binary_Op;
5752 -----------------------------------
5753 -- Analyze_User_Defined_Unary_Op --
5754 -----------------------------------
5756 procedure Analyze_User_Defined_Unary_Op
5757 (N : Node_Id;
5758 Op_Id : Entity_Id)
5760 begin
5761 -- Only do analysis if the operator Comes_From_Source, since otherwise
5762 -- the operator was generated by the expander, and all such operators
5763 -- always refer to the operators in package Standard.
5765 if Comes_From_Source (N) then
5766 declare
5767 F : constant Entity_Id := First_Formal (Op_Id);
5769 begin
5770 -- Verify that Op_Id is a visible unary function. Note that since
5771 -- we know Op_Id is overloaded, potentially use visible means use
5772 -- visible for sure (RM 9.4(11)).
5774 if Ekind (Op_Id) = E_Function
5775 and then No (Next_Formal (F))
5776 and then (Is_Immediately_Visible (Op_Id)
5777 or else Is_Potentially_Use_Visible (Op_Id))
5778 and then Has_Compatible_Type (Right_Opnd (N), Etype (F))
5779 then
5780 Add_One_Interp (N, Op_Id, Etype (Op_Id));
5781 end if;
5782 end;
5783 end if;
5784 end Analyze_User_Defined_Unary_Op;
5786 ---------------------------
5787 -- Check_Arithmetic_Pair --
5788 ---------------------------
5790 procedure Check_Arithmetic_Pair
5791 (T1, T2 : Entity_Id;
5792 Op_Id : Entity_Id;
5793 N : Node_Id)
5795 Op_Name : constant Name_Id := Chars (Op_Id);
5797 function Has_Fixed_Op (Typ : Entity_Id; Op : Entity_Id) return Boolean;
5798 -- Check whether the fixed-point type Typ has a user-defined operator
5799 -- (multiplication or division) that should hide the corresponding
5800 -- predefined operator. Used to implement Ada 2005 AI-264, to make
5801 -- such operators more visible and therefore useful.
5803 -- If the name of the operation is an expanded name with prefix
5804 -- Standard, the predefined universal fixed operator is available,
5805 -- as specified by AI-420 (RM 4.5.5 (19.1/2)).
5807 function Specific_Type (T1, T2 : Entity_Id) return Entity_Id;
5808 -- Get specific type (i.e. non-universal type if there is one)
5810 ------------------
5811 -- Has_Fixed_Op --
5812 ------------------
5814 function Has_Fixed_Op (Typ : Entity_Id; Op : Entity_Id) return Boolean is
5815 Bas : constant Entity_Id := Base_Type (Typ);
5816 Ent : Entity_Id;
5817 F1 : Entity_Id;
5818 F2 : Entity_Id;
5820 begin
5821 -- If the universal_fixed operation is given explicitly the rule
5822 -- concerning primitive operations of the type do not apply.
5824 if Nkind (N) = N_Function_Call
5825 and then Nkind (Name (N)) = N_Expanded_Name
5826 and then Entity (Prefix (Name (N))) = Standard_Standard
5827 then
5828 return False;
5829 end if;
5831 -- The operation is treated as primitive if it is declared in the
5832 -- same scope as the type, and therefore on the same entity chain.
5834 Ent := Next_Entity (Typ);
5835 while Present (Ent) loop
5836 if Chars (Ent) = Chars (Op) then
5837 F1 := First_Formal (Ent);
5838 F2 := Next_Formal (F1);
5840 -- The operation counts as primitive if either operand or
5841 -- result are of the given base type, and both operands are
5842 -- fixed point types.
5844 if (Base_Type (Etype (F1)) = Bas
5845 and then Is_Fixed_Point_Type (Etype (F2)))
5847 or else
5848 (Base_Type (Etype (F2)) = Bas
5849 and then Is_Fixed_Point_Type (Etype (F1)))
5851 or else
5852 (Base_Type (Etype (Ent)) = Bas
5853 and then Is_Fixed_Point_Type (Etype (F1))
5854 and then Is_Fixed_Point_Type (Etype (F2)))
5855 then
5856 return True;
5857 end if;
5858 end if;
5860 Next_Entity (Ent);
5861 end loop;
5863 return False;
5864 end Has_Fixed_Op;
5866 -------------------
5867 -- Specific_Type --
5868 -------------------
5870 function Specific_Type (T1, T2 : Entity_Id) return Entity_Id is
5871 begin
5872 if T1 = Universal_Integer or else T1 = Universal_Real then
5873 return Base_Type (T2);
5874 else
5875 return Base_Type (T1);
5876 end if;
5877 end Specific_Type;
5879 -- Start of processing for Check_Arithmetic_Pair
5881 begin
5882 if Nam_In (Op_Name, Name_Op_Add, Name_Op_Subtract) then
5883 if Is_Numeric_Type (T1)
5884 and then Is_Numeric_Type (T2)
5885 and then (Covers (T1 => T1, T2 => T2)
5886 or else
5887 Covers (T1 => T2, T2 => T1))
5888 then
5889 Add_One_Interp (N, Op_Id, Specific_Type (T1, T2));
5890 end if;
5892 elsif Nam_In (Op_Name, Name_Op_Multiply, Name_Op_Divide) then
5893 if Is_Fixed_Point_Type (T1)
5894 and then (Is_Fixed_Point_Type (T2) or else T2 = Universal_Real)
5895 then
5896 -- If Treat_Fixed_As_Integer is set then the Etype is already set
5897 -- and no further processing is required (this is the case of an
5898 -- operator constructed by Exp_Fixd for a fixed point operation)
5899 -- Otherwise add one interpretation with universal fixed result
5900 -- If the operator is given in functional notation, it comes
5901 -- from source and Fixed_As_Integer cannot apply.
5903 if (Nkind (N) not in N_Op
5904 or else not Treat_Fixed_As_Integer (N))
5905 and then
5906 (not Has_Fixed_Op (T1, Op_Id)
5907 or else Nkind (Parent (N)) = N_Type_Conversion)
5908 then
5909 Add_One_Interp (N, Op_Id, Universal_Fixed);
5910 end if;
5912 elsif Is_Fixed_Point_Type (T2)
5913 and then (Nkind (N) not in N_Op
5914 or else not Treat_Fixed_As_Integer (N))
5915 and then T1 = Universal_Real
5916 and then
5917 (not Has_Fixed_Op (T1, Op_Id)
5918 or else Nkind (Parent (N)) = N_Type_Conversion)
5919 then
5920 Add_One_Interp (N, Op_Id, Universal_Fixed);
5922 elsif Is_Numeric_Type (T1)
5923 and then Is_Numeric_Type (T2)
5924 and then (Covers (T1 => T1, T2 => T2)
5925 or else
5926 Covers (T1 => T2, T2 => T1))
5927 then
5928 Add_One_Interp (N, Op_Id, Specific_Type (T1, T2));
5930 elsif Is_Fixed_Point_Type (T1)
5931 and then (Base_Type (T2) = Base_Type (Standard_Integer)
5932 or else T2 = Universal_Integer)
5933 then
5934 Add_One_Interp (N, Op_Id, T1);
5936 elsif T2 = Universal_Real
5937 and then Base_Type (T1) = Base_Type (Standard_Integer)
5938 and then Op_Name = Name_Op_Multiply
5939 then
5940 Add_One_Interp (N, Op_Id, Any_Fixed);
5942 elsif T1 = Universal_Real
5943 and then Base_Type (T2) = Base_Type (Standard_Integer)
5944 then
5945 Add_One_Interp (N, Op_Id, Any_Fixed);
5947 elsif Is_Fixed_Point_Type (T2)
5948 and then (Base_Type (T1) = Base_Type (Standard_Integer)
5949 or else T1 = Universal_Integer)
5950 and then Op_Name = Name_Op_Multiply
5951 then
5952 Add_One_Interp (N, Op_Id, T2);
5954 elsif T1 = Universal_Real and then T2 = Universal_Integer then
5955 Add_One_Interp (N, Op_Id, T1);
5957 elsif T2 = Universal_Real
5958 and then T1 = Universal_Integer
5959 and then Op_Name = Name_Op_Multiply
5960 then
5961 Add_One_Interp (N, Op_Id, T2);
5962 end if;
5964 elsif Op_Name = Name_Op_Mod or else Op_Name = Name_Op_Rem then
5966 -- Note: The fixed-point operands case with Treat_Fixed_As_Integer
5967 -- set does not require any special processing, since the Etype is
5968 -- already set (case of operation constructed by Exp_Fixed).
5970 if Is_Integer_Type (T1)
5971 and then (Covers (T1 => T1, T2 => T2)
5972 or else
5973 Covers (T1 => T2, T2 => T1))
5974 then
5975 Add_One_Interp (N, Op_Id, Specific_Type (T1, T2));
5976 end if;
5978 elsif Op_Name = Name_Op_Expon then
5979 if Is_Numeric_Type (T1)
5980 and then not Is_Fixed_Point_Type (T1)
5981 and then (Base_Type (T2) = Base_Type (Standard_Integer)
5982 or else T2 = Universal_Integer)
5983 then
5984 Add_One_Interp (N, Op_Id, Base_Type (T1));
5985 end if;
5987 else pragma Assert (Nkind (N) in N_Op_Shift);
5989 -- If not one of the predefined operators, the node may be one
5990 -- of the intrinsic functions. Its kind is always specific, and
5991 -- we can use it directly, rather than the name of the operation.
5993 if Is_Integer_Type (T1)
5994 and then (Base_Type (T2) = Base_Type (Standard_Integer)
5995 or else T2 = Universal_Integer)
5996 then
5997 Add_One_Interp (N, Op_Id, Base_Type (T1));
5998 end if;
5999 end if;
6000 end Check_Arithmetic_Pair;
6002 -------------------------------
6003 -- Check_Misspelled_Selector --
6004 -------------------------------
6006 procedure Check_Misspelled_Selector
6007 (Prefix : Entity_Id;
6008 Sel : Node_Id)
6010 Max_Suggestions : constant := 2;
6011 Nr_Of_Suggestions : Natural := 0;
6013 Suggestion_1 : Entity_Id := Empty;
6014 Suggestion_2 : Entity_Id := Empty;
6016 Comp : Entity_Id;
6018 begin
6019 -- All the components of the prefix of selector Sel are matched against
6020 -- Sel and a count is maintained of possible misspellings. When at
6021 -- the end of the analysis there are one or two (not more) possible
6022 -- misspellings, these misspellings will be suggested as possible
6023 -- correction.
6025 if not (Is_Private_Type (Prefix) or else Is_Record_Type (Prefix)) then
6027 -- Concurrent types should be handled as well ???
6029 return;
6030 end if;
6032 Comp := First_Entity (Prefix);
6033 while Nr_Of_Suggestions <= Max_Suggestions and then Present (Comp) loop
6034 if Is_Visible_Component (Comp, Sel) then
6035 if Is_Bad_Spelling_Of (Chars (Comp), Chars (Sel)) then
6036 Nr_Of_Suggestions := Nr_Of_Suggestions + 1;
6038 case Nr_Of_Suggestions is
6039 when 1 => Suggestion_1 := Comp;
6040 when 2 => Suggestion_2 := Comp;
6041 when others => null;
6042 end case;
6043 end if;
6044 end if;
6046 Comp := Next_Entity (Comp);
6047 end loop;
6049 -- Report at most two suggestions
6051 if Nr_Of_Suggestions = 1 then
6052 Error_Msg_NE -- CODEFIX
6053 ("\possible misspelling of&", Sel, Suggestion_1);
6055 elsif Nr_Of_Suggestions = 2 then
6056 Error_Msg_Node_2 := Suggestion_2;
6057 Error_Msg_NE -- CODEFIX
6058 ("\possible misspelling of& or&", Sel, Suggestion_1);
6059 end if;
6060 end Check_Misspelled_Selector;
6062 ----------------------
6063 -- Defined_In_Scope --
6064 ----------------------
6066 function Defined_In_Scope (T : Entity_Id; S : Entity_Id) return Boolean
6068 S1 : constant Entity_Id := Scope (Base_Type (T));
6069 begin
6070 return S1 = S
6071 or else (S1 = System_Aux_Id and then S = Scope (S1));
6072 end Defined_In_Scope;
6074 -------------------
6075 -- Diagnose_Call --
6076 -------------------
6078 procedure Diagnose_Call (N : Node_Id; Nam : Node_Id) is
6079 Actual : Node_Id;
6080 X : Interp_Index;
6081 It : Interp;
6082 Err_Mode : Boolean;
6083 New_Nam : Node_Id;
6084 Void_Interp_Seen : Boolean := False;
6086 Success : Boolean;
6087 pragma Warnings (Off, Boolean);
6089 begin
6090 if Ada_Version >= Ada_2005 then
6091 Actual := First_Actual (N);
6092 while Present (Actual) loop
6094 -- Ada 2005 (AI-50217): Post an error in case of premature
6095 -- usage of an entity from the limited view.
6097 if not Analyzed (Etype (Actual))
6098 and then From_Limited_With (Etype (Actual))
6099 then
6100 Error_Msg_Qual_Level := 1;
6101 Error_Msg_NE
6102 ("missing with_clause for scope of imported type&",
6103 Actual, Etype (Actual));
6104 Error_Msg_Qual_Level := 0;
6105 end if;
6107 Next_Actual (Actual);
6108 end loop;
6109 end if;
6111 -- Before listing the possible candidates, check whether this is
6112 -- a prefix of a selected component that has been rewritten as a
6113 -- parameterless function call because there is a callable candidate
6114 -- interpretation. If there is a hidden package in the list of homonyms
6115 -- of the function name (bad programming style in any case) suggest that
6116 -- this is the intended entity.
6118 if No (Parameter_Associations (N))
6119 and then Nkind (Parent (N)) = N_Selected_Component
6120 and then Nkind (Parent (Parent (N))) in N_Declaration
6121 and then Is_Overloaded (Nam)
6122 then
6123 declare
6124 Ent : Entity_Id;
6126 begin
6127 Ent := Current_Entity (Nam);
6128 while Present (Ent) loop
6129 if Ekind (Ent) = E_Package then
6130 Error_Msg_N
6131 ("no legal interpretations as function call,!", Nam);
6132 Error_Msg_NE ("\package& is not visible", N, Ent);
6134 Rewrite (Parent (N),
6135 New_Occurrence_Of (Any_Type, Sloc (N)));
6136 return;
6137 end if;
6139 Ent := Homonym (Ent);
6140 end loop;
6141 end;
6142 end if;
6144 -- Analyze each candidate call again, with full error reporting for
6145 -- each.
6147 Error_Msg_N
6148 ("no candidate interpretations match the actuals:!", Nam);
6149 Err_Mode := All_Errors_Mode;
6150 All_Errors_Mode := True;
6152 -- If this is a call to an operation of a concurrent type,
6153 -- the failed interpretations have been removed from the
6154 -- name. Recover them to provide full diagnostics.
6156 if Nkind (Parent (Nam)) = N_Selected_Component then
6157 Set_Entity (Nam, Empty);
6158 New_Nam := New_Copy_Tree (Parent (Nam));
6159 Set_Is_Overloaded (New_Nam, False);
6160 Set_Is_Overloaded (Selector_Name (New_Nam), False);
6161 Set_Parent (New_Nam, Parent (Parent (Nam)));
6162 Analyze_Selected_Component (New_Nam);
6163 Get_First_Interp (Selector_Name (New_Nam), X, It);
6164 else
6165 Get_First_Interp (Nam, X, It);
6166 end if;
6168 while Present (It.Nam) loop
6169 if Etype (It.Nam) = Standard_Void_Type then
6170 Void_Interp_Seen := True;
6171 end if;
6173 Analyze_One_Call (N, It.Nam, True, Success);
6174 Get_Next_Interp (X, It);
6175 end loop;
6177 if Nkind (N) = N_Function_Call then
6178 Get_First_Interp (Nam, X, It);
6179 while Present (It.Nam) loop
6180 if Ekind_In (It.Nam, E_Function, E_Operator) then
6181 return;
6182 else
6183 Get_Next_Interp (X, It);
6184 end if;
6185 end loop;
6187 -- If all interpretations are procedures, this deserves a
6188 -- more precise message. Ditto if this appears as the prefix
6189 -- of a selected component, which may be a lexical error.
6191 Error_Msg_N
6192 ("\context requires function call, found procedure name", Nam);
6194 if Nkind (Parent (N)) = N_Selected_Component
6195 and then N = Prefix (Parent (N))
6196 then
6197 Error_Msg_N -- CODEFIX
6198 ("\period should probably be semicolon", Parent (N));
6199 end if;
6201 elsif Nkind (N) = N_Procedure_Call_Statement
6202 and then not Void_Interp_Seen
6203 then
6204 Error_Msg_N (
6205 "\function name found in procedure call", Nam);
6206 end if;
6208 All_Errors_Mode := Err_Mode;
6209 end Diagnose_Call;
6211 ---------------------------
6212 -- Find_Arithmetic_Types --
6213 ---------------------------
6215 procedure Find_Arithmetic_Types
6216 (L, R : Node_Id;
6217 Op_Id : Entity_Id;
6218 N : Node_Id)
6220 Index1 : Interp_Index;
6221 Index2 : Interp_Index;
6222 It1 : Interp;
6223 It2 : Interp;
6225 procedure Check_Right_Argument (T : Entity_Id);
6226 -- Check right operand of operator
6228 --------------------------
6229 -- Check_Right_Argument --
6230 --------------------------
6232 procedure Check_Right_Argument (T : Entity_Id) is
6233 begin
6234 if not Is_Overloaded (R) then
6235 Check_Arithmetic_Pair (T, Etype (R), Op_Id, N);
6236 else
6237 Get_First_Interp (R, Index2, It2);
6238 while Present (It2.Typ) loop
6239 Check_Arithmetic_Pair (T, It2.Typ, Op_Id, N);
6240 Get_Next_Interp (Index2, It2);
6241 end loop;
6242 end if;
6243 end Check_Right_Argument;
6245 -- Start of processing for Find_Arithmetic_Types
6247 begin
6248 if not Is_Overloaded (L) then
6249 Check_Right_Argument (Etype (L));
6251 else
6252 Get_First_Interp (L, Index1, It1);
6253 while Present (It1.Typ) loop
6254 Check_Right_Argument (It1.Typ);
6255 Get_Next_Interp (Index1, It1);
6256 end loop;
6257 end if;
6259 end Find_Arithmetic_Types;
6261 ------------------------
6262 -- Find_Boolean_Types --
6263 ------------------------
6265 procedure Find_Boolean_Types
6266 (L, R : Node_Id;
6267 Op_Id : Entity_Id;
6268 N : Node_Id)
6270 Index : Interp_Index;
6271 It : Interp;
6273 procedure Check_Numeric_Argument (T : Entity_Id);
6274 -- Special case for logical operations one of whose operands is an
6275 -- integer literal. If both are literal the result is any modular type.
6277 ----------------------------
6278 -- Check_Numeric_Argument --
6279 ----------------------------
6281 procedure Check_Numeric_Argument (T : Entity_Id) is
6282 begin
6283 if T = Universal_Integer then
6284 Add_One_Interp (N, Op_Id, Any_Modular);
6286 elsif Is_Modular_Integer_Type (T) then
6287 Add_One_Interp (N, Op_Id, T);
6288 end if;
6289 end Check_Numeric_Argument;
6291 -- Start of processing for Find_Boolean_Types
6293 begin
6294 if not Is_Overloaded (L) then
6295 if Etype (L) = Universal_Integer
6296 or else Etype (L) = Any_Modular
6297 then
6298 if not Is_Overloaded (R) then
6299 Check_Numeric_Argument (Etype (R));
6301 else
6302 Get_First_Interp (R, Index, It);
6303 while Present (It.Typ) loop
6304 Check_Numeric_Argument (It.Typ);
6305 Get_Next_Interp (Index, It);
6306 end loop;
6307 end if;
6309 -- If operands are aggregates, we must assume that they may be
6310 -- boolean arrays, and leave disambiguation for the second pass.
6311 -- If only one is an aggregate, verify that the other one has an
6312 -- interpretation as a boolean array
6314 elsif Nkind (L) = N_Aggregate then
6315 if Nkind (R) = N_Aggregate then
6316 Add_One_Interp (N, Op_Id, Etype (L));
6318 elsif not Is_Overloaded (R) then
6319 if Valid_Boolean_Arg (Etype (R)) then
6320 Add_One_Interp (N, Op_Id, Etype (R));
6321 end if;
6323 else
6324 Get_First_Interp (R, Index, It);
6325 while Present (It.Typ) loop
6326 if Valid_Boolean_Arg (It.Typ) then
6327 Add_One_Interp (N, Op_Id, It.Typ);
6328 end if;
6330 Get_Next_Interp (Index, It);
6331 end loop;
6332 end if;
6334 elsif Valid_Boolean_Arg (Etype (L))
6335 and then Has_Compatible_Type (R, Etype (L))
6336 then
6337 Add_One_Interp (N, Op_Id, Etype (L));
6338 end if;
6340 else
6341 Get_First_Interp (L, Index, It);
6342 while Present (It.Typ) loop
6343 if Valid_Boolean_Arg (It.Typ)
6344 and then Has_Compatible_Type (R, It.Typ)
6345 then
6346 Add_One_Interp (N, Op_Id, It.Typ);
6347 end if;
6349 Get_Next_Interp (Index, It);
6350 end loop;
6351 end if;
6352 end Find_Boolean_Types;
6354 ---------------------------
6355 -- Find_Comparison_Types --
6356 ---------------------------
6358 procedure Find_Comparison_Types
6359 (L, R : Node_Id;
6360 Op_Id : Entity_Id;
6361 N : Node_Id)
6363 Index : Interp_Index;
6364 It : Interp;
6365 Found : Boolean := False;
6366 I_F : Interp_Index;
6367 T_F : Entity_Id;
6368 Scop : Entity_Id := Empty;
6370 procedure Try_One_Interp (T1 : Entity_Id);
6371 -- Routine to try one proposed interpretation. Note that the context
6372 -- of the operator plays no role in resolving the arguments, so that
6373 -- if there is more than one interpretation of the operands that is
6374 -- compatible with comparison, the operation is ambiguous.
6376 --------------------
6377 -- Try_One_Interp --
6378 --------------------
6380 procedure Try_One_Interp (T1 : Entity_Id) is
6381 begin
6382 -- If the operator is an expanded name, then the type of the operand
6383 -- must be defined in the corresponding scope. If the type is
6384 -- universal, the context will impose the correct type. Note that we
6385 -- also avoid returning if we are currently within a generic instance
6386 -- due to the fact that the generic package declaration has already
6387 -- been successfully analyzed and Defined_In_Scope expects the base
6388 -- type to be defined within the instance which will never be the
6389 -- case.
6391 if Present (Scop)
6392 and then not Defined_In_Scope (T1, Scop)
6393 and then not In_Instance
6394 and then T1 /= Universal_Integer
6395 and then T1 /= Universal_Real
6396 and then T1 /= Any_String
6397 and then T1 /= Any_Composite
6398 then
6399 return;
6400 end if;
6402 if Valid_Comparison_Arg (T1) and then Has_Compatible_Type (R, T1) then
6403 if Found and then Base_Type (T1) /= Base_Type (T_F) then
6404 It := Disambiguate (L, I_F, Index, Any_Type);
6406 if It = No_Interp then
6407 Ambiguous_Operands (N);
6408 Set_Etype (L, Any_Type);
6409 return;
6411 else
6412 T_F := It.Typ;
6413 end if;
6414 else
6415 Found := True;
6416 T_F := T1;
6417 I_F := Index;
6418 end if;
6420 Set_Etype (L, T_F);
6421 Find_Non_Universal_Interpretations (N, R, Op_Id, T1);
6422 end if;
6423 end Try_One_Interp;
6425 -- Start of processing for Find_Comparison_Types
6427 begin
6428 -- If left operand is aggregate, the right operand has to
6429 -- provide a usable type for it.
6431 if Nkind (L) = N_Aggregate and then Nkind (R) /= N_Aggregate then
6432 Find_Comparison_Types (L => R, R => L, Op_Id => Op_Id, N => N);
6433 return;
6434 end if;
6436 if Nkind (N) = N_Function_Call
6437 and then Nkind (Name (N)) = N_Expanded_Name
6438 then
6439 Scop := Entity (Prefix (Name (N)));
6441 -- The prefix may be a package renaming, and the subsequent test
6442 -- requires the original package.
6444 if Ekind (Scop) = E_Package
6445 and then Present (Renamed_Entity (Scop))
6446 then
6447 Scop := Renamed_Entity (Scop);
6448 Set_Entity (Prefix (Name (N)), Scop);
6449 end if;
6450 end if;
6452 if not Is_Overloaded (L) then
6453 Try_One_Interp (Etype (L));
6455 else
6456 Get_First_Interp (L, Index, It);
6457 while Present (It.Typ) loop
6458 Try_One_Interp (It.Typ);
6459 Get_Next_Interp (Index, It);
6460 end loop;
6461 end if;
6462 end Find_Comparison_Types;
6464 ----------------------------------------
6465 -- Find_Non_Universal_Interpretations --
6466 ----------------------------------------
6468 procedure Find_Non_Universal_Interpretations
6469 (N : Node_Id;
6470 R : Node_Id;
6471 Op_Id : Entity_Id;
6472 T1 : Entity_Id)
6474 Index : Interp_Index;
6475 It : Interp;
6477 begin
6478 if T1 = Universal_Integer or else T1 = Universal_Real
6480 -- If the left operand of an equality operator is null, the visibility
6481 -- of the operator must be determined from the interpretation of the
6482 -- right operand. This processing must be done for Any_Access, which
6483 -- is the internal representation of the type of the literal null.
6485 or else T1 = Any_Access
6486 then
6487 if not Is_Overloaded (R) then
6488 Add_One_Interp (N, Op_Id, Standard_Boolean, Base_Type (Etype (R)));
6489 else
6490 Get_First_Interp (R, Index, It);
6491 while Present (It.Typ) loop
6492 if Covers (It.Typ, T1) then
6493 Add_One_Interp
6494 (N, Op_Id, Standard_Boolean, Base_Type (It.Typ));
6495 end if;
6497 Get_Next_Interp (Index, It);
6498 end loop;
6499 end if;
6500 else
6501 Add_One_Interp (N, Op_Id, Standard_Boolean, Base_Type (T1));
6502 end if;
6503 end Find_Non_Universal_Interpretations;
6505 ------------------------------
6506 -- Find_Concatenation_Types --
6507 ------------------------------
6509 procedure Find_Concatenation_Types
6510 (L, R : Node_Id;
6511 Op_Id : Entity_Id;
6512 N : Node_Id)
6514 Is_String : constant Boolean := Nkind (L) = N_String_Literal
6515 or else
6516 Nkind (R) = N_String_Literal;
6517 Op_Type : constant Entity_Id := Etype (Op_Id);
6519 begin
6520 if Is_Array_Type (Op_Type)
6522 -- Small but very effective optimization: if at least one operand is a
6523 -- string literal, then the type of the operator must be either array
6524 -- of characters or array of strings.
6526 and then (not Is_String
6527 or else
6528 Is_Character_Type (Component_Type (Op_Type))
6529 or else
6530 Is_String_Type (Component_Type (Op_Type)))
6532 and then not Is_Limited_Type (Op_Type)
6534 and then (Has_Compatible_Type (L, Op_Type)
6535 or else
6536 Has_Compatible_Type (L, Component_Type (Op_Type)))
6538 and then (Has_Compatible_Type (R, Op_Type)
6539 or else
6540 Has_Compatible_Type (R, Component_Type (Op_Type)))
6541 then
6542 Add_One_Interp (N, Op_Id, Op_Type);
6543 end if;
6544 end Find_Concatenation_Types;
6546 -------------------------
6547 -- Find_Equality_Types --
6548 -------------------------
6550 procedure Find_Equality_Types
6551 (L, R : Node_Id;
6552 Op_Id : Entity_Id;
6553 N : Node_Id)
6555 Index : Interp_Index;
6556 It : Interp;
6557 Found : Boolean := False;
6558 I_F : Interp_Index;
6559 T_F : Entity_Id;
6560 Scop : Entity_Id := Empty;
6562 procedure Try_One_Interp (T1 : Entity_Id);
6563 -- The context of the equality operator plays no role in resolving the
6564 -- arguments, so that if there is more than one interpretation of the
6565 -- operands that is compatible with equality, the construct is ambiguous
6566 -- and an error can be emitted now, after trying to disambiguate, i.e.
6567 -- applying preference rules.
6569 --------------------
6570 -- Try_One_Interp --
6571 --------------------
6573 procedure Try_One_Interp (T1 : Entity_Id) is
6574 Bas : Entity_Id;
6576 begin
6577 -- Perform a sanity check in case of previous errors
6579 if No (T1) then
6580 return;
6581 end if;
6583 Bas := Base_Type (T1);
6585 -- If the operator is an expanded name, then the type of the operand
6586 -- must be defined in the corresponding scope. If the type is
6587 -- universal, the context will impose the correct type. An anonymous
6588 -- type for a 'Access reference is also universal in this sense, as
6589 -- the actual type is obtained from context.
6591 -- In Ada 2005, the equality operator for anonymous access types
6592 -- is declared in Standard, and preference rules apply to it.
6594 if Present (Scop) then
6596 -- Note that we avoid returning if we are currently within a
6597 -- generic instance due to the fact that the generic package
6598 -- declaration has already been successfully analyzed and
6599 -- Defined_In_Scope expects the base type to be defined within
6600 -- the instance which will never be the case.
6602 if Defined_In_Scope (T1, Scop)
6603 or else In_Instance
6604 or else T1 = Universal_Integer
6605 or else T1 = Universal_Real
6606 or else T1 = Any_Access
6607 or else T1 = Any_String
6608 or else T1 = Any_Composite
6609 or else (Ekind (T1) = E_Access_Subprogram_Type
6610 and then not Comes_From_Source (T1))
6611 then
6612 null;
6614 elsif Ekind (T1) = E_Anonymous_Access_Type
6615 and then Scop = Standard_Standard
6616 then
6617 null;
6619 else
6620 -- The scope does not contain an operator for the type
6622 return;
6623 end if;
6625 -- If we have infix notation, the operator must be usable. Within
6626 -- an instance, if the type is already established we know it is
6627 -- correct. If an operand is universal it is compatible with any
6628 -- numeric type.
6630 elsif In_Open_Scopes (Scope (Bas))
6631 or else Is_Potentially_Use_Visible (Bas)
6632 or else In_Use (Bas)
6633 or else (In_Use (Scope (Bas)) and then not Is_Hidden (Bas))
6635 -- In an instance, the type may have been immediately visible.
6636 -- Either the types are compatible, or one operand is universal
6637 -- (numeric or null).
6639 or else
6640 ((In_Instance or else In_Inlined_Body)
6641 and then
6642 (First_Subtype (T1) = First_Subtype (Etype (R))
6643 or else Nkind (R) = N_Null
6644 or else
6645 (Is_Numeric_Type (T1)
6646 and then Is_Universal_Numeric_Type (Etype (R)))))
6648 -- In Ada 2005, the equality on anonymous access types is declared
6649 -- in Standard, and is always visible.
6651 or else Ekind (T1) = E_Anonymous_Access_Type
6652 then
6653 null;
6655 else
6656 -- Save candidate type for subsequent error message, if any
6658 if not Is_Limited_Type (T1) then
6659 Candidate_Type := T1;
6660 end if;
6662 return;
6663 end if;
6665 -- Ada 2005 (AI-230): Keep restriction imposed by Ada 83 and 95:
6666 -- Do not allow anonymous access types in equality operators.
6668 if Ada_Version < Ada_2005
6669 and then Ekind (T1) = E_Anonymous_Access_Type
6670 then
6671 return;
6672 end if;
6674 -- If the right operand has a type compatible with T1, check for an
6675 -- acceptable interpretation, unless T1 is limited (no predefined
6676 -- equality available), or this is use of a "/=" for a tagged type.
6677 -- In the latter case, possible interpretations of equality need
6678 -- to be considered, we don't want the default inequality declared
6679 -- in Standard to be chosen, and the "/=" will be rewritten as a
6680 -- negation of "=" (see the end of Analyze_Equality_Op). This ensures
6681 -- that rewriting happens during analysis rather than being
6682 -- delayed until expansion (this is needed for ASIS, which only sees
6683 -- the unexpanded tree). Note that if the node is N_Op_Ne, but Op_Id
6684 -- is Name_Op_Eq then we still proceed with the interpretation,
6685 -- because that indicates the potential rewriting case where the
6686 -- interpretation to consider is actually "=" and the node may be
6687 -- about to be rewritten by Analyze_Equality_Op.
6689 if T1 /= Standard_Void_Type
6690 and then Has_Compatible_Type (R, T1)
6692 and then
6693 ((not Is_Limited_Type (T1)
6694 and then not Is_Limited_Composite (T1))
6696 or else
6697 (Is_Array_Type (T1)
6698 and then not Is_Limited_Type (Component_Type (T1))
6699 and then Available_Full_View_Of_Component (T1)))
6701 and then
6702 (Nkind (N) /= N_Op_Ne
6703 or else not Is_Tagged_Type (T1)
6704 or else Chars (Op_Id) = Name_Op_Eq)
6705 then
6706 if Found
6707 and then Base_Type (T1) /= Base_Type (T_F)
6708 then
6709 It := Disambiguate (L, I_F, Index, Any_Type);
6711 if It = No_Interp then
6712 Ambiguous_Operands (N);
6713 Set_Etype (L, Any_Type);
6714 return;
6716 else
6717 T_F := It.Typ;
6718 end if;
6720 else
6721 Found := True;
6722 T_F := T1;
6723 I_F := Index;
6724 end if;
6726 if not Analyzed (L) then
6727 Set_Etype (L, T_F);
6728 end if;
6730 Find_Non_Universal_Interpretations (N, R, Op_Id, T1);
6732 -- Case of operator was not visible, Etype still set to Any_Type
6734 if Etype (N) = Any_Type then
6735 Found := False;
6736 end if;
6738 elsif Scop = Standard_Standard
6739 and then Ekind (T1) = E_Anonymous_Access_Type
6740 then
6741 Found := True;
6742 end if;
6743 end Try_One_Interp;
6745 -- Start of processing for Find_Equality_Types
6747 begin
6748 -- If left operand is aggregate, the right operand has to
6749 -- provide a usable type for it.
6751 if Nkind (L) = N_Aggregate
6752 and then Nkind (R) /= N_Aggregate
6753 then
6754 Find_Equality_Types (L => R, R => L, Op_Id => Op_Id, N => N);
6755 return;
6756 end if;
6758 if Nkind (N) = N_Function_Call
6759 and then Nkind (Name (N)) = N_Expanded_Name
6760 then
6761 Scop := Entity (Prefix (Name (N)));
6763 -- The prefix may be a package renaming, and the subsequent test
6764 -- requires the original package.
6766 if Ekind (Scop) = E_Package
6767 and then Present (Renamed_Entity (Scop))
6768 then
6769 Scop := Renamed_Entity (Scop);
6770 Set_Entity (Prefix (Name (N)), Scop);
6771 end if;
6772 end if;
6774 if not Is_Overloaded (L) then
6775 Try_One_Interp (Etype (L));
6777 else
6778 Get_First_Interp (L, Index, It);
6779 while Present (It.Typ) loop
6780 Try_One_Interp (It.Typ);
6781 Get_Next_Interp (Index, It);
6782 end loop;
6783 end if;
6784 end Find_Equality_Types;
6786 -------------------------
6787 -- Find_Negation_Types --
6788 -------------------------
6790 procedure Find_Negation_Types
6791 (R : Node_Id;
6792 Op_Id : Entity_Id;
6793 N : Node_Id)
6795 Index : Interp_Index;
6796 It : Interp;
6798 begin
6799 if not Is_Overloaded (R) then
6800 if Etype (R) = Universal_Integer then
6801 Add_One_Interp (N, Op_Id, Any_Modular);
6802 elsif Valid_Boolean_Arg (Etype (R)) then
6803 Add_One_Interp (N, Op_Id, Etype (R));
6804 end if;
6806 else
6807 Get_First_Interp (R, Index, It);
6808 while Present (It.Typ) loop
6809 if Valid_Boolean_Arg (It.Typ) then
6810 Add_One_Interp (N, Op_Id, It.Typ);
6811 end if;
6813 Get_Next_Interp (Index, It);
6814 end loop;
6815 end if;
6816 end Find_Negation_Types;
6818 ------------------------------
6819 -- Find_Primitive_Operation --
6820 ------------------------------
6822 function Find_Primitive_Operation (N : Node_Id) return Boolean is
6823 Obj : constant Node_Id := Prefix (N);
6824 Op : constant Node_Id := Selector_Name (N);
6826 Prim : Elmt_Id;
6827 Prims : Elist_Id;
6828 Typ : Entity_Id;
6830 begin
6831 Set_Etype (Op, Any_Type);
6833 if Is_Access_Type (Etype (Obj)) then
6834 Typ := Designated_Type (Etype (Obj));
6835 else
6836 Typ := Etype (Obj);
6837 end if;
6839 if Is_Class_Wide_Type (Typ) then
6840 Typ := Root_Type (Typ);
6841 end if;
6843 Prims := Primitive_Operations (Typ);
6845 Prim := First_Elmt (Prims);
6846 while Present (Prim) loop
6847 if Chars (Node (Prim)) = Chars (Op) then
6848 Add_One_Interp (Op, Node (Prim), Etype (Node (Prim)));
6849 Set_Etype (N, Etype (Node (Prim)));
6850 end if;
6852 Next_Elmt (Prim);
6853 end loop;
6855 -- Now look for class-wide operations of the type or any of its
6856 -- ancestors by iterating over the homonyms of the selector.
6858 declare
6859 Cls_Type : constant Entity_Id := Class_Wide_Type (Typ);
6860 Hom : Entity_Id;
6862 begin
6863 Hom := Current_Entity (Op);
6864 while Present (Hom) loop
6865 if (Ekind (Hom) = E_Procedure
6866 or else
6867 Ekind (Hom) = E_Function)
6868 and then Scope (Hom) = Scope (Typ)
6869 and then Present (First_Formal (Hom))
6870 and then
6871 (Base_Type (Etype (First_Formal (Hom))) = Cls_Type
6872 or else
6873 (Is_Access_Type (Etype (First_Formal (Hom)))
6874 and then
6875 Ekind (Etype (First_Formal (Hom))) =
6876 E_Anonymous_Access_Type
6877 and then
6878 Base_Type
6879 (Designated_Type (Etype (First_Formal (Hom)))) =
6880 Cls_Type))
6881 then
6882 Add_One_Interp (Op, Hom, Etype (Hom));
6883 Set_Etype (N, Etype (Hom));
6884 end if;
6886 Hom := Homonym (Hom);
6887 end loop;
6888 end;
6890 return Etype (Op) /= Any_Type;
6891 end Find_Primitive_Operation;
6893 ----------------------
6894 -- Find_Unary_Types --
6895 ----------------------
6897 procedure Find_Unary_Types
6898 (R : Node_Id;
6899 Op_Id : Entity_Id;
6900 N : Node_Id)
6902 Index : Interp_Index;
6903 It : Interp;
6905 begin
6906 if not Is_Overloaded (R) then
6907 if Is_Numeric_Type (Etype (R)) then
6909 -- In an instance a generic actual may be a numeric type even if
6910 -- the formal in the generic unit was not. In that case, the
6911 -- predefined operator was not a possible interpretation in the
6912 -- generic, and cannot be one in the instance, unless the operator
6913 -- is an actual of an instance.
6915 if In_Instance
6916 and then
6917 not Is_Numeric_Type (Corresponding_Generic_Type (Etype (R)))
6918 then
6919 null;
6920 else
6921 Add_One_Interp (N, Op_Id, Base_Type (Etype (R)));
6922 end if;
6923 end if;
6925 else
6926 Get_First_Interp (R, Index, It);
6927 while Present (It.Typ) loop
6928 if Is_Numeric_Type (It.Typ) then
6929 if In_Instance
6930 and then
6931 not Is_Numeric_Type
6932 (Corresponding_Generic_Type (Etype (It.Typ)))
6933 then
6934 null;
6936 else
6937 Add_One_Interp (N, Op_Id, Base_Type (It.Typ));
6938 end if;
6939 end if;
6941 Get_Next_Interp (Index, It);
6942 end loop;
6943 end if;
6944 end Find_Unary_Types;
6946 ------------------
6947 -- Junk_Operand --
6948 ------------------
6950 function Junk_Operand (N : Node_Id) return Boolean is
6951 Enode : Node_Id;
6953 begin
6954 if Error_Posted (N) then
6955 return False;
6956 end if;
6958 -- Get entity to be tested
6960 if Is_Entity_Name (N)
6961 and then Present (Entity (N))
6962 then
6963 Enode := N;
6965 -- An odd case, a procedure name gets converted to a very peculiar
6966 -- function call, and here is where we detect this happening.
6968 elsif Nkind (N) = N_Function_Call
6969 and then Is_Entity_Name (Name (N))
6970 and then Present (Entity (Name (N)))
6971 then
6972 Enode := Name (N);
6974 -- Another odd case, there are at least some cases of selected
6975 -- components where the selected component is not marked as having
6976 -- an entity, even though the selector does have an entity
6978 elsif Nkind (N) = N_Selected_Component
6979 and then Present (Entity (Selector_Name (N)))
6980 then
6981 Enode := Selector_Name (N);
6983 else
6984 return False;
6985 end if;
6987 -- Now test the entity we got to see if it is a bad case
6989 case Ekind (Entity (Enode)) is
6990 when E_Package =>
6991 Error_Msg_N
6992 ("package name cannot be used as operand", Enode);
6994 when Generic_Unit_Kind =>
6995 Error_Msg_N
6996 ("generic unit name cannot be used as operand", Enode);
6998 when Type_Kind =>
6999 Error_Msg_N
7000 ("subtype name cannot be used as operand", Enode);
7002 when Entry_Kind =>
7003 Error_Msg_N
7004 ("entry name cannot be used as operand", Enode);
7006 when E_Procedure =>
7007 Error_Msg_N
7008 ("procedure name cannot be used as operand", Enode);
7010 when E_Exception =>
7011 Error_Msg_N
7012 ("exception name cannot be used as operand", Enode);
7014 when E_Block
7015 | E_Label
7016 | E_Loop
7018 Error_Msg_N
7019 ("label name cannot be used as operand", Enode);
7021 when others =>
7022 return False;
7023 end case;
7025 return True;
7026 end Junk_Operand;
7028 --------------------
7029 -- Operator_Check --
7030 --------------------
7032 procedure Operator_Check (N : Node_Id) is
7033 begin
7034 Remove_Abstract_Operations (N);
7036 -- Test for case of no interpretation found for operator
7038 if Etype (N) = Any_Type then
7039 declare
7040 L : Node_Id;
7041 R : Node_Id;
7042 Op_Id : Entity_Id := Empty;
7044 begin
7045 R := Right_Opnd (N);
7047 if Nkind (N) in N_Binary_Op then
7048 L := Left_Opnd (N);
7049 else
7050 L := Empty;
7051 end if;
7053 -- If either operand has no type, then don't complain further,
7054 -- since this simply means that we have a propagated error.
7056 if R = Error
7057 or else Etype (R) = Any_Type
7058 or else (Nkind (N) in N_Binary_Op and then Etype (L) = Any_Type)
7059 then
7060 -- For the rather unusual case where one of the operands is
7061 -- a Raise_Expression, whose initial type is Any_Type, use
7062 -- the type of the other operand.
7064 if Nkind (L) = N_Raise_Expression then
7065 Set_Etype (L, Etype (R));
7066 Set_Etype (N, Etype (R));
7068 elsif Nkind (R) = N_Raise_Expression then
7069 Set_Etype (R, Etype (L));
7070 Set_Etype (N, Etype (L));
7071 end if;
7073 return;
7075 -- We explicitly check for the case of concatenation of component
7076 -- with component to avoid reporting spurious matching array types
7077 -- that might happen to be lurking in distant packages (such as
7078 -- run-time packages). This also prevents inconsistencies in the
7079 -- messages for certain ACVC B tests, which can vary depending on
7080 -- types declared in run-time interfaces. Another improvement when
7081 -- aggregates are present is to look for a well-typed operand.
7083 elsif Present (Candidate_Type)
7084 and then (Nkind (N) /= N_Op_Concat
7085 or else Is_Array_Type (Etype (L))
7086 or else Is_Array_Type (Etype (R)))
7087 then
7088 if Nkind (N) = N_Op_Concat then
7089 if Etype (L) /= Any_Composite
7090 and then Is_Array_Type (Etype (L))
7091 then
7092 Candidate_Type := Etype (L);
7094 elsif Etype (R) /= Any_Composite
7095 and then Is_Array_Type (Etype (R))
7096 then
7097 Candidate_Type := Etype (R);
7098 end if;
7099 end if;
7101 Error_Msg_NE -- CODEFIX
7102 ("operator for} is not directly visible!",
7103 N, First_Subtype (Candidate_Type));
7105 declare
7106 U : constant Node_Id :=
7107 Cunit (Get_Source_Unit (Candidate_Type));
7108 begin
7109 if Unit_Is_Visible (U) then
7110 Error_Msg_N -- CODEFIX
7111 ("use clause would make operation legal!", N);
7112 else
7113 Error_Msg_NE -- CODEFIX
7114 ("add with_clause and use_clause for&!",
7115 N, Defining_Entity (Unit (U)));
7116 end if;
7117 end;
7118 return;
7120 -- If either operand is a junk operand (e.g. package name), then
7121 -- post appropriate error messages, but do not complain further.
7123 -- Note that the use of OR in this test instead of OR ELSE is
7124 -- quite deliberate, we may as well check both operands in the
7125 -- binary operator case.
7127 elsif Junk_Operand (R)
7128 or -- really mean OR here and not OR ELSE, see above
7129 (Nkind (N) in N_Binary_Op and then Junk_Operand (L))
7130 then
7131 return;
7133 -- If we have a logical operator, one of whose operands is
7134 -- Boolean, then we know that the other operand cannot resolve to
7135 -- Boolean (since we got no interpretations), but in that case we
7136 -- pretty much know that the other operand should be Boolean, so
7137 -- resolve it that way (generating an error).
7139 elsif Nkind_In (N, N_Op_And, N_Op_Or, N_Op_Xor) then
7140 if Etype (L) = Standard_Boolean then
7141 Resolve (R, Standard_Boolean);
7142 return;
7143 elsif Etype (R) = Standard_Boolean then
7144 Resolve (L, Standard_Boolean);
7145 return;
7146 end if;
7148 -- For an arithmetic operator or comparison operator, if one
7149 -- of the operands is numeric, then we know the other operand
7150 -- is not the same numeric type. If it is a non-numeric type,
7151 -- then probably it is intended to match the other operand.
7153 elsif Nkind_In (N, N_Op_Add,
7154 N_Op_Divide,
7155 N_Op_Ge,
7156 N_Op_Gt,
7157 N_Op_Le)
7158 or else
7159 Nkind_In (N, N_Op_Lt,
7160 N_Op_Mod,
7161 N_Op_Multiply,
7162 N_Op_Rem,
7163 N_Op_Subtract)
7164 then
7165 -- If Allow_Integer_Address is active, check whether the
7166 -- operation becomes legal after converting an operand.
7168 if Is_Numeric_Type (Etype (L))
7169 and then not Is_Numeric_Type (Etype (R))
7170 then
7171 if Address_Integer_Convert_OK (Etype (R), Etype (L)) then
7172 Rewrite (R,
7173 Unchecked_Convert_To (Etype (L), Relocate_Node (R)));
7175 if Nkind_In (N, N_Op_Ge, N_Op_Gt, N_Op_Le, N_Op_Lt) then
7176 Analyze_Comparison_Op (N);
7177 else
7178 Analyze_Arithmetic_Op (N);
7179 end if;
7180 else
7181 Resolve (R, Etype (L));
7182 end if;
7184 return;
7186 elsif Is_Numeric_Type (Etype (R))
7187 and then not Is_Numeric_Type (Etype (L))
7188 then
7189 if Address_Integer_Convert_OK (Etype (L), Etype (R)) then
7190 Rewrite (L,
7191 Unchecked_Convert_To (Etype (R), Relocate_Node (L)));
7193 if Nkind_In (N, N_Op_Ge, N_Op_Gt, N_Op_Le, N_Op_Lt) then
7194 Analyze_Comparison_Op (N);
7195 else
7196 Analyze_Arithmetic_Op (N);
7197 end if;
7199 return;
7201 else
7202 Resolve (L, Etype (R));
7203 end if;
7205 return;
7207 elsif Allow_Integer_Address
7208 and then Is_Descendant_Of_Address (Etype (L))
7209 and then Is_Descendant_Of_Address (Etype (R))
7210 and then not Error_Posted (N)
7211 then
7212 declare
7213 Addr_Type : constant Entity_Id := Etype (L);
7215 begin
7216 Rewrite (L,
7217 Unchecked_Convert_To (
7218 Standard_Integer, Relocate_Node (L)));
7219 Rewrite (R,
7220 Unchecked_Convert_To (
7221 Standard_Integer, Relocate_Node (R)));
7223 if Nkind_In (N, N_Op_Ge, N_Op_Gt, N_Op_Le, N_Op_Lt) then
7224 Analyze_Comparison_Op (N);
7225 else
7226 Analyze_Arithmetic_Op (N);
7227 end if;
7229 -- If this is an operand in an enclosing arithmetic
7230 -- operation, Convert the result as an address so that
7231 -- arithmetic folding of address can continue.
7233 if Nkind (Parent (N)) in N_Op then
7234 Rewrite (N,
7235 Unchecked_Convert_To (Addr_Type, Relocate_Node (N)));
7236 end if;
7238 return;
7239 end;
7241 -- Under relaxed RM semantics silently replace occurrences of
7242 -- null by System.Address_Null.
7244 elsif Null_To_Null_Address_Convert_OK (N) then
7245 Replace_Null_By_Null_Address (N);
7247 if Nkind_In (N, N_Op_Ge, N_Op_Gt, N_Op_Le, N_Op_Lt) then
7248 Analyze_Comparison_Op (N);
7249 else
7250 Analyze_Arithmetic_Op (N);
7251 end if;
7253 return;
7254 end if;
7256 -- Comparisons on A'Access are common enough to deserve a
7257 -- special message.
7259 elsif Nkind_In (N, N_Op_Eq, N_Op_Ne)
7260 and then Ekind (Etype (L)) = E_Access_Attribute_Type
7261 and then Ekind (Etype (R)) = E_Access_Attribute_Type
7262 then
7263 Error_Msg_N
7264 ("two access attributes cannot be compared directly", N);
7265 Error_Msg_N
7266 ("\use qualified expression for one of the operands",
7268 return;
7270 -- Another one for C programmers
7272 elsif Nkind (N) = N_Op_Concat
7273 and then Valid_Boolean_Arg (Etype (L))
7274 and then Valid_Boolean_Arg (Etype (R))
7275 then
7276 Error_Msg_N ("invalid operands for concatenation", N);
7277 Error_Msg_N -- CODEFIX
7278 ("\maybe AND was meant", N);
7279 return;
7281 -- A special case for comparison of access parameter with null
7283 elsif Nkind (N) = N_Op_Eq
7284 and then Is_Entity_Name (L)
7285 and then Nkind (Parent (Entity (L))) = N_Parameter_Specification
7286 and then Nkind (Parameter_Type (Parent (Entity (L)))) =
7287 N_Access_Definition
7288 and then Nkind (R) = N_Null
7289 then
7290 Error_Msg_N ("access parameter is not allowed to be null", L);
7291 Error_Msg_N ("\(call would raise Constraint_Error)", L);
7292 return;
7294 -- Another special case for exponentiation, where the right
7295 -- operand must be Natural, independently of the base.
7297 elsif Nkind (N) = N_Op_Expon
7298 and then Is_Numeric_Type (Etype (L))
7299 and then not Is_Overloaded (R)
7300 and then
7301 First_Subtype (Base_Type (Etype (R))) /= Standard_Integer
7302 and then Base_Type (Etype (R)) /= Universal_Integer
7303 then
7304 if Ada_Version >= Ada_2012
7305 and then Has_Dimension_System (Etype (L))
7306 then
7307 Error_Msg_NE
7308 ("exponent for dimensioned type must be a rational" &
7309 ", found}", R, Etype (R));
7310 else
7311 Error_Msg_NE
7312 ("exponent must be of type Natural, found}", R, Etype (R));
7313 end if;
7315 return;
7317 elsif Nkind_In (N, N_Op_Eq, N_Op_Ne) then
7318 if Address_Integer_Convert_OK (Etype (R), Etype (L)) then
7319 Rewrite (R,
7320 Unchecked_Convert_To (Etype (L), Relocate_Node (R)));
7321 Analyze_Equality_Op (N);
7322 return;
7324 -- Under relaxed RM semantics silently replace occurrences of
7325 -- null by System.Address_Null.
7327 elsif Null_To_Null_Address_Convert_OK (N) then
7328 Replace_Null_By_Null_Address (N);
7329 Analyze_Equality_Op (N);
7330 return;
7331 end if;
7332 end if;
7334 -- If we fall through then just give general message. Note that in
7335 -- the following messages, if the operand is overloaded we choose
7336 -- an arbitrary type to complain about, but that is probably more
7337 -- useful than not giving a type at all.
7339 if Nkind (N) in N_Unary_Op then
7340 Error_Msg_Node_2 := Etype (R);
7341 Error_Msg_N ("operator& not defined for}", N);
7342 return;
7344 else
7345 if Nkind (N) in N_Binary_Op then
7346 if not Is_Overloaded (L)
7347 and then not Is_Overloaded (R)
7348 and then Base_Type (Etype (L)) = Base_Type (Etype (R))
7349 then
7350 Error_Msg_Node_2 := First_Subtype (Etype (R));
7351 Error_Msg_N ("there is no applicable operator& for}", N);
7353 else
7354 -- Another attempt to find a fix: one of the candidate
7355 -- interpretations may not be use-visible. This has
7356 -- already been checked for predefined operators, so
7357 -- we examine only user-defined functions.
7359 Op_Id := Get_Name_Entity_Id (Chars (N));
7361 while Present (Op_Id) loop
7362 if Ekind (Op_Id) /= E_Operator
7363 and then Is_Overloadable (Op_Id)
7364 then
7365 if not Is_Immediately_Visible (Op_Id)
7366 and then not In_Use (Scope (Op_Id))
7367 and then not Is_Abstract_Subprogram (Op_Id)
7368 and then not Is_Hidden (Op_Id)
7369 and then Ekind (Scope (Op_Id)) = E_Package
7370 and then
7371 Has_Compatible_Type
7372 (L, Etype (First_Formal (Op_Id)))
7373 and then Present
7374 (Next_Formal (First_Formal (Op_Id)))
7375 and then
7376 Has_Compatible_Type
7378 Etype (Next_Formal (First_Formal (Op_Id))))
7379 then
7380 Error_Msg_N
7381 ("No legal interpretation for operator&", N);
7382 Error_Msg_NE
7383 ("\use clause on& would make operation legal",
7384 N, Scope (Op_Id));
7385 exit;
7386 end if;
7387 end if;
7389 Op_Id := Homonym (Op_Id);
7390 end loop;
7392 if No (Op_Id) then
7393 Error_Msg_N ("invalid operand types for operator&", N);
7395 if Nkind (N) /= N_Op_Concat then
7396 Error_Msg_NE ("\left operand has}!", N, Etype (L));
7397 Error_Msg_NE ("\right operand has}!", N, Etype (R));
7399 -- For concatenation operators it is more difficult to
7400 -- determine which is the wrong operand. It is worth
7401 -- flagging explicitly an access type, for those who
7402 -- might think that a dereference happens here.
7404 elsif Is_Access_Type (Etype (L)) then
7405 Error_Msg_N ("\left operand is access type", N);
7407 elsif Is_Access_Type (Etype (R)) then
7408 Error_Msg_N ("\right operand is access type", N);
7409 end if;
7410 end if;
7411 end if;
7412 end if;
7413 end if;
7414 end;
7415 end if;
7416 end Operator_Check;
7418 -----------------------------------------
7419 -- Process_Implicit_Dereference_Prefix --
7420 -----------------------------------------
7422 function Process_Implicit_Dereference_Prefix
7423 (E : Entity_Id;
7424 P : Entity_Id) return Entity_Id
7426 Ref : Node_Id;
7427 Typ : constant Entity_Id := Designated_Type (Etype (P));
7429 begin
7430 if Present (E)
7431 and then (Operating_Mode = Check_Semantics or else not Expander_Active)
7432 then
7433 -- We create a dummy reference to E to ensure that the reference is
7434 -- not considered as part of an assignment (an implicit dereference
7435 -- can never assign to its prefix). The Comes_From_Source attribute
7436 -- needs to be propagated for accurate warnings.
7438 Ref := New_Occurrence_Of (E, Sloc (P));
7439 Set_Comes_From_Source (Ref, Comes_From_Source (P));
7440 Generate_Reference (E, Ref);
7441 end if;
7443 -- An implicit dereference is a legal occurrence of an incomplete type
7444 -- imported through a limited_with clause, if the full view is visible.
7446 if From_Limited_With (Typ)
7447 and then not From_Limited_With (Scope (Typ))
7448 and then
7449 (Is_Immediately_Visible (Scope (Typ))
7450 or else
7451 (Is_Child_Unit (Scope (Typ))
7452 and then Is_Visible_Lib_Unit (Scope (Typ))))
7453 then
7454 return Available_View (Typ);
7455 else
7456 return Typ;
7457 end if;
7458 end Process_Implicit_Dereference_Prefix;
7460 --------------------------------
7461 -- Remove_Abstract_Operations --
7462 --------------------------------
7464 procedure Remove_Abstract_Operations (N : Node_Id) is
7465 Abstract_Op : Entity_Id := Empty;
7466 Address_Descendant : Boolean := False;
7467 I : Interp_Index;
7468 It : Interp;
7470 -- AI-310: If overloaded, remove abstract non-dispatching operations. We
7471 -- activate this if either extensions are enabled, or if the abstract
7472 -- operation in question comes from a predefined file. This latter test
7473 -- allows us to use abstract to make operations invisible to users. In
7474 -- particular, if type Address is non-private and abstract subprograms
7475 -- are used to hide its operators, they will be truly hidden.
7477 type Operand_Position is (First_Op, Second_Op);
7478 Univ_Type : constant Entity_Id := Universal_Interpretation (N);
7480 procedure Remove_Address_Interpretations (Op : Operand_Position);
7481 -- Ambiguities may arise when the operands are literal and the address
7482 -- operations in s-auxdec are visible. In that case, remove the
7483 -- interpretation of a literal as Address, to retain the semantics
7484 -- of Address as a private type.
7486 ------------------------------------
7487 -- Remove_Address_Interpretations --
7488 ------------------------------------
7490 procedure Remove_Address_Interpretations (Op : Operand_Position) is
7491 Formal : Entity_Id;
7493 begin
7494 if Is_Overloaded (N) then
7495 Get_First_Interp (N, I, It);
7496 while Present (It.Nam) loop
7497 Formal := First_Entity (It.Nam);
7499 if Op = Second_Op then
7500 Formal := Next_Entity (Formal);
7501 end if;
7503 if Is_Descendant_Of_Address (Etype (Formal)) then
7504 Address_Descendant := True;
7505 Remove_Interp (I);
7506 end if;
7508 Get_Next_Interp (I, It);
7509 end loop;
7510 end if;
7511 end Remove_Address_Interpretations;
7513 -- Start of processing for Remove_Abstract_Operations
7515 begin
7516 if Is_Overloaded (N) then
7517 if Debug_Flag_V then
7518 Write_Str ("Remove_Abstract_Operations: ");
7519 Write_Overloads (N);
7520 end if;
7522 Get_First_Interp (N, I, It);
7524 while Present (It.Nam) loop
7525 if Is_Overloadable (It.Nam)
7526 and then Is_Abstract_Subprogram (It.Nam)
7527 and then not Is_Dispatching_Operation (It.Nam)
7528 then
7529 Abstract_Op := It.Nam;
7531 if Is_Descendant_Of_Address (It.Typ) then
7532 Address_Descendant := True;
7533 Remove_Interp (I);
7534 exit;
7536 -- In Ada 2005, this operation does not participate in overload
7537 -- resolution. If the operation is defined in a predefined
7538 -- unit, it is one of the operations declared abstract in some
7539 -- variants of System, and it must be removed as well.
7541 elsif Ada_Version >= Ada_2005
7542 or else In_Predefined_Unit (It.Nam)
7543 then
7544 Remove_Interp (I);
7545 exit;
7546 end if;
7547 end if;
7549 Get_Next_Interp (I, It);
7550 end loop;
7552 if No (Abstract_Op) then
7554 -- If some interpretation yields an integer type, it is still
7555 -- possible that there are address interpretations. Remove them
7556 -- if one operand is a literal, to avoid spurious ambiguities
7557 -- on systems where Address is a visible integer type.
7559 if Is_Overloaded (N)
7560 and then Nkind (N) in N_Op
7561 and then Is_Integer_Type (Etype (N))
7562 then
7563 if Nkind (N) in N_Binary_Op then
7564 if Nkind (Right_Opnd (N)) = N_Integer_Literal then
7565 Remove_Address_Interpretations (Second_Op);
7567 elsif Nkind (Left_Opnd (N)) = N_Integer_Literal then
7568 Remove_Address_Interpretations (First_Op);
7569 end if;
7570 end if;
7571 end if;
7573 elsif Nkind (N) in N_Op then
7575 -- Remove interpretations that treat literals as addresses. This
7576 -- is never appropriate, even when Address is defined as a visible
7577 -- Integer type. The reason is that we would really prefer Address
7578 -- to behave as a private type, even in this case. If Address is a
7579 -- visible integer type, we get lots of overload ambiguities.
7581 if Nkind (N) in N_Binary_Op then
7582 declare
7583 U1 : constant Boolean :=
7584 Present (Universal_Interpretation (Right_Opnd (N)));
7585 U2 : constant Boolean :=
7586 Present (Universal_Interpretation (Left_Opnd (N)));
7588 begin
7589 if U1 then
7590 Remove_Address_Interpretations (Second_Op);
7591 end if;
7593 if U2 then
7594 Remove_Address_Interpretations (First_Op);
7595 end if;
7597 if not (U1 and U2) then
7599 -- Remove corresponding predefined operator, which is
7600 -- always added to the overload set.
7602 Get_First_Interp (N, I, It);
7603 while Present (It.Nam) loop
7604 if Scope (It.Nam) = Standard_Standard
7605 and then Base_Type (It.Typ) =
7606 Base_Type (Etype (Abstract_Op))
7607 then
7608 Remove_Interp (I);
7609 end if;
7611 Get_Next_Interp (I, It);
7612 end loop;
7614 elsif Is_Overloaded (N)
7615 and then Present (Univ_Type)
7616 then
7617 -- If both operands have a universal interpretation,
7618 -- it is still necessary to remove interpretations that
7619 -- yield Address. Any remaining ambiguities will be
7620 -- removed in Disambiguate.
7622 Get_First_Interp (N, I, It);
7623 while Present (It.Nam) loop
7624 if Is_Descendant_Of_Address (It.Typ) then
7625 Remove_Interp (I);
7627 elsif not Is_Type (It.Nam) then
7628 Set_Entity (N, It.Nam);
7629 end if;
7631 Get_Next_Interp (I, It);
7632 end loop;
7633 end if;
7634 end;
7635 end if;
7637 elsif Nkind (N) = N_Function_Call
7638 and then
7639 (Nkind (Name (N)) = N_Operator_Symbol
7640 or else
7641 (Nkind (Name (N)) = N_Expanded_Name
7642 and then
7643 Nkind (Selector_Name (Name (N))) = N_Operator_Symbol))
7644 then
7646 declare
7647 Arg1 : constant Node_Id := First (Parameter_Associations (N));
7648 U1 : constant Boolean :=
7649 Present (Universal_Interpretation (Arg1));
7650 U2 : constant Boolean :=
7651 Present (Next (Arg1)) and then
7652 Present (Universal_Interpretation (Next (Arg1)));
7654 begin
7655 if U1 then
7656 Remove_Address_Interpretations (First_Op);
7657 end if;
7659 if U2 then
7660 Remove_Address_Interpretations (Second_Op);
7661 end if;
7663 if not (U1 and U2) then
7664 Get_First_Interp (N, I, It);
7665 while Present (It.Nam) loop
7666 if Scope (It.Nam) = Standard_Standard
7667 and then It.Typ = Base_Type (Etype (Abstract_Op))
7668 then
7669 Remove_Interp (I);
7670 end if;
7672 Get_Next_Interp (I, It);
7673 end loop;
7674 end if;
7675 end;
7676 end if;
7678 -- If the removal has left no valid interpretations, emit an error
7679 -- message now and label node as illegal.
7681 if Present (Abstract_Op) then
7682 Get_First_Interp (N, I, It);
7684 if No (It.Nam) then
7686 -- Removal of abstract operation left no viable candidate
7688 Set_Etype (N, Any_Type);
7689 Error_Msg_Sloc := Sloc (Abstract_Op);
7690 Error_Msg_NE
7691 ("cannot call abstract operation& declared#", N, Abstract_Op);
7693 -- In Ada 2005, an abstract operation may disable predefined
7694 -- operators. Since the context is not yet known, we mark the
7695 -- predefined operators as potentially hidden. Do not include
7696 -- predefined operators when addresses are involved since this
7697 -- case is handled separately.
7699 elsif Ada_Version >= Ada_2005 and then not Address_Descendant then
7700 while Present (It.Nam) loop
7701 if Is_Numeric_Type (It.Typ)
7702 and then Scope (It.Typ) = Standard_Standard
7703 then
7704 Set_Abstract_Op (I, Abstract_Op);
7705 end if;
7707 Get_Next_Interp (I, It);
7708 end loop;
7709 end if;
7710 end if;
7712 if Debug_Flag_V then
7713 Write_Str ("Remove_Abstract_Operations done: ");
7714 Write_Overloads (N);
7715 end if;
7716 end if;
7717 end Remove_Abstract_Operations;
7719 ----------------------------
7720 -- Try_Container_Indexing --
7721 ----------------------------
7723 function Try_Container_Indexing
7724 (N : Node_Id;
7725 Prefix : Node_Id;
7726 Exprs : List_Id) return Boolean
7728 Pref_Typ : constant Entity_Id := Etype (Prefix);
7730 function Constant_Indexing_OK return Boolean;
7731 -- Constant_Indexing is legal if there is no Variable_Indexing defined
7732 -- for the type, or else node not a target of assignment, or an actual
7733 -- for an IN OUT or OUT formal (RM 4.1.6 (11)).
7735 function Expr_Matches_In_Formal
7736 (Subp : Entity_Id;
7737 Par : Node_Id) return Boolean;
7738 -- Find formal corresponding to given indexed component that is an
7739 -- actual in a call. Note that the enclosing subprogram call has not
7740 -- been analyzed yet, and the parameter list is not normalized, so
7741 -- that if the argument is a parameter association we must match it
7742 -- by name and not by position.
7744 function Find_Indexing_Operations
7745 (T : Entity_Id;
7746 Nam : Name_Id;
7747 Is_Constant : Boolean) return Node_Id;
7748 -- Return a reference to the primitive operation of type T denoted by
7749 -- name Nam. If the operation is overloaded, the reference carries all
7750 -- interpretations. Flag Is_Constant should be set when the context is
7751 -- constant indexing.
7753 --------------------------
7754 -- Constant_Indexing_OK --
7755 --------------------------
7757 function Constant_Indexing_OK return Boolean is
7758 Par : Node_Id;
7760 begin
7761 if No (Find_Value_Of_Aspect (Pref_Typ, Aspect_Variable_Indexing)) then
7762 return True;
7764 elsif not Is_Variable (Prefix) then
7765 return True;
7766 end if;
7768 Par := N;
7769 while Present (Par) loop
7770 if Nkind (Parent (Par)) = N_Assignment_Statement
7771 and then Par = Name (Parent (Par))
7772 then
7773 return False;
7775 -- The call may be overloaded, in which case we assume that its
7776 -- resolution does not depend on the type of the parameter that
7777 -- includes the indexing operation.
7779 elsif Nkind_In (Parent (Par), N_Function_Call,
7780 N_Procedure_Call_Statement)
7781 and then Is_Entity_Name (Name (Parent (Par)))
7782 then
7783 declare
7784 Proc : Entity_Id;
7786 begin
7787 -- We should look for an interpretation with the proper
7788 -- number of formals, and determine whether it is an
7789 -- In_Parameter, but for now we examine the formal that
7790 -- corresponds to the indexing, and assume that variable
7791 -- indexing is required if some interpretation has an
7792 -- assignable formal at that position. Still does not
7793 -- cover the most complex cases ???
7795 if Is_Overloaded (Name (Parent (Par))) then
7796 declare
7797 Proc : constant Node_Id := Name (Parent (Par));
7798 I : Interp_Index;
7799 It : Interp;
7801 begin
7802 Get_First_Interp (Proc, I, It);
7803 while Present (It.Nam) loop
7804 if not Expr_Matches_In_Formal (It.Nam, Par) then
7805 return False;
7806 end if;
7808 Get_Next_Interp (I, It);
7809 end loop;
7810 end;
7812 -- All interpretations have a matching in-mode formal
7814 return True;
7816 else
7817 Proc := Entity (Name (Parent (Par)));
7819 -- If this is an indirect call, get formals from
7820 -- designated type.
7822 if Is_Access_Subprogram_Type (Etype (Proc)) then
7823 Proc := Designated_Type (Etype (Proc));
7824 end if;
7825 end if;
7827 return Expr_Matches_In_Formal (Proc, Par);
7828 end;
7830 elsif Nkind (Parent (Par)) = N_Object_Renaming_Declaration then
7831 return False;
7833 -- If the indexed component is a prefix it may be the first actual
7834 -- of a prefixed call. Retrieve the called entity, if any, and
7835 -- check its first formal. Determine if the context is a procedure
7836 -- or function call.
7838 elsif Nkind (Parent (Par)) = N_Selected_Component then
7839 declare
7840 Sel : constant Node_Id := Selector_Name (Parent (Par));
7841 Nam : constant Entity_Id := Current_Entity (Sel);
7843 begin
7844 if Present (Nam) and then Is_Overloadable (Nam) then
7845 if Nkind (Parent (Parent (Par))) =
7846 N_Procedure_Call_Statement
7847 then
7848 return False;
7850 elsif Ekind (Nam) = E_Function
7851 and then Present (First_Formal (Nam))
7852 then
7853 return Ekind (First_Formal (Nam)) = E_In_Parameter;
7854 end if;
7855 end if;
7856 end;
7858 elsif Nkind (Par) in N_Op then
7859 return True;
7860 end if;
7862 Par := Parent (Par);
7863 end loop;
7865 -- In all other cases, constant indexing is legal
7867 return True;
7868 end Constant_Indexing_OK;
7870 ----------------------------
7871 -- Expr_Matches_In_Formal --
7872 ----------------------------
7874 function Expr_Matches_In_Formal
7875 (Subp : Entity_Id;
7876 Par : Node_Id) return Boolean
7878 Actual : Node_Id;
7879 Formal : Node_Id;
7881 begin
7882 Formal := First_Formal (Subp);
7883 Actual := First (Parameter_Associations ((Parent (Par))));
7885 if Nkind (Par) /= N_Parameter_Association then
7887 -- Match by position
7889 while Present (Actual) and then Present (Formal) loop
7890 exit when Actual = Par;
7891 Next (Actual);
7893 if Present (Formal) then
7894 Next_Formal (Formal);
7896 -- Otherwise this is a parameter mismatch, the error is
7897 -- reported elsewhere, or else variable indexing is implied.
7899 else
7900 return False;
7901 end if;
7902 end loop;
7904 else
7905 -- Match by name
7907 while Present (Formal) loop
7908 exit when Chars (Formal) = Chars (Selector_Name (Par));
7909 Next_Formal (Formal);
7911 if No (Formal) then
7912 return False;
7913 end if;
7914 end loop;
7915 end if;
7917 return Present (Formal) and then Ekind (Formal) = E_In_Parameter;
7918 end Expr_Matches_In_Formal;
7920 ------------------------------
7921 -- Find_Indexing_Operations --
7922 ------------------------------
7924 function Find_Indexing_Operations
7925 (T : Entity_Id;
7926 Nam : Name_Id;
7927 Is_Constant : Boolean) return Node_Id
7929 procedure Inspect_Declarations
7930 (Typ : Entity_Id;
7931 Ref : in out Node_Id);
7932 -- Traverse the declarative list where type Typ resides and collect
7933 -- all suitable interpretations in node Ref.
7935 procedure Inspect_Primitives
7936 (Typ : Entity_Id;
7937 Ref : in out Node_Id);
7938 -- Traverse the list of primitive operations of type Typ and collect
7939 -- all suitable interpretations in node Ref.
7941 function Is_OK_Candidate
7942 (Subp_Id : Entity_Id;
7943 Typ : Entity_Id) return Boolean;
7944 -- Determine whether subprogram Subp_Id is a suitable indexing
7945 -- operation for type Typ. To qualify as such, the subprogram must
7946 -- be a function, have at least two parameters, and the type of the
7947 -- first parameter must be either Typ, or Typ'Class, or access [to
7948 -- constant] with designated type Typ or Typ'Class.
7950 procedure Record_Interp (Subp_Id : Entity_Id; Ref : in out Node_Id);
7951 -- Store subprogram Subp_Id as an interpretation in node Ref
7953 --------------------------
7954 -- Inspect_Declarations --
7955 --------------------------
7957 procedure Inspect_Declarations
7958 (Typ : Entity_Id;
7959 Ref : in out Node_Id)
7961 Typ_Decl : constant Node_Id := Declaration_Node (Typ);
7962 Decl : Node_Id;
7963 Subp_Id : Entity_Id;
7965 begin
7966 -- Ensure that the routine is not called with itypes, which lack a
7967 -- declarative node.
7969 pragma Assert (Present (Typ_Decl));
7970 pragma Assert (Is_List_Member (Typ_Decl));
7972 Decl := First (List_Containing (Typ_Decl));
7973 while Present (Decl) loop
7974 if Nkind (Decl) = N_Subprogram_Declaration then
7975 Subp_Id := Defining_Entity (Decl);
7977 if Is_OK_Candidate (Subp_Id, Typ) then
7978 Record_Interp (Subp_Id, Ref);
7979 end if;
7980 end if;
7982 Next (Decl);
7983 end loop;
7984 end Inspect_Declarations;
7986 ------------------------
7987 -- Inspect_Primitives --
7988 ------------------------
7990 procedure Inspect_Primitives
7991 (Typ : Entity_Id;
7992 Ref : in out Node_Id)
7994 Prim_Elmt : Elmt_Id;
7995 Prim_Id : Entity_Id;
7997 begin
7998 Prim_Elmt := First_Elmt (Primitive_Operations (Typ));
7999 while Present (Prim_Elmt) loop
8000 Prim_Id := Node (Prim_Elmt);
8002 if Is_OK_Candidate (Prim_Id, Typ) then
8003 Record_Interp (Prim_Id, Ref);
8004 end if;
8006 Next_Elmt (Prim_Elmt);
8007 end loop;
8008 end Inspect_Primitives;
8010 ---------------------
8011 -- Is_OK_Candidate --
8012 ---------------------
8014 function Is_OK_Candidate
8015 (Subp_Id : Entity_Id;
8016 Typ : Entity_Id) return Boolean
8018 Formal : Entity_Id;
8019 Formal_Typ : Entity_Id;
8020 Param_Typ : Node_Id;
8022 begin
8023 -- To classify as a suitable candidate, the subprogram must be a
8024 -- function whose name matches the argument of aspect Constant or
8025 -- Variable_Indexing.
8027 if Ekind (Subp_Id) = E_Function and then Chars (Subp_Id) = Nam then
8028 Formal := First_Formal (Subp_Id);
8030 -- The candidate requires at least two parameters
8032 if Present (Formal) and then Present (Next_Formal (Formal)) then
8033 Formal_Typ := Empty;
8034 Param_Typ := Parameter_Type (Parent (Formal));
8036 -- Use the designated type when the first parameter is of an
8037 -- access type.
8039 if Nkind (Param_Typ) = N_Access_Definition
8040 and then Present (Subtype_Mark (Param_Typ))
8041 then
8042 -- When the context is a constant indexing, the access
8043 -- definition must be access-to-constant. This does not
8044 -- apply to variable indexing.
8046 if not Is_Constant
8047 or else Constant_Present (Param_Typ)
8048 then
8049 Formal_Typ := Etype (Subtype_Mark (Param_Typ));
8050 end if;
8052 -- Otherwise use the parameter type
8054 else
8055 Formal_Typ := Etype (Param_Typ);
8056 end if;
8058 if Present (Formal_Typ) then
8060 -- Use the specific type when the parameter type is
8061 -- class-wide.
8063 if Is_Class_Wide_Type (Formal_Typ) then
8064 Formal_Typ := Etype (Base_Type (Formal_Typ));
8065 end if;
8067 -- Use the full view when the parameter type is private
8068 -- or incomplete.
8070 if Is_Incomplete_Or_Private_Type (Formal_Typ)
8071 and then Present (Full_View (Formal_Typ))
8072 then
8073 Formal_Typ := Full_View (Formal_Typ);
8074 end if;
8076 -- The type of the first parameter must denote the type
8077 -- of the container or acts as its ancestor type.
8079 return
8080 Formal_Typ = Typ
8081 or else Is_Ancestor (Formal_Typ, Typ);
8082 end if;
8083 end if;
8084 end if;
8086 return False;
8087 end Is_OK_Candidate;
8089 -------------------
8090 -- Record_Interp --
8091 -------------------
8093 procedure Record_Interp (Subp_Id : Entity_Id; Ref : in out Node_Id) is
8094 begin
8095 if Present (Ref) then
8096 Add_One_Interp (Ref, Subp_Id, Etype (Subp_Id));
8098 -- Otherwise this is the first interpretation. Create a reference
8099 -- where all remaining interpretations will be collected.
8101 else
8102 Ref := New_Occurrence_Of (Subp_Id, Sloc (T));
8103 end if;
8104 end Record_Interp;
8106 -- Local variables
8108 Ref : Node_Id;
8109 Typ : Entity_Id;
8111 -- Start of processing for Find_Indexing_Operations
8113 begin
8114 Typ := T;
8116 -- Use the specific type when the parameter type is class-wide
8118 if Is_Class_Wide_Type (Typ) then
8119 Typ := Root_Type (Typ);
8120 end if;
8122 Ref := Empty;
8123 Typ := Underlying_Type (Base_Type (Typ));
8125 Inspect_Primitives (Typ, Ref);
8127 -- Now look for explicit declarations of an indexing operation.
8128 -- If the type is private the operation may be declared in the
8129 -- visible part that contains the partial view.
8131 if Is_Private_Type (T) then
8132 Inspect_Declarations (T, Ref);
8133 end if;
8135 Inspect_Declarations (Typ, Ref);
8137 return Ref;
8138 end Find_Indexing_Operations;
8140 -- Local variables
8142 Loc : constant Source_Ptr := Sloc (N);
8143 Assoc : List_Id;
8144 C_Type : Entity_Id;
8145 Func : Entity_Id;
8146 Func_Name : Node_Id;
8147 Indexing : Node_Id;
8149 Is_Constant_Indexing : Boolean := False;
8150 -- This flag reflects the nature of the container indexing. Note that
8151 -- the context may be suited for constant indexing, but the type may
8152 -- lack a Constant_Indexing annotation.
8154 -- Start of processing for Try_Container_Indexing
8156 begin
8157 -- Node may have been analyzed already when testing for a prefixed
8158 -- call, in which case do not redo analysis.
8160 if Present (Generalized_Indexing (N)) then
8161 return True;
8162 end if;
8164 C_Type := Pref_Typ;
8166 -- If indexing a class-wide container, obtain indexing primitive from
8167 -- specific type.
8169 if Is_Class_Wide_Type (C_Type) then
8170 C_Type := Etype (Base_Type (C_Type));
8171 end if;
8173 -- Check whether the type has a specified indexing aspect
8175 Func_Name := Empty;
8177 -- The context is suitable for constant indexing, so obtain the name of
8178 -- the indexing function from aspect Constant_Indexing.
8180 if Constant_Indexing_OK then
8181 Func_Name :=
8182 Find_Value_Of_Aspect (Pref_Typ, Aspect_Constant_Indexing);
8183 end if;
8185 if Present (Func_Name) then
8186 Is_Constant_Indexing := True;
8188 -- Otherwise attempt variable indexing
8190 else
8191 Func_Name :=
8192 Find_Value_Of_Aspect (Pref_Typ, Aspect_Variable_Indexing);
8193 end if;
8195 -- The type is not subject to either form of indexing, therefore the
8196 -- indexed component does not denote container indexing. If this is a
8197 -- true error, it is diagnosed by the caller.
8199 if No (Func_Name) then
8201 -- The prefix itself may be an indexing of a container. Rewrite it
8202 -- as such and retry.
8204 if Has_Implicit_Dereference (Pref_Typ) then
8205 Build_Explicit_Dereference (Prefix, First_Discriminant (Pref_Typ));
8206 return Try_Container_Indexing (N, Prefix, Exprs);
8208 -- Otherwise this is definitely not container indexing
8210 else
8211 return False;
8212 end if;
8214 -- If the container type is derived from another container type, the
8215 -- value of the inherited aspect is the Reference operation declared
8216 -- for the parent type.
8218 -- However, Reference is also a primitive operation of the type, and the
8219 -- inherited operation has a different signature. We retrieve the right
8220 -- ones (the function may be overloaded) from the list of primitive
8221 -- operations of the derived type.
8223 -- Note that predefined containers are typically all derived from one of
8224 -- the Controlled types. The code below is motivated by containers that
8225 -- are derived from other types with a Reference aspect.
8227 elsif Is_Derived_Type (C_Type)
8228 and then Etype (First_Formal (Entity (Func_Name))) /= Pref_Typ
8229 then
8230 Func_Name :=
8231 Find_Indexing_Operations
8232 (T => C_Type,
8233 Nam => Chars (Func_Name),
8234 Is_Constant => Is_Constant_Indexing);
8235 end if;
8237 Assoc := New_List (Relocate_Node (Prefix));
8239 -- A generalized indexing may have nore than one index expression, so
8240 -- transfer all of them to the argument list to be used in the call.
8241 -- Note that there may be named associations, in which case the node
8242 -- was rewritten earlier as a call, and has been transformed back into
8243 -- an indexed expression to share the following processing.
8245 -- The generalized indexing node is the one on which analysis and
8246 -- resolution take place. Before expansion the original node is replaced
8247 -- with the generalized indexing node, which is a call, possibly with a
8248 -- dereference operation.
8250 if Comes_From_Source (N) then
8251 Check_Compiler_Unit ("generalized indexing", N);
8252 end if;
8254 -- Create argument list for function call that represents generalized
8255 -- indexing. Note that indices (i.e. actuals) may themselves be
8256 -- overloaded.
8258 declare
8259 Arg : Node_Id;
8260 New_Arg : Node_Id;
8262 begin
8263 Arg := First (Exprs);
8264 while Present (Arg) loop
8265 New_Arg := Relocate_Node (Arg);
8267 -- The arguments can be parameter associations, in which case the
8268 -- explicit actual parameter carries the overloadings.
8270 if Nkind (New_Arg) /= N_Parameter_Association then
8271 Save_Interps (Arg, New_Arg);
8272 end if;
8274 Append (New_Arg, Assoc);
8275 Next (Arg);
8276 end loop;
8277 end;
8279 if not Is_Overloaded (Func_Name) then
8280 Func := Entity (Func_Name);
8282 Indexing :=
8283 Make_Function_Call (Loc,
8284 Name => New_Occurrence_Of (Func, Loc),
8285 Parameter_Associations => Assoc);
8287 Set_Parent (Indexing, Parent (N));
8288 Set_Generalized_Indexing (N, Indexing);
8289 Analyze (Indexing);
8290 Set_Etype (N, Etype (Indexing));
8292 -- If the return type of the indexing function is a reference type,
8293 -- add the dereference as a possible interpretation. Note that the
8294 -- indexing aspect may be a function that returns the element type
8295 -- with no intervening implicit dereference, and that the reference
8296 -- discriminant is not the first discriminant.
8298 if Has_Discriminants (Etype (Func)) then
8299 Check_Implicit_Dereference (N, Etype (Func));
8300 end if;
8302 else
8303 -- If there are multiple indexing functions, build a function call
8304 -- and analyze it for each of the possible interpretations.
8306 Indexing :=
8307 Make_Function_Call (Loc,
8308 Name =>
8309 Make_Identifier (Loc, Chars (Func_Name)),
8310 Parameter_Associations => Assoc);
8311 Set_Parent (Indexing, Parent (N));
8312 Set_Generalized_Indexing (N, Indexing);
8313 Set_Etype (N, Any_Type);
8314 Set_Etype (Name (Indexing), Any_Type);
8316 declare
8317 I : Interp_Index;
8318 It : Interp;
8319 Success : Boolean;
8321 begin
8322 Get_First_Interp (Func_Name, I, It);
8323 Set_Etype (Indexing, Any_Type);
8325 -- Analyze each candidate function with the given actuals
8327 while Present (It.Nam) loop
8328 Analyze_One_Call (Indexing, It.Nam, False, Success);
8329 Get_Next_Interp (I, It);
8330 end loop;
8332 -- If there are several successful candidates, resolution will
8333 -- be by result. Mark the interpretations of the function name
8334 -- itself.
8336 if Is_Overloaded (Indexing) then
8337 Get_First_Interp (Indexing, I, It);
8339 while Present (It.Nam) loop
8340 Add_One_Interp (Name (Indexing), It.Nam, It.Typ);
8341 Get_Next_Interp (I, It);
8342 end loop;
8344 else
8345 Set_Etype (Name (Indexing), Etype (Indexing));
8346 end if;
8348 -- Now add the candidate interpretations to the indexing node
8349 -- itself, to be replaced later by the function call.
8351 if Is_Overloaded (Name (Indexing)) then
8352 Get_First_Interp (Name (Indexing), I, It);
8354 while Present (It.Nam) loop
8355 Add_One_Interp (N, It.Nam, It.Typ);
8357 -- Add dereference interpretation if the result type has
8358 -- implicit reference discriminants.
8360 if Has_Discriminants (Etype (It.Nam)) then
8361 Check_Implicit_Dereference (N, Etype (It.Nam));
8362 end if;
8364 Get_Next_Interp (I, It);
8365 end loop;
8367 else
8368 Set_Etype (N, Etype (Name (Indexing)));
8369 if Has_Discriminants (Etype (N)) then
8370 Check_Implicit_Dereference (N, Etype (N));
8371 end if;
8372 end if;
8373 end;
8374 end if;
8376 if Etype (Indexing) = Any_Type then
8377 Error_Msg_NE
8378 ("container cannot be indexed with&", N, Etype (First (Exprs)));
8379 Rewrite (N, New_Occurrence_Of (Any_Id, Loc));
8380 end if;
8382 return True;
8383 end Try_Container_Indexing;
8385 -----------------------
8386 -- Try_Indirect_Call --
8387 -----------------------
8389 function Try_Indirect_Call
8390 (N : Node_Id;
8391 Nam : Entity_Id;
8392 Typ : Entity_Id) return Boolean
8394 Actual : Node_Id;
8395 Formal : Entity_Id;
8397 Call_OK : Boolean;
8398 pragma Warnings (Off, Call_OK);
8400 begin
8401 Normalize_Actuals (N, Designated_Type (Typ), False, Call_OK);
8403 Actual := First_Actual (N);
8404 Formal := First_Formal (Designated_Type (Typ));
8405 while Present (Actual) and then Present (Formal) loop
8406 if not Has_Compatible_Type (Actual, Etype (Formal)) then
8407 return False;
8408 end if;
8410 Next (Actual);
8411 Next_Formal (Formal);
8412 end loop;
8414 if No (Actual) and then No (Formal) then
8415 Add_One_Interp (N, Nam, Etype (Designated_Type (Typ)));
8417 -- Nam is a candidate interpretation for the name in the call,
8418 -- if it is not an indirect call.
8420 if not Is_Type (Nam)
8421 and then Is_Entity_Name (Name (N))
8422 then
8423 Set_Entity (Name (N), Nam);
8424 end if;
8426 return True;
8428 else
8429 return False;
8430 end if;
8431 end Try_Indirect_Call;
8433 ----------------------
8434 -- Try_Indexed_Call --
8435 ----------------------
8437 function Try_Indexed_Call
8438 (N : Node_Id;
8439 Nam : Entity_Id;
8440 Typ : Entity_Id;
8441 Skip_First : Boolean) return Boolean
8443 Loc : constant Source_Ptr := Sloc (N);
8444 Actuals : constant List_Id := Parameter_Associations (N);
8445 Actual : Node_Id;
8446 Index : Entity_Id;
8448 begin
8449 Actual := First (Actuals);
8451 -- If the call was originally written in prefix form, skip the first
8452 -- actual, which is obviously not defaulted.
8454 if Skip_First then
8455 Next (Actual);
8456 end if;
8458 Index := First_Index (Typ);
8459 while Present (Actual) and then Present (Index) loop
8461 -- If the parameter list has a named association, the expression
8462 -- is definitely a call and not an indexed component.
8464 if Nkind (Actual) = N_Parameter_Association then
8465 return False;
8466 end if;
8468 if Is_Entity_Name (Actual)
8469 and then Is_Type (Entity (Actual))
8470 and then No (Next (Actual))
8471 then
8472 -- A single actual that is a type name indicates a slice if the
8473 -- type is discrete, and an error otherwise.
8475 if Is_Discrete_Type (Entity (Actual)) then
8476 Rewrite (N,
8477 Make_Slice (Loc,
8478 Prefix =>
8479 Make_Function_Call (Loc,
8480 Name => Relocate_Node (Name (N))),
8481 Discrete_Range =>
8482 New_Occurrence_Of (Entity (Actual), Sloc (Actual))));
8484 Analyze (N);
8486 else
8487 Error_Msg_N ("invalid use of type in expression", Actual);
8488 Set_Etype (N, Any_Type);
8489 end if;
8491 return True;
8493 elsif not Has_Compatible_Type (Actual, Etype (Index)) then
8494 return False;
8495 end if;
8497 Next (Actual);
8498 Next_Index (Index);
8499 end loop;
8501 if No (Actual) and then No (Index) then
8502 Add_One_Interp (N, Nam, Component_Type (Typ));
8504 -- Nam is a candidate interpretation for the name in the call,
8505 -- if it is not an indirect call.
8507 if not Is_Type (Nam)
8508 and then Is_Entity_Name (Name (N))
8509 then
8510 Set_Entity (Name (N), Nam);
8511 end if;
8513 return True;
8514 else
8515 return False;
8516 end if;
8517 end Try_Indexed_Call;
8519 --------------------------
8520 -- Try_Object_Operation --
8521 --------------------------
8523 function Try_Object_Operation
8524 (N : Node_Id; CW_Test_Only : Boolean := False) return Boolean
8526 K : constant Node_Kind := Nkind (Parent (N));
8527 Is_Subprg_Call : constant Boolean := K in N_Subprogram_Call;
8528 Loc : constant Source_Ptr := Sloc (N);
8529 Obj : constant Node_Id := Prefix (N);
8531 Subprog : constant Node_Id :=
8532 Make_Identifier (Sloc (Selector_Name (N)),
8533 Chars => Chars (Selector_Name (N)));
8534 -- Identifier on which possible interpretations will be collected
8536 Report_Error : Boolean := False;
8537 -- If no candidate interpretation matches the context, redo analysis
8538 -- with Report_Error True to provide additional information.
8540 Actual : Node_Id;
8541 Candidate : Entity_Id := Empty;
8542 New_Call_Node : Node_Id := Empty;
8543 Node_To_Replace : Node_Id;
8544 Obj_Type : Entity_Id := Etype (Obj);
8545 Success : Boolean := False;
8547 procedure Complete_Object_Operation
8548 (Call_Node : Node_Id;
8549 Node_To_Replace : Node_Id);
8550 -- Make Subprog the name of Call_Node, replace Node_To_Replace with
8551 -- Call_Node, insert the object (or its dereference) as the first actual
8552 -- in the call, and complete the analysis of the call.
8554 procedure Report_Ambiguity (Op : Entity_Id);
8555 -- If a prefixed procedure call is ambiguous, indicate whether the call
8556 -- includes an implicit dereference or an implicit 'Access.
8558 procedure Transform_Object_Operation
8559 (Call_Node : out Node_Id;
8560 Node_To_Replace : out Node_Id);
8561 -- Transform Obj.Operation (X, Y,,) into Operation (Obj, X, Y ..)
8562 -- Call_Node is the resulting subprogram call, Node_To_Replace is
8563 -- either N or the parent of N, and Subprog is a reference to the
8564 -- subprogram we are trying to match.
8566 function Try_Class_Wide_Operation
8567 (Call_Node : Node_Id;
8568 Node_To_Replace : Node_Id) return Boolean;
8569 -- Traverse all ancestor types looking for a class-wide subprogram for
8570 -- which the current operation is a valid non-dispatching call.
8572 procedure Try_One_Prefix_Interpretation (T : Entity_Id);
8573 -- If prefix is overloaded, its interpretation may include different
8574 -- tagged types, and we must examine the primitive operations and the
8575 -- class-wide operations of each in order to find candidate
8576 -- interpretations for the call as a whole.
8578 function Try_Primitive_Operation
8579 (Call_Node : Node_Id;
8580 Node_To_Replace : Node_Id) return Boolean;
8581 -- Traverse the list of primitive subprograms looking for a dispatching
8582 -- operation for which the current node is a valid call.
8584 function Valid_Candidate
8585 (Success : Boolean;
8586 Call : Node_Id;
8587 Subp : Entity_Id) return Entity_Id;
8588 -- If the subprogram is a valid interpretation, record it, and add to
8589 -- the list of interpretations of Subprog. Otherwise return Empty.
8591 -------------------------------
8592 -- Complete_Object_Operation --
8593 -------------------------------
8595 procedure Complete_Object_Operation
8596 (Call_Node : Node_Id;
8597 Node_To_Replace : Node_Id)
8599 Control : constant Entity_Id := First_Formal (Entity (Subprog));
8600 Formal_Type : constant Entity_Id := Etype (Control);
8601 First_Actual : Node_Id;
8603 begin
8604 -- Place the name of the operation, with its interpretations,
8605 -- on the rewritten call.
8607 Set_Name (Call_Node, Subprog);
8609 First_Actual := First (Parameter_Associations (Call_Node));
8611 -- For cross-reference purposes, treat the new node as being in the
8612 -- source if the original one is. Set entity and type, even though
8613 -- they may be overwritten during resolution if overloaded.
8615 Set_Comes_From_Source (Subprog, Comes_From_Source (N));
8616 Set_Comes_From_Source (Call_Node, Comes_From_Source (N));
8618 if Nkind (N) = N_Selected_Component
8619 and then not Inside_A_Generic
8620 then
8621 Set_Entity (Selector_Name (N), Entity (Subprog));
8622 Set_Etype (Selector_Name (N), Etype (Entity (Subprog)));
8623 end if;
8625 -- If need be, rewrite first actual as an explicit dereference. If
8626 -- the call is overloaded, the rewriting can only be done once the
8627 -- primitive operation is identified.
8629 if Is_Overloaded (Subprog) then
8631 -- The prefix itself may be overloaded, and its interpretations
8632 -- must be propagated to the new actual in the call.
8634 if Is_Overloaded (Obj) then
8635 Save_Interps (Obj, First_Actual);
8636 end if;
8638 Rewrite (First_Actual, Obj);
8640 elsif not Is_Access_Type (Formal_Type)
8641 and then Is_Access_Type (Etype (Obj))
8642 then
8643 Rewrite (First_Actual,
8644 Make_Explicit_Dereference (Sloc (Obj), Obj));
8645 Analyze (First_Actual);
8647 -- If we need to introduce an explicit dereference, verify that
8648 -- the resulting actual is compatible with the mode of the formal.
8650 if Ekind (First_Formal (Entity (Subprog))) /= E_In_Parameter
8651 and then Is_Access_Constant (Etype (Obj))
8652 then
8653 Error_Msg_NE
8654 ("expect variable in call to&", Prefix (N), Entity (Subprog));
8655 end if;
8657 -- Conversely, if the formal is an access parameter and the object is
8658 -- not an access type or a reference type (i.e. a type with the
8659 -- Implicit_Dereference aspect specified), replace the actual with a
8660 -- 'Access reference. Its analysis will check that the object is
8661 -- aliased.
8663 elsif Is_Access_Type (Formal_Type)
8664 and then not Is_Access_Type (Etype (Obj))
8665 and then
8666 (not Has_Implicit_Dereference (Etype (Obj))
8667 or else
8668 not Is_Access_Type (Designated_Type (Etype
8669 (Get_Reference_Discriminant (Etype (Obj))))))
8670 then
8671 -- A special case: A.all'Access is illegal if A is an access to a
8672 -- constant and the context requires an access to a variable.
8674 if not Is_Access_Constant (Formal_Type) then
8675 if (Nkind (Obj) = N_Explicit_Dereference
8676 and then Is_Access_Constant (Etype (Prefix (Obj))))
8677 or else not Is_Variable (Obj)
8678 then
8679 Error_Msg_NE
8680 ("actual for & must be a variable", Obj, Control);
8681 end if;
8682 end if;
8684 Rewrite (First_Actual,
8685 Make_Attribute_Reference (Loc,
8686 Attribute_Name => Name_Access,
8687 Prefix => Relocate_Node (Obj)));
8689 -- If the object is not overloaded verify that taking access of
8690 -- it is legal. Otherwise check is made during resolution.
8692 if not Is_Overloaded (Obj)
8693 and then not Is_Aliased_View (Obj)
8694 then
8695 Error_Msg_NE
8696 ("object in prefixed call to & must be aliased "
8697 & "(RM 4.1.3 (13 1/2))", Prefix (First_Actual), Subprog);
8698 end if;
8700 Analyze (First_Actual);
8702 else
8703 if Is_Overloaded (Obj) then
8704 Save_Interps (Obj, First_Actual);
8705 end if;
8707 Rewrite (First_Actual, Obj);
8708 end if;
8710 -- The operation is obtained from the dispatch table and not by
8711 -- visibility, and may be declared in a unit that is not explicitly
8712 -- referenced in the source, but is nevertheless required in the
8713 -- context of the current unit. Indicate that operation and its scope
8714 -- are referenced, to prevent spurious and misleading warnings. If
8715 -- the operation is overloaded, all primitives are in the same scope
8716 -- and we can use any of them.
8718 Set_Referenced (Entity (Subprog), True);
8719 Set_Referenced (Scope (Entity (Subprog)), True);
8721 Rewrite (Node_To_Replace, Call_Node);
8723 -- Propagate the interpretations collected in subprog to the new
8724 -- function call node, to be resolved from context.
8726 if Is_Overloaded (Subprog) then
8727 Save_Interps (Subprog, Node_To_Replace);
8729 else
8730 -- The type of the subprogram may be a limited view obtained
8731 -- transitively from another unit. If full view is available,
8732 -- use it to analyze call. If there is no nonlimited view, then
8733 -- this is diagnosed when analyzing the rewritten call.
8735 declare
8736 T : constant Entity_Id := Etype (Subprog);
8737 begin
8738 if From_Limited_With (T) then
8739 Set_Etype (Entity (Subprog), Available_View (T));
8740 end if;
8741 end;
8743 Analyze (Node_To_Replace);
8745 -- If the operation has been rewritten into a call, which may get
8746 -- subsequently an explicit dereference, preserve the type on the
8747 -- original node (selected component or indexed component) for
8748 -- subsequent legality tests, e.g. Is_Variable. which examines
8749 -- the original node.
8751 if Nkind (Node_To_Replace) = N_Function_Call then
8752 Set_Etype
8753 (Original_Node (Node_To_Replace), Etype (Node_To_Replace));
8754 end if;
8755 end if;
8756 end Complete_Object_Operation;
8758 ----------------------
8759 -- Report_Ambiguity --
8760 ----------------------
8762 procedure Report_Ambiguity (Op : Entity_Id) is
8763 Access_Actual : constant Boolean :=
8764 Is_Access_Type (Etype (Prefix (N)));
8765 Access_Formal : Boolean := False;
8767 begin
8768 Error_Msg_Sloc := Sloc (Op);
8770 if Present (First_Formal (Op)) then
8771 Access_Formal := Is_Access_Type (Etype (First_Formal (Op)));
8772 end if;
8774 if Access_Formal and then not Access_Actual then
8775 if Nkind (Parent (Op)) = N_Full_Type_Declaration then
8776 Error_Msg_N
8777 ("\possible interpretation "
8778 & "(inherited, with implicit 'Access) #", N);
8779 else
8780 Error_Msg_N
8781 ("\possible interpretation (with implicit 'Access) #", N);
8782 end if;
8784 elsif not Access_Formal and then Access_Actual then
8785 if Nkind (Parent (Op)) = N_Full_Type_Declaration then
8786 Error_Msg_N
8787 ("\possible interpretation "
8788 & "(inherited, with implicit dereference) #", N);
8789 else
8790 Error_Msg_N
8791 ("\possible interpretation (with implicit dereference) #", N);
8792 end if;
8794 else
8795 if Nkind (Parent (Op)) = N_Full_Type_Declaration then
8796 Error_Msg_N ("\possible interpretation (inherited)#", N);
8797 else
8798 Error_Msg_N -- CODEFIX
8799 ("\possible interpretation#", N);
8800 end if;
8801 end if;
8802 end Report_Ambiguity;
8804 --------------------------------
8805 -- Transform_Object_Operation --
8806 --------------------------------
8808 procedure Transform_Object_Operation
8809 (Call_Node : out Node_Id;
8810 Node_To_Replace : out Node_Id)
8812 Dummy : constant Node_Id := New_Copy (Obj);
8813 -- Placeholder used as a first parameter in the call, replaced
8814 -- eventually by the proper object.
8816 Parent_Node : constant Node_Id := Parent (N);
8818 Actual : Node_Id;
8819 Actuals : List_Id;
8821 begin
8822 -- Obj may already have been rewritten if it involves an implicit
8823 -- dereference (e.g. if it is an access to a limited view). Preserve
8824 -- a link to the original node for ASIS use.
8826 if not Comes_From_Source (Obj) then
8827 Set_Original_Node (Dummy, Original_Node (Obj));
8828 end if;
8830 -- Common case covering 1) Call to a procedure and 2) Call to a
8831 -- function that has some additional actuals.
8833 if Nkind (Parent_Node) in N_Subprogram_Call
8835 -- N is a selected component node containing the name of the
8836 -- subprogram. If N is not the name of the parent node we must
8837 -- not replace the parent node by the new construct. This case
8838 -- occurs when N is a parameterless call to a subprogram that
8839 -- is an actual parameter of a call to another subprogram. For
8840 -- example:
8841 -- Some_Subprogram (..., Obj.Operation, ...)
8843 and then Name (Parent_Node) = N
8844 then
8845 Node_To_Replace := Parent_Node;
8847 Actuals := Parameter_Associations (Parent_Node);
8849 if Present (Actuals) then
8850 Prepend (Dummy, Actuals);
8851 else
8852 Actuals := New_List (Dummy);
8853 end if;
8855 if Nkind (Parent_Node) = N_Procedure_Call_Statement then
8856 Call_Node :=
8857 Make_Procedure_Call_Statement (Loc,
8858 Name => New_Copy (Subprog),
8859 Parameter_Associations => Actuals);
8861 else
8862 Call_Node :=
8863 Make_Function_Call (Loc,
8864 Name => New_Copy (Subprog),
8865 Parameter_Associations => Actuals);
8866 end if;
8868 -- Before analysis, a function call appears as an indexed component
8869 -- if there are no named associations.
8871 elsif Nkind (Parent_Node) = N_Indexed_Component
8872 and then N = Prefix (Parent_Node)
8873 then
8874 Node_To_Replace := Parent_Node;
8875 Actuals := Expressions (Parent_Node);
8877 Actual := First (Actuals);
8878 while Present (Actual) loop
8879 Analyze (Actual);
8880 Next (Actual);
8881 end loop;
8883 Prepend (Dummy, Actuals);
8885 Call_Node :=
8886 Make_Function_Call (Loc,
8887 Name => New_Copy (Subprog),
8888 Parameter_Associations => Actuals);
8890 -- Parameterless call: Obj.F is rewritten as F (Obj)
8892 else
8893 Node_To_Replace := N;
8895 Call_Node :=
8896 Make_Function_Call (Loc,
8897 Name => New_Copy (Subprog),
8898 Parameter_Associations => New_List (Dummy));
8899 end if;
8900 end Transform_Object_Operation;
8902 ------------------------------
8903 -- Try_Class_Wide_Operation --
8904 ------------------------------
8906 function Try_Class_Wide_Operation
8907 (Call_Node : Node_Id;
8908 Node_To_Replace : Node_Id) return Boolean
8910 Anc_Type : Entity_Id;
8911 Matching_Op : Entity_Id := Empty;
8912 Error : Boolean;
8914 procedure Traverse_Homonyms
8915 (Anc_Type : Entity_Id;
8916 Error : out Boolean);
8917 -- Traverse the homonym chain of the subprogram searching for those
8918 -- homonyms whose first formal has the Anc_Type's class-wide type,
8919 -- or an anonymous access type designating the class-wide type. If
8920 -- an ambiguity is detected, then Error is set to True.
8922 procedure Traverse_Interfaces
8923 (Anc_Type : Entity_Id;
8924 Error : out Boolean);
8925 -- Traverse the list of interfaces, if any, associated with Anc_Type
8926 -- and search for acceptable class-wide homonyms associated with each
8927 -- interface. If an ambiguity is detected, then Error is set to True.
8929 -----------------------
8930 -- Traverse_Homonyms --
8931 -----------------------
8933 procedure Traverse_Homonyms
8934 (Anc_Type : Entity_Id;
8935 Error : out Boolean)
8937 Cls_Type : Entity_Id;
8938 Hom : Entity_Id;
8939 Hom_Ref : Node_Id;
8940 Success : Boolean;
8942 begin
8943 Error := False;
8945 Cls_Type := Class_Wide_Type (Anc_Type);
8947 Hom := Current_Entity (Subprog);
8949 -- Find a non-hidden operation whose first parameter is of the
8950 -- class-wide type, a subtype thereof, or an anonymous access
8951 -- to same. If in an instance, the operation can be considered
8952 -- even if hidden (it may be hidden because the instantiation
8953 -- is expanded after the containing package has been analyzed).
8955 while Present (Hom) loop
8956 if Ekind_In (Hom, E_Procedure, E_Function)
8957 and then (not Is_Hidden (Hom) or else In_Instance)
8958 and then Scope (Hom) = Scope (Base_Type (Anc_Type))
8959 and then Present (First_Formal (Hom))
8960 and then
8961 (Base_Type (Etype (First_Formal (Hom))) = Cls_Type
8962 or else
8963 (Is_Access_Type (Etype (First_Formal (Hom)))
8964 and then
8965 Ekind (Etype (First_Formal (Hom))) =
8966 E_Anonymous_Access_Type
8967 and then
8968 Base_Type
8969 (Designated_Type (Etype (First_Formal (Hom)))) =
8970 Cls_Type))
8971 then
8972 -- If the context is a procedure call, ignore functions
8973 -- in the name of the call.
8975 if Ekind (Hom) = E_Function
8976 and then Nkind (Parent (N)) = N_Procedure_Call_Statement
8977 and then N = Name (Parent (N))
8978 then
8979 goto Next_Hom;
8981 -- If the context is a function call, ignore procedures
8982 -- in the name of the call.
8984 elsif Ekind (Hom) = E_Procedure
8985 and then Nkind (Parent (N)) /= N_Procedure_Call_Statement
8986 then
8987 goto Next_Hom;
8988 end if;
8990 Set_Etype (Call_Node, Any_Type);
8991 Set_Is_Overloaded (Call_Node, False);
8992 Success := False;
8994 if No (Matching_Op) then
8995 Hom_Ref := New_Occurrence_Of (Hom, Sloc (Subprog));
8996 Set_Etype (Call_Node, Any_Type);
8997 Set_Parent (Call_Node, Parent (Node_To_Replace));
8999 Set_Name (Call_Node, Hom_Ref);
9001 Analyze_One_Call
9002 (N => Call_Node,
9003 Nam => Hom,
9004 Report => Report_Error,
9005 Success => Success,
9006 Skip_First => True);
9008 Matching_Op :=
9009 Valid_Candidate (Success, Call_Node, Hom);
9011 else
9012 Analyze_One_Call
9013 (N => Call_Node,
9014 Nam => Hom,
9015 Report => Report_Error,
9016 Success => Success,
9017 Skip_First => True);
9019 -- The same operation may be encountered on two homonym
9020 -- traversals, before and after looking at interfaces.
9021 -- Check for this case before reporting a real ambiguity.
9023 if Present (Valid_Candidate (Success, Call_Node, Hom))
9024 and then Nkind (Call_Node) /= N_Function_Call
9025 and then Hom /= Matching_Op
9026 then
9027 Error_Msg_NE ("ambiguous call to&", N, Hom);
9028 Report_Ambiguity (Matching_Op);
9029 Report_Ambiguity (Hom);
9030 Error := True;
9031 return;
9032 end if;
9033 end if;
9034 end if;
9036 <<Next_Hom>>
9037 Hom := Homonym (Hom);
9038 end loop;
9039 end Traverse_Homonyms;
9041 -------------------------
9042 -- Traverse_Interfaces --
9043 -------------------------
9045 procedure Traverse_Interfaces
9046 (Anc_Type : Entity_Id;
9047 Error : out Boolean)
9049 Intface_List : constant List_Id :=
9050 Abstract_Interface_List (Anc_Type);
9051 Intface : Node_Id;
9053 begin
9054 Error := False;
9056 if Is_Non_Empty_List (Intface_List) then
9057 Intface := First (Intface_List);
9058 while Present (Intface) loop
9060 -- Look for acceptable class-wide homonyms associated with
9061 -- the interface.
9063 Traverse_Homonyms (Etype (Intface), Error);
9065 if Error then
9066 return;
9067 end if;
9069 -- Continue the search by looking at each of the interface's
9070 -- associated interface ancestors.
9072 Traverse_Interfaces (Etype (Intface), Error);
9074 if Error then
9075 return;
9076 end if;
9078 Next (Intface);
9079 end loop;
9080 end if;
9081 end Traverse_Interfaces;
9083 -- Start of processing for Try_Class_Wide_Operation
9085 begin
9086 -- If we are searching only for conflicting class-wide subprograms
9087 -- then initialize directly Matching_Op with the target entity.
9089 if CW_Test_Only then
9090 Matching_Op := Entity (Selector_Name (N));
9091 end if;
9093 -- Loop through ancestor types (including interfaces), traversing
9094 -- the homonym chain of the subprogram, trying out those homonyms
9095 -- whose first formal has the class-wide type of the ancestor, or
9096 -- an anonymous access type designating the class-wide type.
9098 Anc_Type := Obj_Type;
9099 loop
9100 -- Look for a match among homonyms associated with the ancestor
9102 Traverse_Homonyms (Anc_Type, Error);
9104 if Error then
9105 return True;
9106 end if;
9108 -- Continue the search for matches among homonyms associated with
9109 -- any interfaces implemented by the ancestor.
9111 Traverse_Interfaces (Anc_Type, Error);
9113 if Error then
9114 return True;
9115 end if;
9117 exit when Etype (Anc_Type) = Anc_Type;
9118 Anc_Type := Etype (Anc_Type);
9119 end loop;
9121 if Present (Matching_Op) then
9122 Set_Etype (Call_Node, Etype (Matching_Op));
9123 end if;
9125 return Present (Matching_Op);
9126 end Try_Class_Wide_Operation;
9128 -----------------------------------
9129 -- Try_One_Prefix_Interpretation --
9130 -----------------------------------
9132 procedure Try_One_Prefix_Interpretation (T : Entity_Id) is
9133 Prev_Obj_Type : constant Entity_Id := Obj_Type;
9134 -- If the interpretation does not have a valid candidate type,
9135 -- preserve current value of Obj_Type for subsequent errors.
9137 begin
9138 Obj_Type := T;
9140 if Is_Access_Type (Obj_Type) then
9141 Obj_Type := Designated_Type (Obj_Type);
9142 end if;
9144 if Ekind_In (Obj_Type, E_Private_Subtype,
9145 E_Record_Subtype_With_Private)
9146 then
9147 Obj_Type := Base_Type (Obj_Type);
9148 end if;
9150 if Is_Class_Wide_Type (Obj_Type) then
9151 Obj_Type := Etype (Class_Wide_Type (Obj_Type));
9152 end if;
9154 -- The type may have be obtained through a limited_with clause,
9155 -- in which case the primitive operations are available on its
9156 -- nonlimited view. If still incomplete, retrieve full view.
9158 if Ekind (Obj_Type) = E_Incomplete_Type
9159 and then From_Limited_With (Obj_Type)
9160 and then Has_Non_Limited_View (Obj_Type)
9161 then
9162 Obj_Type := Get_Full_View (Non_Limited_View (Obj_Type));
9163 end if;
9165 -- If the object is not tagged, or the type is still an incomplete
9166 -- type, this is not a prefixed call. Restore the previous type as
9167 -- the current one is not a legal candidate.
9169 if not Is_Tagged_Type (Obj_Type)
9170 or else Is_Incomplete_Type (Obj_Type)
9171 then
9172 Obj_Type := Prev_Obj_Type;
9173 return;
9174 end if;
9176 declare
9177 Dup_Call_Node : constant Node_Id := New_Copy (New_Call_Node);
9178 Ignore : Boolean;
9179 Prim_Result : Boolean := False;
9181 begin
9182 if not CW_Test_Only then
9183 Prim_Result :=
9184 Try_Primitive_Operation
9185 (Call_Node => New_Call_Node,
9186 Node_To_Replace => Node_To_Replace);
9187 end if;
9189 -- Check if there is a class-wide subprogram covering the
9190 -- primitive. This check must be done even if a candidate
9191 -- was found in order to report ambiguous calls.
9193 if not Prim_Result then
9194 Ignore :=
9195 Try_Class_Wide_Operation
9196 (Call_Node => New_Call_Node,
9197 Node_To_Replace => Node_To_Replace);
9199 -- If we found a primitive we search for class-wide subprograms
9200 -- using a duplicate of the call node (done to avoid missing its
9201 -- decoration if there is no ambiguity).
9203 else
9204 Ignore :=
9205 Try_Class_Wide_Operation
9206 (Call_Node => Dup_Call_Node,
9207 Node_To_Replace => Node_To_Replace);
9208 end if;
9209 end;
9210 end Try_One_Prefix_Interpretation;
9212 -----------------------------
9213 -- Try_Primitive_Operation --
9214 -----------------------------
9216 function Try_Primitive_Operation
9217 (Call_Node : Node_Id;
9218 Node_To_Replace : Node_Id) return Boolean
9220 Elmt : Elmt_Id;
9221 Prim_Op : Entity_Id;
9222 Matching_Op : Entity_Id := Empty;
9223 Prim_Op_Ref : Node_Id := Empty;
9225 Corr_Type : Entity_Id := Empty;
9226 -- If the prefix is a synchronized type, the controlling type of
9227 -- the primitive operation is the corresponding record type, else
9228 -- this is the object type itself.
9230 Success : Boolean := False;
9232 function Collect_Generic_Type_Ops (T : Entity_Id) return Elist_Id;
9233 -- For tagged types the candidate interpretations are found in
9234 -- the list of primitive operations of the type and its ancestors.
9235 -- For formal tagged types we have to find the operations declared
9236 -- in the same scope as the type (including in the generic formal
9237 -- part) because the type itself carries no primitive operations,
9238 -- except for formal derived types that inherit the operations of
9239 -- the parent and progenitors.
9241 -- If the context is a generic subprogram body, the generic formals
9242 -- are visible by name, but are not in the entity list of the
9243 -- subprogram because that list starts with the subprogram formals.
9244 -- We retrieve the candidate operations from the generic declaration.
9246 function Extended_Primitive_Ops (T : Entity_Id) return Elist_Id;
9247 -- Prefix notation can also be used on operations that are not
9248 -- primitives of the type, but are declared in the same immediate
9249 -- declarative part, which can only mean the corresponding package
9250 -- body (See RM 4.1.3 (9.2/3)). If we are in that body we extend the
9251 -- list of primitives with body operations with the same name that
9252 -- may be candidates, so that Try_Primitive_Operations can examine
9253 -- them if no real primitive is found.
9255 function Is_Private_Overriding (Op : Entity_Id) return Boolean;
9256 -- An operation that overrides an inherited operation in the private
9257 -- part of its package may be hidden, but if the inherited operation
9258 -- is visible a direct call to it will dispatch to the private one,
9259 -- which is therefore a valid candidate.
9261 function Names_Match
9262 (Obj_Type : Entity_Id;
9263 Prim_Op : Entity_Id;
9264 Subprog : Entity_Id) return Boolean;
9265 -- Return True if the names of Prim_Op and Subprog match. If Obj_Type
9266 -- is a protected type then compare also the original name of Prim_Op
9267 -- with the name of Subprog (since the expander may have added a
9268 -- prefix to its original name --see Exp_Ch9.Build_Selected_Name).
9270 function Valid_First_Argument_Of (Op : Entity_Id) return Boolean;
9271 -- Verify that the prefix, dereferenced if need be, is a valid
9272 -- controlling argument in a call to Op. The remaining actuals
9273 -- are checked in the subsequent call to Analyze_One_Call.
9275 ------------------------------
9276 -- Collect_Generic_Type_Ops --
9277 ------------------------------
9279 function Collect_Generic_Type_Ops (T : Entity_Id) return Elist_Id is
9280 Bas : constant Entity_Id := Base_Type (T);
9281 Candidates : constant Elist_Id := New_Elmt_List;
9282 Subp : Entity_Id;
9283 Formal : Entity_Id;
9285 procedure Check_Candidate;
9286 -- The operation is a candidate if its first parameter is a
9287 -- controlling operand of the desired type.
9289 -----------------------
9290 -- Check_Candidate; --
9291 -----------------------
9293 procedure Check_Candidate is
9294 begin
9295 Formal := First_Formal (Subp);
9297 if Present (Formal)
9298 and then Is_Controlling_Formal (Formal)
9299 and then
9300 (Base_Type (Etype (Formal)) = Bas
9301 or else
9302 (Is_Access_Type (Etype (Formal))
9303 and then Designated_Type (Etype (Formal)) = Bas))
9304 then
9305 Append_Elmt (Subp, Candidates);
9306 end if;
9307 end Check_Candidate;
9309 -- Start of processing for Collect_Generic_Type_Ops
9311 begin
9312 if Is_Derived_Type (T) then
9313 return Primitive_Operations (T);
9315 elsif Ekind_In (Scope (T), E_Procedure, E_Function) then
9317 -- Scan the list of generic formals to find subprograms
9318 -- that may have a first controlling formal of the type.
9320 if Nkind (Unit_Declaration_Node (Scope (T))) =
9321 N_Generic_Subprogram_Declaration
9322 then
9323 declare
9324 Decl : Node_Id;
9326 begin
9327 Decl :=
9328 First (Generic_Formal_Declarations
9329 (Unit_Declaration_Node (Scope (T))));
9330 while Present (Decl) loop
9331 if Nkind (Decl) in N_Formal_Subprogram_Declaration then
9332 Subp := Defining_Entity (Decl);
9333 Check_Candidate;
9334 end if;
9336 Next (Decl);
9337 end loop;
9338 end;
9339 end if;
9340 return Candidates;
9342 else
9343 -- Scan the list of entities declared in the same scope as
9344 -- the type. In general this will be an open scope, given that
9345 -- the call we are analyzing can only appear within a generic
9346 -- declaration or body (either the one that declares T, or a
9347 -- child unit).
9349 -- For a subtype representing a generic actual type, go to the
9350 -- base type.
9352 if Is_Generic_Actual_Type (T) then
9353 Subp := First_Entity (Scope (Base_Type (T)));
9354 else
9355 Subp := First_Entity (Scope (T));
9356 end if;
9358 while Present (Subp) loop
9359 if Is_Overloadable (Subp) then
9360 Check_Candidate;
9361 end if;
9363 Next_Entity (Subp);
9364 end loop;
9366 return Candidates;
9367 end if;
9368 end Collect_Generic_Type_Ops;
9370 ----------------------------
9371 -- Extended_Primitive_Ops --
9372 ----------------------------
9374 function Extended_Primitive_Ops (T : Entity_Id) return Elist_Id is
9375 Type_Scope : constant Entity_Id := Scope (T);
9377 Body_Decls : List_Id;
9378 Op_Found : Boolean;
9379 Op : Entity_Id;
9380 Op_List : Elist_Id;
9382 begin
9383 Op_List := Primitive_Operations (T);
9385 if Ekind (Type_Scope) = E_Package
9386 and then In_Package_Body (Type_Scope)
9387 and then In_Open_Scopes (Type_Scope)
9388 then
9389 -- Retrieve list of declarations of package body.
9391 Body_Decls :=
9392 Declarations
9393 (Unit_Declaration_Node
9394 (Corresponding_Body
9395 (Unit_Declaration_Node (Type_Scope))));
9397 Op := Current_Entity (Subprog);
9398 Op_Found := False;
9399 while Present (Op) loop
9400 if Comes_From_Source (Op)
9401 and then Is_Overloadable (Op)
9403 -- Exclude overriding primitive operations of a type
9404 -- extension declared in the package body, to prevent
9405 -- duplicates in extended list.
9407 and then not Is_Primitive (Op)
9408 and then Is_List_Member (Unit_Declaration_Node (Op))
9409 and then List_Containing (Unit_Declaration_Node (Op)) =
9410 Body_Decls
9411 then
9412 if not Op_Found then
9414 -- Copy list of primitives so it is not affected for
9415 -- other uses.
9417 Op_List := New_Copy_Elist (Op_List);
9418 Op_Found := True;
9419 end if;
9421 Append_Elmt (Op, Op_List);
9422 end if;
9424 Op := Homonym (Op);
9425 end loop;
9426 end if;
9428 return Op_List;
9429 end Extended_Primitive_Ops;
9431 ---------------------------
9432 -- Is_Private_Overriding --
9433 ---------------------------
9435 function Is_Private_Overriding (Op : Entity_Id) return Boolean is
9436 Visible_Op : Entity_Id;
9438 begin
9439 -- The subprogram may be overloaded with both visible and private
9440 -- entities with the same name. We have to scan the chain of
9441 -- homonyms to determine whether there is a previous implicit
9442 -- declaration in the same scope that is overridden by the
9443 -- private candidate.
9445 Visible_Op := Homonym (Op);
9446 while Present (Visible_Op) loop
9447 if Scope (Op) /= Scope (Visible_Op) then
9448 return False;
9450 elsif not Comes_From_Source (Visible_Op)
9451 and then Alias (Visible_Op) = Op
9452 and then not Is_Hidden (Visible_Op)
9453 then
9454 return True;
9455 end if;
9457 Visible_Op := Homonym (Visible_Op);
9458 end loop;
9460 return False;
9461 end Is_Private_Overriding;
9463 -----------------
9464 -- Names_Match --
9465 -----------------
9467 function Names_Match
9468 (Obj_Type : Entity_Id;
9469 Prim_Op : Entity_Id;
9470 Subprog : Entity_Id) return Boolean is
9471 begin
9472 -- Common case: exact match
9474 if Chars (Prim_Op) = Chars (Subprog) then
9475 return True;
9477 -- For protected type primitives the expander may have built the
9478 -- name of the dispatching primitive prepending the type name to
9479 -- avoid conflicts with the name of the protected subprogram (see
9480 -- Exp_Ch9.Build_Selected_Name).
9482 elsif Is_Protected_Type (Obj_Type) then
9483 return
9484 Present (Original_Protected_Subprogram (Prim_Op))
9485 and then Chars (Original_Protected_Subprogram (Prim_Op)) =
9486 Chars (Subprog);
9487 end if;
9489 return False;
9490 end Names_Match;
9492 -----------------------------
9493 -- Valid_First_Argument_Of --
9494 -----------------------------
9496 function Valid_First_Argument_Of (Op : Entity_Id) return Boolean is
9497 Typ : Entity_Id := Etype (First_Formal (Op));
9499 begin
9500 if Is_Concurrent_Type (Typ)
9501 and then Present (Corresponding_Record_Type (Typ))
9502 then
9503 Typ := Corresponding_Record_Type (Typ);
9504 end if;
9506 -- Simple case. Object may be a subtype of the tagged type or may
9507 -- be the corresponding record of a synchronized type.
9509 return Obj_Type = Typ
9510 or else Base_Type (Obj_Type) = Typ
9511 or else Corr_Type = Typ
9513 -- Object may be of a derived type whose parent has unknown
9514 -- discriminants, in which case the type matches the underlying
9515 -- record view of its base.
9517 or else
9518 (Has_Unknown_Discriminants (Typ)
9519 and then Typ = Underlying_Record_View (Base_Type (Obj_Type)))
9521 -- Prefix can be dereferenced
9523 or else
9524 (Is_Access_Type (Corr_Type)
9525 and then Designated_Type (Corr_Type) = Typ)
9527 -- Formal is an access parameter, for which the object can
9528 -- provide an access.
9530 or else
9531 (Ekind (Typ) = E_Anonymous_Access_Type
9532 and then
9533 Base_Type (Designated_Type (Typ)) = Base_Type (Corr_Type));
9534 end Valid_First_Argument_Of;
9536 -- Start of processing for Try_Primitive_Operation
9538 begin
9539 -- Look for subprograms in the list of primitive operations. The name
9540 -- must be identical, and the kind of call indicates the expected
9541 -- kind of operation (function or procedure). If the type is a
9542 -- (tagged) synchronized type, the primitive ops are attached to the
9543 -- corresponding record (base) type.
9545 if Is_Concurrent_Type (Obj_Type) then
9546 if Present (Corresponding_Record_Type (Obj_Type)) then
9547 Corr_Type := Base_Type (Corresponding_Record_Type (Obj_Type));
9548 Elmt := First_Elmt (Primitive_Operations (Corr_Type));
9549 else
9550 Corr_Type := Obj_Type;
9551 Elmt := First_Elmt (Collect_Generic_Type_Ops (Obj_Type));
9552 end if;
9554 elsif not Is_Generic_Type (Obj_Type) then
9555 Corr_Type := Obj_Type;
9556 Elmt := First_Elmt (Extended_Primitive_Ops (Obj_Type));
9558 else
9559 Corr_Type := Obj_Type;
9560 Elmt := First_Elmt (Collect_Generic_Type_Ops (Obj_Type));
9561 end if;
9563 while Present (Elmt) loop
9564 Prim_Op := Node (Elmt);
9566 if Names_Match (Obj_Type, Prim_Op, Subprog)
9567 and then Present (First_Formal (Prim_Op))
9568 and then Valid_First_Argument_Of (Prim_Op)
9569 and then
9570 (Nkind (Call_Node) = N_Function_Call)
9572 (Ekind (Prim_Op) = E_Function)
9573 then
9574 -- Ada 2005 (AI-251): If this primitive operation corresponds
9575 -- to an immediate ancestor interface there is no need to add
9576 -- it to the list of interpretations; the corresponding aliased
9577 -- primitive is also in this list of primitive operations and
9578 -- will be used instead.
9580 if (Present (Interface_Alias (Prim_Op))
9581 and then Is_Ancestor (Find_Dispatching_Type
9582 (Alias (Prim_Op)), Corr_Type))
9584 -- Do not consider hidden primitives unless the type is in an
9585 -- open scope or we are within an instance, where visibility
9586 -- is known to be correct, or else if this is an overriding
9587 -- operation in the private part for an inherited operation.
9589 or else (Is_Hidden (Prim_Op)
9590 and then not Is_Immediately_Visible (Obj_Type)
9591 and then not In_Instance
9592 and then not Is_Private_Overriding (Prim_Op))
9593 then
9594 goto Continue;
9595 end if;
9597 Set_Etype (Call_Node, Any_Type);
9598 Set_Is_Overloaded (Call_Node, False);
9600 if No (Matching_Op) then
9601 Prim_Op_Ref := New_Occurrence_Of (Prim_Op, Sloc (Subprog));
9602 Candidate := Prim_Op;
9604 Set_Parent (Call_Node, Parent (Node_To_Replace));
9606 Set_Name (Call_Node, Prim_Op_Ref);
9607 Success := False;
9609 Analyze_One_Call
9610 (N => Call_Node,
9611 Nam => Prim_Op,
9612 Report => Report_Error,
9613 Success => Success,
9614 Skip_First => True);
9616 Matching_Op := Valid_Candidate (Success, Call_Node, Prim_Op);
9618 -- More than one interpretation, collect for subsequent
9619 -- disambiguation. If this is a procedure call and there
9620 -- is another match, report ambiguity now.
9622 else
9623 Analyze_One_Call
9624 (N => Call_Node,
9625 Nam => Prim_Op,
9626 Report => Report_Error,
9627 Success => Success,
9628 Skip_First => True);
9630 if Present (Valid_Candidate (Success, Call_Node, Prim_Op))
9631 and then Nkind (Call_Node) /= N_Function_Call
9632 then
9633 Error_Msg_NE ("ambiguous call to&", N, Prim_Op);
9634 Report_Ambiguity (Matching_Op);
9635 Report_Ambiguity (Prim_Op);
9636 return True;
9637 end if;
9638 end if;
9639 end if;
9641 <<Continue>>
9642 Next_Elmt (Elmt);
9643 end loop;
9645 if Present (Matching_Op) then
9646 Set_Etype (Call_Node, Etype (Matching_Op));
9647 end if;
9649 return Present (Matching_Op);
9650 end Try_Primitive_Operation;
9652 ---------------------
9653 -- Valid_Candidate --
9654 ---------------------
9656 function Valid_Candidate
9657 (Success : Boolean;
9658 Call : Node_Id;
9659 Subp : Entity_Id) return Entity_Id
9661 Arr_Type : Entity_Id;
9662 Comp_Type : Entity_Id;
9664 begin
9665 -- If the subprogram is a valid interpretation, record it in global
9666 -- variable Subprog, to collect all possible overloadings.
9668 if Success then
9669 if Subp /= Entity (Subprog) then
9670 Add_One_Interp (Subprog, Subp, Etype (Subp));
9671 end if;
9672 end if;
9674 -- If the call may be an indexed call, retrieve component type of
9675 -- resulting expression, and add possible interpretation.
9677 Arr_Type := Empty;
9678 Comp_Type := Empty;
9680 if Nkind (Call) = N_Function_Call
9681 and then Nkind (Parent (N)) = N_Indexed_Component
9682 and then Needs_One_Actual (Subp)
9683 then
9684 if Is_Array_Type (Etype (Subp)) then
9685 Arr_Type := Etype (Subp);
9687 elsif Is_Access_Type (Etype (Subp))
9688 and then Is_Array_Type (Designated_Type (Etype (Subp)))
9689 then
9690 Arr_Type := Designated_Type (Etype (Subp));
9691 end if;
9692 end if;
9694 if Present (Arr_Type) then
9696 -- Verify that the actuals (excluding the object) match the types
9697 -- of the indexes.
9699 declare
9700 Actual : Node_Id;
9701 Index : Node_Id;
9703 begin
9704 Actual := Next (First_Actual (Call));
9705 Index := First_Index (Arr_Type);
9706 while Present (Actual) and then Present (Index) loop
9707 if not Has_Compatible_Type (Actual, Etype (Index)) then
9708 Arr_Type := Empty;
9709 exit;
9710 end if;
9712 Next_Actual (Actual);
9713 Next_Index (Index);
9714 end loop;
9716 if No (Actual)
9717 and then No (Index)
9718 and then Present (Arr_Type)
9719 then
9720 Comp_Type := Component_Type (Arr_Type);
9721 end if;
9722 end;
9724 if Present (Comp_Type)
9725 and then Etype (Subprog) /= Comp_Type
9726 then
9727 Add_One_Interp (Subprog, Subp, Comp_Type);
9728 end if;
9729 end if;
9731 if Etype (Call) /= Any_Type then
9732 return Subp;
9733 else
9734 return Empty;
9735 end if;
9736 end Valid_Candidate;
9738 -- Start of processing for Try_Object_Operation
9740 begin
9741 Analyze_Expression (Obj);
9743 -- Analyze the actuals if node is known to be a subprogram call
9745 if Is_Subprg_Call and then N = Name (Parent (N)) then
9746 Actual := First (Parameter_Associations (Parent (N)));
9747 while Present (Actual) loop
9748 Analyze_Expression (Actual);
9749 Next (Actual);
9750 end loop;
9751 end if;
9753 -- Build a subprogram call node, using a copy of Obj as its first
9754 -- actual. This is a placeholder, to be replaced by an explicit
9755 -- dereference when needed.
9757 Transform_Object_Operation
9758 (Call_Node => New_Call_Node,
9759 Node_To_Replace => Node_To_Replace);
9761 Set_Etype (New_Call_Node, Any_Type);
9762 Set_Etype (Subprog, Any_Type);
9763 Set_Parent (New_Call_Node, Parent (Node_To_Replace));
9765 if not Is_Overloaded (Obj) then
9766 Try_One_Prefix_Interpretation (Obj_Type);
9768 else
9769 declare
9770 I : Interp_Index;
9771 It : Interp;
9772 begin
9773 Get_First_Interp (Obj, I, It);
9774 while Present (It.Nam) loop
9775 Try_One_Prefix_Interpretation (It.Typ);
9776 Get_Next_Interp (I, It);
9777 end loop;
9778 end;
9779 end if;
9781 if Etype (New_Call_Node) /= Any_Type then
9783 -- No need to complete the tree transformations if we are only
9784 -- searching for conflicting class-wide subprograms
9786 if CW_Test_Only then
9787 return False;
9788 else
9789 Complete_Object_Operation
9790 (Call_Node => New_Call_Node,
9791 Node_To_Replace => Node_To_Replace);
9792 return True;
9793 end if;
9795 elsif Present (Candidate) then
9797 -- The argument list is not type correct. Re-analyze with error
9798 -- reporting enabled, and use one of the possible candidates.
9799 -- In All_Errors_Mode, re-analyze all failed interpretations.
9801 if All_Errors_Mode then
9802 Report_Error := True;
9803 if Try_Primitive_Operation
9804 (Call_Node => New_Call_Node,
9805 Node_To_Replace => Node_To_Replace)
9807 or else
9808 Try_Class_Wide_Operation
9809 (Call_Node => New_Call_Node,
9810 Node_To_Replace => Node_To_Replace)
9811 then
9812 null;
9813 end if;
9815 else
9816 Analyze_One_Call
9817 (N => New_Call_Node,
9818 Nam => Candidate,
9819 Report => True,
9820 Success => Success,
9821 Skip_First => True);
9822 end if;
9824 -- No need for further errors
9826 return True;
9828 else
9829 -- There was no candidate operation, so report it as an error
9830 -- in the caller: Analyze_Selected_Component.
9832 return False;
9833 end if;
9834 end Try_Object_Operation;
9836 ---------
9837 -- wpo --
9838 ---------
9840 procedure wpo (T : Entity_Id) is
9841 Op : Entity_Id;
9842 E : Elmt_Id;
9844 begin
9845 if not Is_Tagged_Type (T) then
9846 return;
9847 end if;
9849 E := First_Elmt (Primitive_Operations (Base_Type (T)));
9850 while Present (E) loop
9851 Op := Node (E);
9852 Write_Int (Int (Op));
9853 Write_Str (" === ");
9854 Write_Name (Chars (Op));
9855 Write_Str (" in ");
9856 Write_Name (Chars (Scope (Op)));
9857 Next_Elmt (E);
9858 Write_Eol;
9859 end loop;
9860 end wpo;
9862 end Sem_Ch4;