1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 1992-2002, 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 Debug
; use Debug
;
29 with Einfo
; use Einfo
;
30 with Errout
; use Errout
;
31 with Exp_Util
; use Exp_Util
;
32 with Hostparm
; use Hostparm
;
33 with Itypes
; use Itypes
;
34 with Lib
.Xref
; use Lib
.Xref
;
35 with Namet
; use Namet
;
36 with Nlists
; use Nlists
;
37 with Nmake
; use Nmake
;
39 with Output
; use Output
;
40 with Restrict
; use Restrict
;
42 with Sem_Cat
; use Sem_Cat
;
43 with Sem_Ch3
; use Sem_Ch3
;
44 with Sem_Ch8
; use Sem_Ch8
;
45 with Sem_Dist
; use Sem_Dist
;
46 with Sem_Eval
; use Sem_Eval
;
47 with Sem_Res
; use Sem_Res
;
48 with Sem_Util
; use Sem_Util
;
49 with Sem_Type
; use Sem_Type
;
50 with Stand
; use Stand
;
51 with Sinfo
; use Sinfo
;
52 with Snames
; use Snames
;
53 with Tbuild
; use Tbuild
;
55 with GNAT
.Spelling_Checker
; use GNAT
.Spelling_Checker
;
57 package body Sem_Ch4
is
59 -----------------------
60 -- Local Subprograms --
61 -----------------------
63 procedure Analyze_Expression
(N
: Node_Id
);
64 -- For expressions that are not names, this is just a call to analyze.
65 -- If the expression is a name, it may be a call to a parameterless
66 -- function, and if so must be converted into an explicit call node
67 -- and analyzed as such. This deproceduring must be done during the first
68 -- pass of overload resolution, because otherwise a procedure call with
69 -- overloaded actuals may fail to resolve. See 4327-001 for an example.
71 procedure Analyze_Operator_Call
(N
: Node_Id
; Op_Id
: Entity_Id
);
72 -- Analyze a call of the form "+"(x, y), etc. The prefix of the call
73 -- is an operator name or an expanded name whose selector is an operator
74 -- name, and one possible interpretation is as a predefined operator.
76 procedure Analyze_Overloaded_Selected_Component
(N
: Node_Id
);
77 -- If the prefix of a selected_component is overloaded, the proper
78 -- interpretation that yields a record type with the proper selector
79 -- name must be selected.
81 procedure Analyze_User_Defined_Binary_Op
(N
: Node_Id
; Op_Id
: Entity_Id
);
82 -- Procedure to analyze a user defined binary operator, which is resolved
83 -- like a function, but instead of a list of actuals it is presented
84 -- with the left and right operands of an operator node.
86 procedure Analyze_User_Defined_Unary_Op
(N
: Node_Id
; Op_Id
: Entity_Id
);
87 -- Procedure to analyze a user defined unary operator, which is resolved
88 -- like a function, but instead of a list of actuals, it is presented with
89 -- the operand of the operator node.
91 procedure Ambiguous_Operands
(N
: Node_Id
);
92 -- for equality, membership, and comparison operators with overloaded
93 -- arguments, list possible interpretations.
95 procedure Insert_Explicit_Dereference
(N
: Node_Id
);
96 -- In a context that requires a composite or subprogram type and
97 -- where a prefix is an access type, insert an explicit dereference.
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.
209 -- If none was found, determine whether a use clause would make the
210 -- operation legal. The variable Candidate_Type (defined in Sem_Type) is
211 -- set for every type compatible with the operator, even if the operator
212 -- for the type is not directly visible. The routine uses this type to emit
213 -- a more informative message.
215 function Try_Indexed_Call
220 -- If a function has defaults for all its actuals, a call to it may
221 -- in fact be an indexing on the result of the call. Try_Indexed_Call
222 -- attempts the interpretation as an indexing, prior to analysis as
223 -- a call. If both are possible, the node is overloaded with both
224 -- interpretations (same symbol but two different types).
226 function Try_Indirect_Call
231 -- Similarly, a function F that needs no actuals can return an access
232 -- to a subprogram, and the call F (X) interpreted as F.all (X). In
233 -- this case the call may be overloaded with both interpretations.
235 ------------------------
236 -- Ambiguous_Operands --
237 ------------------------
239 procedure Ambiguous_Operands
(N
: Node_Id
) is
240 procedure List_Interps
(Opnd
: Node_Id
);
242 procedure List_Interps
(Opnd
: Node_Id
) is
243 Index
: Interp_Index
;
249 if Is_Overloaded
(Opnd
) then
250 if Nkind
(Opnd
) in N_Op
then
253 elsif Nkind
(Opnd
) = N_Function_Call
then
264 if Opnd
= Left_Opnd
(N
) then
266 ("\left operand has the following interpretations", N
);
269 ("\right operand has the following interpretations", N
);
273 Get_First_Interp
(Nam
, Index
, It
);
275 while Present
(It
.Nam
) loop
277 if Scope
(It
.Nam
) = Standard_Standard
278 and then Scope
(It
.Typ
) /= Standard_Standard
280 Error_Msg_Sloc
:= Sloc
(Parent
(It
.Typ
));
281 Error_Msg_NE
(" & (inherited) declared#!", Err
, It
.Nam
);
284 Error_Msg_Sloc
:= Sloc
(It
.Nam
);
285 Error_Msg_NE
(" & declared#!", Err
, It
.Nam
);
288 Get_Next_Interp
(Index
, It
);
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_Interps
(Left_Opnd
(N
));
309 List_Interps
(Right_Opnd
(N
));
314 "\use '/'R'E'P'O'R'T'_'E'R'R'O'R'S'='F'U'L'L for details",
317 Error_Msg_N
("\use -gnatf for details", N
);
320 end Ambiguous_Operands
;
322 -----------------------
323 -- Analyze_Aggregate --
324 -----------------------
326 -- Most of the analysis of Aggregates requires that the type be known,
327 -- and is therefore put off until resolution.
329 procedure Analyze_Aggregate
(N
: Node_Id
) is
331 if No
(Etype
(N
)) then
332 Set_Etype
(N
, Any_Composite
);
334 end Analyze_Aggregate
;
336 -----------------------
337 -- Analyze_Allocator --
338 -----------------------
340 procedure Analyze_Allocator
(N
: Node_Id
) is
341 Loc
: constant Source_Ptr
:= Sloc
(N
);
342 Sav_Errs
: constant Nat
:= Serious_Errors_Detected
;
343 E
: Node_Id
:= Expression
(N
);
344 Acc_Type
: Entity_Id
;
348 Check_Restriction
(No_Allocators
, N
);
350 if Nkind
(E
) = N_Qualified_Expression
then
351 Acc_Type
:= Create_Itype
(E_Allocator_Type
, N
);
352 Set_Etype
(Acc_Type
, Acc_Type
);
353 Init_Size_Align
(Acc_Type
);
354 Find_Type
(Subtype_Mark
(E
));
355 Type_Id
:= Entity
(Subtype_Mark
(E
));
356 Check_Fully_Declared
(Type_Id
, N
);
357 Set_Directly_Designated_Type
(Acc_Type
, Type_Id
);
359 if Is_Protected_Type
(Type_Id
) then
360 Check_Restriction
(No_Protected_Type_Allocators
, N
);
363 if Is_Limited_Type
(Type_Id
)
364 and then Comes_From_Source
(N
)
365 and then not In_Instance_Body
367 Error_Msg_N
("initialization not allowed for limited types", N
);
370 Analyze_And_Resolve
(Expression
(E
), Type_Id
);
372 -- A qualified expression requires an exact match of the type,
373 -- class-wide matching is not allowed.
375 if Is_Class_Wide_Type
(Type_Id
)
376 and then Base_Type
(Etype
(Expression
(E
))) /= Base_Type
(Type_Id
)
378 Wrong_Type
(Expression
(E
), Type_Id
);
381 Check_Non_Static_Context
(Expression
(E
));
383 -- We don't analyze the qualified expression itself because it's
384 -- part of the allocator
386 Set_Etype
(E
, Type_Id
);
393 -- If the allocator includes a N_Subtype_Indication then a
394 -- constraint is present, otherwise the node is a subtype mark.
395 -- Introduce an explicit subtype declaration into the tree
396 -- defining some anonymous subtype and rewrite the allocator to
397 -- use this subtype rather than the subtype indication.
399 -- It is important to introduce the explicit subtype declaration
400 -- so that the bounds of the subtype indication are attached to
401 -- the tree in case the allocator is inside a generic unit.
403 if Nkind
(E
) = N_Subtype_Indication
then
405 -- A constraint is only allowed for a composite type in Ada
406 -- 95. In Ada 83, a constraint is also allowed for an
407 -- access-to-composite type, but the constraint is ignored.
409 Find_Type
(Subtype_Mark
(E
));
411 if Is_Elementary_Type
(Entity
(Subtype_Mark
(E
))) then
413 and then Is_Access_Type
(Entity
(Subtype_Mark
(E
))))
415 Error_Msg_N
("constraint not allowed here", E
);
417 if Nkind
(Constraint
(E
))
418 = N_Index_Or_Discriminant_Constraint
421 ("\if qualified expression was meant, " &
422 "use apostrophe", Constraint
(E
));
426 -- Get rid of the bogus constraint:
428 Rewrite
(E
, New_Copy_Tree
(Subtype_Mark
(E
)));
429 Analyze_Allocator
(N
);
433 if Expander_Active
then
435 Make_Defining_Identifier
(Loc
, New_Internal_Name
('S'));
438 Make_Subtype_Declaration
(Loc
,
439 Defining_Identifier
=> Def_Id
,
440 Subtype_Indication
=> Relocate_Node
(E
)));
442 if Sav_Errs
/= Serious_Errors_Detected
443 and then Nkind
(Constraint
(E
))
444 = N_Index_Or_Discriminant_Constraint
447 ("if qualified expression was meant, " &
448 "use apostrophe!", Constraint
(E
));
451 E
:= New_Occurrence_Of
(Def_Id
, Loc
);
452 Rewrite
(Expression
(N
), E
);
456 Type_Id
:= Process_Subtype
(E
, N
);
457 Acc_Type
:= Create_Itype
(E_Allocator_Type
, N
);
458 Set_Etype
(Acc_Type
, Acc_Type
);
459 Init_Size_Align
(Acc_Type
);
460 Set_Directly_Designated_Type
(Acc_Type
, Type_Id
);
461 Check_Fully_Declared
(Type_Id
, N
);
463 -- Check for missing initialization. Skip this check if we already
464 -- had errors on analyzing the allocator, since in that case these
465 -- are probably cascaded errors
467 if Is_Indefinite_Subtype
(Type_Id
)
468 and then Serious_Errors_Detected
= Sav_Errs
470 if Is_Class_Wide_Type
(Type_Id
) then
472 ("initialization required in class-wide allocation", N
);
475 ("initialization required in unconstrained allocation", N
);
481 if Is_Abstract
(Type_Id
) then
482 Error_Msg_N
("cannot allocate abstract object", E
);
485 if Has_Task
(Designated_Type
(Acc_Type
)) then
486 Check_Restriction
(No_Task_Allocators
, N
);
489 Set_Etype
(N
, Acc_Type
);
491 if not Is_Library_Level_Entity
(Acc_Type
) then
492 Check_Restriction
(No_Local_Allocators
, N
);
495 if Serious_Errors_Detected
> Sav_Errs
then
496 Set_Error_Posted
(N
);
497 Set_Etype
(N
, Any_Type
);
500 end Analyze_Allocator
;
502 ---------------------------
503 -- Analyze_Arithmetic_Op --
504 ---------------------------
506 procedure Analyze_Arithmetic_Op
(N
: Node_Id
) is
507 L
: constant Node_Id
:= Left_Opnd
(N
);
508 R
: constant Node_Id
:= Right_Opnd
(N
);
512 Candidate_Type
:= Empty
;
513 Analyze_Expression
(L
);
514 Analyze_Expression
(R
);
516 -- If the entity is already set, the node is the instantiation of
517 -- a generic node with a non-local reference, or was manufactured
518 -- by a call to Make_Op_xxx. In either case the entity is known to
519 -- be valid, and we do not need to collect interpretations, instead
520 -- we just get the single possible interpretation.
524 if Present
(Op_Id
) then
525 if Ekind
(Op_Id
) = E_Operator
then
527 if (Nkind
(N
) = N_Op_Divide
or else
528 Nkind
(N
) = N_Op_Mod
or else
529 Nkind
(N
) = N_Op_Multiply
or else
530 Nkind
(N
) = N_Op_Rem
)
531 and then Treat_Fixed_As_Integer
(N
)
535 Set_Etype
(N
, Any_Type
);
536 Find_Arithmetic_Types
(L
, R
, Op_Id
, N
);
540 Set_Etype
(N
, Any_Type
);
541 Add_One_Interp
(N
, Op_Id
, Etype
(Op_Id
));
544 -- Entity is not already set, so we do need to collect interpretations
547 Op_Id
:= Get_Name_Entity_Id
(Chars
(N
));
548 Set_Etype
(N
, Any_Type
);
550 while Present
(Op_Id
) loop
551 if Ekind
(Op_Id
) = E_Operator
552 and then Present
(Next_Entity
(First_Entity
(Op_Id
)))
554 Find_Arithmetic_Types
(L
, R
, Op_Id
, N
);
556 -- The following may seem superfluous, because an operator cannot
557 -- be generic, but this ignores the cleverness of the author of
560 elsif Is_Overloadable
(Op_Id
) then
561 Analyze_User_Defined_Binary_Op
(N
, Op_Id
);
564 Op_Id
:= Homonym
(Op_Id
);
569 end Analyze_Arithmetic_Op
;
575 -- Function, procedure, and entry calls are checked here. The Name
576 -- in the call may be overloaded. The actuals have been analyzed
577 -- and may themselves be overloaded. On exit from this procedure, the node
578 -- N may have zero, one or more interpretations. In the first case an error
579 -- message is produced. In the last case, the node is flagged as overloaded
580 -- and the interpretations are collected in All_Interp.
582 -- If the name is an Access_To_Subprogram, it cannot be overloaded, but
583 -- the type-checking is similar to that of other calls.
585 procedure Analyze_Call
(N
: Node_Id
) is
586 Actuals
: constant List_Id
:= Parameter_Associations
(N
);
587 Nam
: Node_Id
:= Name
(N
);
591 Success
: Boolean := False;
593 function Name_Denotes_Function
return Boolean;
594 -- If the type of the name is an access to subprogram, this may be
595 -- the type of a name, or the return type of the function being called.
596 -- If the name is not an entity then it can denote a protected function.
597 -- Until we distinguish Etype from Return_Type, we must use this
598 -- routine to resolve the meaning of the name in the call.
600 ---------------------------
601 -- Name_Denotes_Function --
602 ---------------------------
604 function Name_Denotes_Function
return Boolean is
606 if Is_Entity_Name
(Nam
) then
607 return Ekind
(Entity
(Nam
)) = E_Function
;
609 elsif Nkind
(Nam
) = N_Selected_Component
then
610 return Ekind
(Entity
(Selector_Name
(Nam
))) = E_Function
;
615 end Name_Denotes_Function
;
617 -- Start of processing for Analyze_Call
620 -- Initialize the type of the result of the call to the error type,
621 -- which will be reset if the type is successfully resolved.
623 Set_Etype
(N
, Any_Type
);
625 if not Is_Overloaded
(Nam
) then
627 -- Only one interpretation to check
629 if Ekind
(Etype
(Nam
)) = E_Subprogram_Type
then
630 Nam_Ent
:= Etype
(Nam
);
632 elsif Is_Access_Type
(Etype
(Nam
))
633 and then Ekind
(Designated_Type
(Etype
(Nam
))) = E_Subprogram_Type
634 and then not Name_Denotes_Function
636 Nam_Ent
:= Designated_Type
(Etype
(Nam
));
637 Insert_Explicit_Dereference
(Nam
);
639 -- Selected component case. Simple entry or protected operation,
640 -- where the entry name is given by the selector name.
642 elsif Nkind
(Nam
) = N_Selected_Component
then
643 Nam_Ent
:= Entity
(Selector_Name
(Nam
));
645 if Ekind
(Nam_Ent
) /= E_Entry
646 and then Ekind
(Nam_Ent
) /= E_Entry_Family
647 and then Ekind
(Nam_Ent
) /= E_Function
648 and then Ekind
(Nam_Ent
) /= E_Procedure
650 Error_Msg_N
("name in call is not a callable entity", Nam
);
651 Set_Etype
(N
, Any_Type
);
655 -- If the name is an Indexed component, it can be a call to a member
656 -- of an entry family. The prefix must be a selected component whose
657 -- selector is the entry. Analyze_Procedure_Call normalizes several
658 -- kinds of call into this form.
660 elsif Nkind
(Nam
) = N_Indexed_Component
then
662 if Nkind
(Prefix
(Nam
)) = N_Selected_Component
then
663 Nam_Ent
:= Entity
(Selector_Name
(Prefix
(Nam
)));
666 Error_Msg_N
("name in call is not a callable entity", Nam
);
667 Set_Etype
(N
, Any_Type
);
672 elsif not Is_Entity_Name
(Nam
) then
673 Error_Msg_N
("name in call is not a callable entity", Nam
);
674 Set_Etype
(N
, Any_Type
);
678 Nam_Ent
:= Entity
(Nam
);
680 -- If no interpretations, give error message
682 if not Is_Overloadable
(Nam_Ent
) then
684 L
: constant Boolean := Is_List_Member
(N
);
685 K
: constant Node_Kind
:= Nkind
(Parent
(N
));
688 -- If the node is in a list whose parent is not an
689 -- expression then it must be an attempted procedure call.
691 if L
and then K
not in N_Subexpr
then
692 if Ekind
(Entity
(Nam
)) = E_Generic_Procedure
then
694 ("must instantiate generic procedure& before call",
698 ("procedure or entry name expected", Nam
);
701 -- Check for tasking cases where only an entry call will do
704 and then (K
= N_Entry_Call_Alternative
705 or else K
= N_Triggering_Alternative
)
707 Error_Msg_N
("entry name expected", Nam
);
709 -- Otherwise give general error message
712 Error_Msg_N
("invalid prefix in call", Nam
);
720 Analyze_One_Call
(N
, Nam_Ent
, True, Success
);
723 -- An overloaded selected component must denote overloaded
724 -- operations of a concurrent type. The interpretations are
725 -- attached to the simple name of those operations.
727 if Nkind
(Nam
) = N_Selected_Component
then
728 Nam
:= Selector_Name
(Nam
);
731 Get_First_Interp
(Nam
, X
, It
);
733 while Present
(It
.Nam
) loop
736 -- Name may be call that returns an access to subprogram, or more
737 -- generally an overloaded expression one of whose interpretations
738 -- yields an access to subprogram. If the name is an entity, we
739 -- do not dereference, because the node is a call that returns
740 -- the access type: note difference between f(x), where the call
741 -- may return an access subprogram type, and f(x)(y), where the
742 -- type returned by the call to f is implicitly dereferenced to
743 -- analyze the outer call.
745 if Is_Access_Type
(Nam_Ent
) then
746 Nam_Ent
:= Designated_Type
(Nam_Ent
);
748 elsif Is_Access_Type
(Etype
(Nam_Ent
))
749 and then not Is_Entity_Name
(Nam
)
750 and then Ekind
(Designated_Type
(Etype
(Nam_Ent
)))
753 Nam_Ent
:= Designated_Type
(Etype
(Nam_Ent
));
756 Analyze_One_Call
(N
, Nam_Ent
, False, Success
);
758 -- If the interpretation succeeds, mark the proper type of the
759 -- prefix (any valid candidate will do). If not, remove the
760 -- candidate interpretation. This only needs to be done for
761 -- overloaded protected operations, for other entities disambi-
762 -- guation is done directly in Resolve.
765 Set_Etype
(Nam
, It
.Typ
);
767 elsif Nkind
(Name
(N
)) = N_Selected_Component
then
771 Get_Next_Interp
(X
, It
);
774 -- If the name is the result of a function call, it can only
775 -- be a call to a function returning an access to subprogram.
776 -- Insert explicit dereference.
778 if Nkind
(Nam
) = N_Function_Call
then
779 Insert_Explicit_Dereference
(Nam
);
782 if Etype
(N
) = Any_Type
then
784 -- None of the interpretations is compatible with the actuals
786 Diagnose_Call
(N
, Nam
);
788 -- Special checks for uninstantiated put routines
790 if Nkind
(N
) = N_Procedure_Call_Statement
791 and then Is_Entity_Name
(Nam
)
792 and then Chars
(Nam
) = Name_Put
793 and then List_Length
(Actuals
) = 1
796 Arg
: constant Node_Id
:= First
(Actuals
);
800 if Nkind
(Arg
) = N_Parameter_Association
then
801 Typ
:= Etype
(Explicit_Actual_Parameter
(Arg
));
806 if Is_Signed_Integer_Type
(Typ
) then
808 ("possible missing instantiation of " &
809 "'Text_'I'O.'Integer_'I'O!", Nam
);
811 elsif Is_Modular_Integer_Type
(Typ
) then
813 ("possible missing instantiation of " &
814 "'Text_'I'O.'Modular_'I'O!", Nam
);
816 elsif Is_Floating_Point_Type
(Typ
) then
818 ("possible missing instantiation of " &
819 "'Text_'I'O.'Float_'I'O!", Nam
);
821 elsif Is_Ordinary_Fixed_Point_Type
(Typ
) then
823 ("possible missing instantiation of " &
824 "'Text_'I'O.'Fixed_'I'O!", Nam
);
826 elsif Is_Decimal_Fixed_Point_Type
(Typ
) then
828 ("possible missing instantiation of " &
829 "'Text_'I'O.'Decimal_'I'O!", Nam
);
831 elsif Is_Enumeration_Type
(Typ
) then
833 ("possible missing instantiation of " &
834 "'Text_'I'O.'Enumeration_'I'O!", Nam
);
839 elsif not Is_Overloaded
(N
)
840 and then Is_Entity_Name
(Nam
)
842 -- Resolution yields a single interpretation. Verify that
843 -- is has the proper capitalization.
845 Set_Entity_With_Style_Check
(Nam
, Entity
(Nam
));
846 Generate_Reference
(Entity
(Nam
), Nam
);
848 Set_Etype
(Nam
, Etype
(Entity
(Nam
)));
855 ---------------------------
856 -- Analyze_Comparison_Op --
857 ---------------------------
859 procedure Analyze_Comparison_Op
(N
: Node_Id
) is
860 L
: constant Node_Id
:= Left_Opnd
(N
);
861 R
: constant Node_Id
:= Right_Opnd
(N
);
862 Op_Id
: Entity_Id
:= Entity
(N
);
865 Set_Etype
(N
, Any_Type
);
866 Candidate_Type
:= Empty
;
868 Analyze_Expression
(L
);
869 Analyze_Expression
(R
);
871 if Present
(Op_Id
) then
873 if Ekind
(Op_Id
) = E_Operator
then
874 Find_Comparison_Types
(L
, R
, Op_Id
, N
);
876 Add_One_Interp
(N
, Op_Id
, Etype
(Op_Id
));
879 if Is_Overloaded
(L
) then
880 Set_Etype
(L
, Intersect_Types
(L
, R
));
884 Op_Id
:= Get_Name_Entity_Id
(Chars
(N
));
886 while Present
(Op_Id
) loop
888 if Ekind
(Op_Id
) = E_Operator
then
889 Find_Comparison_Types
(L
, R
, Op_Id
, N
);
891 Analyze_User_Defined_Binary_Op
(N
, Op_Id
);
894 Op_Id
:= Homonym
(Op_Id
);
899 end Analyze_Comparison_Op
;
901 ---------------------------
902 -- Analyze_Concatenation --
903 ---------------------------
905 -- If the only one-dimensional array type in scope is String,
906 -- this is the resulting type of the operation. Otherwise there
907 -- will be a concatenation operation defined for each user-defined
908 -- one-dimensional array.
910 procedure Analyze_Concatenation
(N
: Node_Id
) is
911 L
: constant Node_Id
:= Left_Opnd
(N
);
912 R
: constant Node_Id
:= Right_Opnd
(N
);
913 Op_Id
: Entity_Id
:= Entity
(N
);
918 Set_Etype
(N
, Any_Type
);
919 Candidate_Type
:= Empty
;
921 Analyze_Expression
(L
);
922 Analyze_Expression
(R
);
924 -- If the entity is present, the node appears in an instance,
925 -- and denotes a predefined concatenation operation. The resulting
926 -- type is obtained from the arguments when possible.
928 if Present
(Op_Id
) then
929 if Ekind
(Op_Id
) = E_Operator
then
931 LT
:= Base_Type
(Etype
(L
));
932 RT
:= Base_Type
(Etype
(R
));
934 if Is_Array_Type
(LT
)
935 and then (RT
= LT
or else RT
= Base_Type
(Component_Type
(LT
)))
937 Add_One_Interp
(N
, Op_Id
, LT
);
939 elsif Is_Array_Type
(RT
)
940 and then LT
= Base_Type
(Component_Type
(RT
))
942 Add_One_Interp
(N
, Op_Id
, RT
);
945 Add_One_Interp
(N
, Op_Id
, Etype
(Op_Id
));
949 Add_One_Interp
(N
, Op_Id
, Etype
(Op_Id
));
953 Op_Id
:= Get_Name_Entity_Id
(Name_Op_Concat
);
955 while Present
(Op_Id
) loop
956 if Ekind
(Op_Id
) = E_Operator
then
957 Find_Concatenation_Types
(L
, R
, Op_Id
, N
);
959 Analyze_User_Defined_Binary_Op
(N
, Op_Id
);
962 Op_Id
:= Homonym
(Op_Id
);
967 end Analyze_Concatenation
;
969 ------------------------------------
970 -- Analyze_Conditional_Expression --
971 ------------------------------------
973 procedure Analyze_Conditional_Expression
(N
: Node_Id
) is
974 Condition
: constant Node_Id
:= First
(Expressions
(N
));
975 Then_Expr
: constant Node_Id
:= Next
(Condition
);
976 Else_Expr
: constant Node_Id
:= Next
(Then_Expr
);
979 Analyze_Expression
(Condition
);
980 Analyze_Expression
(Then_Expr
);
981 Analyze_Expression
(Else_Expr
);
982 Set_Etype
(N
, Etype
(Then_Expr
));
983 end Analyze_Conditional_Expression
;
985 -------------------------
986 -- Analyze_Equality_Op --
987 -------------------------
989 procedure Analyze_Equality_Op
(N
: Node_Id
) is
990 Loc
: constant Source_Ptr
:= Sloc
(N
);
991 L
: constant Node_Id
:= Left_Opnd
(N
);
992 R
: constant Node_Id
:= Right_Opnd
(N
);
996 Set_Etype
(N
, Any_Type
);
997 Candidate_Type
:= Empty
;
999 Analyze_Expression
(L
);
1000 Analyze_Expression
(R
);
1002 -- If the entity is set, the node is a generic instance with a non-local
1003 -- reference to the predefined operator or to a user-defined function.
1004 -- It can also be an inequality that is expanded into the negation of a
1005 -- call to a user-defined equality operator.
1007 -- For the predefined case, the result is Boolean, regardless of the
1008 -- type of the operands. The operands may even be limited, if they are
1009 -- generic actuals. If they are overloaded, label the left argument with
1010 -- the common type that must be present, or with the type of the formal
1011 -- of the user-defined function.
1013 if Present
(Entity
(N
)) then
1015 Op_Id
:= Entity
(N
);
1017 if Ekind
(Op_Id
) = E_Operator
then
1018 Add_One_Interp
(N
, Op_Id
, Standard_Boolean
);
1020 Add_One_Interp
(N
, Op_Id
, Etype
(Op_Id
));
1023 if Is_Overloaded
(L
) then
1025 if Ekind
(Op_Id
) = E_Operator
then
1026 Set_Etype
(L
, Intersect_Types
(L
, R
));
1028 Set_Etype
(L
, Etype
(First_Formal
(Op_Id
)));
1033 Op_Id
:= Get_Name_Entity_Id
(Chars
(N
));
1035 while Present
(Op_Id
) loop
1037 if Ekind
(Op_Id
) = E_Operator
then
1038 Find_Equality_Types
(L
, R
, Op_Id
, N
);
1040 Analyze_User_Defined_Binary_Op
(N
, Op_Id
);
1043 Op_Id
:= Homonym
(Op_Id
);
1047 -- If there was no match, and the operator is inequality, this may
1048 -- be a case where inequality has not been made explicit, as for
1049 -- tagged types. Analyze the node as the negation of an equality
1050 -- operation. This cannot be done earlier, because before analysis
1051 -- we cannot rule out the presence of an explicit inequality.
1053 if Etype
(N
) = Any_Type
1054 and then Nkind
(N
) = N_Op_Ne
1056 Op_Id
:= Get_Name_Entity_Id
(Name_Op_Eq
);
1058 while Present
(Op_Id
) loop
1060 if Ekind
(Op_Id
) = E_Operator
then
1061 Find_Equality_Types
(L
, R
, Op_Id
, N
);
1063 Analyze_User_Defined_Binary_Op
(N
, Op_Id
);
1066 Op_Id
:= Homonym
(Op_Id
);
1069 if Etype
(N
) /= Any_Type
then
1070 Op_Id
:= Entity
(N
);
1076 Left_Opnd
=> Relocate_Node
(Left_Opnd
(N
)),
1077 Right_Opnd
=> Relocate_Node
(Right_Opnd
(N
)))));
1079 Set_Entity
(Right_Opnd
(N
), Op_Id
);
1085 end Analyze_Equality_Op
;
1087 ----------------------------------
1088 -- Analyze_Explicit_Dereference --
1089 ----------------------------------
1091 procedure Analyze_Explicit_Dereference
(N
: Node_Id
) is
1092 Loc
: constant Source_Ptr
:= Sloc
(N
);
1093 P
: constant Node_Id
:= Prefix
(N
);
1099 function Is_Function_Type
return Boolean;
1100 -- Check whether node may be interpreted as an implicit function call.
1102 function Is_Function_Type
return Boolean is
1107 if not Is_Overloaded
(N
) then
1108 return Ekind
(Base_Type
(Etype
(N
))) = E_Subprogram_Type
1109 and then Etype
(Base_Type
(Etype
(N
))) /= Standard_Void_Type
;
1112 Get_First_Interp
(N
, I
, It
);
1114 while Present
(It
.Nam
) loop
1115 if Ekind
(Base_Type
(It
.Typ
)) /= E_Subprogram_Type
1116 or else Etype
(Base_Type
(It
.Typ
)) = Standard_Void_Type
1121 Get_Next_Interp
(I
, It
);
1126 end Is_Function_Type
;
1130 Set_Etype
(N
, Any_Type
);
1132 -- Test for remote access to subprogram type, and if so return
1133 -- after rewriting the original tree.
1135 if Remote_AST_E_Dereference
(P
) then
1139 -- Normal processing for other than remote access to subprogram type
1141 if not Is_Overloaded
(P
) then
1142 if Is_Access_Type
(Etype
(P
)) then
1144 -- Set the Etype. We need to go thru Is_For_Access_Subtypes
1145 -- to avoid other problems caused by the Private_Subtype
1146 -- and it is safe to go to the Base_Type because this is the
1147 -- same as converting the access value to its Base_Type.
1150 DT
: Entity_Id
:= Designated_Type
(Etype
(P
));
1153 if Ekind
(DT
) = E_Private_Subtype
1154 and then Is_For_Access_Subtype
(DT
)
1156 DT
:= Base_Type
(DT
);
1162 elsif Etype
(P
) /= Any_Type
then
1163 Error_Msg_N
("prefix of dereference must be an access type", N
);
1168 Get_First_Interp
(P
, I
, It
);
1170 while Present
(It
.Nam
) loop
1173 if Is_Access_Type
(T
) then
1174 Add_One_Interp
(N
, Designated_Type
(T
), Designated_Type
(T
));
1177 Get_Next_Interp
(I
, It
);
1182 -- Error if no interpretation of the prefix has an access type.
1184 if Etype
(N
) = Any_Type
then
1186 ("access type required in prefix of explicit dereference", P
);
1187 Set_Etype
(N
, Any_Type
);
1193 and then Nkind
(Parent
(N
)) /= N_Indexed_Component
1195 and then (Nkind
(Parent
(N
)) /= N_Function_Call
1196 or else N
/= Name
(Parent
(N
)))
1198 and then (Nkind
(Parent
(N
)) /= N_Procedure_Call_Statement
1199 or else N
/= Name
(Parent
(N
)))
1201 and then Nkind
(Parent
(N
)) /= N_Subprogram_Renaming_Declaration
1202 and then (Nkind
(Parent
(N
)) /= N_Attribute_Reference
1204 (Attribute_Name
(Parent
(N
)) /= Name_Address
1206 Attribute_Name
(Parent
(N
)) /= Name_Access
))
1208 -- Name is a function call with no actuals, in a context that
1209 -- requires deproceduring (including as an actual in an enclosing
1210 -- function or procedure call). We can conceive of pathological cases
1211 -- where the prefix might include functions that return access to
1212 -- subprograms and others that return a regular type. Disambiguation
1213 -- of those will have to take place in Resolve. See e.g. 7117-014.
1216 Make_Function_Call
(Loc
,
1217 Name
=> Make_Explicit_Dereference
(Loc
, P
),
1218 Parameter_Associations
=> New_List
);
1220 -- If the prefix is overloaded, remove operations that have formals,
1221 -- we know that this is a parameterless call.
1223 if Is_Overloaded
(P
) then
1224 Get_First_Interp
(P
, I
, It
);
1226 while Present
(It
.Nam
) loop
1229 if No
(First_Formal
(Base_Type
(Designated_Type
(T
)))) then
1235 Get_Next_Interp
(I
, It
);
1243 -- A value of remote access-to-class-wide must not be dereferenced
1246 Validate_Remote_Access_To_Class_Wide_Type
(N
);
1248 end Analyze_Explicit_Dereference
;
1250 ------------------------
1251 -- Analyze_Expression --
1252 ------------------------
1254 procedure Analyze_Expression
(N
: Node_Id
) is
1257 Check_Parameterless_Call
(N
);
1258 end Analyze_Expression
;
1260 ------------------------------------
1261 -- Analyze_Indexed_Component_Form --
1262 ------------------------------------
1264 procedure Analyze_Indexed_Component_Form
(N
: Node_Id
) is
1265 P
: constant Node_Id
:= Prefix
(N
);
1266 Exprs
: List_Id
:= Expressions
(N
);
1272 procedure Process_Function_Call
;
1273 -- Prefix in indexed component form is an overloadable entity,
1274 -- so the node is a function call. Reformat it as such.
1276 procedure Process_Indexed_Component
;
1277 -- Prefix in indexed component form is actually an indexed component.
1278 -- This routine processes it, knowing that the prefix is already
1281 procedure Process_Indexed_Component_Or_Slice
;
1282 -- An indexed component with a single index may designate a slice if
1283 -- the index is a subtype mark. This routine disambiguates these two
1284 -- cases by resolving the prefix to see if it is a subtype mark.
1286 procedure Process_Overloaded_Indexed_Component
;
1287 -- If the prefix of an indexed component is overloaded, the proper
1288 -- interpretation is selected by the index types and the context.
1290 ---------------------------
1291 -- Process_Function_Call --
1292 ---------------------------
1294 procedure Process_Function_Call
is
1298 Change_Node
(N
, N_Function_Call
);
1300 Set_Parameter_Associations
(N
, Exprs
);
1301 Actual
:= First
(Parameter_Associations
(N
));
1303 while Present
(Actual
) loop
1305 Check_Parameterless_Call
(Actual
);
1306 Next_Actual
(Actual
);
1310 end Process_Function_Call
;
1312 -------------------------------
1313 -- Process_Indexed_Component --
1314 -------------------------------
1316 procedure Process_Indexed_Component
is
1318 Array_Type
: Entity_Id
;
1320 Entry_Family
: Entity_Id
;
1323 Exp
:= First
(Exprs
);
1325 if Is_Overloaded
(P
) then
1326 Process_Overloaded_Indexed_Component
;
1329 Array_Type
:= Etype
(P
);
1331 -- Prefix must be appropriate for an array type.
1332 -- Dereference the prefix if it is an access type.
1334 if Is_Access_Type
(Array_Type
) then
1335 Array_Type
:= Designated_Type
(Array_Type
);
1337 if Warn_On_Dereference
then
1338 Error_Msg_N
("?implicit dereference", N
);
1342 if Is_Array_Type
(Array_Type
) then
1345 elsif (Is_Entity_Name
(P
)
1347 Ekind
(Entity
(P
)) = E_Entry_Family
)
1349 (Nkind
(P
) = N_Selected_Component
1351 Is_Entity_Name
(Selector_Name
(P
))
1353 Ekind
(Entity
(Selector_Name
(P
))) = E_Entry_Family
)
1355 if Is_Entity_Name
(P
) then
1356 Entry_Family
:= Entity
(P
);
1358 Entry_Family
:= Entity
(Selector_Name
(P
));
1362 Set_Etype
(N
, Any_Type
);
1364 if not Has_Compatible_Type
1365 (Exp
, Entry_Index_Type
(Entry_Family
))
1367 Error_Msg_N
("invalid index type in entry name", N
);
1369 elsif Present
(Next
(Exp
)) then
1370 Error_Msg_N
("too many subscripts in entry reference", N
);
1373 Set_Etype
(N
, Etype
(P
));
1378 elsif Is_Record_Type
(Array_Type
)
1379 and then Remote_AST_I_Dereference
(P
)
1383 elsif Array_Type
= Any_Type
then
1384 Set_Etype
(N
, Any_Type
);
1387 -- Here we definitely have a bad indexing
1390 if Nkind
(Parent
(N
)) = N_Requeue_Statement
1392 ((Is_Entity_Name
(P
)
1393 and then Ekind
(Entity
(P
)) = E_Entry
)
1395 (Nkind
(P
) = N_Selected_Component
1396 and then Is_Entity_Name
(Selector_Name
(P
))
1397 and then Ekind
(Entity
(Selector_Name
(P
))) = E_Entry
))
1400 ("REQUEUE does not permit parameters", First
(Exprs
));
1402 elsif Is_Entity_Name
(P
)
1403 and then Etype
(P
) = Standard_Void_Type
1405 Error_Msg_NE
("incorrect use of&", P
, Entity
(P
));
1408 Error_Msg_N
("array type required in indexed component", P
);
1411 Set_Etype
(N
, Any_Type
);
1415 Index
:= First_Index
(Array_Type
);
1417 while Present
(Index
) and then Present
(Exp
) loop
1418 if not Has_Compatible_Type
(Exp
, Etype
(Index
)) then
1419 Wrong_Type
(Exp
, Etype
(Index
));
1420 Set_Etype
(N
, Any_Type
);
1428 Set_Etype
(N
, Component_Type
(Array_Type
));
1430 if Present
(Index
) then
1432 ("too few subscripts in array reference", First
(Exprs
));
1434 elsif Present
(Exp
) then
1435 Error_Msg_N
("too many subscripts in array reference", Exp
);
1439 end Process_Indexed_Component
;
1441 ----------------------------------------
1442 -- Process_Indexed_Component_Or_Slice --
1443 ----------------------------------------
1445 procedure Process_Indexed_Component_Or_Slice
is
1447 Exp
:= First
(Exprs
);
1449 while Present
(Exp
) loop
1450 Analyze_Expression
(Exp
);
1454 Exp
:= First
(Exprs
);
1456 -- If one index is present, and it is a subtype name, then the
1457 -- node denotes a slice (note that the case of an explicit range
1458 -- for a slice was already built as an N_Slice node in the first
1459 -- place, so that case is not handled here).
1461 -- We use a replace rather than a rewrite here because this is one
1462 -- of the cases in which the tree built by the parser is plain wrong.
1465 and then Is_Entity_Name
(Exp
)
1466 and then Is_Type
(Entity
(Exp
))
1469 Make_Slice
(Sloc
(N
),
1471 Discrete_Range
=> New_Copy
(Exp
)));
1474 -- Otherwise (more than one index present, or single index is not
1475 -- a subtype name), then we have the indexed component case.
1478 Process_Indexed_Component
;
1480 end Process_Indexed_Component_Or_Slice
;
1482 ------------------------------------------
1483 -- Process_Overloaded_Indexed_Component --
1484 ------------------------------------------
1486 procedure Process_Overloaded_Indexed_Component
is
1495 Set_Etype
(N
, Any_Type
);
1496 Get_First_Interp
(P
, I
, It
);
1498 while Present
(It
.Nam
) loop
1501 if Is_Access_Type
(Typ
) then
1502 Typ
:= Designated_Type
(Typ
);
1504 if Warn_On_Dereference
then
1505 Error_Msg_N
("?implicit dereference", N
);
1509 if Is_Array_Type
(Typ
) then
1511 -- Got a candidate: verify that index types are compatible
1513 Index
:= First_Index
(Typ
);
1516 Exp
:= First
(Exprs
);
1518 while Present
(Index
) and then Present
(Exp
) loop
1519 if Has_Compatible_Type
(Exp
, Etype
(Index
)) then
1531 if Found
and then No
(Index
) and then No
(Exp
) then
1533 Etype
(Component_Type
(Typ
)),
1534 Etype
(Component_Type
(Typ
)));
1538 Get_Next_Interp
(I
, It
);
1541 if Etype
(N
) = Any_Type
then
1542 Error_Msg_N
("no legal interpetation for indexed component", N
);
1543 Set_Is_Overloaded
(N
, False);
1547 end Process_Overloaded_Indexed_Component
;
1549 ------------------------------------
1550 -- Analyze_Indexed_Component_Form --
1551 ------------------------------------
1554 -- Get name of array, function or type
1557 P_T
:= Base_Type
(Etype
(P
));
1559 if Is_Entity_Name
(P
)
1560 or else Nkind
(P
) = N_Operator_Symbol
1564 if Ekind
(U_N
) in Type_Kind
then
1566 -- Reformat node as a type conversion.
1568 E
:= Remove_Head
(Exprs
);
1570 if Present
(First
(Exprs
)) then
1572 ("argument of type conversion must be single expression", N
);
1575 Change_Node
(N
, N_Type_Conversion
);
1576 Set_Subtype_Mark
(N
, P
);
1578 Set_Expression
(N
, E
);
1580 -- After changing the node, call for the specific Analysis
1581 -- routine directly, to avoid a double call to the expander.
1583 Analyze_Type_Conversion
(N
);
1587 if Is_Overloadable
(U_N
) then
1588 Process_Function_Call
;
1590 elsif Ekind
(Etype
(P
)) = E_Subprogram_Type
1591 or else (Is_Access_Type
(Etype
(P
))
1593 Ekind
(Designated_Type
(Etype
(P
))) = E_Subprogram_Type
)
1595 -- Call to access_to-subprogram with possible implicit dereference
1597 Process_Function_Call
;
1599 elsif Ekind
(U_N
) = E_Generic_Function
1600 or else Ekind
(U_N
) = E_Generic_Procedure
1602 -- A common beginner's (or C++ templates fan) error.
1604 Error_Msg_N
("generic subprogram cannot be called", N
);
1605 Set_Etype
(N
, Any_Type
);
1609 Process_Indexed_Component_Or_Slice
;
1612 -- If not an entity name, prefix is an expression that may denote
1613 -- an array or an access-to-subprogram.
1617 if (Ekind
(P_T
) = E_Subprogram_Type
)
1618 or else (Is_Access_Type
(P_T
)
1620 Ekind
(Designated_Type
(P_T
)) = E_Subprogram_Type
)
1622 Process_Function_Call
;
1624 elsif Nkind
(P
) = N_Selected_Component
1625 and then Ekind
(Entity
(Selector_Name
(P
))) = E_Function
1627 Process_Function_Call
;
1630 -- Indexed component, slice, or a call to a member of a family
1631 -- entry, which will be converted to an entry call later.
1632 Process_Indexed_Component_Or_Slice
;
1635 end Analyze_Indexed_Component_Form
;
1637 ------------------------
1638 -- Analyze_Logical_Op --
1639 ------------------------
1641 procedure Analyze_Logical_Op
(N
: Node_Id
) is
1642 L
: constant Node_Id
:= Left_Opnd
(N
);
1643 R
: constant Node_Id
:= Right_Opnd
(N
);
1644 Op_Id
: Entity_Id
:= Entity
(N
);
1647 Set_Etype
(N
, Any_Type
);
1648 Candidate_Type
:= Empty
;
1650 Analyze_Expression
(L
);
1651 Analyze_Expression
(R
);
1653 if Present
(Op_Id
) then
1655 if Ekind
(Op_Id
) = E_Operator
then
1656 Find_Boolean_Types
(L
, R
, Op_Id
, N
);
1658 Add_One_Interp
(N
, Op_Id
, Etype
(Op_Id
));
1662 Op_Id
:= Get_Name_Entity_Id
(Chars
(N
));
1664 while Present
(Op_Id
) loop
1665 if Ekind
(Op_Id
) = E_Operator
then
1666 Find_Boolean_Types
(L
, R
, Op_Id
, N
);
1668 Analyze_User_Defined_Binary_Op
(N
, Op_Id
);
1671 Op_Id
:= Homonym
(Op_Id
);
1676 end Analyze_Logical_Op
;
1678 ---------------------------
1679 -- Analyze_Membership_Op --
1680 ---------------------------
1682 procedure Analyze_Membership_Op
(N
: Node_Id
) is
1683 L
: constant Node_Id
:= Left_Opnd
(N
);
1684 R
: constant Node_Id
:= Right_Opnd
(N
);
1686 Index
: Interp_Index
;
1688 Found
: Boolean := False;
1692 procedure Try_One_Interp
(T1
: Entity_Id
);
1693 -- Routine to try one proposed interpretation. Note that the context
1694 -- of the operation plays no role in resolving the arguments, so that
1695 -- if there is more than one interpretation of the operands that is
1696 -- compatible with a membership test, the operation is ambiguous.
1698 procedure Try_One_Interp
(T1
: Entity_Id
) is
1700 if Has_Compatible_Type
(R
, T1
) then
1702 and then Base_Type
(T1
) /= Base_Type
(T_F
)
1704 It
:= Disambiguate
(L
, I_F
, Index
, Any_Type
);
1706 if It
= No_Interp
then
1707 Ambiguous_Operands
(N
);
1708 Set_Etype
(L
, Any_Type
);
1726 -- Start of processing for Analyze_Membership_Op
1729 Analyze_Expression
(L
);
1731 if Nkind
(R
) = N_Range
1732 or else (Nkind
(R
) = N_Attribute_Reference
1733 and then Attribute_Name
(R
) = Name_Range
)
1737 if not Is_Overloaded
(L
) then
1738 Try_One_Interp
(Etype
(L
));
1741 Get_First_Interp
(L
, Index
, It
);
1743 while Present
(It
.Typ
) loop
1744 Try_One_Interp
(It
.Typ
);
1745 Get_Next_Interp
(Index
, It
);
1749 -- If not a range, it can only be a subtype mark, or else there
1750 -- is a more basic error, to be diagnosed in Find_Type.
1755 if Is_Entity_Name
(R
) then
1756 Check_Fully_Declared
(Entity
(R
), R
);
1760 -- Compatibility between expression and subtype mark or range is
1761 -- checked during resolution. The result of the operation is Boolean
1764 Set_Etype
(N
, Standard_Boolean
);
1765 end Analyze_Membership_Op
;
1767 ----------------------
1768 -- Analyze_Negation --
1769 ----------------------
1771 procedure Analyze_Negation
(N
: Node_Id
) is
1772 R
: constant Node_Id
:= Right_Opnd
(N
);
1773 Op_Id
: Entity_Id
:= Entity
(N
);
1776 Set_Etype
(N
, Any_Type
);
1777 Candidate_Type
:= Empty
;
1779 Analyze_Expression
(R
);
1781 if Present
(Op_Id
) then
1782 if Ekind
(Op_Id
) = E_Operator
then
1783 Find_Negation_Types
(R
, Op_Id
, N
);
1785 Add_One_Interp
(N
, Op_Id
, Etype
(Op_Id
));
1789 Op_Id
:= Get_Name_Entity_Id
(Chars
(N
));
1791 while Present
(Op_Id
) loop
1792 if Ekind
(Op_Id
) = E_Operator
then
1793 Find_Negation_Types
(R
, Op_Id
, N
);
1795 Analyze_User_Defined_Unary_Op
(N
, Op_Id
);
1798 Op_Id
:= Homonym
(Op_Id
);
1803 end Analyze_Negation
;
1809 procedure Analyze_Null
(N
: Node_Id
) is
1811 Set_Etype
(N
, Any_Access
);
1814 ----------------------
1815 -- Analyze_One_Call --
1816 ----------------------
1818 procedure Analyze_One_Call
1822 Success
: out Boolean)
1824 Actuals
: constant List_Id
:= Parameter_Associations
(N
);
1825 Prev_T
: constant Entity_Id
:= Etype
(N
);
1828 Is_Indexed
: Boolean := False;
1829 Subp_Type
: constant Entity_Id
:= Etype
(Nam
);
1833 -- If candidate interpretation matches, indicate name and type of
1834 -- result on call node.
1840 procedure Set_Name
is
1842 Add_One_Interp
(N
, Nam
, Etype
(Nam
));
1845 -- If the prefix of the call is a name, indicate the entity
1846 -- being called. If it is not a name, it is an expression that
1847 -- denotes an access to subprogram or else an entry or family. In
1848 -- the latter case, the name is a selected component, and the entity
1849 -- being called is noted on the selector.
1851 if not Is_Type
(Nam
) then
1852 if Is_Entity_Name
(Name
(N
))
1853 or else Nkind
(Name
(N
)) = N_Operator_Symbol
1855 Set_Entity
(Name
(N
), Nam
);
1857 elsif Nkind
(Name
(N
)) = N_Selected_Component
then
1858 Set_Entity
(Selector_Name
(Name
(N
)), Nam
);
1862 if Debug_Flag_E
and not Report
then
1863 Write_Str
(" Overloaded call ");
1864 Write_Int
(Int
(N
));
1865 Write_Str
(" compatible with ");
1866 Write_Int
(Int
(Nam
));
1871 -- Start of processing for Analyze_One_Call
1876 -- If the subprogram has no formals, or if all the formals have
1877 -- defaults, and the return type is an array type, the node may
1878 -- denote an indexing of the result of a parameterless call.
1880 if Needs_No_Actuals
(Nam
)
1881 and then Present
(Actuals
)
1883 if Is_Array_Type
(Subp_Type
) then
1884 Is_Indexed
:= Try_Indexed_Call
(N
, Nam
, Subp_Type
);
1886 elsif Is_Access_Type
(Subp_Type
)
1887 and then Is_Array_Type
(Designated_Type
(Subp_Type
))
1890 Try_Indexed_Call
(N
, Nam
, Designated_Type
(Subp_Type
));
1892 elsif Is_Access_Type
(Subp_Type
)
1893 and then Ekind
(Designated_Type
(Subp_Type
)) = E_Subprogram_Type
1895 Is_Indexed
:= Try_Indirect_Call
(N
, Nam
, Subp_Type
);
1900 Normalize_Actuals
(N
, Nam
, (Report
and not Is_Indexed
), Norm_OK
);
1904 -- Mismatch in number or names of parameters
1906 if Debug_Flag_E
then
1907 Write_Str
(" normalization fails in call ");
1908 Write_Int
(Int
(N
));
1909 Write_Str
(" with subprogram ");
1910 Write_Int
(Int
(Nam
));
1914 -- If the context expects a function call, discard any interpretation
1915 -- that is a procedure. If the node is not overloaded, leave as is for
1916 -- better error reporting when type mismatch is found.
1918 elsif Nkind
(N
) = N_Function_Call
1919 and then Is_Overloaded
(Name
(N
))
1920 and then Ekind
(Nam
) = E_Procedure
1924 -- Ditto for function calls in a procedure context.
1926 elsif Nkind
(N
) = N_Procedure_Call_Statement
1927 and then Is_Overloaded
(Name
(N
))
1928 and then Etype
(Nam
) /= Standard_Void_Type
1932 elsif not Present
(Actuals
) then
1934 -- If Normalize succeeds, then there are default parameters for
1939 elsif Ekind
(Nam
) = E_Operator
then
1941 if Nkind
(N
) = N_Procedure_Call_Statement
then
1945 -- This can occur when the prefix of the call is an operator
1946 -- name or an expanded name whose selector is an operator name.
1948 Analyze_Operator_Call
(N
, Nam
);
1950 if Etype
(N
) /= Prev_T
then
1952 -- There may be a user-defined operator that hides the
1953 -- current interpretation. We must check for this independently
1954 -- of the analysis of the call with the user-defined operation,
1955 -- because the parameter names may be wrong and yet the hiding
1956 -- takes place. Fixes b34014o.
1958 if Is_Overloaded
(Name
(N
)) then
1964 Get_First_Interp
(Name
(N
), I
, It
);
1966 while Present
(It
.Nam
) loop
1968 if Ekind
(It
.Nam
) /= E_Operator
1969 and then Hides_Op
(It
.Nam
, Nam
)
1972 (First_Actual
(N
), Etype
(First_Formal
(It
.Nam
)))
1973 and then (No
(Next_Actual
(First_Actual
(N
)))
1974 or else Has_Compatible_Type
1975 (Next_Actual
(First_Actual
(N
)),
1976 Etype
(Next_Formal
(First_Formal
(It
.Nam
)))))
1978 Set_Etype
(N
, Prev_T
);
1982 Get_Next_Interp
(I
, It
);
1987 -- If operator matches formals, record its name on the call.
1988 -- If the operator is overloaded, Resolve will select the
1989 -- correct one from the list of interpretations. The call
1990 -- node itself carries the first candidate.
1992 Set_Entity
(Name
(N
), Nam
);
1995 elsif Report
and then Etype
(N
) = Any_Type
then
1996 Error_Msg_N
("incompatible arguments for operator", N
);
2000 -- Normalize_Actuals has chained the named associations in the
2001 -- correct order of the formals.
2003 Actual
:= First_Actual
(N
);
2004 Formal
:= First_Formal
(Nam
);
2006 while Present
(Actual
) and then Present
(Formal
) loop
2008 if (Nkind
(Parent
(Actual
)) /= N_Parameter_Association
2009 or else Chars
(Selector_Name
(Parent
(Actual
))) = Chars
(Formal
))
2011 if Has_Compatible_Type
(Actual
, Etype
(Formal
)) then
2012 Next_Actual
(Actual
);
2013 Next_Formal
(Formal
);
2016 if Debug_Flag_E
then
2017 Write_Str
(" type checking fails in call ");
2018 Write_Int
(Int
(N
));
2019 Write_Str
(" with formal ");
2020 Write_Int
(Int
(Formal
));
2021 Write_Str
(" in subprogram ");
2022 Write_Int
(Int
(Nam
));
2026 if Report
and not Is_Indexed
then
2028 Wrong_Type
(Actual
, Etype
(Formal
));
2030 if Nkind
(Actual
) = N_Op_Eq
2031 and then Nkind
(Left_Opnd
(Actual
)) = N_Identifier
2033 Formal
:= First_Formal
(Nam
);
2035 while Present
(Formal
) loop
2037 if Chars
(Left_Opnd
(Actual
)) = Chars
(Formal
) then
2039 ("possible misspelling of `=>`!", Actual
);
2043 Next_Formal
(Formal
);
2047 if All_Errors_Mode
then
2048 Error_Msg_Sloc
:= Sloc
(Nam
);
2050 if Is_Overloadable
(Nam
)
2051 and then Present
(Alias
(Nam
))
2052 and then not Comes_From_Source
(Nam
)
2055 (" ==> in call to &#(inherited)!", Actual
, Nam
);
2057 Error_Msg_NE
(" ==> in call to &#!", Actual
, Nam
);
2066 -- Normalize_Actuals has verified that a default value exists
2067 -- for this formal. Current actual names a subsequent formal.
2069 Next_Formal
(Formal
);
2073 -- On exit, all actuals match.
2077 end Analyze_One_Call
;
2079 ----------------------------
2080 -- Analyze_Operator_Call --
2081 ----------------------------
2083 procedure Analyze_Operator_Call
(N
: Node_Id
; Op_Id
: Entity_Id
) is
2084 Op_Name
: constant Name_Id
:= Chars
(Op_Id
);
2085 Act1
: constant Node_Id
:= First_Actual
(N
);
2086 Act2
: constant Node_Id
:= Next_Actual
(Act1
);
2089 if Present
(Act2
) then
2091 -- Maybe binary operators
2093 if Present
(Next_Actual
(Act2
)) then
2095 -- Too many actuals for an operator
2099 elsif Op_Name
= Name_Op_Add
2100 or else Op_Name
= Name_Op_Subtract
2101 or else Op_Name
= Name_Op_Multiply
2102 or else Op_Name
= Name_Op_Divide
2103 or else Op_Name
= Name_Op_Mod
2104 or else Op_Name
= Name_Op_Rem
2105 or else Op_Name
= Name_Op_Expon
2107 Find_Arithmetic_Types
(Act1
, Act2
, Op_Id
, N
);
2109 elsif Op_Name
= Name_Op_And
2110 or else Op_Name
= Name_Op_Or
2111 or else Op_Name
= Name_Op_Xor
2113 Find_Boolean_Types
(Act1
, Act2
, Op_Id
, N
);
2115 elsif Op_Name
= Name_Op_Lt
2116 or else Op_Name
= Name_Op_Le
2117 or else Op_Name
= Name_Op_Gt
2118 or else Op_Name
= Name_Op_Ge
2120 Find_Comparison_Types
(Act1
, Act2
, Op_Id
, N
);
2122 elsif Op_Name
= Name_Op_Eq
2123 or else Op_Name
= Name_Op_Ne
2125 Find_Equality_Types
(Act1
, Act2
, Op_Id
, N
);
2127 elsif Op_Name
= Name_Op_Concat
then
2128 Find_Concatenation_Types
(Act1
, Act2
, Op_Id
, N
);
2130 -- Is this else null correct, or should it be an abort???
2139 if Op_Name
= Name_Op_Subtract
or else
2140 Op_Name
= Name_Op_Add
or else
2141 Op_Name
= Name_Op_Abs
2143 Find_Unary_Types
(Act1
, Op_Id
, N
);
2146 Op_Name
= Name_Op_Not
2148 Find_Negation_Types
(Act1
, Op_Id
, N
);
2150 -- Is this else null correct, or should it be an abort???
2156 end Analyze_Operator_Call
;
2158 -------------------------------------------
2159 -- Analyze_Overloaded_Selected_Component --
2160 -------------------------------------------
2162 procedure Analyze_Overloaded_Selected_Component
(N
: Node_Id
) is
2164 Nam
: Node_Id
:= Prefix
(N
);
2165 Sel
: Node_Id
:= Selector_Name
(N
);
2171 Get_First_Interp
(Nam
, I
, It
);
2173 Set_Etype
(Sel
, Any_Type
);
2175 while Present
(It
.Typ
) loop
2176 if Is_Access_Type
(It
.Typ
) then
2177 T
:= Designated_Type
(It
.Typ
);
2179 if Warn_On_Dereference
then
2180 Error_Msg_N
("?implicit dereference", N
);
2187 if Is_Record_Type
(T
) then
2188 Comp
:= First_Entity
(T
);
2190 while Present
(Comp
) loop
2192 if Chars
(Comp
) = Chars
(Sel
)
2193 and then Is_Visible_Component
(Comp
)
2195 Set_Entity_With_Style_Check
(Sel
, Comp
);
2196 Generate_Reference
(Comp
, Sel
);
2198 Set_Etype
(Sel
, Etype
(Comp
));
2199 Add_One_Interp
(N
, Etype
(Comp
), Etype
(Comp
));
2201 -- This also specifies a candidate to resolve the name.
2202 -- Further overloading will be resolved from context.
2204 Set_Etype
(Nam
, It
.Typ
);
2210 elsif Is_Concurrent_Type
(T
) then
2211 Comp
:= First_Entity
(T
);
2213 while Present
(Comp
)
2214 and then Comp
/= First_Private_Entity
(T
)
2216 if Chars
(Comp
) = Chars
(Sel
) then
2217 if Is_Overloadable
(Comp
) then
2218 Add_One_Interp
(Sel
, Comp
, Etype
(Comp
));
2220 Set_Entity_With_Style_Check
(Sel
, Comp
);
2221 Generate_Reference
(Comp
, Sel
);
2224 Set_Etype
(Sel
, Etype
(Comp
));
2225 Set_Etype
(N
, Etype
(Comp
));
2226 Set_Etype
(Nam
, It
.Typ
);
2228 -- For access type case, introduce explicit deference for
2229 -- more uniform treatment of entry calls.
2231 if Is_Access_Type
(Etype
(Nam
)) then
2232 Insert_Explicit_Dereference
(Nam
);
2234 if Warn_On_Dereference
then
2235 Error_Msg_N
("?implicit dereference", N
);
2243 Set_Is_Overloaded
(N
, Is_Overloaded
(Sel
));
2246 Get_Next_Interp
(I
, It
);
2249 if Etype
(N
) = Any_Type
then
2250 Error_Msg_NE
("undefined selector& for overloaded prefix", N
, Sel
);
2251 Set_Entity
(Sel
, Any_Id
);
2252 Set_Etype
(Sel
, Any_Type
);
2255 end Analyze_Overloaded_Selected_Component
;
2257 ----------------------------------
2258 -- Analyze_Qualified_Expression --
2259 ----------------------------------
2261 procedure Analyze_Qualified_Expression
(N
: Node_Id
) is
2262 Mark
: constant Entity_Id
:= Subtype_Mark
(N
);
2266 Set_Etype
(N
, Any_Type
);
2270 if T
= Any_Type
then
2273 Check_Fully_Declared
(T
, N
);
2275 Analyze_Expression
(Expression
(N
));
2277 end Analyze_Qualified_Expression
;
2283 procedure Analyze_Range
(N
: Node_Id
) is
2284 L
: constant Node_Id
:= Low_Bound
(N
);
2285 H
: constant Node_Id
:= High_Bound
(N
);
2286 I1
, I2
: Interp_Index
;
2289 procedure Check_Common_Type
(T1
, T2
: Entity_Id
);
2290 -- Verify the compatibility of two types, and choose the
2291 -- non universal one if the other is universal.
2293 procedure Check_High_Bound
(T
: Entity_Id
);
2294 -- Test one interpretation of the low bound against all those
2295 -- of the high bound.
2297 -----------------------
2298 -- Check_Common_Type --
2299 -----------------------
2301 procedure Check_Common_Type
(T1
, T2
: Entity_Id
) is
2303 if Covers
(T1
, T2
) or else Covers
(T2
, T1
) then
2304 if T1
= Universal_Integer
2305 or else T1
= Universal_Real
2306 or else T1
= Any_Character
2308 Add_One_Interp
(N
, Base_Type
(T2
), Base_Type
(T2
));
2310 elsif (T1
= T2
) then
2311 Add_One_Interp
(N
, T1
, T1
);
2314 Add_One_Interp
(N
, Base_Type
(T1
), Base_Type
(T1
));
2317 end Check_Common_Type
;
2319 ----------------------
2320 -- Check_High_Bound --
2321 ----------------------
2323 procedure Check_High_Bound
(T
: Entity_Id
) is
2325 if not Is_Overloaded
(H
) then
2326 Check_Common_Type
(T
, Etype
(H
));
2328 Get_First_Interp
(H
, I2
, It2
);
2330 while Present
(It2
.Typ
) loop
2331 Check_Common_Type
(T
, It2
.Typ
);
2332 Get_Next_Interp
(I2
, It2
);
2335 end Check_High_Bound
;
2337 -- Start of processing for Analyze_Range
2340 Set_Etype
(N
, Any_Type
);
2341 Analyze_Expression
(L
);
2342 Analyze_Expression
(H
);
2344 if Etype
(L
) = Any_Type
or else Etype
(H
) = Any_Type
then
2348 if not Is_Overloaded
(L
) then
2349 Check_High_Bound
(Etype
(L
));
2351 Get_First_Interp
(L
, I1
, It1
);
2353 while Present
(It1
.Typ
) loop
2354 Check_High_Bound
(It1
.Typ
);
2355 Get_Next_Interp
(I1
, It1
);
2359 -- If result is Any_Type, then we did not find a compatible pair
2361 if Etype
(N
) = Any_Type
then
2362 Error_Msg_N
("incompatible types in range ", N
);
2367 -----------------------
2368 -- Analyze_Reference --
2369 -----------------------
2371 procedure Analyze_Reference
(N
: Node_Id
) is
2372 P
: constant Node_Id
:= Prefix
(N
);
2373 Acc_Type
: Entity_Id
;
2377 Acc_Type
:= Create_Itype
(E_Allocator_Type
, N
);
2378 Set_Etype
(Acc_Type
, Acc_Type
);
2379 Init_Size_Align
(Acc_Type
);
2380 Set_Directly_Designated_Type
(Acc_Type
, Etype
(P
));
2381 Set_Etype
(N
, Acc_Type
);
2382 end Analyze_Reference
;
2384 --------------------------------
2385 -- Analyze_Selected_Component --
2386 --------------------------------
2388 -- Prefix is a record type or a task or protected type. In the
2389 -- later case, the selector must denote a visible entry.
2391 procedure Analyze_Selected_Component
(N
: Node_Id
) is
2392 Name
: constant Node_Id
:= Prefix
(N
);
2393 Sel
: constant Node_Id
:= Selector_Name
(N
);
2395 Entity_List
: Entity_Id
;
2396 Prefix_Type
: Entity_Id
;
2401 -- Start of processing for Analyze_Selected_Component
2404 Set_Etype
(N
, Any_Type
);
2406 if Is_Overloaded
(Name
) then
2407 Analyze_Overloaded_Selected_Component
(N
);
2410 elsif Etype
(Name
) = Any_Type
then
2411 Set_Entity
(Sel
, Any_Id
);
2412 Set_Etype
(Sel
, Any_Type
);
2416 -- Function calls that are prefixes of selected components must be
2417 -- fully resolved in case we need to build an actual subtype, or
2418 -- do some other operation requiring a fully resolved prefix.
2420 -- Note: Resolving all Nkinds of nodes here doesn't work.
2421 -- (Breaks 2129-008) ???.
2423 if Nkind
(Name
) = N_Function_Call
then
2424 Resolve
(Name
, Etype
(Name
));
2427 Prefix_Type
:= Etype
(Name
);
2430 if Is_Access_Type
(Prefix_Type
) then
2432 -- A RACW object can never be used as prefix of a selected
2433 -- component since that means it is dereferenced without
2434 -- being a controlling operand of a dispatching operation
2437 if Is_Remote_Access_To_Class_Wide_Type
(Prefix_Type
)
2438 and then Comes_From_Source
(N
)
2441 ("invalid dereference of a remote access to class-wide value",
2444 -- Normal case of selected component applied to access type
2447 if Warn_On_Dereference
then
2448 Error_Msg_N
("?implicit dereference", N
);
2452 Prefix_Type
:= Designated_Type
(Prefix_Type
);
2455 if Ekind
(Prefix_Type
) = E_Private_Subtype
then
2456 Prefix_Type
:= Base_Type
(Prefix_Type
);
2459 Entity_List
:= Prefix_Type
;
2461 -- For class-wide types, use the entity list of the root type. This
2462 -- indirection is specially important for private extensions because
2463 -- only the root type get switched (not the class-wide type).
2465 if Is_Class_Wide_Type
(Prefix_Type
) then
2466 Entity_List
:= Root_Type
(Prefix_Type
);
2469 Comp
:= First_Entity
(Entity_List
);
2471 -- If the selector has an original discriminant, the node appears in
2472 -- an instance. Replace the discriminant with the corresponding one
2473 -- in the current discriminated type. For nested generics, this must
2474 -- be done transitively, so note the new original discriminant.
2476 if Nkind
(Sel
) = N_Identifier
2477 and then Present
(Original_Discriminant
(Sel
))
2479 Comp
:= Find_Corresponding_Discriminant
(Sel
, Prefix_Type
);
2481 -- Mark entity before rewriting, for completeness and because
2482 -- subsequent semantic checks might examine the original node.
2484 Set_Entity
(Sel
, Comp
);
2485 Rewrite
(Selector_Name
(N
),
2486 New_Occurrence_Of
(Comp
, Sloc
(N
)));
2487 Set_Original_Discriminant
(Selector_Name
(N
), Comp
);
2488 Set_Etype
(N
, Etype
(Comp
));
2490 if Is_Access_Type
(Etype
(Name
)) then
2491 Insert_Explicit_Dereference
(Name
);
2493 if Warn_On_Dereference
then
2494 Error_Msg_N
("?implicit dereference", N
);
2498 elsif Is_Record_Type
(Prefix_Type
) then
2500 -- Find component with given name
2502 while Present
(Comp
) loop
2504 if Chars
(Comp
) = Chars
(Sel
)
2505 and then Is_Visible_Component
(Comp
)
2507 Set_Entity_With_Style_Check
(Sel
, Comp
);
2508 Generate_Reference
(Comp
, Sel
);
2510 Set_Etype
(Sel
, Etype
(Comp
));
2512 if Ekind
(Comp
) = E_Discriminant
then
2513 if Is_Unchecked_Union
(Prefix_Type
) then
2515 ("cannot reference discriminant of Unchecked_Union",
2519 if Is_Generic_Type
(Prefix_Type
)
2521 Is_Generic_Type
(Root_Type
(Prefix_Type
))
2523 Set_Original_Discriminant
(Sel
, Comp
);
2527 -- Resolve the prefix early otherwise it is not possible to
2528 -- build the actual subtype of the component: it may need
2529 -- to duplicate this prefix and duplication is only allowed
2530 -- on fully resolved expressions.
2532 Resolve
(Name
, Etype
(Name
));
2534 -- We never need an actual subtype for the case of a selection
2535 -- for a indexed component of a non-packed array, since in
2536 -- this case gigi generates all the checks and can find the
2537 -- necessary bounds information.
2539 -- We also do not need an actual subtype for the case of
2540 -- a first, last, length, or range attribute applied to a
2541 -- non-packed array, since gigi can again get the bounds in
2542 -- these cases (gigi cannot handle the packed case, since it
2543 -- has the bounds of the packed array type, not the original
2544 -- bounds of the type). However, if the prefix is itself a
2545 -- selected component, as in a.b.c (i), gigi may regard a.b.c
2546 -- as a dynamic-sized temporary, so we do generate an actual
2547 -- subtype for this case.
2549 Parent_N
:= Parent
(N
);
2551 if not Is_Packed
(Etype
(Comp
))
2553 ((Nkind
(Parent_N
) = N_Indexed_Component
2554 and then Nkind
(Name
) /= N_Selected_Component
)
2556 (Nkind
(Parent_N
) = N_Attribute_Reference
2557 and then (Attribute_Name
(Parent_N
) = Name_First
2559 Attribute_Name
(Parent_N
) = Name_Last
2561 Attribute_Name
(Parent_N
) = Name_Length
2563 Attribute_Name
(Parent_N
) = Name_Range
)))
2565 Set_Etype
(N
, Etype
(Comp
));
2567 -- In all other cases, we currently build an actual subtype. It
2568 -- seems likely that many of these cases can be avoided, but
2569 -- right now, the front end makes direct references to the
2570 -- bounds (e.g. in egnerating a length check), and if we do
2571 -- not make an actual subtype, we end up getting a direct
2572 -- reference to a discriminant which will not do.
2576 Build_Actual_Subtype_Of_Component
(Etype
(Comp
), N
);
2577 Insert_Action
(N
, Act_Decl
);
2579 if No
(Act_Decl
) then
2580 Set_Etype
(N
, Etype
(Comp
));
2583 -- Component type depends on discriminants. Enter the
2584 -- main attributes of the subtype.
2587 Subt
: Entity_Id
:= Defining_Identifier
(Act_Decl
);
2590 Set_Etype
(Subt
, Base_Type
(Etype
(Comp
)));
2591 Set_Ekind
(Subt
, Ekind
(Etype
(Comp
)));
2592 Set_Etype
(N
, Subt
);
2603 elsif Is_Private_Type
(Prefix_Type
) then
2605 -- Allow access only to discriminants of the type. If the
2606 -- type has no full view, gigi uses the parent type for
2607 -- the components, so we do the same here.
2609 if No
(Full_View
(Prefix_Type
)) then
2610 Entity_List
:= Root_Type
(Base_Type
(Prefix_Type
));
2611 Comp
:= First_Entity
(Entity_List
);
2614 while Present
(Comp
) loop
2616 if Chars
(Comp
) = Chars
(Sel
) then
2617 if Ekind
(Comp
) = E_Discriminant
then
2618 Set_Entity_With_Style_Check
(Sel
, Comp
);
2619 Generate_Reference
(Comp
, Sel
);
2621 Set_Etype
(Sel
, Etype
(Comp
));
2622 Set_Etype
(N
, Etype
(Comp
));
2624 if Is_Generic_Type
(Prefix_Type
)
2626 Is_Generic_Type
(Root_Type
(Prefix_Type
))
2628 Set_Original_Discriminant
(Sel
, Comp
);
2633 ("invisible selector for }",
2634 N
, First_Subtype
(Prefix_Type
));
2635 Set_Entity
(Sel
, Any_Id
);
2636 Set_Etype
(N
, Any_Type
);
2645 elsif Is_Concurrent_Type
(Prefix_Type
) then
2647 -- Prefix is concurrent type. Find visible operation with given name
2648 -- For a task, this can only include entries or discriminants if
2649 -- the task type is not an enclosing scope. If it is an enclosing
2650 -- scope (e.g. in an inner task) then all entities are visible, but
2651 -- the prefix must denote the enclosing scope, i.e. can only be
2652 -- a direct name or an expanded name.
2654 Set_Etype
(Sel
, Any_Type
);
2655 In_Scope
:= In_Open_Scopes
(Prefix_Type
);
2657 while Present
(Comp
) loop
2658 if Chars
(Comp
) = Chars
(Sel
) then
2659 if Is_Overloadable
(Comp
) then
2660 Add_One_Interp
(Sel
, Comp
, Etype
(Comp
));
2662 elsif Ekind
(Comp
) = E_Discriminant
2663 or else Ekind
(Comp
) = E_Entry_Family
2665 and then Is_Entity_Name
(Name
))
2667 Set_Entity_With_Style_Check
(Sel
, Comp
);
2668 Generate_Reference
(Comp
, Sel
);
2674 Set_Etype
(Sel
, Etype
(Comp
));
2675 Set_Etype
(N
, Etype
(Comp
));
2677 if Ekind
(Comp
) = E_Discriminant
then
2678 Set_Original_Discriminant
(Sel
, Comp
);
2681 -- For access type case, introduce explicit deference for
2682 -- more uniform treatment of entry calls.
2684 if Is_Access_Type
(Etype
(Name
)) then
2685 Insert_Explicit_Dereference
(Name
);
2687 if Warn_On_Dereference
then
2688 Error_Msg_N
("?implicit dereference", N
);
2695 exit when not In_Scope
2696 and then Comp
= First_Private_Entity
(Prefix_Type
);
2699 Set_Is_Overloaded
(N
, Is_Overloaded
(Sel
));
2704 Error_Msg_NE
("invalid prefix in selected component&", N
, Sel
);
2707 -- If N still has no type, the component is not defined in the prefix.
2709 if Etype
(N
) = Any_Type
then
2711 -- If the prefix is a single concurrent object, use its name in
2712 -- the error message, rather than that of its anonymous type.
2714 if Is_Concurrent_Type
(Prefix_Type
)
2715 and then Is_Internal_Name
(Chars
(Prefix_Type
))
2716 and then not Is_Derived_Type
(Prefix_Type
)
2717 and then Is_Entity_Name
(Name
)
2720 Error_Msg_Node_2
:= Entity
(Name
);
2721 Error_Msg_NE
("no selector& for&", N
, Sel
);
2723 Check_Misspelled_Selector
(Entity_List
, Sel
);
2725 elsif Is_Generic_Type
(Prefix_Type
)
2726 and then Ekind
(Prefix_Type
) = E_Record_Type_With_Private
2727 and then Prefix_Type
/= Etype
(Prefix_Type
)
2728 and then Is_Record_Type
(Etype
(Prefix_Type
))
2730 -- If this is a derived formal type, the parent may have a
2731 -- different visibility at this point. Try for an inherited
2732 -- component before reporting an error.
2734 Set_Etype
(Prefix
(N
), Etype
(Prefix_Type
));
2735 Analyze_Selected_Component
(N
);
2739 if Ekind
(Prefix_Type
) = E_Record_Subtype
then
2741 -- Check whether this is a component of the base type
2742 -- which is absent from a statically constrained subtype.
2743 -- This will raise constraint error at run-time, but is
2744 -- not a compile-time error. When the selector is illegal
2745 -- for base type as well fall through and generate a
2746 -- compilation error anyway.
2748 Comp
:= First_Component
(Base_Type
(Prefix_Type
));
2750 while Present
(Comp
) loop
2752 if Chars
(Comp
) = Chars
(Sel
)
2753 and then Is_Visible_Component
(Comp
)
2755 Set_Entity_With_Style_Check
(Sel
, Comp
);
2756 Generate_Reference
(Comp
, Sel
);
2757 Set_Etype
(Sel
, Etype
(Comp
));
2758 Set_Etype
(N
, Etype
(Comp
));
2760 -- Emit appropriate message. Gigi will replace the
2761 -- node subsequently with the appropriate Raise.
2763 Apply_Compile_Time_Constraint_Error
2764 (N
, "component not present in }?",
2765 CE_Discriminant_Check_Failed
,
2766 Ent
=> Prefix_Type
, Rep
=> False);
2767 Set_Raises_Constraint_Error
(N
);
2771 Next_Component
(Comp
);
2776 Error_Msg_Node_2
:= First_Subtype
(Prefix_Type
);
2777 Error_Msg_NE
("no selector& for}", N
, Sel
);
2779 Check_Misspelled_Selector
(Entity_List
, Sel
);
2783 Set_Entity
(Sel
, Any_Id
);
2784 Set_Etype
(Sel
, Any_Type
);
2786 end Analyze_Selected_Component
;
2788 ---------------------------
2789 -- Analyze_Short_Circuit --
2790 ---------------------------
2792 procedure Analyze_Short_Circuit
(N
: Node_Id
) is
2793 L
: constant Node_Id
:= Left_Opnd
(N
);
2794 R
: constant Node_Id
:= Right_Opnd
(N
);
2799 Analyze_Expression
(L
);
2800 Analyze_Expression
(R
);
2801 Set_Etype
(N
, Any_Type
);
2803 if not Is_Overloaded
(L
) then
2805 if Root_Type
(Etype
(L
)) = Standard_Boolean
2806 and then Has_Compatible_Type
(R
, Etype
(L
))
2808 Add_One_Interp
(N
, Etype
(L
), Etype
(L
));
2812 Get_First_Interp
(L
, Ind
, It
);
2814 while Present
(It
.Typ
) loop
2815 if Root_Type
(It
.Typ
) = Standard_Boolean
2816 and then Has_Compatible_Type
(R
, It
.Typ
)
2818 Add_One_Interp
(N
, It
.Typ
, It
.Typ
);
2821 Get_Next_Interp
(Ind
, It
);
2825 -- Here we have failed to find an interpretation. Clearly we
2826 -- know that it is not the case that both operands can have
2827 -- an interpretation of Boolean, but this is by far the most
2828 -- likely intended interpretation. So we simply resolve both
2829 -- operands as Booleans, and at least one of these resolutions
2830 -- will generate an error message, and we do not need to give
2831 -- a further error message on the short circuit operation itself.
2833 if Etype
(N
) = Any_Type
then
2834 Resolve
(L
, Standard_Boolean
);
2835 Resolve
(R
, Standard_Boolean
);
2836 Set_Etype
(N
, Standard_Boolean
);
2838 end Analyze_Short_Circuit
;
2844 procedure Analyze_Slice
(N
: Node_Id
) is
2845 P
: constant Node_Id
:= Prefix
(N
);
2846 D
: constant Node_Id
:= Discrete_Range
(N
);
2847 Array_Type
: Entity_Id
;
2849 procedure Analyze_Overloaded_Slice
;
2850 -- If the prefix is overloaded, select those interpretations that
2851 -- yield a one-dimensional array type.
2853 procedure Analyze_Overloaded_Slice
is
2859 Set_Etype
(N
, Any_Type
);
2860 Get_First_Interp
(P
, I
, It
);
2862 while Present
(It
.Nam
) loop
2865 if Is_Access_Type
(Typ
) then
2866 Typ
:= Designated_Type
(Typ
);
2868 if Warn_On_Dereference
then
2869 Error_Msg_N
("?implicit dereference", N
);
2873 if Is_Array_Type
(Typ
)
2874 and then Number_Dimensions
(Typ
) = 1
2875 and then Has_Compatible_Type
(D
, Etype
(First_Index
(Typ
)))
2877 Add_One_Interp
(N
, Typ
, Typ
);
2880 Get_Next_Interp
(I
, It
);
2883 if Etype
(N
) = Any_Type
then
2884 Error_Msg_N
("expect array type in prefix of slice", N
);
2886 end Analyze_Overloaded_Slice
;
2888 -- Start of processing for Analyze_Slice
2891 -- Analyze the prefix if not done already
2893 if No
(Etype
(P
)) then
2899 if Is_Overloaded
(P
) then
2900 Analyze_Overloaded_Slice
;
2903 Array_Type
:= Etype
(P
);
2904 Set_Etype
(N
, Any_Type
);
2906 if Is_Access_Type
(Array_Type
) then
2907 Array_Type
:= Designated_Type
(Array_Type
);
2909 if Warn_On_Dereference
then
2910 Error_Msg_N
("?implicit dereference", N
);
2914 if not Is_Array_Type
(Array_Type
) then
2915 Wrong_Type
(P
, Any_Array
);
2917 elsif Number_Dimensions
(Array_Type
) > 1 then
2919 ("type is not one-dimensional array in slice prefix", N
);
2922 Has_Compatible_Type
(D
, Etype
(First_Index
(Array_Type
)))
2924 Wrong_Type
(D
, Etype
(First_Index
(Array_Type
)));
2927 Set_Etype
(N
, Array_Type
);
2932 -----------------------------
2933 -- Analyze_Type_Conversion --
2934 -----------------------------
2936 procedure Analyze_Type_Conversion
(N
: Node_Id
) is
2937 Expr
: constant Node_Id
:= Expression
(N
);
2941 -- If Conversion_OK is set, then the Etype is already set, and the
2942 -- only processing required is to analyze the expression. This is
2943 -- used to construct certain "illegal" conversions which are not
2944 -- allowed by Ada semantics, but can be handled OK by Gigi, see
2945 -- Sinfo for further details.
2947 if Conversion_OK
(N
) then
2952 -- Otherwise full type analysis is required, as well as some semantic
2953 -- checks to make sure the argument of the conversion is appropriate.
2955 Find_Type
(Subtype_Mark
(N
));
2956 T
:= Entity
(Subtype_Mark
(N
));
2958 Check_Fully_Declared
(T
, N
);
2959 Analyze_Expression
(Expr
);
2960 Validate_Remote_Type_Type_Conversion
(N
);
2962 -- Only remaining step is validity checks on the argument. These
2963 -- are skipped if the conversion does not come from the source.
2965 if not Comes_From_Source
(N
) then
2968 elsif Nkind
(Expr
) = N_Null
then
2969 Error_Msg_N
("argument of conversion cannot be null", N
);
2970 Error_Msg_N
("\use qualified expression instead", N
);
2971 Set_Etype
(N
, Any_Type
);
2973 elsif Nkind
(Expr
) = N_Aggregate
then
2974 Error_Msg_N
("argument of conversion cannot be aggregate", N
);
2975 Error_Msg_N
("\use qualified expression instead", N
);
2977 elsif Nkind
(Expr
) = N_Allocator
then
2978 Error_Msg_N
("argument of conversion cannot be an allocator", N
);
2979 Error_Msg_N
("\use qualified expression instead", N
);
2981 elsif Nkind
(Expr
) = N_String_Literal
then
2982 Error_Msg_N
("argument of conversion cannot be string literal", N
);
2983 Error_Msg_N
("\use qualified expression instead", N
);
2985 elsif Nkind
(Expr
) = N_Character_Literal
then
2989 Error_Msg_N
("argument of conversion cannot be character literal",
2991 Error_Msg_N
("\use qualified expression instead", N
);
2994 elsif Nkind
(Expr
) = N_Attribute_Reference
2996 (Attribute_Name
(Expr
) = Name_Access
or else
2997 Attribute_Name
(Expr
) = Name_Unchecked_Access
or else
2998 Attribute_Name
(Expr
) = Name_Unrestricted_Access
)
3000 Error_Msg_N
("argument of conversion cannot be access", N
);
3001 Error_Msg_N
("\use qualified expression instead", N
);
3004 end Analyze_Type_Conversion
;
3006 ----------------------
3007 -- Analyze_Unary_Op --
3008 ----------------------
3010 procedure Analyze_Unary_Op
(N
: Node_Id
) is
3011 R
: constant Node_Id
:= Right_Opnd
(N
);
3012 Op_Id
: Entity_Id
:= Entity
(N
);
3015 Set_Etype
(N
, Any_Type
);
3016 Candidate_Type
:= Empty
;
3018 Analyze_Expression
(R
);
3020 if Present
(Op_Id
) then
3021 if Ekind
(Op_Id
) = E_Operator
then
3022 Find_Unary_Types
(R
, Op_Id
, N
);
3024 Add_One_Interp
(N
, Op_Id
, Etype
(Op_Id
));
3028 Op_Id
:= Get_Name_Entity_Id
(Chars
(N
));
3030 while Present
(Op_Id
) loop
3032 if Ekind
(Op_Id
) = E_Operator
then
3033 if No
(Next_Entity
(First_Entity
(Op_Id
))) then
3034 Find_Unary_Types
(R
, Op_Id
, N
);
3037 elsif Is_Overloadable
(Op_Id
) then
3038 Analyze_User_Defined_Unary_Op
(N
, Op_Id
);
3041 Op_Id
:= Homonym
(Op_Id
);
3046 end Analyze_Unary_Op
;
3048 ----------------------------------
3049 -- Analyze_Unchecked_Expression --
3050 ----------------------------------
3052 procedure Analyze_Unchecked_Expression
(N
: Node_Id
) is
3054 Analyze
(Expression
(N
), Suppress
=> All_Checks
);
3055 Set_Etype
(N
, Etype
(Expression
(N
)));
3056 Save_Interps
(Expression
(N
), N
);
3057 end Analyze_Unchecked_Expression
;
3059 ---------------------------------------
3060 -- Analyze_Unchecked_Type_Conversion --
3061 ---------------------------------------
3063 procedure Analyze_Unchecked_Type_Conversion
(N
: Node_Id
) is
3065 Find_Type
(Subtype_Mark
(N
));
3066 Analyze_Expression
(Expression
(N
));
3067 Set_Etype
(N
, Entity
(Subtype_Mark
(N
)));
3068 end Analyze_Unchecked_Type_Conversion
;
3070 ------------------------------------
3071 -- Analyze_User_Defined_Binary_Op --
3072 ------------------------------------
3074 procedure Analyze_User_Defined_Binary_Op
3079 -- Only do analysis if the operator Comes_From_Source, since otherwise
3080 -- the operator was generated by the expander, and all such operators
3081 -- always refer to the operators in package Standard.
3083 if Comes_From_Source
(N
) then
3085 F1
: constant Entity_Id
:= First_Formal
(Op_Id
);
3086 F2
: constant Entity_Id
:= Next_Formal
(F1
);
3089 -- Verify that Op_Id is a visible binary function. Note that since
3090 -- we know Op_Id is overloaded, potentially use visible means use
3091 -- visible for sure (RM 9.4(11)).
3093 if Ekind
(Op_Id
) = E_Function
3094 and then Present
(F2
)
3095 and then (Is_Immediately_Visible
(Op_Id
)
3096 or else Is_Potentially_Use_Visible
(Op_Id
))
3097 and then Has_Compatible_Type
(Left_Opnd
(N
), Etype
(F1
))
3098 and then Has_Compatible_Type
(Right_Opnd
(N
), Etype
(F2
))
3100 Add_One_Interp
(N
, Op_Id
, Etype
(Op_Id
));
3102 if Debug_Flag_E
then
3103 Write_Str
("user defined operator ");
3104 Write_Name
(Chars
(Op_Id
));
3105 Write_Str
(" on node ");
3106 Write_Int
(Int
(N
));
3112 end Analyze_User_Defined_Binary_Op
;
3114 -----------------------------------
3115 -- Analyze_User_Defined_Unary_Op --
3116 -----------------------------------
3118 procedure Analyze_User_Defined_Unary_Op
3123 -- Only do analysis if the operator Comes_From_Source, since otherwise
3124 -- the operator was generated by the expander, and all such operators
3125 -- always refer to the operators in package Standard.
3127 if Comes_From_Source
(N
) then
3129 F
: constant Entity_Id
:= First_Formal
(Op_Id
);
3132 -- Verify that Op_Id is a visible unary function. Note that since
3133 -- we know Op_Id is overloaded, potentially use visible means use
3134 -- visible for sure (RM 9.4(11)).
3136 if Ekind
(Op_Id
) = E_Function
3137 and then No
(Next_Formal
(F
))
3138 and then (Is_Immediately_Visible
(Op_Id
)
3139 or else Is_Potentially_Use_Visible
(Op_Id
))
3140 and then Has_Compatible_Type
(Right_Opnd
(N
), Etype
(F
))
3142 Add_One_Interp
(N
, Op_Id
, Etype
(Op_Id
));
3146 end Analyze_User_Defined_Unary_Op
;
3148 ---------------------------
3149 -- Check_Arithmetic_Pair --
3150 ---------------------------
3152 procedure Check_Arithmetic_Pair
3153 (T1
, T2
: Entity_Id
;
3157 Op_Name
: constant Name_Id
:= Chars
(Op_Id
);
3159 function Specific_Type
(T1
, T2
: Entity_Id
) return Entity_Id
;
3160 -- Get specific type (i.e. non-universal type if there is one)
3162 function Specific_Type
(T1
, T2
: Entity_Id
) return Entity_Id
is
3164 if T1
= Universal_Integer
or else T1
= Universal_Real
then
3165 return Base_Type
(T2
);
3167 return Base_Type
(T1
);
3171 -- Start of processing for Check_Arithmetic_Pair
3174 if Op_Name
= Name_Op_Add
or else Op_Name
= Name_Op_Subtract
then
3176 if Is_Numeric_Type
(T1
)
3177 and then Is_Numeric_Type
(T2
)
3178 and then (Covers
(T1
, T2
) or else Covers
(T2
, T1
))
3180 Add_One_Interp
(N
, Op_Id
, Specific_Type
(T1
, T2
));
3183 elsif Op_Name
= Name_Op_Multiply
or else Op_Name
= Name_Op_Divide
then
3185 if Is_Fixed_Point_Type
(T1
)
3186 and then (Is_Fixed_Point_Type
(T2
)
3187 or else T2
= Universal_Real
)
3189 -- If Treat_Fixed_As_Integer is set then the Etype is already set
3190 -- and no further processing is required (this is the case of an
3191 -- operator constructed by Exp_Fixd for a fixed point operation)
3192 -- Otherwise add one interpretation with universal fixed result
3193 -- If the operator is given in functional notation, it comes
3194 -- from source and Fixed_As_Integer cannot apply.
3196 if Nkind
(N
) not in N_Op
3197 or else not Treat_Fixed_As_Integer
(N
) then
3198 Add_One_Interp
(N
, Op_Id
, Universal_Fixed
);
3201 elsif Is_Fixed_Point_Type
(T2
)
3202 and then (Nkind
(N
) not in N_Op
3203 or else not Treat_Fixed_As_Integer
(N
))
3204 and then T1
= Universal_Real
3206 Add_One_Interp
(N
, Op_Id
, Universal_Fixed
);
3208 elsif Is_Numeric_Type
(T1
)
3209 and then Is_Numeric_Type
(T2
)
3210 and then (Covers
(T1
, T2
) or else Covers
(T2
, T1
))
3212 Add_One_Interp
(N
, Op_Id
, Specific_Type
(T1
, T2
));
3214 elsif Is_Fixed_Point_Type
(T1
)
3215 and then (Base_Type
(T2
) = Base_Type
(Standard_Integer
)
3216 or else T2
= Universal_Integer
)
3218 Add_One_Interp
(N
, Op_Id
, T1
);
3220 elsif T2
= Universal_Real
3221 and then Base_Type
(T1
) = Base_Type
(Standard_Integer
)
3222 and then Op_Name
= Name_Op_Multiply
3224 Add_One_Interp
(N
, Op_Id
, Any_Fixed
);
3226 elsif T1
= Universal_Real
3227 and then Base_Type
(T2
) = Base_Type
(Standard_Integer
)
3229 Add_One_Interp
(N
, Op_Id
, Any_Fixed
);
3231 elsif Is_Fixed_Point_Type
(T2
)
3232 and then (Base_Type
(T1
) = Base_Type
(Standard_Integer
)
3233 or else T1
= Universal_Integer
)
3234 and then Op_Name
= Name_Op_Multiply
3236 Add_One_Interp
(N
, Op_Id
, T2
);
3238 elsif T1
= Universal_Real
and then T2
= Universal_Integer
then
3239 Add_One_Interp
(N
, Op_Id
, T1
);
3241 elsif T2
= Universal_Real
3242 and then T1
= Universal_Integer
3243 and then Op_Name
= Name_Op_Multiply
3245 Add_One_Interp
(N
, Op_Id
, T2
);
3248 elsif Op_Name
= Name_Op_Mod
or else Op_Name
= Name_Op_Rem
then
3250 -- Note: The fixed-point operands case with Treat_Fixed_As_Integer
3251 -- set does not require any special processing, since the Etype is
3252 -- already set (case of operation constructed by Exp_Fixed).
3254 if Is_Integer_Type
(T1
)
3255 and then (Covers
(T1
, T2
) or else Covers
(T2
, T1
))
3257 Add_One_Interp
(N
, Op_Id
, Specific_Type
(T1
, T2
));
3260 elsif Op_Name
= Name_Op_Expon
then
3262 if Is_Numeric_Type
(T1
)
3263 and then not Is_Fixed_Point_Type
(T1
)
3264 and then (Base_Type
(T2
) = Base_Type
(Standard_Integer
)
3265 or else T2
= Universal_Integer
)
3267 Add_One_Interp
(N
, Op_Id
, Base_Type
(T1
));
3270 else pragma Assert
(Nkind
(N
) in N_Op_Shift
);
3272 -- If not one of the predefined operators, the node may be one
3273 -- of the intrinsic functions. Its kind is always specific, and
3274 -- we can use it directly, rather than the name of the operation.
3276 if Is_Integer_Type
(T1
)
3277 and then (Base_Type
(T2
) = Base_Type
(Standard_Integer
)
3278 or else T2
= Universal_Integer
)
3280 Add_One_Interp
(N
, Op_Id
, Base_Type
(T1
));
3283 end Check_Arithmetic_Pair
;
3285 -------------------------------
3286 -- Check_Misspelled_Selector --
3287 -------------------------------
3289 procedure Check_Misspelled_Selector
3290 (Prefix
: Entity_Id
;
3293 Max_Suggestions
: constant := 2;
3294 Nr_Of_Suggestions
: Natural := 0;
3296 Suggestion_1
: Entity_Id
:= Empty
;
3297 Suggestion_2
: Entity_Id
:= Empty
;
3302 -- All the components of the prefix of selector Sel are matched
3303 -- against Sel and a count is maintained of possible misspellings.
3304 -- When at the end of the analysis there are one or two (not more!)
3305 -- possible misspellings, these misspellings will be suggested as
3306 -- possible correction.
3308 if not (Is_Private_Type
(Prefix
) or Is_Record_Type
(Prefix
)) then
3309 -- Concurrent types should be handled as well ???
3313 Get_Name_String
(Chars
(Sel
));
3316 S
: constant String (1 .. Name_Len
) :=
3317 Name_Buffer
(1 .. Name_Len
);
3320 Comp
:= First_Entity
(Prefix
);
3322 while Nr_Of_Suggestions
<= Max_Suggestions
3323 and then Present
(Comp
)
3326 if Is_Visible_Component
(Comp
) then
3327 Get_Name_String
(Chars
(Comp
));
3329 if Is_Bad_Spelling_Of
(Name_Buffer
(1 .. Name_Len
), S
) then
3330 Nr_Of_Suggestions
:= Nr_Of_Suggestions
+ 1;
3332 case Nr_Of_Suggestions
is
3333 when 1 => Suggestion_1
:= Comp
;
3334 when 2 => Suggestion_2
:= Comp
;
3335 when others => exit;
3340 Comp
:= Next_Entity
(Comp
);
3343 -- Report at most two suggestions
3345 if Nr_Of_Suggestions
= 1 then
3346 Error_Msg_NE
("\possible misspelling of&", Sel
, Suggestion_1
);
3348 elsif Nr_Of_Suggestions
= 2 then
3349 Error_Msg_Node_2
:= Suggestion_2
;
3350 Error_Msg_NE
("\possible misspelling of& or&",
3354 end Check_Misspelled_Selector
;
3356 ----------------------
3357 -- Defined_In_Scope --
3358 ----------------------
3360 function Defined_In_Scope
(T
: Entity_Id
; S
: Entity_Id
) return Boolean
3362 S1
: constant Entity_Id
:= Scope
(Base_Type
(T
));
3366 or else (S1
= System_Aux_Id
and then S
= Scope
(S1
));
3367 end Defined_In_Scope
;
3373 procedure Diagnose_Call
(N
: Node_Id
; Nam
: Node_Id
) is
3380 if Extensions_Allowed
then
3381 Actual
:= First_Actual
(N
);
3383 while Present
(Actual
) loop
3384 if not Analyzed
(Etype
(Actual
))
3385 and then From_With_Type
(Etype
(Actual
))
3387 Error_Msg_Qual_Level
:= 1;
3389 ("missing with_clause for scope of imported type&",
3390 Actual
, Etype
(Actual
));
3391 Error_Msg_Qual_Level
:= 0;
3394 Next_Actual
(Actual
);
3398 if All_Errors_Mode
then
3400 -- Analyze each candidate call again, with full error reporting
3403 Error_Msg_N
("\no candidate interpretations "
3404 & "match the actuals:!", Nam
);
3406 Get_First_Interp
(Nam
, X
, It
);
3408 while Present
(It
.Nam
) loop
3409 Analyze_One_Call
(N
, It
.Nam
, True, Success
);
3410 Get_Next_Interp
(X
, It
);
3416 ("invalid parameter list in call " &
3417 "('/'R'E'P'O'R'T'_'E'R'R'O'R'S'='F'U'L'L for details)!",
3421 ("invalid parameter list in call (use -gnatf for details)!",
3426 if Nkind
(N
) = N_Function_Call
then
3427 Get_First_Interp
(Nam
, X
, It
);
3429 while Present
(It
.Nam
) loop
3430 if Ekind
(It
.Nam
) = E_Function
3431 or else Ekind
(It
.Nam
) = E_Operator
3435 Get_Next_Interp
(X
, It
);
3439 -- If all interpretations are procedures, this deserves a
3440 -- more precise message. Ditto if this appears as the prefix
3441 -- of a selected component, which may be a lexical error.
3444 "\context requires function call, found procedure name", Nam
);
3446 if Nkind
(Parent
(N
)) = N_Selected_Component
3447 and then N
= Prefix
(Parent
(N
))
3450 "\period should probably be semicolon", Parent
(N
));
3455 ---------------------------
3456 -- Find_Arithmetic_Types --
3457 ---------------------------
3459 procedure Find_Arithmetic_Types
3464 Index1
, Index2
: Interp_Index
;
3467 procedure Check_Right_Argument
(T
: Entity_Id
);
3468 -- Check right operand of operator
3470 procedure Check_Right_Argument
(T
: Entity_Id
) is
3472 if not Is_Overloaded
(R
) then
3473 Check_Arithmetic_Pair
(T
, Etype
(R
), Op_Id
, N
);
3475 Get_First_Interp
(R
, Index2
, It2
);
3477 while Present
(It2
.Typ
) loop
3478 Check_Arithmetic_Pair
(T
, It2
.Typ
, Op_Id
, N
);
3479 Get_Next_Interp
(Index2
, It2
);
3482 end Check_Right_Argument
;
3484 -- Start processing for Find_Arithmetic_Types
3487 if not Is_Overloaded
(L
) then
3488 Check_Right_Argument
(Etype
(L
));
3491 Get_First_Interp
(L
, Index1
, It1
);
3493 while Present
(It1
.Typ
) loop
3494 Check_Right_Argument
(It1
.Typ
);
3495 Get_Next_Interp
(Index1
, It1
);
3499 end Find_Arithmetic_Types
;
3501 ------------------------
3502 -- Find_Boolean_Types --
3503 ------------------------
3505 procedure Find_Boolean_Types
3510 Index
: Interp_Index
;
3513 procedure Check_Numeric_Argument
(T
: Entity_Id
);
3514 -- Special case for logical operations one of whose operands is an
3515 -- integer literal. If both are literal the result is any modular type.
3517 procedure Check_Numeric_Argument
(T
: Entity_Id
) is
3519 if T
= Universal_Integer
then
3520 Add_One_Interp
(N
, Op_Id
, Any_Modular
);
3522 elsif Is_Modular_Integer_Type
(T
) then
3523 Add_One_Interp
(N
, Op_Id
, T
);
3525 end Check_Numeric_Argument
;
3527 -- Start of processing for Find_Boolean_Types
3530 if not Is_Overloaded
(L
) then
3532 if Etype
(L
) = Universal_Integer
3533 or else Etype
(L
) = Any_Modular
3535 if not Is_Overloaded
(R
) then
3536 Check_Numeric_Argument
(Etype
(R
));
3539 Get_First_Interp
(R
, Index
, It
);
3541 while Present
(It
.Typ
) loop
3542 Check_Numeric_Argument
(It
.Typ
);
3544 Get_Next_Interp
(Index
, It
);
3548 elsif Valid_Boolean_Arg
(Etype
(L
))
3549 and then Has_Compatible_Type
(R
, Etype
(L
))
3551 Add_One_Interp
(N
, Op_Id
, Etype
(L
));
3555 Get_First_Interp
(L
, Index
, It
);
3557 while Present
(It
.Typ
) loop
3558 if Valid_Boolean_Arg
(It
.Typ
)
3559 and then Has_Compatible_Type
(R
, It
.Typ
)
3561 Add_One_Interp
(N
, Op_Id
, It
.Typ
);
3564 Get_Next_Interp
(Index
, It
);
3567 end Find_Boolean_Types
;
3569 ---------------------------
3570 -- Find_Comparison_Types --
3571 ---------------------------
3573 procedure Find_Comparison_Types
3578 Index
: Interp_Index
;
3580 Found
: Boolean := False;
3583 Scop
: Entity_Id
:= Empty
;
3585 procedure Try_One_Interp
(T1
: Entity_Id
);
3586 -- Routine to try one proposed interpretation. Note that the context
3587 -- of the operator plays no role in resolving the arguments, so that
3588 -- if there is more than one interpretation of the operands that is
3589 -- compatible with comparison, the operation is ambiguous.
3591 procedure Try_One_Interp
(T1
: Entity_Id
) is
3594 -- If the operator is an expanded name, then the type of the operand
3595 -- must be defined in the corresponding scope. If the type is
3596 -- universal, the context will impose the correct type.
3599 and then not Defined_In_Scope
(T1
, Scop
)
3600 and then T1
/= Universal_Integer
3601 and then T1
/= Universal_Real
3602 and then T1
/= Any_String
3603 and then T1
/= Any_Composite
3608 if Valid_Comparison_Arg
(T1
)
3609 and then Has_Compatible_Type
(R
, T1
)
3612 and then Base_Type
(T1
) /= Base_Type
(T_F
)
3614 It
:= Disambiguate
(L
, I_F
, Index
, Any_Type
);
3616 if It
= No_Interp
then
3617 Ambiguous_Operands
(N
);
3618 Set_Etype
(L
, Any_Type
);
3632 Find_Non_Universal_Interpretations
(N
, R
, Op_Id
, T1
);
3637 -- Start processing for Find_Comparison_Types
3641 if Nkind
(N
) = N_Function_Call
3642 and then Nkind
(Name
(N
)) = N_Expanded_Name
3644 Scop
:= Entity
(Prefix
(Name
(N
)));
3646 -- The prefix may be a package renaming, and the subsequent test
3647 -- requires the original package.
3649 if Ekind
(Scop
) = E_Package
3650 and then Present
(Renamed_Entity
(Scop
))
3652 Scop
:= Renamed_Entity
(Scop
);
3653 Set_Entity
(Prefix
(Name
(N
)), Scop
);
3657 if not Is_Overloaded
(L
) then
3658 Try_One_Interp
(Etype
(L
));
3661 Get_First_Interp
(L
, Index
, It
);
3663 while Present
(It
.Typ
) loop
3664 Try_One_Interp
(It
.Typ
);
3665 Get_Next_Interp
(Index
, It
);
3668 end Find_Comparison_Types
;
3670 ----------------------------------------
3671 -- Find_Non_Universal_Interpretations --
3672 ----------------------------------------
3674 procedure Find_Non_Universal_Interpretations
3680 Index
: Interp_Index
;
3684 if T1
= Universal_Integer
3685 or else T1
= Universal_Real
3687 if not Is_Overloaded
(R
) then
3689 (N
, Op_Id
, Standard_Boolean
, Base_Type
(Etype
(R
)));
3691 Get_First_Interp
(R
, Index
, It
);
3693 while Present
(It
.Typ
) loop
3694 if Covers
(It
.Typ
, T1
) then
3696 (N
, Op_Id
, Standard_Boolean
, Base_Type
(It
.Typ
));
3699 Get_Next_Interp
(Index
, It
);
3703 Add_One_Interp
(N
, Op_Id
, Standard_Boolean
, Base_Type
(T1
));
3705 end Find_Non_Universal_Interpretations
;
3707 ------------------------------
3708 -- Find_Concatenation_Types --
3709 ------------------------------
3711 procedure Find_Concatenation_Types
3716 Op_Type
: constant Entity_Id
:= Etype
(Op_Id
);
3719 if Is_Array_Type
(Op_Type
)
3720 and then not Is_Limited_Type
(Op_Type
)
3722 and then (Has_Compatible_Type
(L
, Op_Type
)
3724 Has_Compatible_Type
(L
, Component_Type
(Op_Type
)))
3726 and then (Has_Compatible_Type
(R
, Op_Type
)
3728 Has_Compatible_Type
(R
, Component_Type
(Op_Type
)))
3730 Add_One_Interp
(N
, Op_Id
, Op_Type
);
3732 end Find_Concatenation_Types
;
3734 -------------------------
3735 -- Find_Equality_Types --
3736 -------------------------
3738 procedure Find_Equality_Types
3743 Index
: Interp_Index
;
3745 Found
: Boolean := False;
3748 Scop
: Entity_Id
:= Empty
;
3750 procedure Try_One_Interp
(T1
: Entity_Id
);
3751 -- The context of the operator plays no role in resolving the
3752 -- arguments, so that if there is more than one interpretation
3753 -- of the operands that is compatible with equality, the construct
3754 -- is ambiguous and an error can be emitted now, after trying to
3755 -- disambiguate, i.e. applying preference rules.
3757 procedure Try_One_Interp
(T1
: Entity_Id
) is
3760 -- If the operator is an expanded name, then the type of the operand
3761 -- must be defined in the corresponding scope. If the type is
3762 -- universal, the context will impose the correct type. An anonymous
3763 -- type for a 'Access reference is also universal in this sense, as
3764 -- the actual type is obtained from context.
3767 and then not Defined_In_Scope
(T1
, Scop
)
3768 and then T1
/= Universal_Integer
3769 and then T1
/= Universal_Real
3770 and then T1
/= Any_Access
3771 and then T1
/= Any_String
3772 and then T1
/= Any_Composite
3773 and then (Ekind
(T1
) /= E_Access_Subprogram_Type
3774 or else Comes_From_Source
(T1
))
3779 if T1
/= Standard_Void_Type
3780 and then not Is_Limited_Type
(T1
)
3781 and then not Is_Limited_Composite
(T1
)
3782 and then Ekind
(T1
) /= E_Anonymous_Access_Type
3783 and then Has_Compatible_Type
(R
, T1
)
3786 and then Base_Type
(T1
) /= Base_Type
(T_F
)
3788 It
:= Disambiguate
(L
, I_F
, Index
, Any_Type
);
3790 if It
= No_Interp
then
3791 Ambiguous_Operands
(N
);
3792 Set_Etype
(L
, Any_Type
);
3805 if not Analyzed
(L
) then
3809 Find_Non_Universal_Interpretations
(N
, R
, Op_Id
, T1
);
3811 if Etype
(N
) = Any_Type
then
3813 -- Operator was not visible.
3820 -- Start of processing for Find_Equality_Types
3824 if Nkind
(N
) = N_Function_Call
3825 and then Nkind
(Name
(N
)) = N_Expanded_Name
3827 Scop
:= Entity
(Prefix
(Name
(N
)));
3829 -- The prefix may be a package renaming, and the subsequent test
3830 -- requires the original package.
3832 if Ekind
(Scop
) = E_Package
3833 and then Present
(Renamed_Entity
(Scop
))
3835 Scop
:= Renamed_Entity
(Scop
);
3836 Set_Entity
(Prefix
(Name
(N
)), Scop
);
3840 if not Is_Overloaded
(L
) then
3841 Try_One_Interp
(Etype
(L
));
3844 Get_First_Interp
(L
, Index
, It
);
3846 while Present
(It
.Typ
) loop
3847 Try_One_Interp
(It
.Typ
);
3848 Get_Next_Interp
(Index
, It
);
3851 end Find_Equality_Types
;
3853 -------------------------
3854 -- Find_Negation_Types --
3855 -------------------------
3857 procedure Find_Negation_Types
3862 Index
: Interp_Index
;
3866 if not Is_Overloaded
(R
) then
3868 if Etype
(R
) = Universal_Integer
then
3869 Add_One_Interp
(N
, Op_Id
, Any_Modular
);
3871 elsif Valid_Boolean_Arg
(Etype
(R
)) then
3872 Add_One_Interp
(N
, Op_Id
, Etype
(R
));
3876 Get_First_Interp
(R
, Index
, It
);
3878 while Present
(It
.Typ
) loop
3879 if Valid_Boolean_Arg
(It
.Typ
) then
3880 Add_One_Interp
(N
, Op_Id
, It
.Typ
);
3883 Get_Next_Interp
(Index
, It
);
3886 end Find_Negation_Types
;
3888 ----------------------
3889 -- Find_Unary_Types --
3890 ----------------------
3892 procedure Find_Unary_Types
3897 Index
: Interp_Index
;
3901 if not Is_Overloaded
(R
) then
3902 if Is_Numeric_Type
(Etype
(R
)) then
3903 Add_One_Interp
(N
, Op_Id
, Base_Type
(Etype
(R
)));
3907 Get_First_Interp
(R
, Index
, It
);
3909 while Present
(It
.Typ
) loop
3910 if Is_Numeric_Type
(It
.Typ
) then
3911 Add_One_Interp
(N
, Op_Id
, Base_Type
(It
.Typ
));
3914 Get_Next_Interp
(Index
, It
);
3917 end Find_Unary_Types
;
3919 ---------------------------------
3920 -- Insert_Explicit_Dereference --
3921 ---------------------------------
3923 procedure Insert_Explicit_Dereference
(N
: Node_Id
) is
3924 New_Prefix
: Node_Id
:= Relocate_Node
(N
);
3930 Save_Interps
(N
, New_Prefix
);
3932 Make_Explicit_Dereference
(Sloc
(N
), Prefix
=> New_Prefix
));
3934 Set_Etype
(N
, Designated_Type
(Etype
(New_Prefix
)));
3936 if Is_Overloaded
(New_Prefix
) then
3938 -- The deference is also overloaded, and its interpretations are the
3939 -- designated types of the interpretations of the original node.
3941 Set_Is_Overloaded
(N
);
3942 Get_First_Interp
(New_Prefix
, I
, It
);
3944 while Present
(It
.Nam
) loop
3947 if Is_Access_Type
(T
) then
3948 Add_One_Interp
(N
, Designated_Type
(T
), Designated_Type
(T
));
3951 Get_Next_Interp
(I
, It
);
3957 end Insert_Explicit_Dereference
;
3963 function Junk_Operand
(N
: Node_Id
) return Boolean is
3967 if Error_Posted
(N
) then
3971 -- Get entity to be tested
3973 if Is_Entity_Name
(N
)
3974 and then Present
(Entity
(N
))
3978 -- An odd case, a procedure name gets converted to a very peculiar
3979 -- function call, and here is where we detect this happening.
3981 elsif Nkind
(N
) = N_Function_Call
3982 and then Is_Entity_Name
(Name
(N
))
3983 and then Present
(Entity
(Name
(N
)))
3987 -- Another odd case, there are at least some cases of selected
3988 -- components where the selected component is not marked as having
3989 -- an entity, even though the selector does have an entity
3991 elsif Nkind
(N
) = N_Selected_Component
3992 and then Present
(Entity
(Selector_Name
(N
)))
3994 Enode
:= Selector_Name
(N
);
4000 -- Now test the entity we got to see if it a bad case
4002 case Ekind
(Entity
(Enode
)) is
4006 ("package name cannot be used as operand", Enode
);
4008 when Generic_Unit_Kind
=>
4010 ("generic unit name cannot be used as operand", Enode
);
4014 ("subtype name cannot be used as operand", Enode
);
4018 ("entry name cannot be used as operand", Enode
);
4022 ("procedure name cannot be used as operand", Enode
);
4026 ("exception name cannot be used as operand", Enode
);
4028 when E_Block | E_Label | E_Loop
=>
4030 ("label name cannot be used as operand", Enode
);
4040 --------------------
4041 -- Operator_Check --
4042 --------------------
4044 procedure Operator_Check
(N
: Node_Id
) is
4046 -- Test for case of no interpretation found for operator
4048 if Etype
(N
) = Any_Type
then
4054 R
:= Right_Opnd
(N
);
4056 if Nkind
(N
) in N_Binary_Op
then
4062 -- If either operand has no type, then don't complain further,
4063 -- since this simply means that we have a propragated error.
4066 or else Etype
(R
) = Any_Type
4067 or else (Nkind
(N
) in N_Binary_Op
and then Etype
(L
) = Any_Type
)
4071 -- We explicitly check for the case of concatenation of
4072 -- component with component to avoid reporting spurious
4073 -- matching array types that might happen to be lurking
4074 -- in distant packages (such as run-time packages). This
4075 -- also prevents inconsistencies in the messages for certain
4076 -- ACVC B tests, which can vary depending on types declared
4077 -- in run-time interfaces. A further improvement, when
4078 -- aggregates are present, is to look for a well-typed operand.
4080 elsif Present
(Candidate_Type
)
4081 and then (Nkind
(N
) /= N_Op_Concat
4082 or else Is_Array_Type
(Etype
(L
))
4083 or else Is_Array_Type
(Etype
(R
)))
4086 if Nkind
(N
) = N_Op_Concat
then
4087 if Etype
(L
) /= Any_Composite
4088 and then Is_Array_Type
(Etype
(L
))
4090 Candidate_Type
:= Etype
(L
);
4092 elsif Etype
(R
) /= Any_Composite
4093 and then Is_Array_Type
(Etype
(R
))
4095 Candidate_Type
:= Etype
(R
);
4100 ("operator for} is not directly visible!",
4101 N
, First_Subtype
(Candidate_Type
));
4102 Error_Msg_N
("use clause would make operation legal!", N
);
4105 -- If either operand is a junk operand (e.g. package name), then
4106 -- post appropriate error messages, but do not complain further.
4108 -- Note that the use of OR in this test instead of OR ELSE
4109 -- is quite deliberate, we may as well check both operands
4110 -- in the binary operator case.
4112 elsif Junk_Operand
(R
)
4113 or (Nkind
(N
) in N_Binary_Op
and then Junk_Operand
(L
))
4117 -- If we have a logical operator, one of whose operands is
4118 -- Boolean, then we know that the other operand cannot resolve
4119 -- to Boolean (since we got no interpretations), but in that
4120 -- case we pretty much know that the other operand should be
4121 -- Boolean, so resolve it that way (generating an error)
4123 elsif Nkind
(N
) = N_Op_And
4127 Nkind
(N
) = N_Op_Xor
4129 if Etype
(L
) = Standard_Boolean
then
4130 Resolve
(R
, Standard_Boolean
);
4132 elsif Etype
(R
) = Standard_Boolean
then
4133 Resolve
(L
, Standard_Boolean
);
4137 -- For an arithmetic operator or comparison operator, if one
4138 -- of the operands is numeric, then we know the other operand
4139 -- is not the same numeric type. If it is a non-numeric type,
4140 -- then probably it is intended to match the other operand.
4142 elsif Nkind
(N
) = N_Op_Add
or else
4143 Nkind
(N
) = N_Op_Divide
or else
4144 Nkind
(N
) = N_Op_Ge
or else
4145 Nkind
(N
) = N_Op_Gt
or else
4146 Nkind
(N
) = N_Op_Le
or else
4147 Nkind
(N
) = N_Op_Lt
or else
4148 Nkind
(N
) = N_Op_Mod
or else
4149 Nkind
(N
) = N_Op_Multiply
or else
4150 Nkind
(N
) = N_Op_Rem
or else
4151 Nkind
(N
) = N_Op_Subtract
4153 if Is_Numeric_Type
(Etype
(L
))
4154 and then not Is_Numeric_Type
(Etype
(R
))
4156 Resolve
(R
, Etype
(L
));
4159 elsif Is_Numeric_Type
(Etype
(R
))
4160 and then not Is_Numeric_Type
(Etype
(L
))
4162 Resolve
(L
, Etype
(R
));
4166 -- Comparisons on A'Access are common enough to deserve a
4169 elsif (Nkind
(N
) = N_Op_Eq
or else
4170 Nkind
(N
) = N_Op_Ne
)
4171 and then Ekind
(Etype
(L
)) = E_Access_Attribute_Type
4172 and then Ekind
(Etype
(R
)) = E_Access_Attribute_Type
4175 ("two access attributes cannot be compared directly", N
);
4177 ("\they must be converted to an explicit type for comparison",
4181 -- Another one for C programmers
4183 elsif Nkind
(N
) = N_Op_Concat
4184 and then Valid_Boolean_Arg
(Etype
(L
))
4185 and then Valid_Boolean_Arg
(Etype
(R
))
4187 Error_Msg_N
("invalid operands for concatenation", N
);
4188 Error_Msg_N
("\maybe AND was meant", N
);
4191 -- A special case for comparison of access parameter with null
4193 elsif Nkind
(N
) = N_Op_Eq
4194 and then Is_Entity_Name
(L
)
4195 and then Nkind
(Parent
(Entity
(L
))) = N_Parameter_Specification
4196 and then Nkind
(Parameter_Type
(Parent
(Entity
(L
)))) =
4198 and then Nkind
(R
) = N_Null
4200 Error_Msg_N
("access parameter is not allowed to be null", L
);
4201 Error_Msg_N
("\(call would raise Constraint_Error)", L
);
4205 -- If we fall through then just give general message. Note
4206 -- that in the following messages, if the operand is overloaded
4207 -- we choose an arbitrary type to complain about, but that is
4208 -- probably more useful than not giving a type at all.
4210 if Nkind
(N
) in N_Unary_Op
then
4211 Error_Msg_Node_2
:= Etype
(R
);
4212 Error_Msg_N
("operator& not defined for}", N
);
4216 Error_Msg_N
("invalid operand types for operator&", N
);
4218 if Nkind
(N
) in N_Binary_Op
4219 and then Nkind
(N
) /= N_Op_Concat
4221 Error_Msg_NE
("\left operand has}!", N
, Etype
(L
));
4222 Error_Msg_NE
("\right operand has}!", N
, Etype
(R
));
4229 -----------------------
4230 -- Try_Indirect_Call --
4231 -----------------------
4233 function Try_Indirect_Call
4239 Actuals
: List_Id
:= Parameter_Associations
(N
);
4240 Actual
: Node_Id
:= First
(Actuals
);
4241 Formal
: Entity_Id
:= First_Formal
(Designated_Type
(Typ
));
4244 while Present
(Actual
)
4245 and then Present
(Formal
)
4247 if not Has_Compatible_Type
(Actual
, Etype
(Formal
)) then
4252 Next_Formal
(Formal
);
4255 if No
(Actual
) and then No
(Formal
) then
4256 Add_One_Interp
(N
, Nam
, Etype
(Designated_Type
(Typ
)));
4258 -- Nam is a candidate interpretation for the name in the call,
4259 -- if it is not an indirect call.
4261 if not Is_Type
(Nam
)
4262 and then Is_Entity_Name
(Name
(N
))
4264 Set_Entity
(Name
(N
), Nam
);
4271 end Try_Indirect_Call
;
4273 ----------------------
4274 -- Try_Indexed_Call --
4275 ----------------------
4277 function Try_Indexed_Call
4283 Actuals
: List_Id
:= Parameter_Associations
(N
);
4284 Actual
: Node_Id
:= First
(Actuals
);
4285 Index
: Entity_Id
:= First_Index
(Typ
);
4288 while Present
(Actual
)
4289 and then Present
(Index
)
4291 -- If the parameter list has a named association, the expression
4292 -- is definitely a call and not an indexed component.
4294 if Nkind
(Actual
) = N_Parameter_Association
then
4298 if not Has_Compatible_Type
(Actual
, Etype
(Index
)) then
4306 if No
(Actual
) and then No
(Index
) then
4307 Add_One_Interp
(N
, Nam
, Component_Type
(Typ
));
4309 -- Nam is a candidate interpretation for the name in the call,
4310 -- if it is not an indirect call.
4312 if not Is_Type
(Nam
)
4313 and then Is_Entity_Name
(Name
(N
))
4315 Set_Entity
(Name
(N
), Nam
);
4323 end Try_Indexed_Call
;