1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 1992-2005, Free Software Foundation, Inc. --
11 -- GNAT is free software; you can redistribute it and/or modify it under --
12 -- terms of the GNU General Public License as published by the Free Soft- --
13 -- ware Foundation; either version 2, or (at your option) any later ver- --
14 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
17 -- for more details. You should have received a copy of the GNU General --
18 -- Public License distributed with GNAT; see file COPYING. If not, write --
19 -- to the Free Software Foundation, 51 Franklin Street, Fifth Floor, --
20 -- Boston, MA 02110-1301, 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
;
29 with Debug
; use Debug
;
30 with Einfo
; use Einfo
;
31 with Elists
; use Elists
;
32 with Nlists
; use Nlists
;
33 with Errout
; use Errout
;
36 with Output
; use Output
;
38 with Sem_Ch6
; use Sem_Ch6
;
39 with Sem_Ch8
; use Sem_Ch8
;
40 with Sem_Util
; use Sem_Util
;
41 with Stand
; use Stand
;
42 with Sinfo
; use Sinfo
;
43 with Snames
; use Snames
;
45 with Uintp
; use Uintp
;
47 package body Sem_Type
is
53 -- The following data structures establish a mapping between nodes and
54 -- their interpretations. An overloaded node has an entry in Interp_Map,
55 -- which in turn contains a pointer into the All_Interp array. The
56 -- interpretations of a given node are contiguous in All_Interp. Each
57 -- set of interpretations is terminated with the marker No_Interp.
58 -- In order to speed up the retrieval of the interpretations of an
59 -- overloaded node, the Interp_Map table is accessed by means of a simple
60 -- hashing scheme, and the entries in Interp_Map are chained. The heads
61 -- of clash lists are stored in array Headers.
63 -- Headers Interp_Map All_Interp
65 -- _ +-----+ +--------+
66 -- |_| |_____| --->|interp1 |
67 -- |_|---------->|node | | |interp2 |
68 -- |_| |index|---------| |nointerp|
73 -- This scheme does not currently reclaim interpretations. In principle,
74 -- after a unit is compiled, all overloadings have been resolved, and the
75 -- candidate interpretations should be deleted. This should be easier
76 -- now than with the previous scheme???
78 package All_Interp
is new Table
.Table
(
79 Table_Component_Type
=> Interp
,
80 Table_Index_Type
=> Int
,
82 Table_Initial
=> Alloc
.All_Interp_Initial
,
83 Table_Increment
=> Alloc
.All_Interp_Increment
,
84 Table_Name
=> "All_Interp");
86 type Interp_Ref
is record
92 Header_Size
: constant Int
:= 2 ** 12;
93 No_Entry
: constant Int
:= -1;
94 Headers
: array (0 .. Header_Size
) of Int
:= (others => No_Entry
);
96 package Interp_Map
is new Table
.Table
(
97 Table_Component_Type
=> Interp_Ref
,
98 Table_Index_Type
=> Int
,
100 Table_Initial
=> Alloc
.Interp_Map_Initial
,
101 Table_Increment
=> Alloc
.Interp_Map_Increment
,
102 Table_Name
=> "Interp_Map");
104 function Hash
(N
: Node_Id
) return Int
;
105 -- A trivial hashing function for nodes, used to insert an overloaded
106 -- node into the Interp_Map table.
108 -------------------------------------
109 -- Handling of Overload Resolution --
110 -------------------------------------
112 -- Overload resolution uses two passes over the syntax tree of a complete
113 -- context. In the first, bottom-up pass, the types of actuals in calls
114 -- are used to resolve possibly overloaded subprogram and operator names.
115 -- In the second top-down pass, the type of the context (for example the
116 -- condition in a while statement) is used to resolve a possibly ambiguous
117 -- call, and the unique subprogram name in turn imposes a specific context
118 -- on each of its actuals.
120 -- Most expressions are in fact unambiguous, and the bottom-up pass is
121 -- sufficient to resolve most everything. To simplify the common case,
122 -- names and expressions carry a flag Is_Overloaded to indicate whether
123 -- they have more than one interpretation. If the flag is off, then each
124 -- name has already a unique meaning and type, and the bottom-up pass is
125 -- sufficient (and much simpler).
127 --------------------------
128 -- Operator Overloading --
129 --------------------------
131 -- The visibility of operators is handled differently from that of
132 -- other entities. We do not introduce explicit versions of primitive
133 -- operators for each type definition. As a result, there is only one
134 -- entity corresponding to predefined addition on all numeric types, etc.
135 -- The back-end resolves predefined operators according to their type.
136 -- The visibility of primitive operations then reduces to the visibility
137 -- of the resulting type: (a + b) is a legal interpretation of some
138 -- primitive operator + if the type of the result (which must also be
139 -- the type of a and b) is directly visible (i.e. either immediately
140 -- visible or use-visible.)
142 -- User-defined operators are treated like other functions, but the
143 -- visibility of these user-defined operations must be special-cased
144 -- to determine whether they hide or are hidden by predefined operators.
145 -- The form P."+" (x, y) requires additional handling.
147 -- Concatenation is treated more conventionally: for every one-dimensional
148 -- array type we introduce a explicit concatenation operator. This is
149 -- necessary to handle the case of (element & element => array) which
150 -- cannot be handled conveniently if there is no explicit instance of
151 -- resulting type of the operation.
153 -----------------------
154 -- Local Subprograms --
155 -----------------------
157 procedure All_Overloads
;
158 pragma Warnings
(Off
, All_Overloads
);
159 -- Debugging procedure: list full contents of Overloads table
161 procedure New_Interps
(N
: Node_Id
);
162 -- Initialize collection of interpretations for the given node, which is
163 -- either an overloaded entity, or an operation whose arguments have
164 -- multiple interpretations. Interpretations can be added to only one
167 function Specific_Type
(T1
, T2
: Entity_Id
) return Entity_Id
;
168 -- If T1 and T2 are compatible, return the one that is not
169 -- universal or is not a "class" type (any_character, etc).
175 procedure Add_One_Interp
179 Opnd_Type
: Entity_Id
:= Empty
)
181 Vis_Type
: Entity_Id
;
183 procedure Add_Entry
(Name
: Entity_Id
; Typ
: Entity_Id
);
184 -- Add one interpretation to node. Node is already known to be
185 -- overloaded. Add new interpretation if not hidden by previous
186 -- one, and remove previous one if hidden by new one.
188 function Is_Universal_Operation
(Op
: Entity_Id
) return Boolean;
189 -- True if the entity is a predefined operator and the operands have
190 -- a universal Interpretation.
196 procedure Add_Entry
(Name
: Entity_Id
; Typ
: Entity_Id
) is
197 Index
: Interp_Index
;
201 Get_First_Interp
(N
, Index
, It
);
202 while Present
(It
.Nam
) loop
204 -- A user-defined subprogram hides another declared at an outer
205 -- level, or one that is use-visible. So return if previous
206 -- definition hides new one (which is either in an outer
207 -- scope, or use-visible). Note that for functions use-visible
208 -- is the same as potentially use-visible. If new one hides
209 -- previous one, replace entry in table of interpretations.
210 -- If this is a universal operation, retain the operator in case
211 -- preference rule applies.
213 if (((Ekind
(Name
) = E_Function
or else Ekind
(Name
) = E_Procedure
)
214 and then Ekind
(Name
) = Ekind
(It
.Nam
))
215 or else (Ekind
(Name
) = E_Operator
216 and then Ekind
(It
.Nam
) = E_Function
))
218 and then Is_Immediately_Visible
(It
.Nam
)
219 and then Type_Conformant
(Name
, It
.Nam
)
220 and then Base_Type
(It
.Typ
) = Base_Type
(T
)
222 if Is_Universal_Operation
(Name
) then
225 -- If node is an operator symbol, we have no actuals with
226 -- which to check hiding, and this is done in full in the
227 -- caller (Analyze_Subprogram_Renaming) so we include the
228 -- predefined operator in any case.
230 elsif Nkind
(N
) = N_Operator_Symbol
231 or else (Nkind
(N
) = N_Expanded_Name
233 Nkind
(Selector_Name
(N
)) = N_Operator_Symbol
)
237 elsif not In_Open_Scopes
(Scope
(Name
))
238 or else Scope_Depth
(Scope
(Name
)) <=
239 Scope_Depth
(Scope
(It
.Nam
))
241 -- If ambiguity within instance, and entity is not an
242 -- implicit operation, save for later disambiguation.
244 if Scope
(Name
) = Scope
(It
.Nam
)
245 and then not Is_Inherited_Operation
(Name
)
254 All_Interp
.Table
(Index
).Nam
:= Name
;
258 -- Avoid making duplicate entries in overloads
261 and then Base_Type
(It
.Typ
) = Base_Type
(T
)
265 -- Otherwise keep going
268 Get_Next_Interp
(Index
, It
);
273 -- On exit, enter new interpretation. The context, or a preference
274 -- rule, will resolve the ambiguity on the second pass.
276 All_Interp
.Table
(All_Interp
.Last
) := (Name
, Typ
);
277 All_Interp
.Increment_Last
;
278 All_Interp
.Table
(All_Interp
.Last
) := No_Interp
;
281 ----------------------------
282 -- Is_Universal_Operation --
283 ----------------------------
285 function Is_Universal_Operation
(Op
: Entity_Id
) return Boolean is
289 if Ekind
(Op
) /= E_Operator
then
292 elsif Nkind
(N
) in N_Binary_Op
then
293 return Present
(Universal_Interpretation
(Left_Opnd
(N
)))
294 and then Present
(Universal_Interpretation
(Right_Opnd
(N
)));
296 elsif Nkind
(N
) in N_Unary_Op
then
297 return Present
(Universal_Interpretation
(Right_Opnd
(N
)));
299 elsif Nkind
(N
) = N_Function_Call
then
300 Arg
:= First_Actual
(N
);
301 while Present
(Arg
) loop
302 if No
(Universal_Interpretation
(Arg
)) then
314 end Is_Universal_Operation
;
316 -- Start of processing for Add_One_Interp
319 -- If the interpretation is a predefined operator, verify that the
320 -- result type is visible, or that the entity has already been
321 -- resolved (case of an instantiation node that refers to a predefined
322 -- operation, or an internally generated operator node, or an operator
323 -- given as an expanded name). If the operator is a comparison or
324 -- equality, it is the type of the operand that matters to determine
325 -- whether the operator is visible. In an instance, the check is not
326 -- performed, given that the operator was visible in the generic.
328 if Ekind
(E
) = E_Operator
then
330 if Present
(Opnd_Type
) then
331 Vis_Type
:= Opnd_Type
;
333 Vis_Type
:= Base_Type
(T
);
336 if In_Open_Scopes
(Scope
(Vis_Type
))
337 or else Is_Potentially_Use_Visible
(Vis_Type
)
338 or else In_Use
(Vis_Type
)
339 or else (In_Use
(Scope
(Vis_Type
))
340 and then not Is_Hidden
(Vis_Type
))
341 or else Nkind
(N
) = N_Expanded_Name
342 or else (Nkind
(N
) in N_Op
and then E
= Entity
(N
))
347 -- If the node is given in functional notation and the prefix
348 -- is an expanded name, then the operator is visible if the
349 -- prefix is the scope of the result type as well. If the
350 -- operator is (implicitly) defined in an extension of system,
351 -- it is know to be valid (see Defined_In_Scope, sem_ch4.adb).
353 elsif Nkind
(N
) = N_Function_Call
354 and then Nkind
(Name
(N
)) = N_Expanded_Name
355 and then (Entity
(Prefix
(Name
(N
))) = Scope
(Base_Type
(T
))
356 or else Entity
(Prefix
(Name
(N
))) = Scope
(Vis_Type
)
357 or else Scope
(Vis_Type
) = System_Aux_Id
)
361 -- Save type for subsequent error message, in case no other
362 -- interpretation is found.
365 Candidate_Type
:= Vis_Type
;
369 -- In an instance, an abstract non-dispatching operation cannot
370 -- be a candidate interpretation, because it could not have been
371 -- one in the generic (it may be a spurious overloading in the
375 and then Is_Abstract
(E
)
376 and then not Is_Dispatching_Operation
(E
)
380 -- An inherited interface operation that is implemented by some
381 -- derived type does not participate in overload resolution, only
382 -- the implementation operation does.
385 and then Is_Subprogram
(E
)
386 and then Present
(Abstract_Interface_Alias
(E
))
388 Add_One_Interp
(N
, Abstract_Interface_Alias
(E
), T
);
392 -- If this is the first interpretation of N, N has type Any_Type.
393 -- In that case place the new type on the node. If one interpretation
394 -- already exists, indicate that the node is overloaded, and store
395 -- both the previous and the new interpretation in All_Interp. If
396 -- this is a later interpretation, just add it to the set.
398 if Etype
(N
) = Any_Type
then
403 -- Record both the operator or subprogram name, and its type
405 if Nkind
(N
) in N_Op
or else Is_Entity_Name
(N
) then
412 -- Either there is no current interpretation in the table for any
413 -- node or the interpretation that is present is for a different
414 -- node. In both cases add a new interpretation to the table.
416 elsif Interp_Map
.Last
< 0
418 (Interp_Map
.Table
(Interp_Map
.Last
).Node
/= N
419 and then not Is_Overloaded
(N
))
423 if (Nkind
(N
) in N_Op
or else Is_Entity_Name
(N
))
424 and then Present
(Entity
(N
))
426 Add_Entry
(Entity
(N
), Etype
(N
));
428 elsif (Nkind
(N
) = N_Function_Call
429 or else Nkind
(N
) = N_Procedure_Call_Statement
)
430 and then (Nkind
(Name
(N
)) = N_Operator_Symbol
431 or else Is_Entity_Name
(Name
(N
)))
433 Add_Entry
(Entity
(Name
(N
)), Etype
(N
));
436 -- Overloaded prefix in indexed or selected component,
437 -- or call whose name is an expression or another call.
439 Add_Entry
(Etype
(N
), Etype
(N
));
453 procedure All_Overloads
is
455 for J
in All_Interp
.First
.. All_Interp
.Last
loop
457 if Present
(All_Interp
.Table
(J
).Nam
) then
458 Write_Entity_Info
(All_Interp
.Table
(J
). Nam
, " ");
460 Write_Str
("No Interp");
463 Write_Str
("=================");
468 ---------------------
469 -- Collect_Interps --
470 ---------------------
472 procedure Collect_Interps
(N
: Node_Id
) is
473 Ent
: constant Entity_Id
:= Entity
(N
);
475 First_Interp
: Interp_Index
;
480 -- Unconditionally add the entity that was initially matched
482 First_Interp
:= All_Interp
.Last
;
483 Add_One_Interp
(N
, Ent
, Etype
(N
));
485 -- For expanded name, pick up all additional entities from the
486 -- same scope, since these are obviously also visible. Note that
487 -- these are not necessarily contiguous on the homonym chain.
489 if Nkind
(N
) = N_Expanded_Name
then
491 while Present
(H
) loop
492 if Scope
(H
) = Scope
(Entity
(N
)) then
493 Add_One_Interp
(N
, H
, Etype
(H
));
499 -- Case of direct name
502 -- First, search the homonym chain for directly visible entities
504 H
:= Current_Entity
(Ent
);
505 while Present
(H
) loop
506 exit when (not Is_Overloadable
(H
))
507 and then Is_Immediately_Visible
(H
);
509 if Is_Immediately_Visible
(H
)
512 -- Only add interpretation if not hidden by an inner
513 -- immediately visible one.
515 for J
in First_Interp
.. All_Interp
.Last
- 1 loop
517 -- Current homograph is not hidden. Add to overloads
519 if not Is_Immediately_Visible
(All_Interp
.Table
(J
).Nam
) then
522 -- Homograph is hidden, unless it is a predefined operator
524 elsif Type_Conformant
(H
, All_Interp
.Table
(J
).Nam
) then
526 -- A homograph in the same scope can occur within an
527 -- instantiation, the resulting ambiguity has to be
530 if Scope
(H
) = Scope
(Ent
)
532 and then not Is_Inherited_Operation
(H
)
534 All_Interp
.Table
(All_Interp
.Last
) := (H
, Etype
(H
));
535 All_Interp
.Increment_Last
;
536 All_Interp
.Table
(All_Interp
.Last
) := No_Interp
;
539 elsif Scope
(H
) /= Standard_Standard
then
545 -- On exit, we know that current homograph is not hidden
547 Add_One_Interp
(N
, H
, Etype
(H
));
550 Write_Str
("Add overloaded Interpretation ");
560 -- Scan list of homographs for use-visible entities only
562 H
:= Current_Entity
(Ent
);
564 while Present
(H
) loop
565 if Is_Potentially_Use_Visible
(H
)
567 and then Is_Overloadable
(H
)
569 for J
in First_Interp
.. All_Interp
.Last
- 1 loop
571 if not Is_Immediately_Visible
(All_Interp
.Table
(J
).Nam
) then
574 elsif Type_Conformant
(H
, All_Interp
.Table
(J
).Nam
) then
575 goto Next_Use_Homograph
;
579 Add_One_Interp
(N
, H
, Etype
(H
));
582 <<Next_Use_Homograph
>>
587 if All_Interp
.Last
= First_Interp
+ 1 then
589 -- The original interpretation is in fact not overloaded
591 Set_Is_Overloaded
(N
, False);
599 function Covers
(T1
, T2
: Entity_Id
) return Boolean is
604 function Full_View_Covers
(Typ1
, Typ2
: Entity_Id
) return Boolean;
605 -- In an instance the proper view may not always be correct for
606 -- private types, but private and full view are compatible. This
607 -- removes spurious errors from nested instantiations that involve,
608 -- among other things, types derived from private types.
610 ----------------------
611 -- Full_View_Covers --
612 ----------------------
614 function Full_View_Covers
(Typ1
, Typ2
: Entity_Id
) return Boolean is
617 Is_Private_Type
(Typ1
)
619 ((Present
(Full_View
(Typ1
))
620 and then Covers
(Full_View
(Typ1
), Typ2
))
621 or else Base_Type
(Typ1
) = Typ2
622 or else Base_Type
(Typ2
) = Typ1
);
623 end Full_View_Covers
;
625 -- Start of processing for Covers
628 -- If either operand missing, then this is an error, but ignore it (and
629 -- pretend we have a cover) if errors already detected, since this may
630 -- simply mean we have malformed trees.
632 if No
(T1
) or else No
(T2
) then
633 if Total_Errors_Detected
/= 0 then
640 BT1
:= Base_Type
(T1
);
641 BT2
:= Base_Type
(T2
);
644 -- Simplest case: same types are compatible, and types that have the
645 -- same base type and are not generic actuals are compatible. Generic
646 -- actuals belong to their class but are not compatible with other
647 -- types of their class, and in particular with other generic actuals.
648 -- They are however compatible with their own subtypes, and itypes
649 -- with the same base are compatible as well. Similarly, constrained
650 -- subtypes obtained from expressions of an unconstrained nominal type
651 -- are compatible with the base type (may lead to spurious ambiguities
652 -- in obscure cases ???)
654 -- Generic actuals require special treatment to avoid spurious ambi-
655 -- guities in an instance, when two formal types are instantiated with
656 -- the same actual, so that different subprograms end up with the same
657 -- signature in the instance.
666 if not Is_Generic_Actual_Type
(T1
) then
669 return (not Is_Generic_Actual_Type
(T2
)
670 or else Is_Itype
(T1
)
671 or else Is_Itype
(T2
)
672 or else Is_Constr_Subt_For_U_Nominal
(T1
)
673 or else Is_Constr_Subt_For_U_Nominal
(T2
)
674 or else Scope
(T1
) /= Scope
(T2
));
677 -- Literals are compatible with types in a given "class"
679 elsif (T2
= Universal_Integer
and then Is_Integer_Type
(T1
))
680 or else (T2
= Universal_Real
and then Is_Real_Type
(T1
))
681 or else (T2
= Universal_Fixed
and then Is_Fixed_Point_Type
(T1
))
682 or else (T2
= Any_Fixed
and then Is_Fixed_Point_Type
(T1
))
683 or else (T2
= Any_String
and then Is_String_Type
(T1
))
684 or else (T2
= Any_Character
and then Is_Character_Type
(T1
))
685 or else (T2
= Any_Access
and then Is_Access_Type
(T1
))
689 -- The context may be class wide
691 elsif Is_Class_Wide_Type
(T1
)
692 and then Is_Ancestor
(Root_Type
(T1
), T2
)
696 elsif Is_Class_Wide_Type
(T1
)
697 and then Is_Class_Wide_Type
(T2
)
698 and then Base_Type
(Etype
(T1
)) = Base_Type
(Etype
(T2
))
702 -- Ada 2005 (AI-345): A class-wide abstract interface type T1 covers a
703 -- task_type or protected_type implementing T1
705 elsif Ada_Version
>= Ada_05
706 and then Is_Class_Wide_Type
(T1
)
707 and then Is_Interface
(Etype
(T1
))
708 and then Is_Concurrent_Type
(T2
)
709 and then Interface_Present_In_Ancestor
710 (Typ
=> Base_Type
(T2
),
715 -- Ada 2005 (AI-251): A class-wide abstract interface type T1 covers an
716 -- object T2 implementing T1
718 elsif Ada_Version
>= Ada_05
719 and then Is_Class_Wide_Type
(T1
)
720 and then Is_Interface
(Etype
(T1
))
721 and then Is_Tagged_Type
(T2
)
723 if Interface_Present_In_Ancestor
(Typ
=> T2
,
728 elsif Present
(Abstract_Interfaces
(T2
)) then
730 -- Ada 2005 (AI-251): A class-wide abstract interface type T1
731 -- covers an object T2 that implements a direct derivation of T1.
734 E
: Elmt_Id
:= First_Elmt
(Abstract_Interfaces
(T2
));
736 while Present
(E
) loop
737 if Is_Ancestor
(Etype
(T1
), Node
(E
)) then
745 -- We should also check the case in which T1 is an ancestor of
746 -- some implemented interface???
754 -- In a dispatching call the actual may be class-wide
756 elsif Is_Class_Wide_Type
(T2
)
757 and then Base_Type
(Root_Type
(T2
)) = Base_Type
(T1
)
761 -- Some contexts require a class of types rather than a specific type
763 elsif (T1
= Any_Integer
and then Is_Integer_Type
(T2
))
764 or else (T1
= Any_Boolean
and then Is_Boolean_Type
(T2
))
765 or else (T1
= Any_Real
and then Is_Real_Type
(T2
))
766 or else (T1
= Any_Fixed
and then Is_Fixed_Point_Type
(T2
))
767 or else (T1
= Any_Discrete
and then Is_Discrete_Type
(T2
))
771 -- An aggregate is compatible with an array or record type
773 elsif T2
= Any_Composite
774 and then Ekind
(T1
) in E_Array_Type
.. E_Record_Subtype
778 -- If the expected type is an anonymous access, the designated type must
779 -- cover that of the expression.
781 elsif Ekind
(T1
) = E_Anonymous_Access_Type
782 and then Is_Access_Type
(T2
)
783 and then Covers
(Designated_Type
(T1
), Designated_Type
(T2
))
787 -- An Access_To_Subprogram is compatible with itself, or with an
788 -- anonymous type created for an attribute reference Access.
790 elsif (Ekind
(BT1
) = E_Access_Subprogram_Type
792 Ekind
(BT1
) = E_Access_Protected_Subprogram_Type
)
793 and then Is_Access_Type
(T2
)
794 and then (not Comes_From_Source
(T1
)
795 or else not Comes_From_Source
(T2
))
796 and then (Is_Overloadable
(Designated_Type
(T2
))
798 Ekind
(Designated_Type
(T2
)) = E_Subprogram_Type
)
800 Type_Conformant
(Designated_Type
(T1
), Designated_Type
(T2
))
802 Mode_Conformant
(Designated_Type
(T1
), Designated_Type
(T2
))
806 -- Ada 2005 (AI-254): An Anonymous_Access_To_Subprogram is compatible
807 -- with itself, or with an anonymous type created for an attribute
810 elsif (Ekind
(BT1
) = E_Anonymous_Access_Subprogram_Type
813 = E_Anonymous_Access_Protected_Subprogram_Type
)
814 and then Is_Access_Type
(T2
)
815 and then (not Comes_From_Source
(T1
)
816 or else not Comes_From_Source
(T2
))
817 and then (Is_Overloadable
(Designated_Type
(T2
))
819 Ekind
(Designated_Type
(T2
)) = E_Subprogram_Type
)
821 Type_Conformant
(Designated_Type
(T1
), Designated_Type
(T2
))
823 Mode_Conformant
(Designated_Type
(T1
), Designated_Type
(T2
))
827 -- The context can be a remote access type, and the expression the
828 -- corresponding source type declared in a categorized package, or
831 elsif Is_Record_Type
(T1
)
832 and then (Is_Remote_Call_Interface
(T1
)
833 or else Is_Remote_Types
(T1
))
834 and then Present
(Corresponding_Remote_Type
(T1
))
836 return Covers
(Corresponding_Remote_Type
(T1
), T2
);
838 elsif Is_Record_Type
(T2
)
839 and then (Is_Remote_Call_Interface
(T2
)
840 or else Is_Remote_Types
(T2
))
841 and then Present
(Corresponding_Remote_Type
(T2
))
843 return Covers
(Corresponding_Remote_Type
(T2
), T1
);
845 elsif Ekind
(T2
) = E_Access_Attribute_Type
846 and then (Ekind
(BT1
) = E_General_Access_Type
847 or else Ekind
(BT1
) = E_Access_Type
)
848 and then Covers
(Designated_Type
(T1
), Designated_Type
(T2
))
850 -- If the target type is a RACW type while the source is an access
851 -- attribute type, we are building a RACW that may be exported.
853 if Is_Remote_Access_To_Class_Wide_Type
(BT1
) then
854 Set_Has_RACW
(Current_Sem_Unit
);
859 elsif Ekind
(T2
) = E_Allocator_Type
860 and then Is_Access_Type
(T1
)
862 return Covers
(Designated_Type
(T1
), Designated_Type
(T2
))
864 (From_With_Type
(Designated_Type
(T1
))
865 and then Covers
(Designated_Type
(T2
), Designated_Type
(T1
)));
867 -- A boolean operation on integer literals is compatible with modular
870 elsif T2
= Any_Modular
871 and then Is_Modular_Integer_Type
(T1
)
875 -- The actual type may be the result of a previous error
877 elsif Base_Type
(T2
) = Any_Type
then
880 -- A packed array type covers its corresponding non-packed type. This is
881 -- not legitimate Ada, but allows the omission of a number of otherwise
882 -- useless unchecked conversions, and since this can only arise in
883 -- (known correct) expanded code, no harm is done
885 elsif Is_Array_Type
(T2
)
886 and then Is_Packed
(T2
)
887 and then T1
= Packed_Array_Type
(T2
)
891 -- Similarly an array type covers its corresponding packed array type
893 elsif Is_Array_Type
(T1
)
894 and then Is_Packed
(T1
)
895 and then T2
= Packed_Array_Type
(T1
)
901 (Full_View_Covers
(T1
, T2
)
902 or else Full_View_Covers
(T2
, T1
))
906 -- In the expansion of inlined bodies, types are compatible if they
907 -- are structurally equivalent.
909 elsif In_Inlined_Body
910 and then (Underlying_Type
(T1
) = Underlying_Type
(T2
)
911 or else (Is_Access_Type
(T1
)
912 and then Is_Access_Type
(T2
)
914 Designated_Type
(T1
) = Designated_Type
(T2
))
915 or else (T1
= Any_Access
916 and then Is_Access_Type
(Underlying_Type
(T2
)))
917 or else (T2
= Any_Composite
919 Is_Composite_Type
(Underlying_Type
(T1
))))
923 -- Ada 2005 (AI-50217): Additional branches to make the shadow entity
924 -- compatible with its real entity.
926 elsif From_With_Type
(T1
) then
928 -- If the expected type is the non-limited view of a type, the
929 -- expression may have the limited view.
931 if Ekind
(T1
) = E_Incomplete_Type
then
932 return Covers
(Non_Limited_View
(T1
), T2
);
934 elsif Ekind
(T1
) = E_Class_Wide_Type
then
936 Covers
(Class_Wide_Type
(Non_Limited_View
(Etype
(T1
))), T2
);
941 elsif From_With_Type
(T2
) then
943 -- If units in the context have Limited_With clauses on each other,
944 -- either type might have a limited view. Checks performed elsewhere
945 -- verify that the context type is the non-limited view.
947 if Ekind
(T2
) = E_Incomplete_Type
then
948 return Covers
(T1
, Non_Limited_View
(T2
));
950 elsif Ekind
(T2
) = E_Class_Wide_Type
then
952 Covers
(T1
, Class_Wide_Type
(Non_Limited_View
(Etype
(T2
))));
957 -- Otherwise it doesn't cover!
968 function Disambiguate
970 I1
, I2
: Interp_Index
;
977 Nam1
, Nam2
: Entity_Id
;
978 Predef_Subp
: Entity_Id
;
979 User_Subp
: Entity_Id
;
981 function Inherited_From_Actual
(S
: Entity_Id
) return Boolean;
982 -- Determine whether one of the candidates is an operation inherited by
983 -- a type that is derived from an actual in an instantiation.
985 function In_Generic_Actual
(Exp
: Node_Id
) return Boolean;
986 -- Determine whether the expression is part of a generic actual. At
987 -- the time the actual is resolved the scope is already that of the
988 -- instance, but conceptually the resolution of the actual takes place
989 -- in the enclosing context, and no special disambiguation rules should
992 function Is_Actual_Subprogram
(S
: Entity_Id
) return Boolean;
993 -- Determine whether a subprogram is an actual in an enclosing instance.
994 -- An overloading between such a subprogram and one declared outside the
995 -- instance is resolved in favor of the first, because it resolved in
998 function Matches
(Actual
, Formal
: Node_Id
) return Boolean;
999 -- Look for exact type match in an instance, to remove spurious
1000 -- ambiguities when two formal types have the same actual.
1002 function Standard_Operator
return Boolean;
1003 -- Comment required ???
1005 function Remove_Conversions
return Interp
;
1006 -- Last chance for pathological cases involving comparisons on literals,
1007 -- and user overloadings of the same operator. Such pathologies have
1008 -- been removed from the ACVC, but still appear in two DEC tests, with
1009 -- the following notable quote from Ben Brosgol:
1011 -- [Note: I disclaim all credit/responsibility/blame for coming up with
1012 -- this example; Robert Dewar brought it to our attention, since it is
1013 -- apparently found in the ACVC 1.5. I did not attempt to find the
1014 -- reason in the Reference Manual that makes the example legal, since I
1015 -- was too nauseated by it to want to pursue it further.]
1017 -- Accordingly, this is not a fully recursive solution, but it handles
1018 -- DEC tests c460vsa, c460vsb. It also handles ai00136a, which pushes
1019 -- pathology in the other direction with calls whose multiple overloaded
1020 -- actuals make them truly unresolvable.
1022 -- The new rules concerning abstract operations create additional
1023 -- for special handling of expressions with universal operands, See
1024 -- comments to Has_Abstract_Interpretation below.
1026 ------------------------
1027 -- In_Generic_Actual --
1028 ------------------------
1030 function In_Generic_Actual
(Exp
: Node_Id
) return Boolean is
1031 Par
: constant Node_Id
:= Parent
(Exp
);
1037 elsif Nkind
(Par
) in N_Declaration
then
1038 if Nkind
(Par
) = N_Object_Declaration
1039 or else Nkind
(Par
) = N_Object_Renaming_Declaration
1041 return Present
(Corresponding_Generic_Association
(Par
));
1046 elsif Nkind
(Par
) in N_Statement_Other_Than_Procedure_Call
then
1050 return In_Generic_Actual
(Parent
(Par
));
1052 end In_Generic_Actual
;
1054 ---------------------------
1055 -- Inherited_From_Actual --
1056 ---------------------------
1058 function Inherited_From_Actual
(S
: Entity_Id
) return Boolean is
1059 Par
: constant Node_Id
:= Parent
(S
);
1061 if Nkind
(Par
) /= N_Full_Type_Declaration
1062 or else Nkind
(Type_Definition
(Par
)) /= N_Derived_Type_Definition
1066 return Is_Entity_Name
(Subtype_Indication
(Type_Definition
(Par
)))
1068 Is_Generic_Actual_Type
(
1069 Entity
(Subtype_Indication
(Type_Definition
(Par
))));
1071 end Inherited_From_Actual
;
1073 --------------------------
1074 -- Is_Actual_Subprogram --
1075 --------------------------
1077 function Is_Actual_Subprogram
(S
: Entity_Id
) return Boolean is
1079 return In_Open_Scopes
(Scope
(S
))
1081 (Is_Generic_Instance
(Scope
(S
))
1082 or else Is_Wrapper_Package
(Scope
(S
)));
1083 end Is_Actual_Subprogram
;
1089 function Matches
(Actual
, Formal
: Node_Id
) return Boolean is
1090 T1
: constant Entity_Id
:= Etype
(Actual
);
1091 T2
: constant Entity_Id
:= Etype
(Formal
);
1095 (Is_Numeric_Type
(T2
)
1097 (T1
= Universal_Real
or else T1
= Universal_Integer
));
1100 ------------------------
1101 -- Remove_Conversions --
1102 ------------------------
1104 function Remove_Conversions
return Interp
is
1112 function Has_Abstract_Interpretation
(N
: Node_Id
) return Boolean;
1113 -- If an operation has universal operands the universal operation
1114 -- is present among its interpretations. If there is an abstract
1115 -- interpretation for the operator, with a numeric result, this
1116 -- interpretation was already removed in sem_ch4, but the universal
1117 -- one is still visible. We must rescan the list of operators and
1118 -- remove the universal interpretation to resolve the ambiguity.
1120 ---------------------------------
1121 -- Has_Abstract_Interpretation --
1122 ---------------------------------
1124 function Has_Abstract_Interpretation
(N
: Node_Id
) return Boolean is
1128 E
:= Current_Entity
(N
);
1129 while Present
(E
) loop
1131 and then Is_Numeric_Type
(Etype
(E
))
1140 end Has_Abstract_Interpretation
;
1142 -- Start of processing for Remove_ConversionsMino
1147 Get_First_Interp
(N
, I
, It
);
1148 while Present
(It
.Typ
) loop
1149 if not Is_Overloadable
(It
.Nam
) then
1153 F1
:= First_Formal
(It
.Nam
);
1159 if Nkind
(N
) = N_Function_Call
1160 or else Nkind
(N
) = N_Procedure_Call_Statement
1162 Act1
:= First_Actual
(N
);
1164 if Present
(Act1
) then
1165 Act2
:= Next_Actual
(Act1
);
1170 elsif Nkind
(N
) in N_Unary_Op
then
1171 Act1
:= Right_Opnd
(N
);
1174 elsif Nkind
(N
) in N_Binary_Op
then
1175 Act1
:= Left_Opnd
(N
);
1176 Act2
:= Right_Opnd
(N
);
1182 if Nkind
(Act1
) in N_Op
1183 and then Is_Overloaded
(Act1
)
1184 and then (Nkind
(Right_Opnd
(Act1
)) = N_Integer_Literal
1185 or else Nkind
(Right_Opnd
(Act1
)) = N_Real_Literal
)
1186 and then Has_Compatible_Type
(Act1
, Standard_Boolean
)
1187 and then Etype
(F1
) = Standard_Boolean
1189 -- If the two candidates are the original ones, the
1190 -- ambiguity is real. Otherwise keep the original, further
1191 -- calls to Disambiguate will take care of others in the
1192 -- list of candidates.
1194 if It1
/= No_Interp
then
1195 if It
= Disambiguate
.It1
1196 or else It
= Disambiguate
.It2
1198 if It1
= Disambiguate
.It1
1199 or else It1
= Disambiguate
.It2
1207 elsif Present
(Act2
)
1208 and then Nkind
(Act2
) in N_Op
1209 and then Is_Overloaded
(Act2
)
1210 and then (Nkind
(Right_Opnd
(Act1
)) = N_Integer_Literal
1212 Nkind
(Right_Opnd
(Act1
)) = N_Real_Literal
)
1213 and then Has_Compatible_Type
(Act2
, Standard_Boolean
)
1215 -- The preference rule on the first actual is not
1216 -- sufficient to disambiguate.
1224 elsif Nkind
(Act1
) in N_Op
1225 and then Is_Overloaded
(Act1
)
1226 and then Present
(Universal_Interpretation
(Act1
))
1227 and then Is_Numeric_Type
(Etype
(F1
))
1228 and then Ada_Version
>= Ada_05
1229 and then Has_Abstract_Interpretation
(Act1
)
1231 if It
= Disambiguate
.It1
then
1232 return Disambiguate
.It2
;
1233 elsif It
= Disambiguate
.It2
then
1234 return Disambiguate
.It1
;
1240 Get_Next_Interp
(I
, It
);
1243 -- After some error, a formal may have Any_Type and yield a spurious
1244 -- match. To avoid cascaded errors if possible, check for such a
1245 -- formal in either candidate.
1247 if Serious_Errors_Detected
> 0 then
1252 Formal
:= First_Formal
(Nam1
);
1253 while Present
(Formal
) loop
1254 if Etype
(Formal
) = Any_Type
then
1255 return Disambiguate
.It2
;
1258 Next_Formal
(Formal
);
1261 Formal
:= First_Formal
(Nam2
);
1262 while Present
(Formal
) loop
1263 if Etype
(Formal
) = Any_Type
then
1264 return Disambiguate
.It1
;
1267 Next_Formal
(Formal
);
1273 end Remove_Conversions
;
1275 -----------------------
1276 -- Standard_Operator --
1277 -----------------------
1279 function Standard_Operator
return Boolean is
1283 if Nkind
(N
) in N_Op
then
1286 elsif Nkind
(N
) = N_Function_Call
then
1289 if Nkind
(Nam
) /= N_Expanded_Name
then
1292 return Entity
(Prefix
(Nam
)) = Standard_Standard
;
1297 end Standard_Operator
;
1299 -- Start of processing for Disambiguate
1302 -- Recover the two legal interpretations
1304 Get_First_Interp
(N
, I
, It
);
1306 Get_Next_Interp
(I
, It
);
1312 Get_Next_Interp
(I
, It
);
1318 if Ada_Version
< Ada_05
then
1320 -- Check whether one of the entities is an Ada 2005 entity and we are
1321 -- operating in an earlier mode, in which case we discard the Ada
1322 -- 2005 entity, so that we get proper Ada 95 overload resolution.
1324 if Is_Ada_2005
(Nam1
) then
1326 elsif Is_Ada_2005
(Nam2
) then
1331 -- If the context is universal, the predefined operator is preferred.
1332 -- This includes bounds in numeric type declarations, and expressions
1333 -- in type conversions. If no interpretation yields a universal type,
1334 -- then we must check whether the user-defined entity hides the prede-
1337 if Chars
(Nam1
) in Any_Operator_Name
1338 and then Standard_Operator
1340 if Typ
= Universal_Integer
1341 or else Typ
= Universal_Real
1342 or else Typ
= Any_Integer
1343 or else Typ
= Any_Discrete
1344 or else Typ
= Any_Real
1345 or else Typ
= Any_Type
1347 -- Find an interpretation that yields the universal type, or else
1348 -- a predefined operator that yields a predefined numeric type.
1351 Candidate
: Interp
:= No_Interp
;
1354 Get_First_Interp
(N
, I
, It
);
1355 while Present
(It
.Typ
) loop
1356 if (Covers
(Typ
, It
.Typ
)
1357 or else Typ
= Any_Type
)
1359 (It
.Typ
= Universal_Integer
1360 or else It
.Typ
= Universal_Real
)
1364 elsif Covers
(Typ
, It
.Typ
)
1365 and then Scope
(It
.Typ
) = Standard_Standard
1366 and then Scope
(It
.Nam
) = Standard_Standard
1367 and then Is_Numeric_Type
(It
.Typ
)
1372 Get_Next_Interp
(I
, It
);
1375 if Candidate
/= No_Interp
then
1380 elsif Chars
(Nam1
) /= Name_Op_Not
1381 and then (Typ
= Standard_Boolean
or else Typ
= Any_Boolean
)
1383 -- Equality or comparison operation. Choose predefined operator if
1384 -- arguments are universal. The node may be an operator, name, or
1385 -- a function call, so unpack arguments accordingly.
1388 Arg1
, Arg2
: Node_Id
;
1391 if Nkind
(N
) in N_Op
then
1392 Arg1
:= Left_Opnd
(N
);
1393 Arg2
:= Right_Opnd
(N
);
1395 elsif Is_Entity_Name
(N
)
1396 or else Nkind
(N
) = N_Operator_Symbol
1398 Arg1
:= First_Entity
(Entity
(N
));
1399 Arg2
:= Next_Entity
(Arg1
);
1402 Arg1
:= First_Actual
(N
);
1403 Arg2
:= Next_Actual
(Arg1
);
1407 and then Present
(Universal_Interpretation
(Arg1
))
1408 and then Universal_Interpretation
(Arg2
) =
1409 Universal_Interpretation
(Arg1
)
1411 Get_First_Interp
(N
, I
, It
);
1412 while Scope
(It
.Nam
) /= Standard_Standard
loop
1413 Get_Next_Interp
(I
, It
);
1422 -- If no universal interpretation, check whether user-defined operator
1423 -- hides predefined one, as well as other special cases. If the node
1424 -- is a range, then one or both bounds are ambiguous. Each will have
1425 -- to be disambiguated w.r.t. the context type. The type of the range
1426 -- itself is imposed by the context, so we can return either legal
1429 if Ekind
(Nam1
) = E_Operator
then
1430 Predef_Subp
:= Nam1
;
1433 elsif Ekind
(Nam2
) = E_Operator
then
1434 Predef_Subp
:= Nam2
;
1437 elsif Nkind
(N
) = N_Range
then
1440 -- If two user defined-subprograms are visible, it is a true ambiguity,
1441 -- unless one of them is an entry and the context is a conditional or
1442 -- timed entry call, or unless we are within an instance and this is
1443 -- results from two formals types with the same actual.
1446 if Nkind
(N
) = N_Procedure_Call_Statement
1447 and then Nkind
(Parent
(N
)) = N_Entry_Call_Alternative
1448 and then N
= Entry_Call_Statement
(Parent
(N
))
1450 if Ekind
(Nam2
) = E_Entry
then
1452 elsif Ekind
(Nam1
) = E_Entry
then
1458 -- If the ambiguity occurs within an instance, it is due to several
1459 -- formal types with the same actual. Look for an exact match between
1460 -- the types of the formals of the overloadable entities, and the
1461 -- actuals in the call, to recover the unambiguous match in the
1462 -- original generic.
1464 -- The ambiguity can also be due to an overloading between a formal
1465 -- subprogram and a subprogram declared outside the generic. If the
1466 -- node is overloaded, it did not resolve to the global entity in
1467 -- the generic, and we choose the formal subprogram.
1469 -- Finally, the ambiguity can be between an explicit subprogram and
1470 -- one inherited (with different defaults) from an actual. In this
1471 -- case the resolution was to the explicit declaration in the
1472 -- generic, and remains so in the instance.
1475 and then not In_Generic_Actual
(N
)
1477 if Nkind
(N
) = N_Function_Call
1478 or else Nkind
(N
) = N_Procedure_Call_Statement
1483 Is_Act1
: constant Boolean := Is_Actual_Subprogram
(Nam1
);
1484 Is_Act2
: constant Boolean := Is_Actual_Subprogram
(Nam2
);
1487 if Is_Act1
and then not Is_Act2
then
1490 elsif Is_Act2
and then not Is_Act1
then
1493 elsif Inherited_From_Actual
(Nam1
)
1494 and then Comes_From_Source
(Nam2
)
1498 elsif Inherited_From_Actual
(Nam2
)
1499 and then Comes_From_Source
(Nam1
)
1504 Actual
:= First_Actual
(N
);
1505 Formal
:= First_Formal
(Nam1
);
1506 while Present
(Actual
) loop
1507 if Etype
(Actual
) /= Etype
(Formal
) then
1511 Next_Actual
(Actual
);
1512 Next_Formal
(Formal
);
1518 elsif Nkind
(N
) in N_Binary_Op
then
1519 if Matches
(Left_Opnd
(N
), First_Formal
(Nam1
))
1521 Matches
(Right_Opnd
(N
), Next_Formal
(First_Formal
(Nam1
)))
1528 elsif Nkind
(N
) in N_Unary_Op
then
1529 if Etype
(Right_Opnd
(N
)) = Etype
(First_Formal
(Nam1
)) then
1536 return Remove_Conversions
;
1539 return Remove_Conversions
;
1543 -- an implicit concatenation operator on a string type cannot be
1544 -- disambiguated from the predefined concatenation. This can only
1545 -- happen with concatenation of string literals.
1547 if Chars
(User_Subp
) = Name_Op_Concat
1548 and then Ekind
(User_Subp
) = E_Operator
1549 and then Is_String_Type
(Etype
(First_Formal
(User_Subp
)))
1553 -- If the user-defined operator is in an open scope, or in the scope
1554 -- of the resulting type, or given by an expanded name that names its
1555 -- scope, it hides the predefined operator for the type. Exponentiation
1556 -- has to be special-cased because the implicit operator does not have
1557 -- a symmetric signature, and may not be hidden by the explicit one.
1559 elsif (Nkind
(N
) = N_Function_Call
1560 and then Nkind
(Name
(N
)) = N_Expanded_Name
1561 and then (Chars
(Predef_Subp
) /= Name_Op_Expon
1562 or else Hides_Op
(User_Subp
, Predef_Subp
))
1563 and then Scope
(User_Subp
) = Entity
(Prefix
(Name
(N
))))
1564 or else Hides_Op
(User_Subp
, Predef_Subp
)
1566 if It1
.Nam
= User_Subp
then
1572 -- Otherwise, the predefined operator has precedence, or if the user-
1573 -- defined operation is directly visible we have a true ambiguity. If
1574 -- this is a fixed-point multiplication and division in Ada83 mode,
1575 -- exclude the universal_fixed operator, which often causes ambiguities
1579 if (In_Open_Scopes
(Scope
(User_Subp
))
1580 or else Is_Potentially_Use_Visible
(User_Subp
))
1581 and then not In_Instance
1583 if Is_Fixed_Point_Type
(Typ
)
1584 and then (Chars
(Nam1
) = Name_Op_Multiply
1585 or else Chars
(Nam1
) = Name_Op_Divide
)
1586 and then Ada_Version
= Ada_83
1588 if It2
.Nam
= Predef_Subp
then
1597 elsif It1
.Nam
= Predef_Subp
then
1606 ---------------------
1607 -- End_Interp_List --
1608 ---------------------
1610 procedure End_Interp_List
is
1612 All_Interp
.Table
(All_Interp
.Last
) := No_Interp
;
1613 All_Interp
.Increment_Last
;
1614 end End_Interp_List
;
1616 -------------------------
1617 -- Entity_Matches_Spec --
1618 -------------------------
1620 function Entity_Matches_Spec
(Old_S
, New_S
: Entity_Id
) return Boolean is
1622 -- Simple case: same entity kinds, type conformance is required. A
1623 -- parameterless function can also rename a literal.
1625 if Ekind
(Old_S
) = Ekind
(New_S
)
1626 or else (Ekind
(New_S
) = E_Function
1627 and then Ekind
(Old_S
) = E_Enumeration_Literal
)
1629 return Type_Conformant
(New_S
, Old_S
);
1631 elsif Ekind
(New_S
) = E_Function
1632 and then Ekind
(Old_S
) = E_Operator
1634 return Operator_Matches_Spec
(Old_S
, New_S
);
1636 elsif Ekind
(New_S
) = E_Procedure
1637 and then Is_Entry
(Old_S
)
1639 return Type_Conformant
(New_S
, Old_S
);
1644 end Entity_Matches_Spec
;
1646 ----------------------
1647 -- Find_Unique_Type --
1648 ----------------------
1650 function Find_Unique_Type
(L
: Node_Id
; R
: Node_Id
) return Entity_Id
is
1651 T
: constant Entity_Id
:= Etype
(L
);
1654 TR
: Entity_Id
:= Any_Type
;
1657 if Is_Overloaded
(R
) then
1658 Get_First_Interp
(R
, I
, It
);
1659 while Present
(It
.Typ
) loop
1660 if Covers
(T
, It
.Typ
) or else Covers
(It
.Typ
, T
) then
1662 -- If several interpretations are possible and L is universal,
1663 -- apply preference rule.
1665 if TR
/= Any_Type
then
1667 if (T
= Universal_Integer
or else T
= Universal_Real
)
1678 Get_Next_Interp
(I
, It
);
1683 -- In the non-overloaded case, the Etype of R is already set correctly
1689 -- If one of the operands is Universal_Fixed, the type of the other
1690 -- operand provides the context.
1692 if Etype
(R
) = Universal_Fixed
then
1695 elsif T
= Universal_Fixed
then
1698 -- Ada 2005 (AI-230): Support the following operators:
1700 -- function "=" (L, R : universal_access) return Boolean;
1701 -- function "/=" (L, R : universal_access) return Boolean;
1703 elsif Ada_Version
>= Ada_05
1704 and then Ekind
(Etype
(L
)) = E_Anonymous_Access_Type
1705 and then Is_Access_Type
(Etype
(R
))
1709 elsif Ada_Version
>= Ada_05
1710 and then Ekind
(Etype
(R
)) = E_Anonymous_Access_Type
1711 and then Is_Access_Type
(Etype
(L
))
1716 return Specific_Type
(T
, Etype
(R
));
1719 end Find_Unique_Type
;
1721 ----------------------
1722 -- Get_First_Interp --
1723 ----------------------
1725 procedure Get_First_Interp
1727 I
: out Interp_Index
;
1731 Int_Ind
: Interp_Index
;
1735 -- If a selected component is overloaded because the selector has
1736 -- multiple interpretations, the node is a call to a protected
1737 -- operation or an indirect call. Retrieve the interpretation from
1738 -- the selector name. The selected component may be overloaded as well
1739 -- if the prefix is overloaded. That case is unchanged.
1741 if Nkind
(N
) = N_Selected_Component
1742 and then Is_Overloaded
(Selector_Name
(N
))
1744 O_N
:= Selector_Name
(N
);
1749 Map_Ptr
:= Headers
(Hash
(O_N
));
1750 while Present
(Interp_Map
.Table
(Map_Ptr
).Node
) loop
1751 if Interp_Map
.Table
(Map_Ptr
).Node
= O_N
then
1752 Int_Ind
:= Interp_Map
.Table
(Map_Ptr
).Index
;
1753 It
:= All_Interp
.Table
(Int_Ind
);
1757 Map_Ptr
:= Interp_Map
.Table
(Map_Ptr
).Next
;
1761 -- Procedure should never be called if the node has no interpretations
1763 raise Program_Error
;
1764 end Get_First_Interp
;
1766 ---------------------
1767 -- Get_Next_Interp --
1768 ---------------------
1770 procedure Get_Next_Interp
(I
: in out Interp_Index
; It
: out Interp
) is
1773 It
:= All_Interp
.Table
(I
);
1774 end Get_Next_Interp
;
1776 -------------------------
1777 -- Has_Compatible_Type --
1778 -------------------------
1780 function Has_Compatible_Type
1793 if Nkind
(N
) = N_Subtype_Indication
1794 or else not Is_Overloaded
(N
)
1797 Covers
(Typ
, Etype
(N
))
1799 -- Ada 2005 (AI-345) The context may be a synchronized interface.
1800 -- If the type is already frozen use the corresponding_record
1801 -- to check whether it is a proper descendant.
1804 (Is_Concurrent_Type
(Etype
(N
))
1805 and then Present
(Corresponding_Record_Type
(Etype
(N
)))
1806 and then Covers
(Typ
, Corresponding_Record_Type
(Etype
(N
))))
1809 (not Is_Tagged_Type
(Typ
)
1810 and then Ekind
(Typ
) /= E_Anonymous_Access_Type
1811 and then Covers
(Etype
(N
), Typ
));
1814 Get_First_Interp
(N
, I
, It
);
1815 while Present
(It
.Typ
) loop
1816 if (Covers
(Typ
, It
.Typ
)
1818 (Scope
(It
.Nam
) /= Standard_Standard
1819 or else not Is_Invisible_Operator
(N
, Base_Type
(Typ
))))
1821 -- Ada 2005 (AI-345)
1824 (Is_Concurrent_Type
(It
.Typ
)
1825 and then Present
(Corresponding_Record_Type
1827 and then Covers
(Typ
, Corresponding_Record_Type
1830 or else (not Is_Tagged_Type
(Typ
)
1831 and then Ekind
(Typ
) /= E_Anonymous_Access_Type
1832 and then Covers
(It
.Typ
, Typ
))
1837 Get_Next_Interp
(I
, It
);
1842 end Has_Compatible_Type
;
1848 function Hash
(N
: Node_Id
) return Int
is
1850 -- Nodes have a size that is power of two, so to select significant
1851 -- bits only we remove the low-order bits.
1853 return ((Int
(N
) / 2 ** 5) mod Header_Size
);
1860 function Hides_Op
(F
: Entity_Id
; Op
: Entity_Id
) return Boolean is
1861 Btyp
: constant Entity_Id
:= Base_Type
(Etype
(First_Formal
(F
)));
1863 return Operator_Matches_Spec
(Op
, F
)
1864 and then (In_Open_Scopes
(Scope
(F
))
1865 or else Scope
(F
) = Scope
(Btyp
)
1866 or else (not In_Open_Scopes
(Scope
(Btyp
))
1867 and then not In_Use
(Btyp
)
1868 and then not In_Use
(Scope
(Btyp
))));
1871 ------------------------
1872 -- Init_Interp_Tables --
1873 ------------------------
1875 procedure Init_Interp_Tables
is
1879 Headers
:= (others => No_Entry
);
1880 end Init_Interp_Tables
;
1882 -----------------------------------
1883 -- Interface_Present_In_Ancestor --
1884 -----------------------------------
1886 function Interface_Present_In_Ancestor
1888 Iface
: Entity_Id
) return Boolean
1890 Target_Typ
: Entity_Id
;
1892 function Iface_Present_In_Ancestor
(Typ
: Entity_Id
) return Boolean;
1893 -- Returns True if Typ or some ancestor of Typ implements Iface
1895 function Iface_Present_In_Ancestor
(Typ
: Entity_Id
) return Boolean is
1905 -- Handle private types
1907 if Present
(Full_View
(Typ
))
1908 and then not Is_Concurrent_Type
(Full_View
(Typ
))
1910 E
:= Full_View
(Typ
);
1916 if Present
(Abstract_Interfaces
(E
))
1917 and then Present
(Abstract_Interfaces
(E
))
1918 and then not Is_Empty_Elmt_List
(Abstract_Interfaces
(E
))
1920 Elmt
:= First_Elmt
(Abstract_Interfaces
(E
));
1921 while Present
(Elmt
) loop
1924 if AI
= Iface
or else Is_Ancestor
(Iface
, AI
) then
1932 exit when Etype
(E
) = E
1934 -- Handle private types
1936 or else (Present
(Full_View
(Etype
(E
)))
1937 and then Full_View
(Etype
(E
)) = E
);
1939 -- Check if the current type is a direct derivation of the
1942 if Etype
(E
) = Iface
then
1946 -- Climb to the immediate ancestor handling private types
1948 if Present
(Full_View
(Etype
(E
))) then
1949 E
:= Full_View
(Etype
(E
));
1956 end Iface_Present_In_Ancestor
;
1958 -- Start of processing for Interface_Present_In_Ancestor
1961 if Is_Access_Type
(Typ
) then
1962 Target_Typ
:= Etype
(Directly_Designated_Type
(Typ
));
1967 -- In case of concurrent types we can't use the Corresponding Record_Typ
1968 -- to look for the interface because it is built by the expander (and
1969 -- hence it is not always available). For this reason we traverse the
1970 -- list of interfaces (available in the parent of the concurrent type)
1972 if Is_Concurrent_Type
(Target_Typ
) then
1973 if Present
(Interface_List
(Parent
(Target_Typ
))) then
1978 AI
:= First
(Interface_List
(Parent
(Target_Typ
)));
1979 while Present
(AI
) loop
1980 if Etype
(AI
) = Iface
then
1983 elsif Present
(Abstract_Interfaces
(Etype
(AI
)))
1984 and then Iface_Present_In_Ancestor
(Etype
(AI
))
1997 if Is_Class_Wide_Type
(Target_Typ
) then
1998 Target_Typ
:= Etype
(Target_Typ
);
2001 if Ekind
(Target_Typ
) = E_Incomplete_Type
then
2002 pragma Assert
(Present
(Non_Limited_View
(Target_Typ
)));
2003 Target_Typ
:= Non_Limited_View
(Target_Typ
);
2005 -- Protect the frontend against previously detected errors
2007 if Ekind
(Target_Typ
) = E_Incomplete_Type
then
2012 return Iface_Present_In_Ancestor
(Target_Typ
);
2013 end Interface_Present_In_Ancestor
;
2015 ---------------------
2016 -- Intersect_Types --
2017 ---------------------
2019 function Intersect_Types
(L
, R
: Node_Id
) return Entity_Id
is
2020 Index
: Interp_Index
;
2024 function Check_Right_Argument
(T
: Entity_Id
) return Entity_Id
;
2025 -- Find interpretation of right arg that has type compatible with T
2027 --------------------------
2028 -- Check_Right_Argument --
2029 --------------------------
2031 function Check_Right_Argument
(T
: Entity_Id
) return Entity_Id
is
2032 Index
: Interp_Index
;
2037 if not Is_Overloaded
(R
) then
2038 return Specific_Type
(T
, Etype
(R
));
2041 Get_First_Interp
(R
, Index
, It
);
2043 T2
:= Specific_Type
(T
, It
.Typ
);
2045 if T2
/= Any_Type
then
2049 Get_Next_Interp
(Index
, It
);
2050 exit when No
(It
.Typ
);
2055 end Check_Right_Argument
;
2057 -- Start processing for Intersect_Types
2060 if Etype
(L
) = Any_Type
or else Etype
(R
) = Any_Type
then
2064 if not Is_Overloaded
(L
) then
2065 Typ
:= Check_Right_Argument
(Etype
(L
));
2069 Get_First_Interp
(L
, Index
, It
);
2070 while Present
(It
.Typ
) loop
2071 Typ
:= Check_Right_Argument
(It
.Typ
);
2072 exit when Typ
/= Any_Type
;
2073 Get_Next_Interp
(Index
, It
);
2078 -- If Typ is Any_Type, it means no compatible pair of types was found
2080 if Typ
= Any_Type
then
2081 if Nkind
(Parent
(L
)) in N_Op
then
2082 Error_Msg_N
("incompatible types for operator", Parent
(L
));
2084 elsif Nkind
(Parent
(L
)) = N_Range
then
2085 Error_Msg_N
("incompatible types given in constraint", Parent
(L
));
2087 -- Ada 2005 (AI-251): Complete the error notification
2089 elsif Is_Class_Wide_Type
(Etype
(R
))
2090 and then Is_Interface
(Etype
(Class_Wide_Type
(Etype
(R
))))
2092 Error_Msg_NE
("(Ada 2005) does not implement interface }",
2093 L
, Etype
(Class_Wide_Type
(Etype
(R
))));
2096 Error_Msg_N
("incompatible types", Parent
(L
));
2101 end Intersect_Types
;
2107 function Is_Ancestor
(T1
, T2
: Entity_Id
) return Boolean is
2111 if Base_Type
(T1
) = Base_Type
(T2
) then
2114 elsif Is_Private_Type
(T1
)
2115 and then Present
(Full_View
(T1
))
2116 and then Base_Type
(T2
) = Base_Type
(Full_View
(T1
))
2124 -- If there was a error on the type declaration, do not recurse
2126 if Error_Posted
(Par
) then
2129 elsif Base_Type
(T1
) = Base_Type
(Par
)
2130 or else (Is_Private_Type
(T1
)
2131 and then Present
(Full_View
(T1
))
2132 and then Base_Type
(Par
) = Base_Type
(Full_View
(T1
)))
2136 elsif Is_Private_Type
(Par
)
2137 and then Present
(Full_View
(Par
))
2138 and then Full_View
(Par
) = Base_Type
(T1
)
2142 elsif Etype
(Par
) /= Par
then
2151 ---------------------------
2152 -- Is_Invisible_Operator --
2153 ---------------------------
2155 function Is_Invisible_Operator
2160 Orig_Node
: constant Node_Id
:= Original_Node
(N
);
2163 if Nkind
(N
) not in N_Op
then
2166 elsif not Comes_From_Source
(N
) then
2169 elsif No
(Universal_Interpretation
(Right_Opnd
(N
))) then
2172 elsif Nkind
(N
) in N_Binary_Op
2173 and then No
(Universal_Interpretation
(Left_Opnd
(N
)))
2179 and then not In_Open_Scopes
(Scope
(T
))
2180 and then not Is_Potentially_Use_Visible
(T
)
2181 and then not In_Use
(T
)
2182 and then not In_Use
(Scope
(T
))
2184 (Nkind
(Orig_Node
) /= N_Function_Call
2185 or else Nkind
(Name
(Orig_Node
)) /= N_Expanded_Name
2186 or else Entity
(Prefix
(Name
(Orig_Node
))) /= Scope
(T
))
2188 and then not In_Instance
;
2190 end Is_Invisible_Operator
;
2196 function Is_Subtype_Of
(T1
: Entity_Id
; T2
: Entity_Id
) return Boolean is
2200 S
:= Ancestor_Subtype
(T1
);
2201 while Present
(S
) loop
2205 S
:= Ancestor_Subtype
(S
);
2216 procedure List_Interps
(Nam
: Node_Id
; Err
: Node_Id
) is
2217 Index
: Interp_Index
;
2221 Get_First_Interp
(Nam
, Index
, It
);
2222 while Present
(It
.Nam
) loop
2223 if Scope
(It
.Nam
) = Standard_Standard
2224 and then Scope
(It
.Typ
) /= Standard_Standard
2226 Error_Msg_Sloc
:= Sloc
(Parent
(It
.Typ
));
2227 Error_Msg_NE
(" & (inherited) declared#!", Err
, It
.Nam
);
2230 Error_Msg_Sloc
:= Sloc
(It
.Nam
);
2231 Error_Msg_NE
(" & declared#!", Err
, It
.Nam
);
2234 Get_Next_Interp
(Index
, It
);
2242 procedure New_Interps
(N
: Node_Id
) is
2246 All_Interp
.Increment_Last
;
2247 All_Interp
.Table
(All_Interp
.Last
) := No_Interp
;
2249 Map_Ptr
:= Headers
(Hash
(N
));
2251 if Map_Ptr
= No_Entry
then
2253 -- Place new node at end of table
2255 Interp_Map
.Increment_Last
;
2256 Headers
(Hash
(N
)) := Interp_Map
.Last
;
2259 -- Place node at end of chain, or locate its previous entry
2262 if Interp_Map
.Table
(Map_Ptr
).Node
= N
then
2264 -- Node is already in the table, and is being rewritten.
2265 -- Start a new interp section, retain hash link.
2267 Interp_Map
.Table
(Map_Ptr
).Node
:= N
;
2268 Interp_Map
.Table
(Map_Ptr
).Index
:= All_Interp
.Last
;
2269 Set_Is_Overloaded
(N
, True);
2273 exit when Interp_Map
.Table
(Map_Ptr
).Next
= No_Entry
;
2274 Map_Ptr
:= Interp_Map
.Table
(Map_Ptr
).Next
;
2278 -- Chain the new node
2280 Interp_Map
.Increment_Last
;
2281 Interp_Map
.Table
(Map_Ptr
).Next
:= Interp_Map
.Last
;
2284 Interp_Map
.Table
(Interp_Map
.Last
) := (N
, All_Interp
.Last
, No_Entry
);
2285 Set_Is_Overloaded
(N
, True);
2288 ---------------------------
2289 -- Operator_Matches_Spec --
2290 ---------------------------
2292 function Operator_Matches_Spec
(Op
, New_S
: Entity_Id
) return Boolean is
2293 Op_Name
: constant Name_Id
:= Chars
(Op
);
2294 T
: constant Entity_Id
:= Etype
(New_S
);
2302 -- To verify that a predefined operator matches a given signature,
2303 -- do a case analysis of the operator classes. Function can have one
2304 -- or two formals and must have the proper result type.
2306 New_F
:= First_Formal
(New_S
);
2307 Old_F
:= First_Formal
(Op
);
2309 while Present
(New_F
) and then Present
(Old_F
) loop
2311 Next_Formal
(New_F
);
2312 Next_Formal
(Old_F
);
2315 -- Definite mismatch if different number of parameters
2317 if Present
(Old_F
) or else Present
(New_F
) then
2323 T1
:= Etype
(First_Formal
(New_S
));
2325 if Op_Name
= Name_Op_Subtract
2326 or else Op_Name
= Name_Op_Add
2327 or else Op_Name
= Name_Op_Abs
2329 return Base_Type
(T1
) = Base_Type
(T
)
2330 and then Is_Numeric_Type
(T
);
2332 elsif Op_Name
= Name_Op_Not
then
2333 return Base_Type
(T1
) = Base_Type
(T
)
2334 and then Valid_Boolean_Arg
(Base_Type
(T
));
2343 T1
:= Etype
(First_Formal
(New_S
));
2344 T2
:= Etype
(Next_Formal
(First_Formal
(New_S
)));
2346 if Op_Name
= Name_Op_And
or else Op_Name
= Name_Op_Or
2347 or else Op_Name
= Name_Op_Xor
2349 return Base_Type
(T1
) = Base_Type
(T2
)
2350 and then Base_Type
(T1
) = Base_Type
(T
)
2351 and then Valid_Boolean_Arg
(Base_Type
(T
));
2353 elsif Op_Name
= Name_Op_Eq
or else Op_Name
= Name_Op_Ne
then
2354 return Base_Type
(T1
) = Base_Type
(T2
)
2355 and then not Is_Limited_Type
(T1
)
2356 and then Is_Boolean_Type
(T
);
2358 elsif Op_Name
= Name_Op_Lt
or else Op_Name
= Name_Op_Le
2359 or else Op_Name
= Name_Op_Gt
or else Op_Name
= Name_Op_Ge
2361 return Base_Type
(T1
) = Base_Type
(T2
)
2362 and then Valid_Comparison_Arg
(T1
)
2363 and then Is_Boolean_Type
(T
);
2365 elsif Op_Name
= Name_Op_Add
or else Op_Name
= Name_Op_Subtract
then
2366 return Base_Type
(T1
) = Base_Type
(T2
)
2367 and then Base_Type
(T1
) = Base_Type
(T
)
2368 and then Is_Numeric_Type
(T
);
2370 -- for division and multiplication, a user-defined function does
2371 -- not match the predefined universal_fixed operation, except in
2374 elsif Op_Name
= Name_Op_Divide
then
2375 return (Base_Type
(T1
) = Base_Type
(T2
)
2376 and then Base_Type
(T1
) = Base_Type
(T
)
2377 and then Is_Numeric_Type
(T
)
2378 and then (not Is_Fixed_Point_Type
(T
)
2379 or else Ada_Version
= Ada_83
))
2381 -- Mixed_Mode operations on fixed-point types
2383 or else (Base_Type
(T1
) = Base_Type
(T
)
2384 and then Base_Type
(T2
) = Base_Type
(Standard_Integer
)
2385 and then Is_Fixed_Point_Type
(T
))
2387 -- A user defined operator can also match (and hide) a mixed
2388 -- operation on universal literals.
2390 or else (Is_Integer_Type
(T2
)
2391 and then Is_Floating_Point_Type
(T1
)
2392 and then Base_Type
(T1
) = Base_Type
(T
));
2394 elsif Op_Name
= Name_Op_Multiply
then
2395 return (Base_Type
(T1
) = Base_Type
(T2
)
2396 and then Base_Type
(T1
) = Base_Type
(T
)
2397 and then Is_Numeric_Type
(T
)
2398 and then (not Is_Fixed_Point_Type
(T
)
2399 or else Ada_Version
= Ada_83
))
2401 -- Mixed_Mode operations on fixed-point types
2403 or else (Base_Type
(T1
) = Base_Type
(T
)
2404 and then Base_Type
(T2
) = Base_Type
(Standard_Integer
)
2405 and then Is_Fixed_Point_Type
(T
))
2407 or else (Base_Type
(T2
) = Base_Type
(T
)
2408 and then Base_Type
(T1
) = Base_Type
(Standard_Integer
)
2409 and then Is_Fixed_Point_Type
(T
))
2411 or else (Is_Integer_Type
(T2
)
2412 and then Is_Floating_Point_Type
(T1
)
2413 and then Base_Type
(T1
) = Base_Type
(T
))
2415 or else (Is_Integer_Type
(T1
)
2416 and then Is_Floating_Point_Type
(T2
)
2417 and then Base_Type
(T2
) = Base_Type
(T
));
2419 elsif Op_Name
= Name_Op_Mod
or else Op_Name
= Name_Op_Rem
then
2420 return Base_Type
(T1
) = Base_Type
(T2
)
2421 and then Base_Type
(T1
) = Base_Type
(T
)
2422 and then Is_Integer_Type
(T
);
2424 elsif Op_Name
= Name_Op_Expon
then
2425 return Base_Type
(T1
) = Base_Type
(T
)
2426 and then Is_Numeric_Type
(T
)
2427 and then Base_Type
(T2
) = Base_Type
(Standard_Integer
);
2429 elsif Op_Name
= Name_Op_Concat
then
2430 return Is_Array_Type
(T
)
2431 and then (Base_Type
(T
) = Base_Type
(Etype
(Op
)))
2432 and then (Base_Type
(T1
) = Base_Type
(T
)
2434 Base_Type
(T1
) = Base_Type
(Component_Type
(T
)))
2435 and then (Base_Type
(T2
) = Base_Type
(T
)
2437 Base_Type
(T2
) = Base_Type
(Component_Type
(T
)));
2443 end Operator_Matches_Spec
;
2449 procedure Remove_Interp
(I
: in out Interp_Index
) is
2453 -- Find end of Interp list and copy downward to erase the discarded one
2456 while Present
(All_Interp
.Table
(II
).Typ
) loop
2460 for J
in I
+ 1 .. II
loop
2461 All_Interp
.Table
(J
- 1) := All_Interp
.Table
(J
);
2464 -- Back up interp. index to insure that iterator will pick up next
2465 -- available interpretation.
2474 procedure Save_Interps
(Old_N
: Node_Id
; New_N
: Node_Id
) is
2476 O_N
: Node_Id
:= Old_N
;
2479 if Is_Overloaded
(Old_N
) then
2480 if Nkind
(Old_N
) = N_Selected_Component
2481 and then Is_Overloaded
(Selector_Name
(Old_N
))
2483 O_N
:= Selector_Name
(Old_N
);
2486 Map_Ptr
:= Headers
(Hash
(O_N
));
2488 while Interp_Map
.Table
(Map_Ptr
).Node
/= O_N
loop
2489 Map_Ptr
:= Interp_Map
.Table
(Map_Ptr
).Next
;
2490 pragma Assert
(Map_Ptr
/= No_Entry
);
2493 New_Interps
(New_N
);
2494 Interp_Map
.Table
(Interp_Map
.Last
).Index
:=
2495 Interp_Map
.Table
(Map_Ptr
).Index
;
2503 function Specific_Type
(T1
, T2
: Entity_Id
) return Entity_Id
is
2504 B1
: constant Entity_Id
:= Base_Type
(T1
);
2505 B2
: constant Entity_Id
:= Base_Type
(T2
);
2507 function Is_Remote_Access
(T
: Entity_Id
) return Boolean;
2508 -- Check whether T is the equivalent type of a remote access type.
2509 -- If distribution is enabled, T is a legal context for Null.
2511 ----------------------
2512 -- Is_Remote_Access --
2513 ----------------------
2515 function Is_Remote_Access
(T
: Entity_Id
) return Boolean is
2517 return Is_Record_Type
(T
)
2518 and then (Is_Remote_Call_Interface
(T
)
2519 or else Is_Remote_Types
(T
))
2520 and then Present
(Corresponding_Remote_Type
(T
))
2521 and then Is_Access_Type
(Corresponding_Remote_Type
(T
));
2522 end Is_Remote_Access
;
2524 -- Start of processing for Specific_Type
2527 if T1
= Any_Type
or else T2
= Any_Type
then
2535 or else (T1
= Universal_Integer
and then Is_Integer_Type
(T2
))
2536 or else (T1
= Universal_Real
and then Is_Real_Type
(T2
))
2537 or else (T1
= Universal_Fixed
and then Is_Fixed_Point_Type
(T2
))
2538 or else (T1
= Any_Fixed
and then Is_Fixed_Point_Type
(T2
))
2543 or else (T2
= Universal_Integer
and then Is_Integer_Type
(T1
))
2544 or else (T2
= Universal_Real
and then Is_Real_Type
(T1
))
2545 or else (T2
= Universal_Fixed
and then Is_Fixed_Point_Type
(T1
))
2546 or else (T2
= Any_Fixed
and then Is_Fixed_Point_Type
(T1
))
2550 elsif T2
= Any_String
and then Is_String_Type
(T1
) then
2553 elsif T1
= Any_String
and then Is_String_Type
(T2
) then
2556 elsif T2
= Any_Character
and then Is_Character_Type
(T1
) then
2559 elsif T1
= Any_Character
and then Is_Character_Type
(T2
) then
2562 elsif T1
= Any_Access
2563 and then (Is_Access_Type
(T2
) or else Is_Remote_Access
(T2
))
2567 elsif T2
= Any_Access
2568 and then (Is_Access_Type
(T1
) or else Is_Remote_Access
(T1
))
2572 elsif T2
= Any_Composite
2573 and then Ekind
(T1
) in E_Array_Type
.. E_Record_Subtype
2577 elsif T1
= Any_Composite
2578 and then Ekind
(T2
) in E_Array_Type
.. E_Record_Subtype
2582 elsif T1
= Any_Modular
and then Is_Modular_Integer_Type
(T2
) then
2585 elsif T2
= Any_Modular
and then Is_Modular_Integer_Type
(T1
) then
2588 -- ----------------------------------------------------------
2589 -- Special cases for equality operators (all other predefined
2590 -- operators can never apply to tagged types)
2591 -- ----------------------------------------------------------
2593 -- Ada 2005 (AI-251): T1 and T2 are class-wide types, and T2 is an
2596 elsif Is_Class_Wide_Type
(T1
)
2597 and then Is_Class_Wide_Type
(T2
)
2598 and then Is_Interface
(Etype
(T2
))
2602 -- Ada 2005 (AI-251): T1 is a concrete type that implements the
2603 -- class-wide interface T2
2605 elsif Is_Class_Wide_Type
(T2
)
2606 and then Is_Interface
(Etype
(T2
))
2607 and then Interface_Present_In_Ancestor
(Typ
=> T1
,
2608 Iface
=> Etype
(T2
))
2612 elsif Is_Class_Wide_Type
(T1
)
2613 and then Is_Ancestor
(Root_Type
(T1
), T2
)
2617 elsif Is_Class_Wide_Type
(T2
)
2618 and then Is_Ancestor
(Root_Type
(T2
), T1
)
2622 elsif (Ekind
(B1
) = E_Access_Subprogram_Type
2624 Ekind
(B1
) = E_Access_Protected_Subprogram_Type
)
2625 and then Ekind
(Designated_Type
(B1
)) /= E_Subprogram_Type
2626 and then Is_Access_Type
(T2
)
2630 elsif (Ekind
(B2
) = E_Access_Subprogram_Type
2632 Ekind
(B2
) = E_Access_Protected_Subprogram_Type
)
2633 and then Ekind
(Designated_Type
(B2
)) /= E_Subprogram_Type
2634 and then Is_Access_Type
(T1
)
2638 elsif (Ekind
(T1
) = E_Allocator_Type
2639 or else Ekind
(T1
) = E_Access_Attribute_Type
2640 or else Ekind
(T1
) = E_Anonymous_Access_Type
)
2641 and then Is_Access_Type
(T2
)
2645 elsif (Ekind
(T2
) = E_Allocator_Type
2646 or else Ekind
(T2
) = E_Access_Attribute_Type
2647 or else Ekind
(T2
) = E_Anonymous_Access_Type
)
2648 and then Is_Access_Type
(T1
)
2652 -- If none of the above cases applies, types are not compatible
2659 -----------------------
2660 -- Valid_Boolean_Arg --
2661 -----------------------
2663 -- In addition to booleans and arrays of booleans, we must include
2664 -- aggregates as valid boolean arguments, because in the first pass of
2665 -- resolution their components are not examined. If it turns out not to be
2666 -- an aggregate of booleans, this will be diagnosed in Resolve.
2667 -- Any_Composite must be checked for prior to the array type checks because
2668 -- Any_Composite does not have any associated indexes.
2670 function Valid_Boolean_Arg
(T
: Entity_Id
) return Boolean is
2672 return Is_Boolean_Type
(T
)
2673 or else T
= Any_Composite
2674 or else (Is_Array_Type
(T
)
2675 and then T
/= Any_String
2676 and then Number_Dimensions
(T
) = 1
2677 and then Is_Boolean_Type
(Component_Type
(T
))
2678 and then (not Is_Private_Composite
(T
)
2679 or else In_Instance
)
2680 and then (not Is_Limited_Composite
(T
)
2681 or else In_Instance
))
2682 or else Is_Modular_Integer_Type
(T
)
2683 or else T
= Universal_Integer
;
2684 end Valid_Boolean_Arg
;
2686 --------------------------
2687 -- Valid_Comparison_Arg --
2688 --------------------------
2690 function Valid_Comparison_Arg
(T
: Entity_Id
) return Boolean is
2693 if T
= Any_Composite
then
2695 elsif Is_Discrete_Type
(T
)
2696 or else Is_Real_Type
(T
)
2699 elsif Is_Array_Type
(T
)
2700 and then Number_Dimensions
(T
) = 1
2701 and then Is_Discrete_Type
(Component_Type
(T
))
2702 and then (not Is_Private_Composite
(T
)
2703 or else In_Instance
)
2704 and then (not Is_Limited_Composite
(T
)
2705 or else In_Instance
)
2708 elsif Is_String_Type
(T
) then
2713 end Valid_Comparison_Arg
;
2715 ---------------------
2716 -- Write_Overloads --
2717 ---------------------
2719 procedure Write_Overloads
(N
: Node_Id
) is
2725 if not Is_Overloaded
(N
) then
2726 Write_Str
("Non-overloaded entity ");
2728 Write_Entity_Info
(Entity
(N
), " ");
2731 Get_First_Interp
(N
, I
, It
);
2732 Write_Str
("Overloaded entity ");
2736 while Present
(Nam
) loop
2737 Write_Entity_Info
(Nam
, " ");
2738 Write_Str
("=================");
2740 Get_Next_Interp
(I
, It
);
2744 end Write_Overloads
;
2746 ----------------------
2747 -- Write_Interp_Ref --
2748 ----------------------
2750 procedure Write_Interp_Ref
(Map_Ptr
: Int
) is
2752 Write_Str
(" Node: ");
2753 Write_Int
(Int
(Interp_Map
.Table
(Map_Ptr
).Node
));
2754 Write_Str
(" Index: ");
2755 Write_Int
(Int
(Interp_Map
.Table
(Map_Ptr
).Index
));
2756 Write_Str
(" Next: ");
2757 Write_Int
(Int
(Interp_Map
.Table
(Map_Ptr
).Next
));
2759 end Write_Interp_Ref
;