1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 1992-2005, Free Software Foundation, Inc. --
11 -- GNAT is free software; you can redistribute it and/or modify it under --
12 -- terms of the GNU General Public License as published by the Free Soft- --
13 -- ware Foundation; either version 2, or (at your option) any later ver- --
14 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
17 -- for more details. You should have received a copy of the GNU General --
18 -- Public License distributed with GNAT; see file COPYING. If not, write --
19 -- to the Free Software Foundation, 59 Temple Place - Suite 330, Boston, --
20 -- MA 02111-1307, USA. --
22 -- GNAT was originally developed by the GNAT team at New York University. --
23 -- Extensive contributions were provided by Ada Core Technologies Inc. --
25 ------------------------------------------------------------------------------
27 with Atree
; use Atree
;
28 with Checks
; use Checks
;
29 with Debug
; use Debug
;
30 with Einfo
; use Einfo
;
31 with Elists
; use Elists
;
32 with Errout
; use Errout
;
33 with Exp_Util
; use Exp_Util
;
34 with Fname
; use Fname
;
35 with Itypes
; use Itypes
;
37 with Lib
.Xref
; use Lib
.Xref
;
38 with Namet
; use Namet
;
39 with Nlists
; use Nlists
;
40 with Nmake
; use Nmake
;
42 with Output
; use Output
;
43 with Restrict
; use Restrict
;
44 with Rident
; use Rident
;
46 with Sem_Cat
; use Sem_Cat
;
47 with Sem_Ch3
; use Sem_Ch3
;
48 with Sem_Ch8
; use Sem_Ch8
;
49 with Sem_Dist
; use Sem_Dist
;
50 with Sem_Eval
; use Sem_Eval
;
51 with Sem_Res
; use Sem_Res
;
52 with Sem_Util
; use Sem_Util
;
53 with Sem_Type
; use Sem_Type
;
54 with Stand
; use Stand
;
55 with Sinfo
; use Sinfo
;
56 with Snames
; use Snames
;
57 with Tbuild
; use Tbuild
;
59 with GNAT
.Spelling_Checker
; use GNAT
.Spelling_Checker
;
61 package body Sem_Ch4
is
63 -----------------------
64 -- Local Subprograms --
65 -----------------------
67 procedure Analyze_Expression
(N
: Node_Id
);
68 -- For expressions that are not names, this is just a call to analyze.
69 -- If the expression is a name, it may be a call to a parameterless
70 -- function, and if so must be converted into an explicit call node
71 -- and analyzed as such. This deproceduring must be done during the first
72 -- pass of overload resolution, because otherwise a procedure call with
73 -- overloaded actuals may fail to resolve. See 4327-001 for an example.
75 procedure Analyze_Operator_Call
(N
: Node_Id
; Op_Id
: Entity_Id
);
76 -- Analyze a call of the form "+"(x, y), etc. The prefix of the call
77 -- is an operator name or an expanded name whose selector is an operator
78 -- name, and one possible interpretation is as a predefined operator.
80 procedure Analyze_Overloaded_Selected_Component
(N
: Node_Id
);
81 -- If the prefix of a selected_component is overloaded, the proper
82 -- interpretation that yields a record type with the proper selector
83 -- name must be selected.
85 procedure Analyze_User_Defined_Binary_Op
(N
: Node_Id
; Op_Id
: Entity_Id
);
86 -- Procedure to analyze a user defined binary operator, which is resolved
87 -- like a function, but instead of a list of actuals it is presented
88 -- with the left and right operands of an operator node.
90 procedure Analyze_User_Defined_Unary_Op
(N
: Node_Id
; Op_Id
: Entity_Id
);
91 -- Procedure to analyze a user defined unary operator, which is resolved
92 -- like a function, but instead of a list of actuals, it is presented with
93 -- the operand of the operator node.
95 procedure Ambiguous_Operands
(N
: Node_Id
);
96 -- for equality, membership, and comparison operators with overloaded
97 -- arguments, list possible interpretations.
99 procedure Analyze_One_Call
103 Success
: out Boolean);
104 -- Check one interpretation of an overloaded subprogram name for
105 -- compatibility with the types of the actuals in a call. If there is a
106 -- single interpretation which does not match, post error if Report is
109 -- Nam is the entity that provides the formals against which the actuals
110 -- are checked. Nam is either the name of a subprogram, or the internal
111 -- subprogram type constructed for an access_to_subprogram. If the actuals
112 -- are compatible with Nam, then Nam is added to the list of candidate
113 -- interpretations for N, and Success is set to True.
115 procedure Check_Misspelled_Selector
118 -- Give possible misspelling diagnostic if Sel is likely to be
119 -- a misspelling of one of the selectors of the Prefix.
120 -- This is called by Analyze_Selected_Component after producing
121 -- an invalid selector error message.
123 function Defined_In_Scope
(T
: Entity_Id
; S
: Entity_Id
) return Boolean;
124 -- Verify that type T is declared in scope S. Used to find intepretations
125 -- for operators given by expanded names. This is abstracted as a separate
126 -- function to handle extensions to System, where S is System, but T is
127 -- declared in the extension.
129 procedure Find_Arithmetic_Types
133 -- L and R are the operands of an arithmetic operator. Find
134 -- consistent pairs of interpretations for L and R that have a
135 -- numeric type consistent with the semantics of the operator.
137 procedure Find_Comparison_Types
141 -- L and R are operands of a comparison operator. Find consistent
142 -- pairs of interpretations for L and R.
144 procedure Find_Concatenation_Types
148 -- For the four varieties of concatenation
150 procedure Find_Equality_Types
154 -- Ditto for equality operators
156 procedure Find_Boolean_Types
160 -- Ditto for binary logical operations
162 procedure Find_Negation_Types
166 -- Find consistent interpretation for operand of negation operator
168 procedure Find_Non_Universal_Interpretations
173 -- For equality and comparison operators, the result is always boolean,
174 -- and the legality of the operation is determined from the visibility
175 -- of the operand types. If one of the operands has a universal interpre-
176 -- tation, the legality check uses some compatible non-universal
177 -- interpretation of the other operand. N can be an operator node, or
178 -- a function call whose name is an operator designator.
180 procedure Find_Unary_Types
184 -- Unary arithmetic types: plus, minus, abs
186 procedure Check_Arithmetic_Pair
190 -- Subsidiary procedure to Find_Arithmetic_Types. T1 and T2 are valid
191 -- types for left and right operand. Determine whether they constitute
192 -- a valid pair for the given operator, and record the corresponding
193 -- interpretation of the operator node. The node N may be an operator
194 -- node (the usual case) or a function call whose prefix is an operator
195 -- designator. In both cases Op_Id is the operator name itself.
197 procedure Diagnose_Call
(N
: Node_Id
; Nam
: Node_Id
);
198 -- Give detailed information on overloaded call where none of the
199 -- interpretations match. N is the call node, Nam the designator for
200 -- the overloaded entity being called.
202 function Junk_Operand
(N
: Node_Id
) return Boolean;
203 -- Test for an operand that is an inappropriate entity (e.g. a package
204 -- name or a label). If so, issue an error message and return True. If
205 -- the operand is not an inappropriate entity kind, return False.
207 procedure Operator_Check
(N
: Node_Id
);
208 -- Verify that an operator has received some valid interpretation. If none
209 -- was found, determine whether a use clause would make the operation
210 -- legal. The variable Candidate_Type (defined in Sem_Type) is set for
211 -- every type compatible with the operator, even if the operator for the
212 -- type is not directly visible. The routine uses this type to emit a more
213 -- informative message.
215 procedure Process_Implicit_Dereference_Prefix
218 -- Called when P is the prefix of an implicit dereference, denoting an
219 -- object E. If in semantics only mode (-gnatc), record that is a
220 -- reference to E. Normally, such a reference is generated only when the
221 -- implicit dereference is expanded into an explicit one. E may be empty,
222 -- in which case this procedure does nothing.
224 procedure Remove_Abstract_Operations
(N
: Node_Id
);
225 -- Ada 2005: implementation of AI-310. An abstract non-dispatching
226 -- operation is not a candidate interpretation.
228 function Try_Indexed_Call
231 Typ
: Entity_Id
) return Boolean;
232 -- If a function has defaults for all its actuals, a call to it may
233 -- in fact be an indexing on the result of the call. Try_Indexed_Call
234 -- attempts the interpretation as an indexing, prior to analysis as
235 -- a call. If both are possible, the node is overloaded with both
236 -- interpretations (same symbol but two different types).
238 function Try_Indirect_Call
241 Typ
: Entity_Id
) return Boolean;
242 -- Similarly, a function F that needs no actuals can return an access
243 -- to a subprogram, and the call F (X) interpreted as F.all (X). In
244 -- this case the call may be overloaded with both interpretations.
246 function Try_Object_Operation
(N
: Node_Id
) return Boolean;
247 -- Ada 2005 (AI-252): Give support to the object operation notation
249 ------------------------
250 -- Ambiguous_Operands --
251 ------------------------
253 procedure Ambiguous_Operands
(N
: Node_Id
) is
254 procedure List_Operand_Interps
(Opnd
: Node_Id
);
256 --------------------------
257 -- List_Operand_Interps --
258 --------------------------
260 procedure List_Operand_Interps
(Opnd
: Node_Id
) is
265 if Is_Overloaded
(Opnd
) then
266 if Nkind
(Opnd
) in N_Op
then
268 elsif Nkind
(Opnd
) = N_Function_Call
then
278 if Opnd
= Left_Opnd
(N
) then
280 ("\left operand has the following interpretations", N
);
283 ("\right operand has the following interpretations", N
);
287 List_Interps
(Nam
, Err
);
288 end List_Operand_Interps
;
290 -- Start of processing for Ambiguous_Operands
294 or else Nkind
(N
) = N_Not_In
296 Error_Msg_N
("ambiguous operands for membership", N
);
298 elsif Nkind
(N
) = N_Op_Eq
299 or else Nkind
(N
) = N_Op_Ne
301 Error_Msg_N
("ambiguous operands for equality", N
);
304 Error_Msg_N
("ambiguous operands for comparison", N
);
307 if All_Errors_Mode
then
308 List_Operand_Interps
(Left_Opnd
(N
));
309 List_Operand_Interps
(Right_Opnd
(N
));
311 Error_Msg_N
("\use -gnatf switch for details", N
);
313 end Ambiguous_Operands
;
315 -----------------------
316 -- Analyze_Aggregate --
317 -----------------------
319 -- Most of the analysis of Aggregates requires that the type be known,
320 -- and is therefore put off until resolution.
322 procedure Analyze_Aggregate
(N
: Node_Id
) is
324 if No
(Etype
(N
)) then
325 Set_Etype
(N
, Any_Composite
);
327 end Analyze_Aggregate
;
329 -----------------------
330 -- Analyze_Allocator --
331 -----------------------
333 procedure Analyze_Allocator
(N
: Node_Id
) is
334 Loc
: constant Source_Ptr
:= Sloc
(N
);
335 Sav_Errs
: constant Nat
:= Serious_Errors_Detected
;
336 E
: Node_Id
:= Expression
(N
);
337 Acc_Type
: Entity_Id
;
341 Check_Restriction
(No_Allocators
, N
);
343 if Nkind
(E
) = N_Qualified_Expression
then
344 Acc_Type
:= Create_Itype
(E_Allocator_Type
, N
);
345 Set_Etype
(Acc_Type
, Acc_Type
);
346 Init_Size_Align
(Acc_Type
);
347 Find_Type
(Subtype_Mark
(E
));
348 Type_Id
:= Entity
(Subtype_Mark
(E
));
349 Check_Fully_Declared
(Type_Id
, N
);
350 Set_Directly_Designated_Type
(Acc_Type
, Type_Id
);
352 if Is_Limited_Type
(Type_Id
)
353 and then Comes_From_Source
(N
)
354 and then not In_Instance_Body
356 -- Ada 2005 (AI-287): Do not post an error if the expression
357 -- corresponds to a limited aggregate. Limited aggregates
358 -- are checked in sem_aggr in a per-component manner
359 -- (compare with handling of Get_Value subprogram).
361 if Ada_Version
>= Ada_05
362 and then Nkind
(Expression
(E
)) = N_Aggregate
366 Error_Msg_N
("initialization not allowed for limited types", N
);
367 Explain_Limited_Type
(Type_Id
, N
);
371 Analyze_And_Resolve
(Expression
(E
), Type_Id
);
373 -- A qualified expression requires an exact match of the type,
374 -- class-wide matching is not allowed.
376 if Is_Class_Wide_Type
(Type_Id
)
377 and then Base_Type
(Etype
(Expression
(E
))) /= Base_Type
(Type_Id
)
379 Wrong_Type
(Expression
(E
), Type_Id
);
382 Check_Non_Static_Context
(Expression
(E
));
384 -- We don't analyze the qualified expression itself because it's
385 -- part of the allocator
387 Set_Etype
(E
, Type_Id
);
389 -- Case where no qualified expression is present
396 -- If the allocator includes a N_Subtype_Indication then a
397 -- constraint is present, otherwise the node is a subtype mark.
398 -- Introduce an explicit subtype declaration into the tree
399 -- defining some anonymous subtype and rewrite the allocator to
400 -- use this subtype rather than the subtype indication.
402 -- It is important to introduce the explicit subtype declaration
403 -- so that the bounds of the subtype indication are attached to
404 -- the tree in case the allocator is inside a generic unit.
406 if Nkind
(E
) = N_Subtype_Indication
then
408 -- A constraint is only allowed for a composite type in Ada
409 -- 95. In Ada 83, a constraint is also allowed for an
410 -- access-to-composite type, but the constraint is ignored.
412 Find_Type
(Subtype_Mark
(E
));
414 if Is_Elementary_Type
(Entity
(Subtype_Mark
(E
))) then
415 if not (Ada_Version
= Ada_83
416 and then Is_Access_Type
(Entity
(Subtype_Mark
(E
))))
418 Error_Msg_N
("constraint not allowed here", E
);
420 if Nkind
(Constraint
(E
))
421 = N_Index_Or_Discriminant_Constraint
424 ("\if qualified expression was meant, " &
425 "use apostrophe", Constraint
(E
));
429 -- Get rid of the bogus constraint:
431 Rewrite
(E
, New_Copy_Tree
(Subtype_Mark
(E
)));
432 Analyze_Allocator
(N
);
436 if Expander_Active
then
438 Make_Defining_Identifier
(Loc
, New_Internal_Name
('S'));
441 Make_Subtype_Declaration
(Loc
,
442 Defining_Identifier
=> Def_Id
,
443 Subtype_Indication
=> Relocate_Node
(E
)));
445 if Sav_Errs
/= Serious_Errors_Detected
446 and then Nkind
(Constraint
(E
))
447 = N_Index_Or_Discriminant_Constraint
450 ("if qualified expression was meant, " &
451 "use apostrophe!", Constraint
(E
));
454 E
:= New_Occurrence_Of
(Def_Id
, Loc
);
455 Rewrite
(Expression
(N
), E
);
459 Type_Id
:= Process_Subtype
(E
, N
);
460 Acc_Type
:= Create_Itype
(E_Allocator_Type
, N
);
461 Set_Etype
(Acc_Type
, Acc_Type
);
462 Init_Size_Align
(Acc_Type
);
463 Set_Directly_Designated_Type
(Acc_Type
, Type_Id
);
464 Check_Fully_Declared
(Type_Id
, N
);
468 if Can_Never_Be_Null
(Type_Id
) then
469 Error_Msg_N
("(Ada 2005) qualified expression required",
473 -- Check restriction against dynamically allocated protected
474 -- objects. Note that when limited aggregates are supported,
475 -- a similar test should be applied to an allocator with a
476 -- qualified expression ???
478 if Is_Protected_Type
(Type_Id
) then
479 Check_Restriction
(No_Protected_Type_Allocators
, N
);
482 -- Check for missing initialization. Skip this check if we already
483 -- had errors on analyzing the allocator, since in that case these
484 -- are probably cascaded errors
486 if Is_Indefinite_Subtype
(Type_Id
)
487 and then Serious_Errors_Detected
= Sav_Errs
489 if Is_Class_Wide_Type
(Type_Id
) then
491 ("initialization required in class-wide allocation", N
);
494 ("initialization required in unconstrained allocation", N
);
500 if Is_Abstract
(Type_Id
) then
501 Error_Msg_N
("cannot allocate abstract object", E
);
504 if Has_Task
(Designated_Type
(Acc_Type
)) then
505 Check_Restriction
(No_Tasking
, N
);
506 Check_Restriction
(Max_Tasks
, N
);
507 Check_Restriction
(No_Task_Allocators
, N
);
510 -- If the No_Streams restriction is set, check that the type of the
511 -- object is not, and does not contain, any subtype derived from
512 -- Ada.Streams.Root_Stream_Type. Note that we guard the call to
513 -- Has_Stream just for efficiency reasons. There is no point in
514 -- spending time on a Has_Stream check if the restriction is not set.
516 if Restrictions
.Set
(No_Streams
) then
517 if Has_Stream
(Designated_Type
(Acc_Type
)) then
518 Check_Restriction
(No_Streams
, N
);
522 Set_Etype
(N
, Acc_Type
);
524 if not Is_Library_Level_Entity
(Acc_Type
) then
525 Check_Restriction
(No_Local_Allocators
, N
);
528 -- Ada 2005 (AI-231): Static checks
530 if Ada_Version
>= Ada_05
531 and then (Null_Exclusion_Present
(N
)
532 or else Can_Never_Be_Null
(Etype
(N
)))
534 Null_Exclusion_Static_Checks
(N
);
537 if Serious_Errors_Detected
> Sav_Errs
then
538 Set_Error_Posted
(N
);
539 Set_Etype
(N
, Any_Type
);
541 end Analyze_Allocator
;
543 ---------------------------
544 -- Analyze_Arithmetic_Op --
545 ---------------------------
547 procedure Analyze_Arithmetic_Op
(N
: Node_Id
) is
548 L
: constant Node_Id
:= Left_Opnd
(N
);
549 R
: constant Node_Id
:= Right_Opnd
(N
);
553 Candidate_Type
:= Empty
;
554 Analyze_Expression
(L
);
555 Analyze_Expression
(R
);
557 -- If the entity is already set, the node is the instantiation of
558 -- a generic node with a non-local reference, or was manufactured
559 -- by a call to Make_Op_xxx. In either case the entity is known to
560 -- be valid, and we do not need to collect interpretations, instead
561 -- we just get the single possible interpretation.
565 if Present
(Op_Id
) then
566 if Ekind
(Op_Id
) = E_Operator
then
568 if (Nkind
(N
) = N_Op_Divide
or else
569 Nkind
(N
) = N_Op_Mod
or else
570 Nkind
(N
) = N_Op_Multiply
or else
571 Nkind
(N
) = N_Op_Rem
)
572 and then Treat_Fixed_As_Integer
(N
)
576 Set_Etype
(N
, Any_Type
);
577 Find_Arithmetic_Types
(L
, R
, Op_Id
, N
);
581 Set_Etype
(N
, Any_Type
);
582 Add_One_Interp
(N
, Op_Id
, Etype
(Op_Id
));
585 -- Entity is not already set, so we do need to collect interpretations
588 Op_Id
:= Get_Name_Entity_Id
(Chars
(N
));
589 Set_Etype
(N
, Any_Type
);
591 while Present
(Op_Id
) loop
592 if Ekind
(Op_Id
) = E_Operator
593 and then Present
(Next_Entity
(First_Entity
(Op_Id
)))
595 Find_Arithmetic_Types
(L
, R
, Op_Id
, N
);
597 -- The following may seem superfluous, because an operator cannot
598 -- be generic, but this ignores the cleverness of the author of
601 elsif Is_Overloadable
(Op_Id
) then
602 Analyze_User_Defined_Binary_Op
(N
, Op_Id
);
605 Op_Id
:= Homonym
(Op_Id
);
610 end Analyze_Arithmetic_Op
;
616 -- Function, procedure, and entry calls are checked here. The Name in
617 -- the call may be overloaded. The actuals have been analyzed and may
618 -- themselves be overloaded. On exit from this procedure, the node N
619 -- may have zero, one or more interpretations. In the first case an
620 -- error message is produced. In the last case, the node is flagged
621 -- as overloaded and the interpretations are collected in All_Interp.
623 -- If the name is an Access_To_Subprogram, it cannot be overloaded, but
624 -- the type-checking is similar to that of other calls.
626 procedure Analyze_Call
(N
: Node_Id
) is
627 Actuals
: constant List_Id
:= Parameter_Associations
(N
);
628 Nam
: Node_Id
:= Name
(N
);
632 Success
: Boolean := False;
634 function Name_Denotes_Function
return Boolean;
635 -- If the type of the name is an access to subprogram, this may be
636 -- the type of a name, or the return type of the function being called.
637 -- If the name is not an entity then it can denote a protected function.
638 -- Until we distinguish Etype from Return_Type, we must use this
639 -- routine to resolve the meaning of the name in the call.
641 ---------------------------
642 -- Name_Denotes_Function --
643 ---------------------------
645 function Name_Denotes_Function
return Boolean is
647 if Is_Entity_Name
(Nam
) then
648 return Ekind
(Entity
(Nam
)) = E_Function
;
650 elsif Nkind
(Nam
) = N_Selected_Component
then
651 return Ekind
(Entity
(Selector_Name
(Nam
))) = E_Function
;
656 end Name_Denotes_Function
;
658 -- Start of processing for Analyze_Call
661 -- Initialize the type of the result of the call to the error type,
662 -- which will be reset if the type is successfully resolved.
664 Set_Etype
(N
, Any_Type
);
666 if not Is_Overloaded
(Nam
) then
668 -- Only one interpretation to check
670 if Ekind
(Etype
(Nam
)) = E_Subprogram_Type
then
671 Nam_Ent
:= Etype
(Nam
);
673 elsif Is_Access_Type
(Etype
(Nam
))
674 and then Ekind
(Designated_Type
(Etype
(Nam
))) = E_Subprogram_Type
675 and then not Name_Denotes_Function
677 Nam_Ent
:= Designated_Type
(Etype
(Nam
));
678 Insert_Explicit_Dereference
(Nam
);
680 -- Selected component case. Simple entry or protected operation,
681 -- where the entry name is given by the selector name.
683 elsif Nkind
(Nam
) = N_Selected_Component
then
684 Nam_Ent
:= Entity
(Selector_Name
(Nam
));
686 if Ekind
(Nam_Ent
) /= E_Entry
687 and then Ekind
(Nam_Ent
) /= E_Entry_Family
688 and then Ekind
(Nam_Ent
) /= E_Function
689 and then Ekind
(Nam_Ent
) /= E_Procedure
691 Error_Msg_N
("name in call is not a callable entity", Nam
);
692 Set_Etype
(N
, Any_Type
);
696 -- If the name is an Indexed component, it can be a call to a member
697 -- of an entry family. The prefix must be a selected component whose
698 -- selector is the entry. Analyze_Procedure_Call normalizes several
699 -- kinds of call into this form.
701 elsif Nkind
(Nam
) = N_Indexed_Component
then
703 if Nkind
(Prefix
(Nam
)) = N_Selected_Component
then
704 Nam_Ent
:= Entity
(Selector_Name
(Prefix
(Nam
)));
706 Error_Msg_N
("name in call is not a callable entity", Nam
);
707 Set_Etype
(N
, Any_Type
);
711 elsif not Is_Entity_Name
(Nam
) then
712 Error_Msg_N
("name in call is not a callable entity", Nam
);
713 Set_Etype
(N
, Any_Type
);
717 Nam_Ent
:= Entity
(Nam
);
719 -- If no interpretations, give error message
721 if not Is_Overloadable
(Nam_Ent
) then
723 L
: constant Boolean := Is_List_Member
(N
);
724 K
: constant Node_Kind
:= Nkind
(Parent
(N
));
727 -- If the node is in a list whose parent is not an
728 -- expression then it must be an attempted procedure call.
730 if L
and then K
not in N_Subexpr
then
731 if Ekind
(Entity
(Nam
)) = E_Generic_Procedure
then
733 ("must instantiate generic procedure& before call",
737 ("procedure or entry name expected", Nam
);
740 -- Check for tasking cases where only an entry call will do
743 and then (K
= N_Entry_Call_Alternative
744 or else K
= N_Triggering_Alternative
)
746 Error_Msg_N
("entry name expected", Nam
);
748 -- Otherwise give general error message
751 Error_Msg_N
("invalid prefix in call", Nam
);
759 Analyze_One_Call
(N
, Nam_Ent
, True, Success
);
762 -- An overloaded selected component must denote overloaded
763 -- operations of a concurrent type. The interpretations are
764 -- attached to the simple name of those operations.
766 if Nkind
(Nam
) = N_Selected_Component
then
767 Nam
:= Selector_Name
(Nam
);
770 Get_First_Interp
(Nam
, X
, It
);
772 while Present
(It
.Nam
) loop
775 -- Name may be call that returns an access to subprogram, or more
776 -- generally an overloaded expression one of whose interpretations
777 -- yields an access to subprogram. If the name is an entity, we
778 -- do not dereference, because the node is a call that returns
779 -- the access type: note difference between f(x), where the call
780 -- may return an access subprogram type, and f(x)(y), where the
781 -- type returned by the call to f is implicitly dereferenced to
782 -- analyze the outer call.
784 if Is_Access_Type
(Nam_Ent
) then
785 Nam_Ent
:= Designated_Type
(Nam_Ent
);
787 elsif Is_Access_Type
(Etype
(Nam_Ent
))
788 and then not Is_Entity_Name
(Nam
)
789 and then Ekind
(Designated_Type
(Etype
(Nam_Ent
)))
792 Nam_Ent
:= Designated_Type
(Etype
(Nam_Ent
));
795 Analyze_One_Call
(N
, Nam_Ent
, False, Success
);
797 -- If the interpretation succeeds, mark the proper type of the
798 -- prefix (any valid candidate will do). If not, remove the
799 -- candidate interpretation. This only needs to be done for
800 -- overloaded protected operations, for other entities disambi-
801 -- guation is done directly in Resolve.
804 Set_Etype
(Nam
, It
.Typ
);
806 elsif Nkind
(Name
(N
)) = N_Selected_Component
807 or else Nkind
(Name
(N
)) = N_Function_Call
812 Get_Next_Interp
(X
, It
);
815 -- If the name is the result of a function call, it can only
816 -- be a call to a function returning an access to subprogram.
817 -- Insert explicit dereference.
819 if Nkind
(Nam
) = N_Function_Call
then
820 Insert_Explicit_Dereference
(Nam
);
823 if Etype
(N
) = Any_Type
then
825 -- None of the interpretations is compatible with the actuals
827 Diagnose_Call
(N
, Nam
);
829 -- Special checks for uninstantiated put routines
831 if Nkind
(N
) = N_Procedure_Call_Statement
832 and then Is_Entity_Name
(Nam
)
833 and then Chars
(Nam
) = Name_Put
834 and then List_Length
(Actuals
) = 1
837 Arg
: constant Node_Id
:= First
(Actuals
);
841 if Nkind
(Arg
) = N_Parameter_Association
then
842 Typ
:= Etype
(Explicit_Actual_Parameter
(Arg
));
847 if Is_Signed_Integer_Type
(Typ
) then
849 ("possible missing instantiation of " &
850 "'Text_'I'O.'Integer_'I'O!", Nam
);
852 elsif Is_Modular_Integer_Type
(Typ
) then
854 ("possible missing instantiation of " &
855 "'Text_'I'O.'Modular_'I'O!", Nam
);
857 elsif Is_Floating_Point_Type
(Typ
) then
859 ("possible missing instantiation of " &
860 "'Text_'I'O.'Float_'I'O!", Nam
);
862 elsif Is_Ordinary_Fixed_Point_Type
(Typ
) then
864 ("possible missing instantiation of " &
865 "'Text_'I'O.'Fixed_'I'O!", Nam
);
867 elsif Is_Decimal_Fixed_Point_Type
(Typ
) then
869 ("possible missing instantiation of " &
870 "'Text_'I'O.'Decimal_'I'O!", Nam
);
872 elsif Is_Enumeration_Type
(Typ
) then
874 ("possible missing instantiation of " &
875 "'Text_'I'O.'Enumeration_'I'O!", Nam
);
880 elsif not Is_Overloaded
(N
)
881 and then Is_Entity_Name
(Nam
)
883 -- Resolution yields a single interpretation. Verify that
884 -- is has the proper capitalization.
886 Set_Entity_With_Style_Check
(Nam
, Entity
(Nam
));
887 Generate_Reference
(Entity
(Nam
), Nam
);
889 Set_Etype
(Nam
, Etype
(Entity
(Nam
)));
891 Remove_Abstract_Operations
(N
);
898 ---------------------------
899 -- Analyze_Comparison_Op --
900 ---------------------------
902 procedure Analyze_Comparison_Op
(N
: Node_Id
) is
903 L
: constant Node_Id
:= Left_Opnd
(N
);
904 R
: constant Node_Id
:= Right_Opnd
(N
);
905 Op_Id
: Entity_Id
:= Entity
(N
);
908 Set_Etype
(N
, Any_Type
);
909 Candidate_Type
:= Empty
;
911 Analyze_Expression
(L
);
912 Analyze_Expression
(R
);
914 if Present
(Op_Id
) then
915 if Ekind
(Op_Id
) = E_Operator
then
916 Find_Comparison_Types
(L
, R
, Op_Id
, N
);
918 Add_One_Interp
(N
, Op_Id
, Etype
(Op_Id
));
921 if Is_Overloaded
(L
) then
922 Set_Etype
(L
, Intersect_Types
(L
, R
));
926 Op_Id
:= Get_Name_Entity_Id
(Chars
(N
));
927 while Present
(Op_Id
) loop
928 if Ekind
(Op_Id
) = E_Operator
then
929 Find_Comparison_Types
(L
, R
, Op_Id
, N
);
931 Analyze_User_Defined_Binary_Op
(N
, Op_Id
);
934 Op_Id
:= Homonym
(Op_Id
);
939 end Analyze_Comparison_Op
;
941 ---------------------------
942 -- Analyze_Concatenation --
943 ---------------------------
945 -- If the only one-dimensional array type in scope is String,
946 -- this is the resulting type of the operation. Otherwise there
947 -- will be a concatenation operation defined for each user-defined
948 -- one-dimensional array.
950 procedure Analyze_Concatenation
(N
: Node_Id
) is
951 L
: constant Node_Id
:= Left_Opnd
(N
);
952 R
: constant Node_Id
:= Right_Opnd
(N
);
953 Op_Id
: Entity_Id
:= Entity
(N
);
958 Set_Etype
(N
, Any_Type
);
959 Candidate_Type
:= Empty
;
961 Analyze_Expression
(L
);
962 Analyze_Expression
(R
);
964 -- If the entity is present, the node appears in an instance,
965 -- and denotes a predefined concatenation operation. The resulting
966 -- type is obtained from the arguments when possible. If the arguments
967 -- are aggregates, the array type and the concatenation type must be
970 if Present
(Op_Id
) then
971 if Ekind
(Op_Id
) = E_Operator
then
973 LT
:= Base_Type
(Etype
(L
));
974 RT
:= Base_Type
(Etype
(R
));
976 if Is_Array_Type
(LT
)
977 and then (RT
= LT
or else RT
= Base_Type
(Component_Type
(LT
)))
979 Add_One_Interp
(N
, Op_Id
, LT
);
981 elsif Is_Array_Type
(RT
)
982 and then LT
= Base_Type
(Component_Type
(RT
))
984 Add_One_Interp
(N
, Op_Id
, RT
);
986 -- If one operand is a string type or a user-defined array type,
987 -- and the other is a literal, result is of the specific type.
990 (Root_Type
(LT
) = Standard_String
991 or else Scope
(LT
) /= Standard_Standard
)
992 and then Etype
(R
) = Any_String
994 Add_One_Interp
(N
, Op_Id
, LT
);
997 (Root_Type
(RT
) = Standard_String
998 or else Scope
(RT
) /= Standard_Standard
)
999 and then Etype
(L
) = Any_String
1001 Add_One_Interp
(N
, Op_Id
, RT
);
1003 elsif not Is_Generic_Type
(Etype
(Op_Id
)) then
1004 Add_One_Interp
(N
, Op_Id
, Etype
(Op_Id
));
1007 -- Type and its operations must be visible
1009 Set_Entity
(N
, Empty
);
1010 Analyze_Concatenation
(N
);
1014 Add_One_Interp
(N
, Op_Id
, Etype
(Op_Id
));
1018 Op_Id
:= Get_Name_Entity_Id
(Name_Op_Concat
);
1019 while Present
(Op_Id
) loop
1020 if Ekind
(Op_Id
) = E_Operator
then
1021 Find_Concatenation_Types
(L
, R
, Op_Id
, N
);
1023 Analyze_User_Defined_Binary_Op
(N
, Op_Id
);
1026 Op_Id
:= Homonym
(Op_Id
);
1031 end Analyze_Concatenation
;
1033 ------------------------------------
1034 -- Analyze_Conditional_Expression --
1035 ------------------------------------
1037 procedure Analyze_Conditional_Expression
(N
: Node_Id
) is
1038 Condition
: constant Node_Id
:= First
(Expressions
(N
));
1039 Then_Expr
: constant Node_Id
:= Next
(Condition
);
1040 Else_Expr
: constant Node_Id
:= Next
(Then_Expr
);
1042 Analyze_Expression
(Condition
);
1043 Analyze_Expression
(Then_Expr
);
1044 Analyze_Expression
(Else_Expr
);
1045 Set_Etype
(N
, Etype
(Then_Expr
));
1046 end Analyze_Conditional_Expression
;
1048 -------------------------
1049 -- Analyze_Equality_Op --
1050 -------------------------
1052 procedure Analyze_Equality_Op
(N
: Node_Id
) is
1053 Loc
: constant Source_Ptr
:= Sloc
(N
);
1054 L
: constant Node_Id
:= Left_Opnd
(N
);
1055 R
: constant Node_Id
:= Right_Opnd
(N
);
1059 Set_Etype
(N
, Any_Type
);
1060 Candidate_Type
:= Empty
;
1062 Analyze_Expression
(L
);
1063 Analyze_Expression
(R
);
1065 -- If the entity is set, the node is a generic instance with a non-local
1066 -- reference to the predefined operator or to a user-defined function.
1067 -- It can also be an inequality that is expanded into the negation of a
1068 -- call to a user-defined equality operator.
1070 -- For the predefined case, the result is Boolean, regardless of the
1071 -- type of the operands. The operands may even be limited, if they are
1072 -- generic actuals. If they are overloaded, label the left argument with
1073 -- the common type that must be present, or with the type of the formal
1074 -- of the user-defined function.
1076 if Present
(Entity
(N
)) then
1077 Op_Id
:= Entity
(N
);
1079 if Ekind
(Op_Id
) = E_Operator
then
1080 Add_One_Interp
(N
, Op_Id
, Standard_Boolean
);
1082 Add_One_Interp
(N
, Op_Id
, Etype
(Op_Id
));
1085 if Is_Overloaded
(L
) then
1086 if Ekind
(Op_Id
) = E_Operator
then
1087 Set_Etype
(L
, Intersect_Types
(L
, R
));
1089 Set_Etype
(L
, Etype
(First_Formal
(Op_Id
)));
1094 Op_Id
:= Get_Name_Entity_Id
(Chars
(N
));
1095 while Present
(Op_Id
) loop
1096 if Ekind
(Op_Id
) = E_Operator
then
1097 Find_Equality_Types
(L
, R
, Op_Id
, N
);
1099 Analyze_User_Defined_Binary_Op
(N
, Op_Id
);
1102 Op_Id
:= Homonym
(Op_Id
);
1106 -- If there was no match, and the operator is inequality, this may
1107 -- be a case where inequality has not been made explicit, as for
1108 -- tagged types. Analyze the node as the negation of an equality
1109 -- operation. This cannot be done earlier, because before analysis
1110 -- we cannot rule out the presence of an explicit inequality.
1112 if Etype
(N
) = Any_Type
1113 and then Nkind
(N
) = N_Op_Ne
1115 Op_Id
:= Get_Name_Entity_Id
(Name_Op_Eq
);
1117 while Present
(Op_Id
) loop
1119 if Ekind
(Op_Id
) = E_Operator
then
1120 Find_Equality_Types
(L
, R
, Op_Id
, N
);
1122 Analyze_User_Defined_Binary_Op
(N
, Op_Id
);
1125 Op_Id
:= Homonym
(Op_Id
);
1128 if Etype
(N
) /= Any_Type
then
1129 Op_Id
:= Entity
(N
);
1135 Left_Opnd
=> Relocate_Node
(Left_Opnd
(N
)),
1136 Right_Opnd
=> Relocate_Node
(Right_Opnd
(N
)))));
1138 Set_Entity
(Right_Opnd
(N
), Op_Id
);
1144 end Analyze_Equality_Op
;
1146 ----------------------------------
1147 -- Analyze_Explicit_Dereference --
1148 ----------------------------------
1150 procedure Analyze_Explicit_Dereference
(N
: Node_Id
) is
1151 Loc
: constant Source_Ptr
:= Sloc
(N
);
1152 P
: constant Node_Id
:= Prefix
(N
);
1158 function Is_Function_Type
return Boolean;
1159 -- Check whether node may be interpreted as an implicit function call
1161 ----------------------
1162 -- Is_Function_Type --
1163 ----------------------
1165 function Is_Function_Type
return Boolean is
1170 if not Is_Overloaded
(N
) then
1171 return Ekind
(Base_Type
(Etype
(N
))) = E_Subprogram_Type
1172 and then Etype
(Base_Type
(Etype
(N
))) /= Standard_Void_Type
;
1175 Get_First_Interp
(N
, I
, It
);
1177 while Present
(It
.Nam
) loop
1178 if Ekind
(Base_Type
(It
.Typ
)) /= E_Subprogram_Type
1179 or else Etype
(Base_Type
(It
.Typ
)) = Standard_Void_Type
1184 Get_Next_Interp
(I
, It
);
1189 end Is_Function_Type
;
1191 -- Start of processing for Analyze_Explicit_Deference
1195 Set_Etype
(N
, Any_Type
);
1197 -- Test for remote access to subprogram type, and if so return
1198 -- after rewriting the original tree.
1200 if Remote_AST_E_Dereference
(P
) then
1204 -- Normal processing for other than remote access to subprogram type
1206 if not Is_Overloaded
(P
) then
1207 if Is_Access_Type
(Etype
(P
)) then
1209 -- Set the Etype. We need to go thru Is_For_Access_Subtypes
1210 -- to avoid other problems caused by the Private_Subtype
1211 -- and it is safe to go to the Base_Type because this is the
1212 -- same as converting the access value to its Base_Type.
1215 DT
: Entity_Id
:= Designated_Type
(Etype
(P
));
1218 if Ekind
(DT
) = E_Private_Subtype
1219 and then Is_For_Access_Subtype
(DT
)
1221 DT
:= Base_Type
(DT
);
1227 elsif Etype
(P
) /= Any_Type
then
1228 Error_Msg_N
("prefix of dereference must be an access type", N
);
1233 Get_First_Interp
(P
, I
, It
);
1235 while Present
(It
.Nam
) loop
1238 if Is_Access_Type
(T
) then
1239 Add_One_Interp
(N
, Designated_Type
(T
), Designated_Type
(T
));
1242 Get_Next_Interp
(I
, It
);
1247 -- Error if no interpretation of the prefix has an access type
1249 if Etype
(N
) = Any_Type
then
1251 ("access type required in prefix of explicit dereference", P
);
1252 Set_Etype
(N
, Any_Type
);
1258 and then Nkind
(Parent
(N
)) /= N_Indexed_Component
1260 and then (Nkind
(Parent
(N
)) /= N_Function_Call
1261 or else N
/= Name
(Parent
(N
)))
1263 and then (Nkind
(Parent
(N
)) /= N_Procedure_Call_Statement
1264 or else N
/= Name
(Parent
(N
)))
1266 and then Nkind
(Parent
(N
)) /= N_Subprogram_Renaming_Declaration
1267 and then (Nkind
(Parent
(N
)) /= N_Attribute_Reference
1269 (Attribute_Name
(Parent
(N
)) /= Name_Address
1271 Attribute_Name
(Parent
(N
)) /= Name_Access
))
1273 -- Name is a function call with no actuals, in a context that
1274 -- requires deproceduring (including as an actual in an enclosing
1275 -- function or procedure call). We can conceive of pathological cases
1276 -- where the prefix might include functions that return access to
1277 -- subprograms and others that return a regular type. Disambiguation
1278 -- of those will have to take place in Resolve. See e.g. 7117-014.
1281 Make_Function_Call
(Loc
,
1282 Name
=> Make_Explicit_Dereference
(Loc
, P
),
1283 Parameter_Associations
=> New_List
);
1285 -- If the prefix is overloaded, remove operations that have formals,
1286 -- we know that this is a parameterless call.
1288 if Is_Overloaded
(P
) then
1289 Get_First_Interp
(P
, I
, It
);
1290 while Present
(It
.Nam
) loop
1293 if No
(First_Formal
(Base_Type
(Designated_Type
(T
)))) then
1299 Get_Next_Interp
(I
, It
);
1307 -- A value of remote access-to-class-wide must not be dereferenced
1310 Validate_Remote_Access_To_Class_Wide_Type
(N
);
1311 end Analyze_Explicit_Dereference
;
1313 ------------------------
1314 -- Analyze_Expression --
1315 ------------------------
1317 procedure Analyze_Expression
(N
: Node_Id
) is
1320 Check_Parameterless_Call
(N
);
1321 end Analyze_Expression
;
1323 ------------------------------------
1324 -- Analyze_Indexed_Component_Form --
1325 ------------------------------------
1327 procedure Analyze_Indexed_Component_Form
(N
: Node_Id
) is
1328 P
: constant Node_Id
:= Prefix
(N
);
1329 Exprs
: constant List_Id
:= Expressions
(N
);
1335 procedure Process_Function_Call
;
1336 -- Prefix in indexed component form is an overloadable entity,
1337 -- so the node is a function call. Reformat it as such.
1339 procedure Process_Indexed_Component
;
1340 -- Prefix in indexed component form is actually an indexed component.
1341 -- This routine processes it, knowing that the prefix is already
1344 procedure Process_Indexed_Component_Or_Slice
;
1345 -- An indexed component with a single index may designate a slice if
1346 -- the index is a subtype mark. This routine disambiguates these two
1347 -- cases by resolving the prefix to see if it is a subtype mark.
1349 procedure Process_Overloaded_Indexed_Component
;
1350 -- If the prefix of an indexed component is overloaded, the proper
1351 -- interpretation is selected by the index types and the context.
1353 ---------------------------
1354 -- Process_Function_Call --
1355 ---------------------------
1357 procedure Process_Function_Call
is
1361 Change_Node
(N
, N_Function_Call
);
1363 Set_Parameter_Associations
(N
, Exprs
);
1365 Actual
:= First
(Parameter_Associations
(N
));
1366 while Present
(Actual
) loop
1368 Check_Parameterless_Call
(Actual
);
1369 Next_Actual
(Actual
);
1373 end Process_Function_Call
;
1375 -------------------------------
1376 -- Process_Indexed_Component --
1377 -------------------------------
1379 procedure Process_Indexed_Component
is
1381 Array_Type
: Entity_Id
;
1383 Pent
: Entity_Id
:= Empty
;
1386 Exp
:= First
(Exprs
);
1388 if Is_Overloaded
(P
) then
1389 Process_Overloaded_Indexed_Component
;
1392 Array_Type
:= Etype
(P
);
1394 if Is_Entity_Name
(P
) then
1396 elsif Nkind
(P
) = N_Selected_Component
1397 and then Is_Entity_Name
(Selector_Name
(P
))
1399 Pent
:= Entity
(Selector_Name
(P
));
1402 -- Prefix must be appropriate for an array type, taking into
1403 -- account a possible implicit dereference.
1405 if Is_Access_Type
(Array_Type
) then
1406 Array_Type
:= Designated_Type
(Array_Type
);
1407 Error_Msg_NW
(Warn_On_Dereference
, "?implicit dereference", N
);
1408 Process_Implicit_Dereference_Prefix
(Pent
, P
);
1411 if Is_Array_Type
(Array_Type
) then
1414 elsif Present
(Pent
) and then Ekind
(Pent
) = E_Entry_Family
then
1416 Set_Etype
(N
, Any_Type
);
1418 if not Has_Compatible_Type
1419 (Exp
, Entry_Index_Type
(Pent
))
1421 Error_Msg_N
("invalid index type in entry name", N
);
1423 elsif Present
(Next
(Exp
)) then
1424 Error_Msg_N
("too many subscripts in entry reference", N
);
1427 Set_Etype
(N
, Etype
(P
));
1432 elsif Is_Record_Type
(Array_Type
)
1433 and then Remote_AST_I_Dereference
(P
)
1437 elsif Array_Type
= Any_Type
then
1438 Set_Etype
(N
, Any_Type
);
1441 -- Here we definitely have a bad indexing
1444 if Nkind
(Parent
(N
)) = N_Requeue_Statement
1445 and then Present
(Pent
) and then Ekind
(Pent
) = E_Entry
1448 ("REQUEUE does not permit parameters", First
(Exprs
));
1450 elsif Is_Entity_Name
(P
)
1451 and then Etype
(P
) = Standard_Void_Type
1453 Error_Msg_NE
("incorrect use of&", P
, Entity
(P
));
1456 Error_Msg_N
("array type required in indexed component", P
);
1459 Set_Etype
(N
, Any_Type
);
1463 Index
:= First_Index
(Array_Type
);
1465 while Present
(Index
) and then Present
(Exp
) loop
1466 if not Has_Compatible_Type
(Exp
, Etype
(Index
)) then
1467 Wrong_Type
(Exp
, Etype
(Index
));
1468 Set_Etype
(N
, Any_Type
);
1476 Set_Etype
(N
, Component_Type
(Array_Type
));
1478 if Present
(Index
) then
1480 ("too few subscripts in array reference", First
(Exprs
));
1482 elsif Present
(Exp
) then
1483 Error_Msg_N
("too many subscripts in array reference", Exp
);
1486 end Process_Indexed_Component
;
1488 ----------------------------------------
1489 -- Process_Indexed_Component_Or_Slice --
1490 ----------------------------------------
1492 procedure Process_Indexed_Component_Or_Slice
is
1494 Exp
:= First
(Exprs
);
1495 while Present
(Exp
) loop
1496 Analyze_Expression
(Exp
);
1500 Exp
:= First
(Exprs
);
1502 -- If one index is present, and it is a subtype name, then the
1503 -- node denotes a slice (note that the case of an explicit range
1504 -- for a slice was already built as an N_Slice node in the first
1505 -- place, so that case is not handled here).
1507 -- We use a replace rather than a rewrite here because this is one
1508 -- of the cases in which the tree built by the parser is plain wrong.
1511 and then Is_Entity_Name
(Exp
)
1512 and then Is_Type
(Entity
(Exp
))
1515 Make_Slice
(Sloc
(N
),
1517 Discrete_Range
=> New_Copy
(Exp
)));
1520 -- Otherwise (more than one index present, or single index is not
1521 -- a subtype name), then we have the indexed component case.
1524 Process_Indexed_Component
;
1526 end Process_Indexed_Component_Or_Slice
;
1528 ------------------------------------------
1529 -- Process_Overloaded_Indexed_Component --
1530 ------------------------------------------
1532 procedure Process_Overloaded_Indexed_Component
is
1541 Set_Etype
(N
, Any_Type
);
1543 Get_First_Interp
(P
, I
, It
);
1544 while Present
(It
.Nam
) loop
1547 if Is_Access_Type
(Typ
) then
1548 Typ
:= Designated_Type
(Typ
);
1549 Error_Msg_NW
(Warn_On_Dereference
, "?implicit dereference", N
);
1552 if Is_Array_Type
(Typ
) then
1554 -- Got a candidate: verify that index types are compatible
1556 Index
:= First_Index
(Typ
);
1558 Exp
:= First
(Exprs
);
1559 while Present
(Index
) and then Present
(Exp
) loop
1560 if Has_Compatible_Type
(Exp
, Etype
(Index
)) then
1572 if Found
and then No
(Index
) and then No
(Exp
) then
1574 Etype
(Component_Type
(Typ
)),
1575 Etype
(Component_Type
(Typ
)));
1579 Get_Next_Interp
(I
, It
);
1582 if Etype
(N
) = Any_Type
then
1583 Error_Msg_N
("no legal interpetation for indexed component", N
);
1584 Set_Is_Overloaded
(N
, False);
1588 end Process_Overloaded_Indexed_Component
;
1590 -- Start of processing for Analyze_Indexed_Component_Form
1593 -- Get name of array, function or type
1596 if Nkind
(N
) = N_Function_Call
1597 or else Nkind
(N
) = N_Procedure_Call_Statement
1599 -- If P is an explicit dereference whose prefix is of a
1600 -- remote access-to-subprogram type, then N has already
1601 -- been rewritten as a subprogram call and analyzed.
1606 pragma Assert
(Nkind
(N
) = N_Indexed_Component
);
1608 P_T
:= Base_Type
(Etype
(P
));
1610 if Is_Entity_Name
(P
)
1611 or else Nkind
(P
) = N_Operator_Symbol
1615 if Ekind
(U_N
) in Type_Kind
then
1617 -- Reformat node as a type conversion
1619 E
:= Remove_Head
(Exprs
);
1621 if Present
(First
(Exprs
)) then
1623 ("argument of type conversion must be single expression", N
);
1626 Change_Node
(N
, N_Type_Conversion
);
1627 Set_Subtype_Mark
(N
, P
);
1629 Set_Expression
(N
, E
);
1631 -- After changing the node, call for the specific Analysis
1632 -- routine directly, to avoid a double call to the expander.
1634 Analyze_Type_Conversion
(N
);
1638 if Is_Overloadable
(U_N
) then
1639 Process_Function_Call
;
1641 elsif Ekind
(Etype
(P
)) = E_Subprogram_Type
1642 or else (Is_Access_Type
(Etype
(P
))
1644 Ekind
(Designated_Type
(Etype
(P
))) = E_Subprogram_Type
)
1646 -- Call to access_to-subprogram with possible implicit dereference
1648 Process_Function_Call
;
1650 elsif Is_Generic_Subprogram
(U_N
) then
1652 -- A common beginner's (or C++ templates fan) error
1654 Error_Msg_N
("generic subprogram cannot be called", N
);
1655 Set_Etype
(N
, Any_Type
);
1659 Process_Indexed_Component_Or_Slice
;
1662 -- If not an entity name, prefix is an expression that may denote
1663 -- an array or an access-to-subprogram.
1666 if Ekind
(P_T
) = E_Subprogram_Type
1667 or else (Is_Access_Type
(P_T
)
1669 Ekind
(Designated_Type
(P_T
)) = E_Subprogram_Type
)
1671 Process_Function_Call
;
1673 elsif Nkind
(P
) = N_Selected_Component
1674 and then Is_Overloadable
(Entity
(Selector_Name
(P
)))
1676 Process_Function_Call
;
1679 -- Indexed component, slice, or a call to a member of a family
1680 -- entry, which will be converted to an entry call later.
1682 Process_Indexed_Component_Or_Slice
;
1685 end Analyze_Indexed_Component_Form
;
1687 ------------------------
1688 -- Analyze_Logical_Op --
1689 ------------------------
1691 procedure Analyze_Logical_Op
(N
: Node_Id
) is
1692 L
: constant Node_Id
:= Left_Opnd
(N
);
1693 R
: constant Node_Id
:= Right_Opnd
(N
);
1694 Op_Id
: Entity_Id
:= Entity
(N
);
1697 Set_Etype
(N
, Any_Type
);
1698 Candidate_Type
:= Empty
;
1700 Analyze_Expression
(L
);
1701 Analyze_Expression
(R
);
1703 if Present
(Op_Id
) then
1705 if Ekind
(Op_Id
) = E_Operator
then
1706 Find_Boolean_Types
(L
, R
, Op_Id
, N
);
1708 Add_One_Interp
(N
, Op_Id
, Etype
(Op_Id
));
1712 Op_Id
:= Get_Name_Entity_Id
(Chars
(N
));
1714 while Present
(Op_Id
) loop
1715 if Ekind
(Op_Id
) = E_Operator
then
1716 Find_Boolean_Types
(L
, R
, Op_Id
, N
);
1718 Analyze_User_Defined_Binary_Op
(N
, Op_Id
);
1721 Op_Id
:= Homonym
(Op_Id
);
1726 end Analyze_Logical_Op
;
1728 ---------------------------
1729 -- Analyze_Membership_Op --
1730 ---------------------------
1732 procedure Analyze_Membership_Op
(N
: Node_Id
) is
1733 L
: constant Node_Id
:= Left_Opnd
(N
);
1734 R
: constant Node_Id
:= Right_Opnd
(N
);
1736 Index
: Interp_Index
;
1738 Found
: Boolean := False;
1742 procedure Try_One_Interp
(T1
: Entity_Id
);
1743 -- Routine to try one proposed interpretation. Note that the context
1744 -- of the operation plays no role in resolving the arguments, so that
1745 -- if there is more than one interpretation of the operands that is
1746 -- compatible with a membership test, the operation is ambiguous.
1748 --------------------
1749 -- Try_One_Interp --
1750 --------------------
1752 procedure Try_One_Interp
(T1
: Entity_Id
) is
1754 if Has_Compatible_Type
(R
, T1
) then
1756 and then Base_Type
(T1
) /= Base_Type
(T_F
)
1758 It
:= Disambiguate
(L
, I_F
, Index
, Any_Type
);
1760 if It
= No_Interp
then
1761 Ambiguous_Operands
(N
);
1762 Set_Etype
(L
, Any_Type
);
1780 -- Start of processing for Analyze_Membership_Op
1783 Analyze_Expression
(L
);
1785 if Nkind
(R
) = N_Range
1786 or else (Nkind
(R
) = N_Attribute_Reference
1787 and then Attribute_Name
(R
) = Name_Range
)
1791 if not Is_Overloaded
(L
) then
1792 Try_One_Interp
(Etype
(L
));
1795 Get_First_Interp
(L
, Index
, It
);
1797 while Present
(It
.Typ
) loop
1798 Try_One_Interp
(It
.Typ
);
1799 Get_Next_Interp
(Index
, It
);
1803 -- If not a range, it can only be a subtype mark, or else there
1804 -- is a more basic error, to be diagnosed in Find_Type.
1809 if Is_Entity_Name
(R
) then
1810 Check_Fully_Declared
(Entity
(R
), R
);
1814 -- Compatibility between expression and subtype mark or range is
1815 -- checked during resolution. The result of the operation is Boolean
1818 Set_Etype
(N
, Standard_Boolean
);
1819 end Analyze_Membership_Op
;
1821 ----------------------
1822 -- Analyze_Negation --
1823 ----------------------
1825 procedure Analyze_Negation
(N
: Node_Id
) is
1826 R
: constant Node_Id
:= Right_Opnd
(N
);
1827 Op_Id
: Entity_Id
:= Entity
(N
);
1830 Set_Etype
(N
, Any_Type
);
1831 Candidate_Type
:= Empty
;
1833 Analyze_Expression
(R
);
1835 if Present
(Op_Id
) then
1836 if Ekind
(Op_Id
) = E_Operator
then
1837 Find_Negation_Types
(R
, Op_Id
, N
);
1839 Add_One_Interp
(N
, Op_Id
, Etype
(Op_Id
));
1843 Op_Id
:= Get_Name_Entity_Id
(Chars
(N
));
1844 while Present
(Op_Id
) loop
1845 if Ekind
(Op_Id
) = E_Operator
then
1846 Find_Negation_Types
(R
, Op_Id
, N
);
1848 Analyze_User_Defined_Unary_Op
(N
, Op_Id
);
1851 Op_Id
:= Homonym
(Op_Id
);
1856 end Analyze_Negation
;
1862 procedure Analyze_Null
(N
: Node_Id
) is
1864 Set_Etype
(N
, Any_Access
);
1867 ----------------------
1868 -- Analyze_One_Call --
1869 ----------------------
1871 procedure Analyze_One_Call
1875 Success
: out Boolean)
1877 Actuals
: constant List_Id
:= Parameter_Associations
(N
);
1878 Prev_T
: constant Entity_Id
:= Etype
(N
);
1881 Is_Indexed
: Boolean := False;
1882 Subp_Type
: constant Entity_Id
:= Etype
(Nam
);
1885 procedure Indicate_Name_And_Type
;
1886 -- If candidate interpretation matches, indicate name and type of
1887 -- result on call node.
1889 ----------------------------
1890 -- Indicate_Name_And_Type --
1891 ----------------------------
1893 procedure Indicate_Name_And_Type
is
1895 Add_One_Interp
(N
, Nam
, Etype
(Nam
));
1898 -- If the prefix of the call is a name, indicate the entity
1899 -- being called. If it is not a name, it is an expression that
1900 -- denotes an access to subprogram or else an entry or family. In
1901 -- the latter case, the name is a selected component, and the entity
1902 -- being called is noted on the selector.
1904 if not Is_Type
(Nam
) then
1905 if Is_Entity_Name
(Name
(N
))
1906 or else Nkind
(Name
(N
)) = N_Operator_Symbol
1908 Set_Entity
(Name
(N
), Nam
);
1910 elsif Nkind
(Name
(N
)) = N_Selected_Component
then
1911 Set_Entity
(Selector_Name
(Name
(N
)), Nam
);
1915 if Debug_Flag_E
and not Report
then
1916 Write_Str
(" Overloaded call ");
1917 Write_Int
(Int
(N
));
1918 Write_Str
(" compatible with ");
1919 Write_Int
(Int
(Nam
));
1922 end Indicate_Name_And_Type
;
1924 -- Start of processing for Analyze_One_Call
1929 -- If the subprogram has no formals, or if all the formals have
1930 -- defaults, and the return type is an array type, the node may
1931 -- denote an indexing of the result of a parameterless call.
1933 if Needs_No_Actuals
(Nam
)
1934 and then Present
(Actuals
)
1936 if Is_Array_Type
(Subp_Type
) then
1937 Is_Indexed
:= Try_Indexed_Call
(N
, Nam
, Subp_Type
);
1939 elsif Is_Access_Type
(Subp_Type
)
1940 and then Is_Array_Type
(Designated_Type
(Subp_Type
))
1943 Try_Indexed_Call
(N
, Nam
, Designated_Type
(Subp_Type
));
1945 elsif Is_Access_Type
(Subp_Type
)
1946 and then Ekind
(Designated_Type
(Subp_Type
)) = E_Subprogram_Type
1948 Is_Indexed
:= Try_Indirect_Call
(N
, Nam
, Subp_Type
);
1953 Normalize_Actuals
(N
, Nam
, (Report
and not Is_Indexed
), Norm_OK
);
1957 -- Mismatch in number or names of parameters
1959 if Debug_Flag_E
then
1960 Write_Str
(" normalization fails in call ");
1961 Write_Int
(Int
(N
));
1962 Write_Str
(" with subprogram ");
1963 Write_Int
(Int
(Nam
));
1967 -- If the context expects a function call, discard any interpretation
1968 -- that is a procedure. If the node is not overloaded, leave as is for
1969 -- better error reporting when type mismatch is found.
1971 elsif Nkind
(N
) = N_Function_Call
1972 and then Is_Overloaded
(Name
(N
))
1973 and then Ekind
(Nam
) = E_Procedure
1977 -- Ditto for function calls in a procedure context
1979 elsif Nkind
(N
) = N_Procedure_Call_Statement
1980 and then Is_Overloaded
(Name
(N
))
1981 and then Etype
(Nam
) /= Standard_Void_Type
1985 elsif not Present
(Actuals
) then
1987 -- If Normalize succeeds, then there are default parameters for
1990 Indicate_Name_And_Type
;
1992 elsif Ekind
(Nam
) = E_Operator
then
1993 if Nkind
(N
) = N_Procedure_Call_Statement
then
1997 -- This can occur when the prefix of the call is an operator
1998 -- name or an expanded name whose selector is an operator name.
2000 Analyze_Operator_Call
(N
, Nam
);
2002 if Etype
(N
) /= Prev_T
then
2004 -- There may be a user-defined operator that hides the
2005 -- current interpretation. We must check for this independently
2006 -- of the analysis of the call with the user-defined operation,
2007 -- because the parameter names may be wrong and yet the hiding
2008 -- takes place. Fixes b34014o.
2010 if Is_Overloaded
(Name
(N
)) then
2016 Get_First_Interp
(Name
(N
), I
, It
);
2017 while Present
(It
.Nam
) loop
2018 if Ekind
(It
.Nam
) /= E_Operator
2019 and then Hides_Op
(It
.Nam
, Nam
)
2022 (First_Actual
(N
), Etype
(First_Formal
(It
.Nam
)))
2023 and then (No
(Next_Actual
(First_Actual
(N
)))
2024 or else Has_Compatible_Type
2025 (Next_Actual
(First_Actual
(N
)),
2026 Etype
(Next_Formal
(First_Formal
(It
.Nam
)))))
2028 Set_Etype
(N
, Prev_T
);
2032 Get_Next_Interp
(I
, It
);
2037 -- If operator matches formals, record its name on the call.
2038 -- If the operator is overloaded, Resolve will select the
2039 -- correct one from the list of interpretations. The call
2040 -- node itself carries the first candidate.
2042 Set_Entity
(Name
(N
), Nam
);
2045 elsif Report
and then Etype
(N
) = Any_Type
then
2046 Error_Msg_N
("incompatible arguments for operator", N
);
2050 -- Normalize_Actuals has chained the named associations in the
2051 -- correct order of the formals.
2053 Actual
:= First_Actual
(N
);
2054 Formal
:= First_Formal
(Nam
);
2055 while Present
(Actual
) and then Present
(Formal
) loop
2056 if Nkind
(Parent
(Actual
)) /= N_Parameter_Association
2057 or else Chars
(Selector_Name
(Parent
(Actual
))) = Chars
(Formal
)
2059 if Has_Compatible_Type
(Actual
, Etype
(Formal
)) then
2060 Next_Actual
(Actual
);
2061 Next_Formal
(Formal
);
2064 if Debug_Flag_E
then
2065 Write_Str
(" type checking fails in call ");
2066 Write_Int
(Int
(N
));
2067 Write_Str
(" with formal ");
2068 Write_Int
(Int
(Formal
));
2069 Write_Str
(" in subprogram ");
2070 Write_Int
(Int
(Nam
));
2074 if Report
and not Is_Indexed
then
2075 Wrong_Type
(Actual
, Etype
(Formal
));
2077 if Nkind
(Actual
) = N_Op_Eq
2078 and then Nkind
(Left_Opnd
(Actual
)) = N_Identifier
2080 Formal
:= First_Formal
(Nam
);
2082 while Present
(Formal
) loop
2084 if Chars
(Left_Opnd
(Actual
)) = Chars
(Formal
) then
2086 ("possible misspelling of `='>`!", Actual
);
2090 Next_Formal
(Formal
);
2094 if All_Errors_Mode
then
2095 Error_Msg_Sloc
:= Sloc
(Nam
);
2097 if Is_Overloadable
(Nam
)
2098 and then Present
(Alias
(Nam
))
2099 and then not Comes_From_Source
(Nam
)
2102 (" =='> in call to &#(inherited)!", Actual
, Nam
);
2104 elsif Ekind
(Nam
) = E_Subprogram_Type
then
2106 Access_To_Subprogram_Typ
:
2107 constant Entity_Id
:=
2109 (Associated_Node_For_Itype
(Nam
));
2112 " =='> in call to dereference of &#!",
2113 Actual
, Access_To_Subprogram_Typ
);
2117 Error_Msg_NE
(" =='> in call to &#!", Actual
, Nam
);
2127 -- Normalize_Actuals has verified that a default value exists
2128 -- for this formal. Current actual names a subsequent formal.
2130 Next_Formal
(Formal
);
2134 -- On exit, all actuals match
2136 Indicate_Name_And_Type
;
2138 end Analyze_One_Call
;
2140 ---------------------------
2141 -- Analyze_Operator_Call --
2142 ---------------------------
2144 procedure Analyze_Operator_Call
(N
: Node_Id
; Op_Id
: Entity_Id
) is
2145 Op_Name
: constant Name_Id
:= Chars
(Op_Id
);
2146 Act1
: constant Node_Id
:= First_Actual
(N
);
2147 Act2
: constant Node_Id
:= Next_Actual
(Act1
);
2150 -- Binary operator case
2152 if Present
(Act2
) then
2154 -- If more than two operands, then not binary operator after all
2156 if Present
(Next_Actual
(Act2
)) then
2159 elsif Op_Name
= Name_Op_Add
2160 or else Op_Name
= Name_Op_Subtract
2161 or else Op_Name
= Name_Op_Multiply
2162 or else Op_Name
= Name_Op_Divide
2163 or else Op_Name
= Name_Op_Mod
2164 or else Op_Name
= Name_Op_Rem
2165 or else Op_Name
= Name_Op_Expon
2167 Find_Arithmetic_Types
(Act1
, Act2
, Op_Id
, N
);
2169 elsif Op_Name
= Name_Op_And
2170 or else Op_Name
= Name_Op_Or
2171 or else Op_Name
= Name_Op_Xor
2173 Find_Boolean_Types
(Act1
, Act2
, Op_Id
, N
);
2175 elsif Op_Name
= Name_Op_Lt
2176 or else Op_Name
= Name_Op_Le
2177 or else Op_Name
= Name_Op_Gt
2178 or else Op_Name
= Name_Op_Ge
2180 Find_Comparison_Types
(Act1
, Act2
, Op_Id
, N
);
2182 elsif Op_Name
= Name_Op_Eq
2183 or else Op_Name
= Name_Op_Ne
2185 Find_Equality_Types
(Act1
, Act2
, Op_Id
, N
);
2187 elsif Op_Name
= Name_Op_Concat
then
2188 Find_Concatenation_Types
(Act1
, Act2
, Op_Id
, N
);
2190 -- Is this else null correct, or should it be an abort???
2196 -- Unary operator case
2199 if Op_Name
= Name_Op_Subtract
or else
2200 Op_Name
= Name_Op_Add
or else
2201 Op_Name
= Name_Op_Abs
2203 Find_Unary_Types
(Act1
, Op_Id
, N
);
2206 Op_Name
= Name_Op_Not
2208 Find_Negation_Types
(Act1
, Op_Id
, N
);
2210 -- Is this else null correct, or should it be an abort???
2216 end Analyze_Operator_Call
;
2218 -------------------------------------------
2219 -- Analyze_Overloaded_Selected_Component --
2220 -------------------------------------------
2222 procedure Analyze_Overloaded_Selected_Component
(N
: Node_Id
) is
2223 Nam
: constant Node_Id
:= Prefix
(N
);
2224 Sel
: constant Node_Id
:= Selector_Name
(N
);
2231 Set_Etype
(Sel
, Any_Type
);
2233 Get_First_Interp
(Nam
, I
, It
);
2234 while Present
(It
.Typ
) loop
2235 if Is_Access_Type
(It
.Typ
) then
2236 T
:= Designated_Type
(It
.Typ
);
2237 Error_Msg_NW
(Warn_On_Dereference
, "?implicit dereference", N
);
2242 if Is_Record_Type
(T
) then
2243 Comp
:= First_Entity
(T
);
2244 while Present
(Comp
) loop
2245 if Chars
(Comp
) = Chars
(Sel
)
2246 and then Is_Visible_Component
(Comp
)
2248 Set_Entity_With_Style_Check
(Sel
, Comp
);
2249 Generate_Reference
(Comp
, Sel
);
2251 Set_Etype
(Sel
, Etype
(Comp
));
2252 Add_One_Interp
(N
, Etype
(Comp
), Etype
(Comp
));
2254 -- This also specifies a candidate to resolve the name.
2255 -- Further overloading will be resolved from context.
2257 Set_Etype
(Nam
, It
.Typ
);
2263 elsif Is_Concurrent_Type
(T
) then
2264 Comp
:= First_Entity
(T
);
2265 while Present
(Comp
)
2266 and then Comp
/= First_Private_Entity
(T
)
2268 if Chars
(Comp
) = Chars
(Sel
) then
2269 if Is_Overloadable
(Comp
) then
2270 Add_One_Interp
(Sel
, Comp
, Etype
(Comp
));
2272 Set_Entity_With_Style_Check
(Sel
, Comp
);
2273 Generate_Reference
(Comp
, Sel
);
2276 Set_Etype
(Sel
, Etype
(Comp
));
2277 Set_Etype
(N
, Etype
(Comp
));
2278 Set_Etype
(Nam
, It
.Typ
);
2280 -- For access type case, introduce explicit deference for
2281 -- more uniform treatment of entry calls.
2283 if Is_Access_Type
(Etype
(Nam
)) then
2284 Insert_Explicit_Dereference
(Nam
);
2286 (Warn_On_Dereference
, "?implicit dereference", N
);
2293 Set_Is_Overloaded
(N
, Is_Overloaded
(Sel
));
2296 Get_Next_Interp
(I
, It
);
2299 if Etype
(N
) = Any_Type
then
2300 Error_Msg_NE
("undefined selector& for overloaded prefix", N
, Sel
);
2301 Set_Entity
(Sel
, Any_Id
);
2302 Set_Etype
(Sel
, Any_Type
);
2304 end Analyze_Overloaded_Selected_Component
;
2306 ----------------------------------
2307 -- Analyze_Qualified_Expression --
2308 ----------------------------------
2310 procedure Analyze_Qualified_Expression
(N
: Node_Id
) is
2311 Mark
: constant Entity_Id
:= Subtype_Mark
(N
);
2315 Set_Etype
(N
, Any_Type
);
2319 if T
= Any_Type
then
2323 Check_Fully_Declared
(T
, N
);
2324 Analyze_Expression
(Expression
(N
));
2326 end Analyze_Qualified_Expression
;
2332 procedure Analyze_Range
(N
: Node_Id
) is
2333 L
: constant Node_Id
:= Low_Bound
(N
);
2334 H
: constant Node_Id
:= High_Bound
(N
);
2335 I1
, I2
: Interp_Index
;
2338 procedure Check_Common_Type
(T1
, T2
: Entity_Id
);
2339 -- Verify the compatibility of two types, and choose the
2340 -- non universal one if the other is universal.
2342 procedure Check_High_Bound
(T
: Entity_Id
);
2343 -- Test one interpretation of the low bound against all those
2344 -- of the high bound.
2346 procedure Check_Universal_Expression
(N
: Node_Id
);
2347 -- In Ada83, reject bounds of a universal range that are not
2348 -- literals or entity names.
2350 -----------------------
2351 -- Check_Common_Type --
2352 -----------------------
2354 procedure Check_Common_Type
(T1
, T2
: Entity_Id
) is
2356 if Covers
(T1
, T2
) or else Covers
(T2
, T1
) then
2357 if T1
= Universal_Integer
2358 or else T1
= Universal_Real
2359 or else T1
= Any_Character
2361 Add_One_Interp
(N
, Base_Type
(T2
), Base_Type
(T2
));
2364 Add_One_Interp
(N
, T1
, T1
);
2367 Add_One_Interp
(N
, Base_Type
(T1
), Base_Type
(T1
));
2370 end Check_Common_Type
;
2372 ----------------------
2373 -- Check_High_Bound --
2374 ----------------------
2376 procedure Check_High_Bound
(T
: Entity_Id
) is
2378 if not Is_Overloaded
(H
) then
2379 Check_Common_Type
(T
, Etype
(H
));
2381 Get_First_Interp
(H
, I2
, It2
);
2382 while Present
(It2
.Typ
) loop
2383 Check_Common_Type
(T
, It2
.Typ
);
2384 Get_Next_Interp
(I2
, It2
);
2387 end Check_High_Bound
;
2389 -----------------------------
2390 -- Is_Universal_Expression --
2391 -----------------------------
2393 procedure Check_Universal_Expression
(N
: Node_Id
) is
2395 if Etype
(N
) = Universal_Integer
2396 and then Nkind
(N
) /= N_Integer_Literal
2397 and then not Is_Entity_Name
(N
)
2398 and then Nkind
(N
) /= N_Attribute_Reference
2400 Error_Msg_N
("illegal bound in discrete range", N
);
2402 end Check_Universal_Expression
;
2404 -- Start of processing for Analyze_Range
2407 Set_Etype
(N
, Any_Type
);
2408 Analyze_Expression
(L
);
2409 Analyze_Expression
(H
);
2411 if Etype
(L
) = Any_Type
or else Etype
(H
) = Any_Type
then
2415 if not Is_Overloaded
(L
) then
2416 Check_High_Bound
(Etype
(L
));
2418 Get_First_Interp
(L
, I1
, It1
);
2419 while Present
(It1
.Typ
) loop
2420 Check_High_Bound
(It1
.Typ
);
2421 Get_Next_Interp
(I1
, It1
);
2425 -- If result is Any_Type, then we did not find a compatible pair
2427 if Etype
(N
) = Any_Type
then
2428 Error_Msg_N
("incompatible types in range ", N
);
2432 if Ada_Version
= Ada_83
2434 (Nkind
(Parent
(N
)) = N_Loop_Parameter_Specification
2435 or else Nkind
(Parent
(N
)) = N_Constrained_Array_Definition
)
2437 Check_Universal_Expression
(L
);
2438 Check_Universal_Expression
(H
);
2442 -----------------------
2443 -- Analyze_Reference --
2444 -----------------------
2446 procedure Analyze_Reference
(N
: Node_Id
) is
2447 P
: constant Node_Id
:= Prefix
(N
);
2448 Acc_Type
: Entity_Id
;
2451 Acc_Type
:= Create_Itype
(E_Allocator_Type
, N
);
2452 Set_Etype
(Acc_Type
, Acc_Type
);
2453 Init_Size_Align
(Acc_Type
);
2454 Set_Directly_Designated_Type
(Acc_Type
, Etype
(P
));
2455 Set_Etype
(N
, Acc_Type
);
2456 end Analyze_Reference
;
2458 --------------------------------
2459 -- Analyze_Selected_Component --
2460 --------------------------------
2462 -- Prefix is a record type or a task or protected type. In the
2463 -- later case, the selector must denote a visible entry.
2465 procedure Analyze_Selected_Component
(N
: Node_Id
) is
2466 Name
: constant Node_Id
:= Prefix
(N
);
2467 Sel
: constant Node_Id
:= Selector_Name
(N
);
2469 Entity_List
: Entity_Id
;
2470 Prefix_Type
: Entity_Id
;
2471 Pent
: Entity_Id
:= Empty
;
2476 -- Start of processing for Analyze_Selected_Component
2479 Set_Etype
(N
, Any_Type
);
2481 if Is_Overloaded
(Name
) then
2482 Analyze_Overloaded_Selected_Component
(N
);
2485 elsif Etype
(Name
) = Any_Type
then
2486 Set_Entity
(Sel
, Any_Id
);
2487 Set_Etype
(Sel
, Any_Type
);
2491 -- Function calls that are prefixes of selected components must be
2492 -- fully resolved in case we need to build an actual subtype, or
2493 -- do some other operation requiring a fully resolved prefix.
2495 -- Note: Resolving all Nkinds of nodes here doesn't work.
2496 -- (Breaks 2129-008) ???.
2498 if Nkind
(Name
) = N_Function_Call
then
2502 Prefix_Type
:= Etype
(Name
);
2505 if Is_Access_Type
(Prefix_Type
) then
2507 -- A RACW object can never be used as prefix of a selected
2508 -- component since that means it is dereferenced without
2509 -- being a controlling operand of a dispatching operation
2512 if Is_Remote_Access_To_Class_Wide_Type
(Prefix_Type
)
2513 and then Comes_From_Source
(N
)
2516 ("invalid dereference of a remote access to class-wide value",
2519 -- Normal case of selected component applied to access type
2522 Error_Msg_NW
(Warn_On_Dereference
, "?implicit dereference", N
);
2524 if Is_Entity_Name
(Name
) then
2525 Pent
:= Entity
(Name
);
2526 elsif Nkind
(Name
) = N_Selected_Component
2527 and then Is_Entity_Name
(Selector_Name
(Name
))
2529 Pent
:= Entity
(Selector_Name
(Name
));
2532 Process_Implicit_Dereference_Prefix
(Pent
, Name
);
2535 Prefix_Type
:= Designated_Type
(Prefix_Type
);
2538 if Ekind
(Prefix_Type
) = E_Private_Subtype
then
2539 Prefix_Type
:= Base_Type
(Prefix_Type
);
2542 Entity_List
:= Prefix_Type
;
2544 -- For class-wide types, use the entity list of the root type. This
2545 -- indirection is specially important for private extensions because
2546 -- only the root type get switched (not the class-wide type).
2548 if Is_Class_Wide_Type
(Prefix_Type
) then
2549 Entity_List
:= Root_Type
(Prefix_Type
);
2552 Comp
:= First_Entity
(Entity_List
);
2554 -- If the selector has an original discriminant, the node appears in
2555 -- an instance. Replace the discriminant with the corresponding one
2556 -- in the current discriminated type. For nested generics, this must
2557 -- be done transitively, so note the new original discriminant.
2559 if Nkind
(Sel
) = N_Identifier
2560 and then Present
(Original_Discriminant
(Sel
))
2562 Comp
:= Find_Corresponding_Discriminant
(Sel
, Prefix_Type
);
2564 -- Mark entity before rewriting, for completeness and because
2565 -- subsequent semantic checks might examine the original node.
2567 Set_Entity
(Sel
, Comp
);
2568 Rewrite
(Selector_Name
(N
),
2569 New_Occurrence_Of
(Comp
, Sloc
(N
)));
2570 Set_Original_Discriminant
(Selector_Name
(N
), Comp
);
2571 Set_Etype
(N
, Etype
(Comp
));
2573 if Is_Access_Type
(Etype
(Name
)) then
2574 Insert_Explicit_Dereference
(Name
);
2575 Error_Msg_NW
(Warn_On_Dereference
, "?implicit dereference", N
);
2578 elsif Is_Record_Type
(Prefix_Type
) then
2580 -- Find component with given name
2582 while Present
(Comp
) loop
2583 if Chars
(Comp
) = Chars
(Sel
)
2584 and then Is_Visible_Component
(Comp
)
2586 Set_Entity_With_Style_Check
(Sel
, Comp
);
2587 Generate_Reference
(Comp
, Sel
);
2589 Set_Etype
(Sel
, Etype
(Comp
));
2591 if Ekind
(Comp
) = E_Discriminant
then
2592 if Is_Unchecked_Union
(Base_Type
(Prefix_Type
)) then
2594 ("cannot reference discriminant of Unchecked_Union",
2598 if Is_Generic_Type
(Prefix_Type
)
2600 Is_Generic_Type
(Root_Type
(Prefix_Type
))
2602 Set_Original_Discriminant
(Sel
, Comp
);
2606 -- Resolve the prefix early otherwise it is not possible to
2607 -- build the actual subtype of the component: it may need
2608 -- to duplicate this prefix and duplication is only allowed
2609 -- on fully resolved expressions.
2613 -- We never need an actual subtype for the case of a selection
2614 -- for a indexed component of a non-packed array, since in
2615 -- this case gigi generates all the checks and can find the
2616 -- necessary bounds information.
2618 -- We also do not need an actual subtype for the case of
2619 -- a first, last, length, or range attribute applied to a
2620 -- non-packed array, since gigi can again get the bounds in
2621 -- these cases (gigi cannot handle the packed case, since it
2622 -- has the bounds of the packed array type, not the original
2623 -- bounds of the type). However, if the prefix is itself a
2624 -- selected component, as in a.b.c (i), gigi may regard a.b.c
2625 -- as a dynamic-sized temporary, so we do generate an actual
2626 -- subtype for this case.
2628 Parent_N
:= Parent
(N
);
2630 if not Is_Packed
(Etype
(Comp
))
2632 ((Nkind
(Parent_N
) = N_Indexed_Component
2633 and then Nkind
(Name
) /= N_Selected_Component
)
2635 (Nkind
(Parent_N
) = N_Attribute_Reference
2636 and then (Attribute_Name
(Parent_N
) = Name_First
2638 Attribute_Name
(Parent_N
) = Name_Last
2640 Attribute_Name
(Parent_N
) = Name_Length
2642 Attribute_Name
(Parent_N
) = Name_Range
)))
2644 Set_Etype
(N
, Etype
(Comp
));
2646 -- In all other cases, we currently build an actual subtype. It
2647 -- seems likely that many of these cases can be avoided, but
2648 -- right now, the front end makes direct references to the
2649 -- bounds (e.g. in generating a length check), and if we do
2650 -- not make an actual subtype, we end up getting a direct
2651 -- reference to a discriminant which will not do.
2655 Build_Actual_Subtype_Of_Component
(Etype
(Comp
), N
);
2656 Insert_Action
(N
, Act_Decl
);
2658 if No
(Act_Decl
) then
2659 Set_Etype
(N
, Etype
(Comp
));
2662 -- Component type depends on discriminants. Enter the
2663 -- main attributes of the subtype.
2666 Subt
: constant Entity_Id
:=
2667 Defining_Identifier
(Act_Decl
);
2670 Set_Etype
(Subt
, Base_Type
(Etype
(Comp
)));
2671 Set_Ekind
(Subt
, Ekind
(Etype
(Comp
)));
2672 Set_Etype
(N
, Subt
);
2683 -- Ada 2005 (AI-252)
2685 if Ada_Version
>= Ada_05
2686 and then Is_Tagged_Type
(Prefix_Type
)
2687 and then Try_Object_Operation
(N
)
2691 -- If the transformation fails, it will be necessary
2692 -- to redo the analysis with all errors enabled, to indicate
2693 -- candidate interpretations and reasons for each failure ???
2697 elsif Is_Private_Type
(Prefix_Type
) then
2699 -- Allow access only to discriminants of the type. If the
2700 -- type has no full view, gigi uses the parent type for
2701 -- the components, so we do the same here.
2703 if No
(Full_View
(Prefix_Type
)) then
2704 Entity_List
:= Root_Type
(Base_Type
(Prefix_Type
));
2705 Comp
:= First_Entity
(Entity_List
);
2708 while Present
(Comp
) loop
2709 if Chars
(Comp
) = Chars
(Sel
) then
2710 if Ekind
(Comp
) = E_Discriminant
then
2711 Set_Entity_With_Style_Check
(Sel
, Comp
);
2712 Generate_Reference
(Comp
, Sel
);
2714 Set_Etype
(Sel
, Etype
(Comp
));
2715 Set_Etype
(N
, Etype
(Comp
));
2717 if Is_Generic_Type
(Prefix_Type
)
2719 Is_Generic_Type
(Root_Type
(Prefix_Type
))
2721 Set_Original_Discriminant
(Sel
, Comp
);
2726 ("invisible selector for }",
2727 N
, First_Subtype
(Prefix_Type
));
2728 Set_Entity
(Sel
, Any_Id
);
2729 Set_Etype
(N
, Any_Type
);
2738 elsif Is_Concurrent_Type
(Prefix_Type
) then
2740 -- Prefix is concurrent type. Find visible operation with given name
2741 -- For a task, this can only include entries or discriminants if
2742 -- the task type is not an enclosing scope. If it is an enclosing
2743 -- scope (e.g. in an inner task) then all entities are visible, but
2744 -- the prefix must denote the enclosing scope, i.e. can only be
2745 -- a direct name or an expanded name.
2747 Set_Etype
(Sel
, Any_Type
);
2748 In_Scope
:= In_Open_Scopes
(Prefix_Type
);
2750 while Present
(Comp
) loop
2751 if Chars
(Comp
) = Chars
(Sel
) then
2752 if Is_Overloadable
(Comp
) then
2753 Add_One_Interp
(Sel
, Comp
, Etype
(Comp
));
2755 elsif Ekind
(Comp
) = E_Discriminant
2756 or else Ekind
(Comp
) = E_Entry_Family
2758 and then Is_Entity_Name
(Name
))
2760 Set_Entity_With_Style_Check
(Sel
, Comp
);
2761 Generate_Reference
(Comp
, Sel
);
2767 Set_Etype
(Sel
, Etype
(Comp
));
2768 Set_Etype
(N
, Etype
(Comp
));
2770 if Ekind
(Comp
) = E_Discriminant
then
2771 Set_Original_Discriminant
(Sel
, Comp
);
2774 -- For access type case, introduce explicit deference for
2775 -- more uniform treatment of entry calls.
2777 if Is_Access_Type
(Etype
(Name
)) then
2778 Insert_Explicit_Dereference
(Name
);
2780 (Warn_On_Dereference
, "?implicit dereference", N
);
2786 exit when not In_Scope
2788 Comp
= First_Private_Entity
(Base_Type
(Prefix_Type
));
2791 Set_Is_Overloaded
(N
, Is_Overloaded
(Sel
));
2796 Error_Msg_NE
("invalid prefix in selected component&", N
, Sel
);
2799 -- If N still has no type, the component is not defined in the prefix
2801 if Etype
(N
) = Any_Type
then
2803 -- If the prefix is a single concurrent object, use its name in
2804 -- the error message, rather than that of its anonymous type.
2806 if Is_Concurrent_Type
(Prefix_Type
)
2807 and then Is_Internal_Name
(Chars
(Prefix_Type
))
2808 and then not Is_Derived_Type
(Prefix_Type
)
2809 and then Is_Entity_Name
(Name
)
2812 Error_Msg_Node_2
:= Entity
(Name
);
2813 Error_Msg_NE
("no selector& for&", N
, Sel
);
2815 Check_Misspelled_Selector
(Entity_List
, Sel
);
2817 elsif Is_Generic_Type
(Prefix_Type
)
2818 and then Ekind
(Prefix_Type
) = E_Record_Type_With_Private
2819 and then Prefix_Type
/= Etype
(Prefix_Type
)
2820 and then Is_Record_Type
(Etype
(Prefix_Type
))
2822 -- If this is a derived formal type, the parent may have a
2823 -- different visibility at this point. Try for an inherited
2824 -- component before reporting an error.
2826 Set_Etype
(Prefix
(N
), Etype
(Prefix_Type
));
2827 Analyze_Selected_Component
(N
);
2830 elsif Ekind
(Prefix_Type
) = E_Record_Subtype_With_Private
2831 and then Is_Generic_Actual_Type
(Prefix_Type
)
2832 and then Present
(Full_View
(Prefix_Type
))
2834 -- Similarly, if this the actual for a formal derived type, the
2835 -- component inherited from the generic parent may not be visible
2836 -- in the actual, but the selected component is legal.
2843 First_Component
(Generic_Parent_Type
(Parent
(Prefix_Type
)));
2844 while Present
(Comp
) loop
2845 if Chars
(Comp
) = Chars
(Sel
) then
2846 Set_Entity_With_Style_Check
(Sel
, Comp
);
2847 Set_Etype
(Sel
, Etype
(Comp
));
2848 Set_Etype
(N
, Etype
(Comp
));
2852 Next_Component
(Comp
);
2855 pragma Assert
(Etype
(N
) /= Any_Type
);
2859 if Ekind
(Prefix_Type
) = E_Record_Subtype
then
2861 -- Check whether this is a component of the base type
2862 -- which is absent from a statically constrained subtype.
2863 -- This will raise constraint error at run-time, but is
2864 -- not a compile-time error. When the selector is illegal
2865 -- for base type as well fall through and generate a
2866 -- compilation error anyway.
2868 Comp
:= First_Component
(Base_Type
(Prefix_Type
));
2869 while Present
(Comp
) loop
2870 if Chars
(Comp
) = Chars
(Sel
)
2871 and then Is_Visible_Component
(Comp
)
2873 Set_Entity_With_Style_Check
(Sel
, Comp
);
2874 Generate_Reference
(Comp
, Sel
);
2875 Set_Etype
(Sel
, Etype
(Comp
));
2876 Set_Etype
(N
, Etype
(Comp
));
2878 -- Emit appropriate message. Gigi will replace the
2879 -- node subsequently with the appropriate Raise.
2881 Apply_Compile_Time_Constraint_Error
2882 (N
, "component not present in }?",
2883 CE_Discriminant_Check_Failed
,
2884 Ent
=> Prefix_Type
, Rep
=> False);
2885 Set_Raises_Constraint_Error
(N
);
2889 Next_Component
(Comp
);
2894 Error_Msg_Node_2
:= First_Subtype
(Prefix_Type
);
2895 Error_Msg_NE
("no selector& for}", N
, Sel
);
2897 Check_Misspelled_Selector
(Entity_List
, Sel
);
2901 Set_Entity
(Sel
, Any_Id
);
2902 Set_Etype
(Sel
, Any_Type
);
2904 end Analyze_Selected_Component
;
2906 ---------------------------
2907 -- Analyze_Short_Circuit --
2908 ---------------------------
2910 procedure Analyze_Short_Circuit
(N
: Node_Id
) is
2911 L
: constant Node_Id
:= Left_Opnd
(N
);
2912 R
: constant Node_Id
:= Right_Opnd
(N
);
2917 Analyze_Expression
(L
);
2918 Analyze_Expression
(R
);
2919 Set_Etype
(N
, Any_Type
);
2921 if not Is_Overloaded
(L
) then
2923 if Root_Type
(Etype
(L
)) = Standard_Boolean
2924 and then Has_Compatible_Type
(R
, Etype
(L
))
2926 Add_One_Interp
(N
, Etype
(L
), Etype
(L
));
2930 Get_First_Interp
(L
, Ind
, It
);
2932 while Present
(It
.Typ
) loop
2933 if Root_Type
(It
.Typ
) = Standard_Boolean
2934 and then Has_Compatible_Type
(R
, It
.Typ
)
2936 Add_One_Interp
(N
, It
.Typ
, It
.Typ
);
2939 Get_Next_Interp
(Ind
, It
);
2943 -- Here we have failed to find an interpretation. Clearly we
2944 -- know that it is not the case that both operands can have
2945 -- an interpretation of Boolean, but this is by far the most
2946 -- likely intended interpretation. So we simply resolve both
2947 -- operands as Booleans, and at least one of these resolutions
2948 -- will generate an error message, and we do not need to give
2949 -- a further error message on the short circuit operation itself.
2951 if Etype
(N
) = Any_Type
then
2952 Resolve
(L
, Standard_Boolean
);
2953 Resolve
(R
, Standard_Boolean
);
2954 Set_Etype
(N
, Standard_Boolean
);
2956 end Analyze_Short_Circuit
;
2962 procedure Analyze_Slice
(N
: Node_Id
) is
2963 P
: constant Node_Id
:= Prefix
(N
);
2964 D
: constant Node_Id
:= Discrete_Range
(N
);
2965 Array_Type
: Entity_Id
;
2967 procedure Analyze_Overloaded_Slice
;
2968 -- If the prefix is overloaded, select those interpretations that
2969 -- yield a one-dimensional array type.
2971 ------------------------------
2972 -- Analyze_Overloaded_Slice --
2973 ------------------------------
2975 procedure Analyze_Overloaded_Slice
is
2981 Set_Etype
(N
, Any_Type
);
2983 Get_First_Interp
(P
, I
, It
);
2984 while Present
(It
.Nam
) loop
2987 if Is_Access_Type
(Typ
) then
2988 Typ
:= Designated_Type
(Typ
);
2989 Error_Msg_NW
(Warn_On_Dereference
, "?implicit dereference", N
);
2992 if Is_Array_Type
(Typ
)
2993 and then Number_Dimensions
(Typ
) = 1
2994 and then Has_Compatible_Type
(D
, Etype
(First_Index
(Typ
)))
2996 Add_One_Interp
(N
, Typ
, Typ
);
2999 Get_Next_Interp
(I
, It
);
3002 if Etype
(N
) = Any_Type
then
3003 Error_Msg_N
("expect array type in prefix of slice", N
);
3005 end Analyze_Overloaded_Slice
;
3007 -- Start of processing for Analyze_Slice
3013 if Is_Overloaded
(P
) then
3014 Analyze_Overloaded_Slice
;
3017 Array_Type
:= Etype
(P
);
3018 Set_Etype
(N
, Any_Type
);
3020 if Is_Access_Type
(Array_Type
) then
3021 Array_Type
:= Designated_Type
(Array_Type
);
3022 Error_Msg_NW
(Warn_On_Dereference
, "?implicit dereference", N
);
3025 if not Is_Array_Type
(Array_Type
) then
3026 Wrong_Type
(P
, Any_Array
);
3028 elsif Number_Dimensions
(Array_Type
) > 1 then
3030 ("type is not one-dimensional array in slice prefix", N
);
3033 Has_Compatible_Type
(D
, Etype
(First_Index
(Array_Type
)))
3035 Wrong_Type
(D
, Etype
(First_Index
(Array_Type
)));
3038 Set_Etype
(N
, Array_Type
);
3043 -----------------------------
3044 -- Analyze_Type_Conversion --
3045 -----------------------------
3047 procedure Analyze_Type_Conversion
(N
: Node_Id
) is
3048 Expr
: constant Node_Id
:= Expression
(N
);
3052 -- If Conversion_OK is set, then the Etype is already set, and the
3053 -- only processing required is to analyze the expression. This is
3054 -- used to construct certain "illegal" conversions which are not
3055 -- allowed by Ada semantics, but can be handled OK by Gigi, see
3056 -- Sinfo for further details.
3058 if Conversion_OK
(N
) then
3063 -- Otherwise full type analysis is required, as well as some semantic
3064 -- checks to make sure the argument of the conversion is appropriate.
3066 Find_Type
(Subtype_Mark
(N
));
3067 T
:= Entity
(Subtype_Mark
(N
));
3069 Check_Fully_Declared
(T
, N
);
3070 Analyze_Expression
(Expr
);
3071 Validate_Remote_Type_Type_Conversion
(N
);
3073 -- Only remaining step is validity checks on the argument. These
3074 -- are skipped if the conversion does not come from the source.
3076 if not Comes_From_Source
(N
) then
3079 elsif Nkind
(Expr
) = N_Null
then
3080 Error_Msg_N
("argument of conversion cannot be null", N
);
3081 Error_Msg_N
("\use qualified expression instead", N
);
3082 Set_Etype
(N
, Any_Type
);
3084 elsif Nkind
(Expr
) = N_Aggregate
then
3085 Error_Msg_N
("argument of conversion cannot be aggregate", N
);
3086 Error_Msg_N
("\use qualified expression instead", N
);
3088 elsif Nkind
(Expr
) = N_Allocator
then
3089 Error_Msg_N
("argument of conversion cannot be an allocator", N
);
3090 Error_Msg_N
("\use qualified expression instead", N
);
3092 elsif Nkind
(Expr
) = N_String_Literal
then
3093 Error_Msg_N
("argument of conversion cannot be string literal", N
);
3094 Error_Msg_N
("\use qualified expression instead", N
);
3096 elsif Nkind
(Expr
) = N_Character_Literal
then
3097 if Ada_Version
= Ada_83
then
3100 Error_Msg_N
("argument of conversion cannot be character literal",
3102 Error_Msg_N
("\use qualified expression instead", N
);
3105 elsif Nkind
(Expr
) = N_Attribute_Reference
3107 (Attribute_Name
(Expr
) = Name_Access
or else
3108 Attribute_Name
(Expr
) = Name_Unchecked_Access
or else
3109 Attribute_Name
(Expr
) = Name_Unrestricted_Access
)
3111 Error_Msg_N
("argument of conversion cannot be access", N
);
3112 Error_Msg_N
("\use qualified expression instead", N
);
3114 end Analyze_Type_Conversion
;
3116 ----------------------
3117 -- Analyze_Unary_Op --
3118 ----------------------
3120 procedure Analyze_Unary_Op
(N
: Node_Id
) is
3121 R
: constant Node_Id
:= Right_Opnd
(N
);
3122 Op_Id
: Entity_Id
:= Entity
(N
);
3125 Set_Etype
(N
, Any_Type
);
3126 Candidate_Type
:= Empty
;
3128 Analyze_Expression
(R
);
3130 if Present
(Op_Id
) then
3131 if Ekind
(Op_Id
) = E_Operator
then
3132 Find_Unary_Types
(R
, Op_Id
, N
);
3134 Add_One_Interp
(N
, Op_Id
, Etype
(Op_Id
));
3138 Op_Id
:= Get_Name_Entity_Id
(Chars
(N
));
3139 while Present
(Op_Id
) loop
3140 if Ekind
(Op_Id
) = E_Operator
then
3141 if No
(Next_Entity
(First_Entity
(Op_Id
))) then
3142 Find_Unary_Types
(R
, Op_Id
, N
);
3145 elsif Is_Overloadable
(Op_Id
) then
3146 Analyze_User_Defined_Unary_Op
(N
, Op_Id
);
3149 Op_Id
:= Homonym
(Op_Id
);
3154 end Analyze_Unary_Op
;
3156 ----------------------------------
3157 -- Analyze_Unchecked_Expression --
3158 ----------------------------------
3160 procedure Analyze_Unchecked_Expression
(N
: Node_Id
) is
3162 Analyze
(Expression
(N
), Suppress
=> All_Checks
);
3163 Set_Etype
(N
, Etype
(Expression
(N
)));
3164 Save_Interps
(Expression
(N
), N
);
3165 end Analyze_Unchecked_Expression
;
3167 ---------------------------------------
3168 -- Analyze_Unchecked_Type_Conversion --
3169 ---------------------------------------
3171 procedure Analyze_Unchecked_Type_Conversion
(N
: Node_Id
) is
3173 Find_Type
(Subtype_Mark
(N
));
3174 Analyze_Expression
(Expression
(N
));
3175 Set_Etype
(N
, Entity
(Subtype_Mark
(N
)));
3176 end Analyze_Unchecked_Type_Conversion
;
3178 ------------------------------------
3179 -- Analyze_User_Defined_Binary_Op --
3180 ------------------------------------
3182 procedure Analyze_User_Defined_Binary_Op
3187 -- Only do analysis if the operator Comes_From_Source, since otherwise
3188 -- the operator was generated by the expander, and all such operators
3189 -- always refer to the operators in package Standard.
3191 if Comes_From_Source
(N
) then
3193 F1
: constant Entity_Id
:= First_Formal
(Op_Id
);
3194 F2
: constant Entity_Id
:= Next_Formal
(F1
);
3197 -- Verify that Op_Id is a visible binary function. Note that since
3198 -- we know Op_Id is overloaded, potentially use visible means use
3199 -- visible for sure (RM 9.4(11)).
3201 if Ekind
(Op_Id
) = E_Function
3202 and then Present
(F2
)
3203 and then (Is_Immediately_Visible
(Op_Id
)
3204 or else Is_Potentially_Use_Visible
(Op_Id
))
3205 and then Has_Compatible_Type
(Left_Opnd
(N
), Etype
(F1
))
3206 and then Has_Compatible_Type
(Right_Opnd
(N
), Etype
(F2
))
3208 Add_One_Interp
(N
, Op_Id
, Etype
(Op_Id
));
3210 if Debug_Flag_E
then
3211 Write_Str
("user defined operator ");
3212 Write_Name
(Chars
(Op_Id
));
3213 Write_Str
(" on node ");
3214 Write_Int
(Int
(N
));
3220 end Analyze_User_Defined_Binary_Op
;
3222 -----------------------------------
3223 -- Analyze_User_Defined_Unary_Op --
3224 -----------------------------------
3226 procedure Analyze_User_Defined_Unary_Op
3231 -- Only do analysis if the operator Comes_From_Source, since otherwise
3232 -- the operator was generated by the expander, and all such operators
3233 -- always refer to the operators in package Standard.
3235 if Comes_From_Source
(N
) then
3237 F
: constant Entity_Id
:= First_Formal
(Op_Id
);
3240 -- Verify that Op_Id is a visible unary function. Note that since
3241 -- we know Op_Id is overloaded, potentially use visible means use
3242 -- visible for sure (RM 9.4(11)).
3244 if Ekind
(Op_Id
) = E_Function
3245 and then No
(Next_Formal
(F
))
3246 and then (Is_Immediately_Visible
(Op_Id
)
3247 or else Is_Potentially_Use_Visible
(Op_Id
))
3248 and then Has_Compatible_Type
(Right_Opnd
(N
), Etype
(F
))
3250 Add_One_Interp
(N
, Op_Id
, Etype
(Op_Id
));
3254 end Analyze_User_Defined_Unary_Op
;
3256 ---------------------------
3257 -- Check_Arithmetic_Pair --
3258 ---------------------------
3260 procedure Check_Arithmetic_Pair
3261 (T1
, T2
: Entity_Id
;
3265 Op_Name
: constant Name_Id
:= Chars
(Op_Id
);
3267 function Has_Fixed_Op
(Typ
: Entity_Id
; Op
: Entity_Id
) return Boolean;
3268 -- Check whether the fixed-point type Typ has a user-defined operator
3269 -- (multiplication or division) that should hide the corresponding
3270 -- predefined operator. Used to implement Ada 2005 AI-264, to make
3271 -- such operators more visible and therefore useful.
3273 function Specific_Type
(T1
, T2
: Entity_Id
) return Entity_Id
;
3274 -- Get specific type (i.e. non-universal type if there is one)
3280 function Has_Fixed_Op
(Typ
: Entity_Id
; Op
: Entity_Id
) return Boolean is
3286 -- The operation is treated as primitive if it is declared in the
3287 -- same scope as the type, and therefore on the same entity chain.
3289 Ent
:= Next_Entity
(Typ
);
3290 while Present
(Ent
) loop
3291 if Chars
(Ent
) = Chars
(Op
) then
3292 F1
:= First_Formal
(Ent
);
3293 F2
:= Next_Formal
(F1
);
3295 -- The operation counts as primitive if either operand or
3296 -- result are of the given type, and both operands are fixed
3299 if (Etype
(F1
) = Typ
3300 and then Is_Fixed_Point_Type
(Etype
(F2
)))
3304 and then Is_Fixed_Point_Type
(Etype
(F1
)))
3308 and then Is_Fixed_Point_Type
(Etype
(F1
))
3309 and then Is_Fixed_Point_Type
(Etype
(F2
)))
3325 function Specific_Type
(T1
, T2
: Entity_Id
) return Entity_Id
is
3327 if T1
= Universal_Integer
or else T1
= Universal_Real
then
3328 return Base_Type
(T2
);
3330 return Base_Type
(T1
);
3334 -- Start of processing for Check_Arithmetic_Pair
3337 if Op_Name
= Name_Op_Add
or else Op_Name
= Name_Op_Subtract
then
3339 if Is_Numeric_Type
(T1
)
3340 and then Is_Numeric_Type
(T2
)
3341 and then (Covers
(T1
, T2
) or else Covers
(T2
, T1
))
3343 Add_One_Interp
(N
, Op_Id
, Specific_Type
(T1
, T2
));
3346 elsif Op_Name
= Name_Op_Multiply
or else Op_Name
= Name_Op_Divide
then
3348 if Is_Fixed_Point_Type
(T1
)
3349 and then (Is_Fixed_Point_Type
(T2
)
3350 or else T2
= Universal_Real
)
3352 -- If Treat_Fixed_As_Integer is set then the Etype is already set
3353 -- and no further processing is required (this is the case of an
3354 -- operator constructed by Exp_Fixd for a fixed point operation)
3355 -- Otherwise add one interpretation with universal fixed result
3356 -- If the operator is given in functional notation, it comes
3357 -- from source and Fixed_As_Integer cannot apply.
3359 if (Nkind
(N
) not in N_Op
3360 or else not Treat_Fixed_As_Integer
(N
))
3362 (not (Ada_Version
>= Ada_05
and then Has_Fixed_Op
(T1
, Op_Id
))
3363 or else Nkind
(Parent
(N
)) = N_Type_Conversion
)
3365 Add_One_Interp
(N
, Op_Id
, Universal_Fixed
);
3368 elsif Is_Fixed_Point_Type
(T2
)
3369 and then (Nkind
(N
) not in N_Op
3370 or else not Treat_Fixed_As_Integer
(N
))
3371 and then T1
= Universal_Real
3373 (not (Ada_Version
>= Ada_05
and then Has_Fixed_Op
(T1
, Op_Id
))
3374 or else Nkind
(Parent
(N
)) = N_Type_Conversion
)
3376 Add_One_Interp
(N
, Op_Id
, Universal_Fixed
);
3378 elsif Is_Numeric_Type
(T1
)
3379 and then Is_Numeric_Type
(T2
)
3380 and then (Covers
(T1
, T2
) or else Covers
(T2
, T1
))
3382 Add_One_Interp
(N
, Op_Id
, Specific_Type
(T1
, T2
));
3384 elsif Is_Fixed_Point_Type
(T1
)
3385 and then (Base_Type
(T2
) = Base_Type
(Standard_Integer
)
3386 or else T2
= Universal_Integer
)
3388 Add_One_Interp
(N
, Op_Id
, T1
);
3390 elsif T2
= Universal_Real
3391 and then Base_Type
(T1
) = Base_Type
(Standard_Integer
)
3392 and then Op_Name
= Name_Op_Multiply
3394 Add_One_Interp
(N
, Op_Id
, Any_Fixed
);
3396 elsif T1
= Universal_Real
3397 and then Base_Type
(T2
) = Base_Type
(Standard_Integer
)
3399 Add_One_Interp
(N
, Op_Id
, Any_Fixed
);
3401 elsif Is_Fixed_Point_Type
(T2
)
3402 and then (Base_Type
(T1
) = Base_Type
(Standard_Integer
)
3403 or else T1
= Universal_Integer
)
3404 and then Op_Name
= Name_Op_Multiply
3406 Add_One_Interp
(N
, Op_Id
, T2
);
3408 elsif T1
= Universal_Real
and then T2
= Universal_Integer
then
3409 Add_One_Interp
(N
, Op_Id
, T1
);
3411 elsif T2
= Universal_Real
3412 and then T1
= Universal_Integer
3413 and then Op_Name
= Name_Op_Multiply
3415 Add_One_Interp
(N
, Op_Id
, T2
);
3418 elsif Op_Name
= Name_Op_Mod
or else Op_Name
= Name_Op_Rem
then
3420 -- Note: The fixed-point operands case with Treat_Fixed_As_Integer
3421 -- set does not require any special processing, since the Etype is
3422 -- already set (case of operation constructed by Exp_Fixed).
3424 if Is_Integer_Type
(T1
)
3425 and then (Covers
(T1
, T2
) or else Covers
(T2
, T1
))
3427 Add_One_Interp
(N
, Op_Id
, Specific_Type
(T1
, T2
));
3430 elsif Op_Name
= Name_Op_Expon
then
3431 if Is_Numeric_Type
(T1
)
3432 and then not Is_Fixed_Point_Type
(T1
)
3433 and then (Base_Type
(T2
) = Base_Type
(Standard_Integer
)
3434 or else T2
= Universal_Integer
)
3436 Add_One_Interp
(N
, Op_Id
, Base_Type
(T1
));
3439 else pragma Assert
(Nkind
(N
) in N_Op_Shift
);
3441 -- If not one of the predefined operators, the node may be one
3442 -- of the intrinsic functions. Its kind is always specific, and
3443 -- we can use it directly, rather than the name of the operation.
3445 if Is_Integer_Type
(T1
)
3446 and then (Base_Type
(T2
) = Base_Type
(Standard_Integer
)
3447 or else T2
= Universal_Integer
)
3449 Add_One_Interp
(N
, Op_Id
, Base_Type
(T1
));
3452 end Check_Arithmetic_Pair
;
3454 -------------------------------
3455 -- Check_Misspelled_Selector --
3456 -------------------------------
3458 procedure Check_Misspelled_Selector
3459 (Prefix
: Entity_Id
;
3462 Max_Suggestions
: constant := 2;
3463 Nr_Of_Suggestions
: Natural := 0;
3465 Suggestion_1
: Entity_Id
:= Empty
;
3466 Suggestion_2
: Entity_Id
:= Empty
;
3471 -- All the components of the prefix of selector Sel are matched
3472 -- against Sel and a count is maintained of possible misspellings.
3473 -- When at the end of the analysis there are one or two (not more!)
3474 -- possible misspellings, these misspellings will be suggested as
3475 -- possible correction.
3477 if not (Is_Private_Type
(Prefix
) or else Is_Record_Type
(Prefix
)) then
3479 -- Concurrent types should be handled as well ???
3484 Get_Name_String
(Chars
(Sel
));
3487 S
: constant String (1 .. Name_Len
) := Name_Buffer
(1 .. Name_Len
);
3490 Comp
:= First_Entity
(Prefix
);
3491 while Nr_Of_Suggestions
<= Max_Suggestions
3492 and then Present
(Comp
)
3494 if Is_Visible_Component
(Comp
) then
3495 Get_Name_String
(Chars
(Comp
));
3497 if Is_Bad_Spelling_Of
(Name_Buffer
(1 .. Name_Len
), S
) then
3498 Nr_Of_Suggestions
:= Nr_Of_Suggestions
+ 1;
3500 case Nr_Of_Suggestions
is
3501 when 1 => Suggestion_1
:= Comp
;
3502 when 2 => Suggestion_2
:= Comp
;
3503 when others => exit;
3508 Comp
:= Next_Entity
(Comp
);
3511 -- Report at most two suggestions
3513 if Nr_Of_Suggestions
= 1 then
3514 Error_Msg_NE
("\possible misspelling of&", Sel
, Suggestion_1
);
3516 elsif Nr_Of_Suggestions
= 2 then
3517 Error_Msg_Node_2
:= Suggestion_2
;
3518 Error_Msg_NE
("\possible misspelling of& or&",
3522 end Check_Misspelled_Selector
;
3524 ----------------------
3525 -- Defined_In_Scope --
3526 ----------------------
3528 function Defined_In_Scope
(T
: Entity_Id
; S
: Entity_Id
) return Boolean
3530 S1
: constant Entity_Id
:= Scope
(Base_Type
(T
));
3533 or else (S1
= System_Aux_Id
and then S
= Scope
(S1
));
3534 end Defined_In_Scope
;
3540 procedure Diagnose_Call
(N
: Node_Id
; Nam
: Node_Id
) is
3547 Void_Interp_Seen
: Boolean := False;
3550 if Ada_Version
>= Ada_05
then
3551 Actual
:= First_Actual
(N
);
3552 while Present
(Actual
) loop
3554 -- Ada 2005 (AI-50217): Post an error in case of premature
3555 -- usage of an entity from the limited view.
3557 if not Analyzed
(Etype
(Actual
))
3558 and then From_With_Type
(Etype
(Actual
))
3560 Error_Msg_Qual_Level
:= 1;
3562 ("missing with_clause for scope of imported type&",
3563 Actual
, Etype
(Actual
));
3564 Error_Msg_Qual_Level
:= 0;
3567 Next_Actual
(Actual
);
3571 -- Analyze each candidate call again, with full error reporting
3575 ("no candidate interpretations match the actuals:!", Nam
);
3576 Err_Mode
:= All_Errors_Mode
;
3577 All_Errors_Mode
:= True;
3579 -- If this is a call to an operation of a concurrent type,
3580 -- the failed interpretations have been removed from the
3581 -- name. Recover them to provide full diagnostics.
3583 if Nkind
(Parent
(Nam
)) = N_Selected_Component
then
3584 Set_Entity
(Nam
, Empty
);
3585 New_Nam
:= New_Copy_Tree
(Parent
(Nam
));
3586 Set_Is_Overloaded
(New_Nam
, False);
3587 Set_Is_Overloaded
(Selector_Name
(New_Nam
), False);
3588 Set_Parent
(New_Nam
, Parent
(Parent
(Nam
)));
3589 Analyze_Selected_Component
(New_Nam
);
3590 Get_First_Interp
(Selector_Name
(New_Nam
), X
, It
);
3592 Get_First_Interp
(Nam
, X
, It
);
3595 while Present
(It
.Nam
) loop
3596 if Etype
(It
.Nam
) = Standard_Void_Type
then
3597 Void_Interp_Seen
:= True;
3600 Analyze_One_Call
(N
, It
.Nam
, True, Success
);
3601 Get_Next_Interp
(X
, It
);
3604 if Nkind
(N
) = N_Function_Call
then
3605 Get_First_Interp
(Nam
, X
, It
);
3606 while Present
(It
.Nam
) loop
3607 if Ekind
(It
.Nam
) = E_Function
3608 or else Ekind
(It
.Nam
) = E_Operator
3612 Get_Next_Interp
(X
, It
);
3616 -- If all interpretations are procedures, this deserves a
3617 -- more precise message. Ditto if this appears as the prefix
3618 -- of a selected component, which may be a lexical error.
3621 ("\context requires function call, found procedure name", Nam
);
3623 if Nkind
(Parent
(N
)) = N_Selected_Component
3624 and then N
= Prefix
(Parent
(N
))
3627 "\period should probably be semicolon", Parent
(N
));
3630 elsif Nkind
(N
) = N_Procedure_Call_Statement
3631 and then not Void_Interp_Seen
3634 "\function name found in procedure call", Nam
);
3637 All_Errors_Mode
:= Err_Mode
;
3640 ---------------------------
3641 -- Find_Arithmetic_Types --
3642 ---------------------------
3644 procedure Find_Arithmetic_Types
3649 Index1
: Interp_Index
;
3650 Index2
: Interp_Index
;
3654 procedure Check_Right_Argument
(T
: Entity_Id
);
3655 -- Check right operand of operator
3657 --------------------------
3658 -- Check_Right_Argument --
3659 --------------------------
3661 procedure Check_Right_Argument
(T
: Entity_Id
) is
3663 if not Is_Overloaded
(R
) then
3664 Check_Arithmetic_Pair
(T
, Etype
(R
), Op_Id
, N
);
3666 Get_First_Interp
(R
, Index2
, It2
);
3667 while Present
(It2
.Typ
) loop
3668 Check_Arithmetic_Pair
(T
, It2
.Typ
, Op_Id
, N
);
3669 Get_Next_Interp
(Index2
, It2
);
3672 end Check_Right_Argument
;
3674 -- Start processing for Find_Arithmetic_Types
3677 if not Is_Overloaded
(L
) then
3678 Check_Right_Argument
(Etype
(L
));
3681 Get_First_Interp
(L
, Index1
, It1
);
3683 while Present
(It1
.Typ
) loop
3684 Check_Right_Argument
(It1
.Typ
);
3685 Get_Next_Interp
(Index1
, It1
);
3689 end Find_Arithmetic_Types
;
3691 ------------------------
3692 -- Find_Boolean_Types --
3693 ------------------------
3695 procedure Find_Boolean_Types
3700 Index
: Interp_Index
;
3703 procedure Check_Numeric_Argument
(T
: Entity_Id
);
3704 -- Special case for logical operations one of whose operands is an
3705 -- integer literal. If both are literal the result is any modular type.
3707 ----------------------------
3708 -- Check_Numeric_Argument --
3709 ----------------------------
3711 procedure Check_Numeric_Argument
(T
: Entity_Id
) is
3713 if T
= Universal_Integer
then
3714 Add_One_Interp
(N
, Op_Id
, Any_Modular
);
3716 elsif Is_Modular_Integer_Type
(T
) then
3717 Add_One_Interp
(N
, Op_Id
, T
);
3719 end Check_Numeric_Argument
;
3721 -- Start of processing for Find_Boolean_Types
3724 if not Is_Overloaded
(L
) then
3725 if Etype
(L
) = Universal_Integer
3726 or else Etype
(L
) = Any_Modular
3728 if not Is_Overloaded
(R
) then
3729 Check_Numeric_Argument
(Etype
(R
));
3732 Get_First_Interp
(R
, Index
, It
);
3733 while Present
(It
.Typ
) loop
3734 Check_Numeric_Argument
(It
.Typ
);
3735 Get_Next_Interp
(Index
, It
);
3739 elsif Valid_Boolean_Arg
(Etype
(L
))
3740 and then Has_Compatible_Type
(R
, Etype
(L
))
3742 Add_One_Interp
(N
, Op_Id
, Etype
(L
));
3746 Get_First_Interp
(L
, Index
, It
);
3747 while Present
(It
.Typ
) loop
3748 if Valid_Boolean_Arg
(It
.Typ
)
3749 and then Has_Compatible_Type
(R
, It
.Typ
)
3751 Add_One_Interp
(N
, Op_Id
, It
.Typ
);
3754 Get_Next_Interp
(Index
, It
);
3757 end Find_Boolean_Types
;
3759 ---------------------------
3760 -- Find_Comparison_Types --
3761 ---------------------------
3763 procedure Find_Comparison_Types
3768 Index
: Interp_Index
;
3770 Found
: Boolean := False;
3773 Scop
: Entity_Id
:= Empty
;
3775 procedure Try_One_Interp
(T1
: Entity_Id
);
3776 -- Routine to try one proposed interpretation. Note that the context
3777 -- of the operator plays no role in resolving the arguments, so that
3778 -- if there is more than one interpretation of the operands that is
3779 -- compatible with comparison, the operation is ambiguous.
3781 --------------------
3782 -- Try_One_Interp --
3783 --------------------
3785 procedure Try_One_Interp
(T1
: Entity_Id
) is
3788 -- If the operator is an expanded name, then the type of the operand
3789 -- must be defined in the corresponding scope. If the type is
3790 -- universal, the context will impose the correct type.
3793 and then not Defined_In_Scope
(T1
, Scop
)
3794 and then T1
/= Universal_Integer
3795 and then T1
/= Universal_Real
3796 and then T1
/= Any_String
3797 and then T1
/= Any_Composite
3802 if Valid_Comparison_Arg
(T1
)
3803 and then Has_Compatible_Type
(R
, T1
)
3806 and then Base_Type
(T1
) /= Base_Type
(T_F
)
3808 It
:= Disambiguate
(L
, I_F
, Index
, Any_Type
);
3810 if It
= No_Interp
then
3811 Ambiguous_Operands
(N
);
3812 Set_Etype
(L
, Any_Type
);
3826 Find_Non_Universal_Interpretations
(N
, R
, Op_Id
, T1
);
3831 -- Start processing for Find_Comparison_Types
3834 -- If left operand is aggregate, the right operand has to
3835 -- provide a usable type for it.
3837 if Nkind
(L
) = N_Aggregate
3838 and then Nkind
(R
) /= N_Aggregate
3840 Find_Comparison_Types
(R
, L
, Op_Id
, N
);
3844 if Nkind
(N
) = N_Function_Call
3845 and then Nkind
(Name
(N
)) = N_Expanded_Name
3847 Scop
:= Entity
(Prefix
(Name
(N
)));
3849 -- The prefix may be a package renaming, and the subsequent test
3850 -- requires the original package.
3852 if Ekind
(Scop
) = E_Package
3853 and then Present
(Renamed_Entity
(Scop
))
3855 Scop
:= Renamed_Entity
(Scop
);
3856 Set_Entity
(Prefix
(Name
(N
)), Scop
);
3860 if not Is_Overloaded
(L
) then
3861 Try_One_Interp
(Etype
(L
));
3864 Get_First_Interp
(L
, Index
, It
);
3865 while Present
(It
.Typ
) loop
3866 Try_One_Interp
(It
.Typ
);
3867 Get_Next_Interp
(Index
, It
);
3870 end Find_Comparison_Types
;
3872 ----------------------------------------
3873 -- Find_Non_Universal_Interpretations --
3874 ----------------------------------------
3876 procedure Find_Non_Universal_Interpretations
3882 Index
: Interp_Index
;
3886 if T1
= Universal_Integer
3887 or else T1
= Universal_Real
3889 if not Is_Overloaded
(R
) then
3891 (N
, Op_Id
, Standard_Boolean
, Base_Type
(Etype
(R
)));
3893 Get_First_Interp
(R
, Index
, It
);
3894 while Present
(It
.Typ
) loop
3895 if Covers
(It
.Typ
, T1
) then
3897 (N
, Op_Id
, Standard_Boolean
, Base_Type
(It
.Typ
));
3900 Get_Next_Interp
(Index
, It
);
3904 Add_One_Interp
(N
, Op_Id
, Standard_Boolean
, Base_Type
(T1
));
3906 end Find_Non_Universal_Interpretations
;
3908 ------------------------------
3909 -- Find_Concatenation_Types --
3910 ------------------------------
3912 procedure Find_Concatenation_Types
3917 Op_Type
: constant Entity_Id
:= Etype
(Op_Id
);
3920 if Is_Array_Type
(Op_Type
)
3921 and then not Is_Limited_Type
(Op_Type
)
3923 and then (Has_Compatible_Type
(L
, Op_Type
)
3925 Has_Compatible_Type
(L
, Component_Type
(Op_Type
)))
3927 and then (Has_Compatible_Type
(R
, Op_Type
)
3929 Has_Compatible_Type
(R
, Component_Type
(Op_Type
)))
3931 Add_One_Interp
(N
, Op_Id
, Op_Type
);
3933 end Find_Concatenation_Types
;
3935 -------------------------
3936 -- Find_Equality_Types --
3937 -------------------------
3939 procedure Find_Equality_Types
3944 Index
: Interp_Index
;
3946 Found
: Boolean := False;
3949 Scop
: Entity_Id
:= Empty
;
3951 procedure Try_One_Interp
(T1
: Entity_Id
);
3952 -- The context of the operator plays no role in resolving the
3953 -- arguments, so that if there is more than one interpretation
3954 -- of the operands that is compatible with equality, the construct
3955 -- is ambiguous and an error can be emitted now, after trying to
3956 -- disambiguate, i.e. applying preference rules.
3958 --------------------
3959 -- Try_One_Interp --
3960 --------------------
3962 procedure Try_One_Interp
(T1
: Entity_Id
) is
3964 -- If the operator is an expanded name, then the type of the operand
3965 -- must be defined in the corresponding scope. If the type is
3966 -- universal, the context will impose the correct type. An anonymous
3967 -- type for a 'Access reference is also universal in this sense, as
3968 -- the actual type is obtained from context.
3971 and then not Defined_In_Scope
(T1
, Scop
)
3972 and then T1
/= Universal_Integer
3973 and then T1
/= Universal_Real
3974 and then T1
/= Any_Access
3975 and then T1
/= Any_String
3976 and then T1
/= Any_Composite
3977 and then (Ekind
(T1
) /= E_Access_Subprogram_Type
3978 or else Comes_From_Source
(T1
))
3983 -- Ada 2005 (AI-230): Keep restriction imposed by Ada 83 and 95:
3984 -- Do not allow anonymous access types in equality operators.
3986 if Ada_Version
< Ada_05
3987 and then Ekind
(T1
) = E_Anonymous_Access_Type
3992 if T1
/= Standard_Void_Type
3993 and then not Is_Limited_Type
(T1
)
3994 and then not Is_Limited_Composite
(T1
)
3995 and then Has_Compatible_Type
(R
, T1
)
3998 and then Base_Type
(T1
) /= Base_Type
(T_F
)
4000 It
:= Disambiguate
(L
, I_F
, Index
, Any_Type
);
4002 if It
= No_Interp
then
4003 Ambiguous_Operands
(N
);
4004 Set_Etype
(L
, Any_Type
);
4017 if not Analyzed
(L
) then
4021 Find_Non_Universal_Interpretations
(N
, R
, Op_Id
, T1
);
4023 -- Case of operator was not visible, Etype still set to Any_Type
4025 if Etype
(N
) = Any_Type
then
4031 -- Start of processing for Find_Equality_Types
4034 -- If left operand is aggregate, the right operand has to
4035 -- provide a usable type for it.
4037 if Nkind
(L
) = N_Aggregate
4038 and then Nkind
(R
) /= N_Aggregate
4040 Find_Equality_Types
(R
, L
, Op_Id
, N
);
4044 if Nkind
(N
) = N_Function_Call
4045 and then Nkind
(Name
(N
)) = N_Expanded_Name
4047 Scop
:= Entity
(Prefix
(Name
(N
)));
4049 -- The prefix may be a package renaming, and the subsequent test
4050 -- requires the original package.
4052 if Ekind
(Scop
) = E_Package
4053 and then Present
(Renamed_Entity
(Scop
))
4055 Scop
:= Renamed_Entity
(Scop
);
4056 Set_Entity
(Prefix
(Name
(N
)), Scop
);
4060 if not Is_Overloaded
(L
) then
4061 Try_One_Interp
(Etype
(L
));
4064 Get_First_Interp
(L
, Index
, It
);
4065 while Present
(It
.Typ
) loop
4066 Try_One_Interp
(It
.Typ
);
4067 Get_Next_Interp
(Index
, It
);
4070 end Find_Equality_Types
;
4072 -------------------------
4073 -- Find_Negation_Types --
4074 -------------------------
4076 procedure Find_Negation_Types
4081 Index
: Interp_Index
;
4085 if not Is_Overloaded
(R
) then
4086 if Etype
(R
) = Universal_Integer
then
4087 Add_One_Interp
(N
, Op_Id
, Any_Modular
);
4088 elsif Valid_Boolean_Arg
(Etype
(R
)) then
4089 Add_One_Interp
(N
, Op_Id
, Etype
(R
));
4093 Get_First_Interp
(R
, Index
, It
);
4094 while Present
(It
.Typ
) loop
4095 if Valid_Boolean_Arg
(It
.Typ
) then
4096 Add_One_Interp
(N
, Op_Id
, It
.Typ
);
4099 Get_Next_Interp
(Index
, It
);
4102 end Find_Negation_Types
;
4104 ----------------------
4105 -- Find_Unary_Types --
4106 ----------------------
4108 procedure Find_Unary_Types
4113 Index
: Interp_Index
;
4117 if not Is_Overloaded
(R
) then
4118 if Is_Numeric_Type
(Etype
(R
)) then
4119 Add_One_Interp
(N
, Op_Id
, Base_Type
(Etype
(R
)));
4123 Get_First_Interp
(R
, Index
, It
);
4124 while Present
(It
.Typ
) loop
4125 if Is_Numeric_Type
(It
.Typ
) then
4126 Add_One_Interp
(N
, Op_Id
, Base_Type
(It
.Typ
));
4129 Get_Next_Interp
(Index
, It
);
4132 end Find_Unary_Types
;
4138 function Junk_Operand
(N
: Node_Id
) return Boolean is
4142 if Error_Posted
(N
) then
4146 -- Get entity to be tested
4148 if Is_Entity_Name
(N
)
4149 and then Present
(Entity
(N
))
4153 -- An odd case, a procedure name gets converted to a very peculiar
4154 -- function call, and here is where we detect this happening.
4156 elsif Nkind
(N
) = N_Function_Call
4157 and then Is_Entity_Name
(Name
(N
))
4158 and then Present
(Entity
(Name
(N
)))
4162 -- Another odd case, there are at least some cases of selected
4163 -- components where the selected component is not marked as having
4164 -- an entity, even though the selector does have an entity
4166 elsif Nkind
(N
) = N_Selected_Component
4167 and then Present
(Entity
(Selector_Name
(N
)))
4169 Enode
:= Selector_Name
(N
);
4175 -- Now test the entity we got to see if it a bad case
4177 case Ekind
(Entity
(Enode
)) is
4181 ("package name cannot be used as operand", Enode
);
4183 when Generic_Unit_Kind
=>
4185 ("generic unit name cannot be used as operand", Enode
);
4189 ("subtype name cannot be used as operand", Enode
);
4193 ("entry name cannot be used as operand", Enode
);
4197 ("procedure name cannot be used as operand", Enode
);
4201 ("exception name cannot be used as operand", Enode
);
4203 when E_Block | E_Label | E_Loop
=>
4205 ("label name cannot be used as operand", Enode
);
4215 --------------------
4216 -- Operator_Check --
4217 --------------------
4219 procedure Operator_Check
(N
: Node_Id
) is
4221 Remove_Abstract_Operations
(N
);
4223 -- Test for case of no interpretation found for operator
4225 if Etype
(N
) = Any_Type
then
4231 R
:= Right_Opnd
(N
);
4233 if Nkind
(N
) in N_Binary_Op
then
4239 -- If either operand has no type, then don't complain further,
4240 -- since this simply means that we have a propragated error.
4243 or else Etype
(R
) = Any_Type
4244 or else (Nkind
(N
) in N_Binary_Op
and then Etype
(L
) = Any_Type
)
4248 -- We explicitly check for the case of concatenation of component
4249 -- with component to avoid reporting spurious matching array types
4250 -- that might happen to be lurking in distant packages (such as
4251 -- run-time packages). This also prevents inconsistencies in the
4252 -- messages for certain ACVC B tests, which can vary depending on
4253 -- types declared in run-time interfaces. Another improvement when
4254 -- aggregates are present is to look for a well-typed operand.
4256 elsif Present
(Candidate_Type
)
4257 and then (Nkind
(N
) /= N_Op_Concat
4258 or else Is_Array_Type
(Etype
(L
))
4259 or else Is_Array_Type
(Etype
(R
)))
4262 if Nkind
(N
) = N_Op_Concat
then
4263 if Etype
(L
) /= Any_Composite
4264 and then Is_Array_Type
(Etype
(L
))
4266 Candidate_Type
:= Etype
(L
);
4268 elsif Etype
(R
) /= Any_Composite
4269 and then Is_Array_Type
(Etype
(R
))
4271 Candidate_Type
:= Etype
(R
);
4276 ("operator for} is not directly visible!",
4277 N
, First_Subtype
(Candidate_Type
));
4278 Error_Msg_N
("use clause would make operation legal!", N
);
4281 -- If either operand is a junk operand (e.g. package name), then
4282 -- post appropriate error messages, but do not complain further.
4284 -- Note that the use of OR in this test instead of OR ELSE
4285 -- is quite deliberate, we may as well check both operands
4286 -- in the binary operator case.
4288 elsif Junk_Operand
(R
)
4289 or (Nkind
(N
) in N_Binary_Op
and then Junk_Operand
(L
))
4293 -- If we have a logical operator, one of whose operands is
4294 -- Boolean, then we know that the other operand cannot resolve
4295 -- to Boolean (since we got no interpretations), but in that
4296 -- case we pretty much know that the other operand should be
4297 -- Boolean, so resolve it that way (generating an error)
4299 elsif Nkind
(N
) = N_Op_And
4303 Nkind
(N
) = N_Op_Xor
4305 if Etype
(L
) = Standard_Boolean
then
4306 Resolve
(R
, Standard_Boolean
);
4308 elsif Etype
(R
) = Standard_Boolean
then
4309 Resolve
(L
, Standard_Boolean
);
4313 -- For an arithmetic operator or comparison operator, if one
4314 -- of the operands is numeric, then we know the other operand
4315 -- is not the same numeric type. If it is a non-numeric type,
4316 -- then probably it is intended to match the other operand.
4318 elsif Nkind
(N
) = N_Op_Add
or else
4319 Nkind
(N
) = N_Op_Divide
or else
4320 Nkind
(N
) = N_Op_Ge
or else
4321 Nkind
(N
) = N_Op_Gt
or else
4322 Nkind
(N
) = N_Op_Le
or else
4323 Nkind
(N
) = N_Op_Lt
or else
4324 Nkind
(N
) = N_Op_Mod
or else
4325 Nkind
(N
) = N_Op_Multiply
or else
4326 Nkind
(N
) = N_Op_Rem
or else
4327 Nkind
(N
) = N_Op_Subtract
4329 if Is_Numeric_Type
(Etype
(L
))
4330 and then not Is_Numeric_Type
(Etype
(R
))
4332 Resolve
(R
, Etype
(L
));
4335 elsif Is_Numeric_Type
(Etype
(R
))
4336 and then not Is_Numeric_Type
(Etype
(L
))
4338 Resolve
(L
, Etype
(R
));
4342 -- Comparisons on A'Access are common enough to deserve a
4345 elsif (Nkind
(N
) = N_Op_Eq
or else
4346 Nkind
(N
) = N_Op_Ne
)
4347 and then Ekind
(Etype
(L
)) = E_Access_Attribute_Type
4348 and then Ekind
(Etype
(R
)) = E_Access_Attribute_Type
4351 ("two access attributes cannot be compared directly", N
);
4353 ("\they must be converted to an explicit type for comparison",
4357 -- Another one for C programmers
4359 elsif Nkind
(N
) = N_Op_Concat
4360 and then Valid_Boolean_Arg
(Etype
(L
))
4361 and then Valid_Boolean_Arg
(Etype
(R
))
4363 Error_Msg_N
("invalid operands for concatenation", N
);
4364 Error_Msg_N
("\maybe AND was meant", N
);
4367 -- A special case for comparison of access parameter with null
4369 elsif Nkind
(N
) = N_Op_Eq
4370 and then Is_Entity_Name
(L
)
4371 and then Nkind
(Parent
(Entity
(L
))) = N_Parameter_Specification
4372 and then Nkind
(Parameter_Type
(Parent
(Entity
(L
)))) =
4374 and then Nkind
(R
) = N_Null
4376 Error_Msg_N
("access parameter is not allowed to be null", L
);
4377 Error_Msg_N
("\(call would raise Constraint_Error)", L
);
4381 -- If we fall through then just give general message. Note
4382 -- that in the following messages, if the operand is overloaded
4383 -- we choose an arbitrary type to complain about, but that is
4384 -- probably more useful than not giving a type at all.
4386 if Nkind
(N
) in N_Unary_Op
then
4387 Error_Msg_Node_2
:= Etype
(R
);
4388 Error_Msg_N
("operator& not defined for}", N
);
4392 if Nkind
(N
) in N_Binary_Op
then
4393 if not Is_Overloaded
(L
)
4394 and then not Is_Overloaded
(R
)
4395 and then Base_Type
(Etype
(L
)) = Base_Type
(Etype
(R
))
4397 Error_Msg_Node_2
:= First_Subtype
(Etype
(R
));
4398 Error_Msg_N
("there is no applicable operator& for}", N
);
4401 Error_Msg_N
("invalid operand types for operator&", N
);
4403 if Nkind
(N
) /= N_Op_Concat
then
4404 Error_Msg_NE
("\left operand has}!", N
, Etype
(L
));
4405 Error_Msg_NE
("\right operand has}!", N
, Etype
(R
));
4414 -----------------------------------------
4415 -- Process_Implicit_Dereference_Prefix --
4416 -----------------------------------------
4418 procedure Process_Implicit_Dereference_Prefix
4425 if Operating_Mode
= Check_Semantics
and then Present
(E
) then
4427 -- We create a dummy reference to E to ensure that the reference
4428 -- is not considered as part of an assignment (an implicit
4429 -- dereference can never assign to its prefix). The Comes_From_Source
4430 -- attribute needs to be propagated for accurate warnings.
4432 Ref
:= New_Reference_To
(E
, Sloc
(P
));
4433 Set_Comes_From_Source
(Ref
, Comes_From_Source
(P
));
4434 Generate_Reference
(E
, Ref
);
4436 end Process_Implicit_Dereference_Prefix
;
4438 --------------------------------
4439 -- Remove_Abstract_Operations --
4440 --------------------------------
4442 procedure Remove_Abstract_Operations
(N
: Node_Id
) is
4445 Abstract_Op
: Entity_Id
:= Empty
;
4447 -- AI-310: If overloaded, remove abstract non-dispatching
4448 -- operations. We activate this if either extensions are
4449 -- enabled, or if the abstract operation in question comes
4450 -- from a predefined file. This latter test allows us to
4451 -- use abstract to make operations invisible to users. In
4452 -- particular, if type Address is non-private and abstract
4453 -- subprograms are used to hide its operators, they will be
4456 type Operand_Position
is (First_Op
, Second_Op
);
4457 Univ_Type
: constant Entity_Id
:= Universal_Interpretation
(N
);
4459 procedure Remove_Address_Interpretations
(Op
: Operand_Position
);
4460 -- Ambiguities may arise when the operands are literal and the
4461 -- address operations in s-auxdec are visible. In that case, remove
4462 -- the interpretation of a literal as Address, to retain the semantics
4463 -- of Address as a private type.
4465 ------------------------------------
4466 -- Remove_Address_Interpretations --
4467 ------------------------------------
4469 procedure Remove_Address_Interpretations
(Op
: Operand_Position
) is
4473 if Is_Overloaded
(N
) then
4474 Get_First_Interp
(N
, I
, It
);
4475 while Present
(It
.Nam
) loop
4476 Formal
:= First_Entity
(It
.Nam
);
4478 if Op
= Second_Op
then
4479 Formal
:= Next_Entity
(Formal
);
4482 if Is_Descendent_Of_Address
(Etype
(Formal
)) then
4486 Get_Next_Interp
(I
, It
);
4489 end Remove_Address_Interpretations
;
4491 -- Start of processing for Remove_Abstract_Operations
4494 if Is_Overloaded
(N
) then
4495 Get_First_Interp
(N
, I
, It
);
4497 while Present
(It
.Nam
) loop
4498 if not Is_Type
(It
.Nam
)
4499 and then Is_Abstract
(It
.Nam
)
4500 and then not Is_Dispatching_Operation
(It
.Nam
)
4502 (Ada_Version
>= Ada_05
4503 or else Is_Predefined_File_Name
4504 (Unit_File_Name
(Get_Source_Unit
(It
.Nam
))))
4507 Abstract_Op
:= It
.Nam
;
4512 Get_Next_Interp
(I
, It
);
4515 if No
(Abstract_Op
) then
4518 elsif Nkind
(N
) in N_Op
then
4520 -- Remove interpretations that treat literals as addresses.
4521 -- This is never appropriate.
4523 if Nkind
(N
) in N_Binary_Op
then
4525 U1
: constant Boolean :=
4526 Present
(Universal_Interpretation
(Right_Opnd
(N
)));
4527 U2
: constant Boolean :=
4528 Present
(Universal_Interpretation
(Left_Opnd
(N
)));
4531 if U1
and then not U2
then
4532 Remove_Address_Interpretations
(Second_Op
);
4534 elsif U2
and then not U1
then
4535 Remove_Address_Interpretations
(First_Op
);
4538 if not (U1
and U2
) then
4540 -- Remove corresponding predefined operator, which is
4541 -- always added to the overload set.
4543 Get_First_Interp
(N
, I
, It
);
4544 while Present
(It
.Nam
) loop
4545 if Scope
(It
.Nam
) = Standard_Standard
4546 and then Base_Type
(It
.Typ
) =
4547 Base_Type
(Etype
(Abstract_Op
))
4552 Get_Next_Interp
(I
, It
);
4555 elsif Is_Overloaded
(N
)
4556 and then Present
(Univ_Type
)
4558 -- If both operands have a universal interpretation,
4559 -- select the predefined operator and discard others.
4561 Get_First_Interp
(N
, I
, It
);
4563 while Present
(It
.Nam
) loop
4564 if Scope
(It
.Nam
) = Standard_Standard
then
4565 Set_Etype
(N
, Univ_Type
);
4566 Set_Entity
(N
, It
.Nam
);
4567 Set_Is_Overloaded
(N
, False);
4571 Get_Next_Interp
(I
, It
);
4577 elsif Nkind
(N
) = N_Function_Call
4579 (Nkind
(Name
(N
)) = N_Operator_Symbol
4581 (Nkind
(Name
(N
)) = N_Expanded_Name
4583 Nkind
(Selector_Name
(Name
(N
))) = N_Operator_Symbol
))
4587 Arg1
: constant Node_Id
:= First
(Parameter_Associations
(N
));
4588 U1
: constant Boolean :=
4589 Present
(Universal_Interpretation
(Arg1
));
4590 U2
: constant Boolean :=
4591 Present
(Next
(Arg1
)) and then
4592 Present
(Universal_Interpretation
(Next
(Arg1
)));
4595 if U1
and then not U2
then
4596 Remove_Address_Interpretations
(First_Op
);
4598 elsif U2
and then not U1
then
4599 Remove_Address_Interpretations
(Second_Op
);
4602 if not (U1
and U2
) then
4603 Get_First_Interp
(N
, I
, It
);
4604 while Present
(It
.Nam
) loop
4605 if Scope
(It
.Nam
) = Standard_Standard
4606 and then It
.Typ
= Base_Type
(Etype
(Abstract_Op
))
4611 Get_Next_Interp
(I
, It
);
4617 -- If the removal has left no valid interpretations, emit
4618 -- error message now and label node as illegal.
4620 if Present
(Abstract_Op
) then
4621 Get_First_Interp
(N
, I
, It
);
4625 -- Removal of abstract operation left no viable candidate
4627 Set_Etype
(N
, Any_Type
);
4628 Error_Msg_Sloc
:= Sloc
(Abstract_Op
);
4630 ("cannot call abstract operation& declared#", N
, Abstract_Op
);
4634 end Remove_Abstract_Operations
;
4636 -----------------------
4637 -- Try_Indirect_Call --
4638 -----------------------
4640 function Try_Indirect_Call
4643 Typ
: Entity_Id
) return Boolean
4650 Normalize_Actuals
(N
, Designated_Type
(Typ
), False, Call_OK
);
4651 Actual
:= First_Actual
(N
);
4652 Formal
:= First_Formal
(Designated_Type
(Typ
));
4654 while Present
(Actual
)
4655 and then Present
(Formal
)
4657 if not Has_Compatible_Type
(Actual
, Etype
(Formal
)) then
4662 Next_Formal
(Formal
);
4665 if No
(Actual
) and then No
(Formal
) then
4666 Add_One_Interp
(N
, Nam
, Etype
(Designated_Type
(Typ
)));
4668 -- Nam is a candidate interpretation for the name in the call,
4669 -- if it is not an indirect call.
4671 if not Is_Type
(Nam
)
4672 and then Is_Entity_Name
(Name
(N
))
4674 Set_Entity
(Name
(N
), Nam
);
4681 end Try_Indirect_Call
;
4683 ----------------------
4684 -- Try_Indexed_Call --
4685 ----------------------
4687 function Try_Indexed_Call
4690 Typ
: Entity_Id
) return Boolean
4692 Actuals
: constant List_Id
:= Parameter_Associations
(N
);
4697 Actual
:= First
(Actuals
);
4698 Index
:= First_Index
(Typ
);
4699 while Present
(Actual
)
4700 and then Present
(Index
)
4702 -- If the parameter list has a named association, the expression
4703 -- is definitely a call and not an indexed component.
4705 if Nkind
(Actual
) = N_Parameter_Association
then
4709 if not Has_Compatible_Type
(Actual
, Etype
(Index
)) then
4717 if No
(Actual
) and then No
(Index
) then
4718 Add_One_Interp
(N
, Nam
, Component_Type
(Typ
));
4720 -- Nam is a candidate interpretation for the name in the call,
4721 -- if it is not an indirect call.
4723 if not Is_Type
(Nam
)
4724 and then Is_Entity_Name
(Name
(N
))
4726 Set_Entity
(Name
(N
), Nam
);
4733 end Try_Indexed_Call
;
4735 --------------------------
4736 -- Try_Object_Operation --
4737 --------------------------
4739 function Try_Object_Operation
(N
: Node_Id
) return Boolean is
4740 K
: constant Node_Kind
:= Nkind
(Parent
(N
));
4741 Loc
: constant Source_Ptr
:= Sloc
(N
);
4742 Is_Subprg_Call
: constant Boolean := K
= N_Procedure_Call_Statement
4743 or else K
= N_Function_Call
;
4744 Obj
: constant Node_Id
:= Prefix
(N
);
4745 Subprog
: constant Node_Id
:= Selector_Name
(N
);
4748 Call_Node
: Node_Id
;
4749 Call_Node_Case
: Node_Id
:= Empty
;
4750 First_Actual
: Node_Id
;
4751 Node_To_Replace
: Node_Id
;
4752 Obj_Type
: Entity_Id
:= Etype
(Obj
);
4754 procedure Complete_Object_Operation
4755 (Call_Node
: Node_Id
;
4756 Node_To_Replace
: Node_Id
;
4758 -- Set Subprog as the name of Call_Node, replace Node_To_Replace with
4759 -- Call_Node and reanalyze Node_To_Replace.
4761 procedure Transform_Object_Operation
4762 (Call_Node
: out Node_Id
;
4763 First_Actual
: Node_Id
;
4764 Node_To_Replace
: out Node_Id
;
4766 -- Transform Object.Operation (...) to Operation (Object, ...)
4767 -- Call_Node is the resulting subprogram call node, First_Actual is
4768 -- either the object Obj or an explicit dereference of Obj in certain
4769 -- cases, Node_To_Replace is either N or the parent of N, and Subprog
4770 -- is the subprogram we are trying to match.
4772 function Try_Class_Wide_Operation
4773 (Call_Node
: Node_Id
;
4774 Node_To_Replace
: Node_Id
) return Boolean;
4775 -- Traverse all the ancestor types looking for a class-wide subprogram
4776 -- that matches Subprog.
4778 function Try_Primitive_Operation
4779 (Call_Node
: Node_Id
;
4780 Node_To_Replace
: Node_Id
) return Boolean;
4781 -- Traverse the list of primitive subprograms looking for a subprogram
4782 -- than matches Subprog.
4784 -------------------------------
4785 -- Complete_Object_Operation --
4786 -------------------------------
4788 procedure Complete_Object_Operation
4789 (Call_Node
: Node_Id
;
4790 Node_To_Replace
: Node_Id
;
4794 Set_Name
(Call_Node
, New_Copy_Tree
(Subprog
));
4795 Set_Analyzed
(Call_Node
, False);
4796 Rewrite
(Node_To_Replace
, Call_Node
);
4797 Analyze
(Node_To_Replace
);
4799 end Complete_Object_Operation
;
4801 --------------------------------
4802 -- Transform_Object_Operation --
4803 --------------------------------
4805 procedure Transform_Object_Operation
4806 (Call_Node
: out Node_Id
;
4807 First_Actual
: Node_Id
;
4808 Node_To_Replace
: out Node_Id
;
4812 Parent_Node
: constant Node_Id
:= Parent
(N
);
4815 Actuals
:= New_List
(New_Copy_Tree
(First_Actual
));
4817 if (Nkind
(Parent_Node
) = N_Function_Call
4819 Nkind
(Parent_Node
) = N_Procedure_Call_Statement
)
4821 -- Avoid recursive calls
4823 and then N
/= First
(Parameter_Associations
(Parent_Node
))
4825 Node_To_Replace
:= Parent_Node
;
4827 -- Copy list of actuals in full before attempting to resolve call.
4828 -- This is necessary to ensure that the chaining of named actuals
4829 -- that happens during matching is done on a separate copy.
4834 Actual
:= First
(Parameter_Associations
(Parent_Node
));
4835 while Present
(Actual
) loop
4836 Append
(New_Copy_Tree
(Actual
), Actuals
);
4841 if Nkind
(Parent_Node
) = N_Procedure_Call_Statement
then
4843 Make_Procedure_Call_Statement
(Loc
,
4844 Name
=> New_Copy_Tree
(Subprog
),
4845 Parameter_Associations
=> Actuals
);
4848 pragma Assert
(Nkind
(Parent_Node
) = N_Function_Call
);
4851 Make_Function_Call
(Loc
,
4852 Name
=> New_Copy_Tree
(Subprog
),
4853 Parameter_Associations
=> Actuals
);
4857 -- Parameterless call
4860 Node_To_Replace
:= N
;
4863 Make_Function_Call
(Loc
,
4864 Name
=> New_Copy_Tree
(Subprog
),
4865 Parameter_Associations
=> Actuals
);
4868 end Transform_Object_Operation
;
4870 ------------------------------
4871 -- Try_Class_Wide_Operation --
4872 ------------------------------
4874 function Try_Class_Wide_Operation
4875 (Call_Node
: Node_Id
;
4876 Node_To_Replace
: Node_Id
) return Boolean
4878 Anc_Type
: Entity_Id
;
4885 -- Loop through ancestor types, traverse their homonym chains and
4886 -- gather all interpretations of the subprogram.
4888 Anc_Type
:= Obj_Type
;
4890 Hom
:= Current_Entity
(Subprog
);
4891 while Present
(Hom
) loop
4892 if (Ekind
(Hom
) = E_Procedure
4894 Ekind
(Hom
) = E_Function
)
4895 and then Present
(First_Formal
(Hom
))
4896 and then Etype
(First_Formal
(Hom
)) =
4897 Class_Wide_Type
(Anc_Type
)
4899 Hom_Ref
:= New_Reference_To
(Hom
, Loc
);
4901 -- When both the type of the object and the type of the
4902 -- first formal of the primitive operation are tagged
4903 -- access types, we use a node with the object as first
4906 if Is_Access_Type
(Etype
(Obj
))
4907 and then Ekind
(Etype
(First_Formal
(Hom
))) =
4908 E_Anonymous_Access_Type
4910 -- Allocate the node only once
4912 if not Present
(Call_Node_Case
) then
4913 Transform_Object_Operation
(
4914 Call_Node
=> Call_Node_Case
,
4915 First_Actual
=> Obj
,
4916 Node_To_Replace
=> Dummy
,
4917 Subprog
=> Subprog
);
4919 Set_Etype
(Call_Node_Case
, Any_Type
);
4920 Set_Parent
(Call_Node_Case
, Parent
(Node_To_Replace
));
4923 Set_Name
(Call_Node_Case
, Hom_Ref
);
4926 N
=> Call_Node_Case
,
4929 Success
=> Success
);
4932 Complete_Object_Operation
(
4933 Call_Node
=> Call_Node_Case
,
4934 Node_To_Replace
=> Node_To_Replace
,
4935 Subprog
=> Hom_Ref
);
4940 -- ??? comment required
4943 Set_Name
(Call_Node
, Hom_Ref
);
4949 Success
=> Success
);
4952 Complete_Object_Operation
(
4953 Call_Node
=> Call_Node
,
4954 Node_To_Replace
=> Node_To_Replace
,
4955 Subprog
=> Hom_Ref
);
4962 Hom
:= Homonym
(Hom
);
4965 -- Climb to ancestor type if there is one
4967 exit when Etype
(Anc_Type
) = Anc_Type
;
4968 Anc_Type
:= Etype
(Anc_Type
);
4972 end Try_Class_Wide_Operation
;
4974 -----------------------------
4975 -- Try_Primitive_Operation --
4976 -----------------------------
4978 function Try_Primitive_Operation
4979 (Call_Node
: Node_Id
;
4980 Node_To_Replace
: Node_Id
) return Boolean
4984 Prim_Op
: Entity_Id
;
4985 Prim_Op_Ref
: Node_Id
;
4989 -- Look for the subprogram in the list of primitive operations
4991 Elmt
:= First_Elmt
(Primitive_Operations
(Obj_Type
));
4992 while Present
(Elmt
) loop
4993 Prim_Op
:= Node
(Elmt
);
4995 if Chars
(Prim_Op
) = Chars
(Subprog
)
4996 and then Present
(First_Formal
(Prim_Op
))
4998 Prim_Op_Ref
:= New_Reference_To
(Prim_Op
, Loc
);
5000 -- When both the type of the object and the type of the first
5001 -- formal of the primitive operation are tagged access types,
5002 -- we use a node with the object as first actual.
5004 if Is_Access_Type
(Etype
(Obj
))
5005 and then Ekind
(Etype
(First_Formal
(Prim_Op
))) =
5006 E_Anonymous_Access_Type
5008 -- Allocate the node only once
5010 if not Present
(Call_Node_Case
) then
5011 Transform_Object_Operation
(
5012 Call_Node
=> Call_Node_Case
,
5013 First_Actual
=> Obj
,
5014 Node_To_Replace
=> Dummy
,
5015 Subprog
=> Subprog
);
5017 Set_Etype
(Call_Node_Case
, Any_Type
);
5018 Set_Parent
(Call_Node_Case
, Parent
(Node_To_Replace
));
5021 Set_Name
(Call_Node_Case
, Prim_Op_Ref
);
5024 N
=> Call_Node_Case
,
5027 Success
=> Success
);
5030 Complete_Object_Operation
(
5031 Call_Node
=> Call_Node_Case
,
5032 Node_To_Replace
=> Node_To_Replace
,
5033 Subprog
=> Prim_Op_Ref
);
5038 -- Comment required ???
5041 Set_Name
(Call_Node
, Prim_Op_Ref
);
5047 Success
=> Success
);
5050 Complete_Object_Operation
(
5051 Call_Node
=> Call_Node
,
5052 Node_To_Replace
=> Node_To_Replace
,
5053 Subprog
=> Prim_Op_Ref
);
5064 end Try_Primitive_Operation
;
5066 -- Start of processing for Try_Object_Operation
5069 if Is_Access_Type
(Obj_Type
) then
5070 Obj_Type
:= Designated_Type
(Obj_Type
);
5073 if Ekind
(Obj_Type
) = E_Private_Subtype
then
5074 Obj_Type
:= Base_Type
(Obj_Type
);
5077 if Is_Class_Wide_Type
(Obj_Type
) then
5078 Obj_Type
:= Etype
(Class_Wide_Type
(Obj_Type
));
5081 -- Analyze the actuals in case of subprogram call
5083 if Is_Subprg_Call
and then N
= Name
(Parent
(N
)) then
5084 Actual
:= First
(Parameter_Associations
(Parent
(N
)));
5085 while Present
(Actual
) loop
5087 Check_Parameterless_Call
(Actual
);
5092 -- If the object is of an Access type, explicit dereference is
5095 if Is_Access_Type
(Etype
(Obj
)) then
5097 Make_Explicit_Dereference
(Sloc
(Obj
), Obj
);
5098 Set_Etype
(First_Actual
, Obj_Type
);
5100 First_Actual
:= Obj
;
5103 -- Build a subprogram call node
5105 Transform_Object_Operation
(
5106 Call_Node
=> Call_Node
,
5107 First_Actual
=> First_Actual
,
5108 Node_To_Replace
=> Node_To_Replace
,
5109 Subprog
=> Subprog
);
5111 Set_Etype
(Call_Node
, Any_Type
);
5112 Set_Parent
(Call_Node
, Parent
(Node_To_Replace
));
5115 Try_Primitive_Operation
5116 (Call_Node
=> Call_Node
,
5117 Node_To_Replace
=> Node_To_Replace
)
5119 Try_Class_Wide_Operation
5120 (Call_Node
=> Call_Node
,
5121 Node_To_Replace
=> Node_To_Replace
);
5122 end Try_Object_Operation
;