* config/arm/arm.md (addsi3_cbranch_scratch): Correct constraints.
[official-gcc.git] / gcc / ada / sem_type.adb
blob8d0cf7577e034ace8cad2f4f69e2b42d37bdcbee
1 ------------------------------------------------------------------------------
2 -- --
3 -- GNAT COMPILER COMPONENTS --
4 -- --
5 -- S E M _ T Y P E --
6 -- --
7 -- B o d y --
8 -- --
9 -- Copyright (C) 1992-2004 Free Software Foundation, Inc. --
10 -- --
11 -- GNAT is free software; you can redistribute it and/or modify it under --
12 -- terms of the GNU General Public License as published by the Free Soft- --
13 -- ware Foundation; either version 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. --
21 -- --
22 -- GNAT was originally developed by the GNAT team at New York University. --
23 -- Extensive contributions were provided by Ada Core Technologies Inc. --
24 -- --
25 ------------------------------------------------------------------------------
27 with Atree; use Atree;
28 with Alloc;
29 with Debug; use Debug;
30 with Einfo; use Einfo;
31 with Errout; use Errout;
32 with Lib; use Lib;
33 with Opt; use Opt;
34 with Output; use Output;
35 with Sem; use Sem;
36 with Sem_Ch6; use Sem_Ch6;
37 with Sem_Ch8; use Sem_Ch8;
38 with Sem_Util; use Sem_Util;
39 with Stand; use Stand;
40 with Sinfo; use Sinfo;
41 with Snames; use Snames;
42 with Table;
43 with Uintp; use Uintp;
45 package body Sem_Type is
47 ---------------------
48 -- Data Structures --
49 ---------------------
51 -- The following data structures establish a mapping between nodes and
52 -- their interpretations. An overloaded node has an entry in Interp_Map,
53 -- which in turn contains a pointer into the All_Interp array. The
54 -- interpretations of a given node are contiguous in All_Interp. Each
55 -- set of interpretations is terminated with the marker No_Interp.
56 -- In order to speed up the retrieval of the interpretations of an
57 -- overloaded node, the Interp_Map table is accessed by means of a simple
58 -- hashing scheme, and the entries in Interp_Map are chained. The heads
59 -- of clash lists are stored in array Headers.
61 -- Headers Interp_Map All_Interp
63 -- _ +-----+ +--------+
64 -- |_| |_____| --->|interp1 |
65 -- |_|---------->|node | | |interp2 |
66 -- |_| |index|---------| |nointerp|
67 -- |_| |next | | |
68 -- |-----| | |
69 -- +-----+ +--------+
71 -- This scheme does not currently reclaim interpretations. In principle,
72 -- after a unit is compiled, all overloadings have been resolved, and the
73 -- candidate interpretations should be deleted. This should be easier
74 -- now than with the previous scheme???
76 package All_Interp is new Table.Table (
77 Table_Component_Type => Interp,
78 Table_Index_Type => Int,
79 Table_Low_Bound => 0,
80 Table_Initial => Alloc.All_Interp_Initial,
81 Table_Increment => Alloc.All_Interp_Increment,
82 Table_Name => "All_Interp");
84 type Interp_Ref is record
85 Node : Node_Id;
86 Index : Interp_Index;
87 Next : Int;
88 end record;
90 Header_Size : constant Int := 2 ** 12;
91 No_Entry : constant Int := -1;
92 Headers : array (0 .. Header_Size) of Int := (others => No_Entry);
94 package Interp_Map is new Table.Table (
95 Table_Component_Type => Interp_Ref,
96 Table_Index_Type => Int,
97 Table_Low_Bound => 0,
98 Table_Initial => Alloc.Interp_Map_Initial,
99 Table_Increment => Alloc.Interp_Map_Increment,
100 Table_Name => "Interp_Map");
102 function Hash (N : Node_Id) return Int;
103 -- A trivial hashing function for nodes, used to insert an overloaded
104 -- node into the Interp_Map table.
106 -------------------------------------
107 -- Handling of Overload Resolution --
108 -------------------------------------
110 -- Overload resolution uses two passes over the syntax tree of a complete
111 -- context. In the first, bottom-up pass, the types of actuals in calls
112 -- are used to resolve possibly overloaded subprogram and operator names.
113 -- In the second top-down pass, the type of the context (for example the
114 -- condition in a while statement) is used to resolve a possibly ambiguous
115 -- call, and the unique subprogram name in turn imposes a specific context
116 -- on each of its actuals.
118 -- Most expressions are in fact unambiguous, and the bottom-up pass is
119 -- sufficient to resolve most everything. To simplify the common case,
120 -- names and expressions carry a flag Is_Overloaded to indicate whether
121 -- they have more than one interpretation. If the flag is off, then each
122 -- name has already a unique meaning and type, and the bottom-up pass is
123 -- sufficient (and much simpler).
125 --------------------------
126 -- Operator Overloading --
127 --------------------------
129 -- The visibility of operators is handled differently from that of
130 -- other entities. We do not introduce explicit versions of primitive
131 -- operators for each type definition. As a result, there is only one
132 -- entity corresponding to predefined addition on all numeric types, etc.
133 -- The back-end resolves predefined operators according to their type.
134 -- The visibility of primitive operations then reduces to the visibility
135 -- of the resulting type: (a + b) is a legal interpretation of some
136 -- primitive operator + if the type of the result (which must also be
137 -- the type of a and b) is directly visible (i.e. either immediately
138 -- visible or use-visible.)
140 -- User-defined operators are treated like other functions, but the
141 -- visibility of these user-defined operations must be special-cased
142 -- to determine whether they hide or are hidden by predefined operators.
143 -- The form P."+" (x, y) requires additional handling.
145 -- Concatenation is treated more conventionally: for every one-dimensional
146 -- array type we introduce a explicit concatenation operator. This is
147 -- necessary to handle the case of (element & element => array) which
148 -- cannot be handled conveniently if there is no explicit instance of
149 -- resulting type of the operation.
151 -----------------------
152 -- Local Subprograms --
153 -----------------------
155 procedure All_Overloads;
156 pragma Warnings (Off, All_Overloads);
157 -- Debugging procedure: list full contents of Overloads table
159 procedure New_Interps (N : Node_Id);
160 -- Initialize collection of interpretations for the given node, which is
161 -- either an overloaded entity, or an operation whose arguments have
162 -- multiple intepretations. Interpretations can be added to only one
163 -- node at a time.
165 function Specific_Type (T1, T2 : Entity_Id) return Entity_Id;
166 -- If T1 and T2 are compatible, return the one that is not
167 -- universal or is not a "class" type (any_character, etc).
169 --------------------
170 -- Add_One_Interp --
171 --------------------
173 procedure Add_One_Interp
174 (N : Node_Id;
175 E : Entity_Id;
176 T : Entity_Id;
177 Opnd_Type : Entity_Id := Empty)
179 Vis_Type : Entity_Id;
181 procedure Add_Entry (Name : Entity_Id; Typ : Entity_Id);
182 -- Add one interpretation to node. Node is already known to be
183 -- overloaded. Add new interpretation if not hidden by previous
184 -- one, and remove previous one if hidden by new one.
186 function Is_Universal_Operation (Op : Entity_Id) return Boolean;
187 -- True if the entity is a predefined operator and the operands have
188 -- a universal Interpretation.
190 ---------------
191 -- Add_Entry --
192 ---------------
194 procedure Add_Entry (Name : Entity_Id; Typ : Entity_Id) is
195 Index : Interp_Index;
196 It : Interp;
198 begin
199 Get_First_Interp (N, Index, It);
200 while Present (It.Nam) loop
202 -- A user-defined subprogram hides another declared at an outer
203 -- level, or one that is use-visible. So return if previous
204 -- definition hides new one (which is either in an outer
205 -- scope, or use-visible). Note that for functions use-visible
206 -- is the same as potentially use-visible. If new one hides
207 -- previous one, replace entry in table of interpretations.
208 -- If this is a universal operation, retain the operator in case
209 -- preference rule applies.
211 if (((Ekind (Name) = E_Function or else Ekind (Name) = E_Procedure)
212 and then Ekind (Name) = Ekind (It.Nam))
213 or else (Ekind (Name) = E_Operator
214 and then Ekind (It.Nam) = E_Function))
216 and then Is_Immediately_Visible (It.Nam)
217 and then Type_Conformant (Name, It.Nam)
218 and then Base_Type (It.Typ) = Base_Type (T)
219 then
220 if Is_Universal_Operation (Name) then
221 exit;
223 -- If node is an operator symbol, we have no actuals with
224 -- which to check hiding, and this is done in full in the
225 -- caller (Analyze_Subprogram_Renaming) so we include the
226 -- predefined operator in any case.
228 elsif Nkind (N) = N_Operator_Symbol
229 or else (Nkind (N) = N_Expanded_Name
230 and then
231 Nkind (Selector_Name (N)) = N_Operator_Symbol)
232 then
233 exit;
235 elsif not In_Open_Scopes (Scope (Name))
236 or else Scope_Depth (Scope (Name)) <=
237 Scope_Depth (Scope (It.Nam))
238 then
239 -- If ambiguity within instance, and entity is not an
240 -- implicit operation, save for later disambiguation.
242 if Scope (Name) = Scope (It.Nam)
243 and then not Is_Inherited_Operation (Name)
244 and then In_Instance
245 then
246 exit;
247 else
248 return;
249 end if;
251 else
252 All_Interp.Table (Index).Nam := Name;
253 return;
254 end if;
256 -- Avoid making duplicate entries in overloads
258 elsif Name = It.Nam
259 and then Base_Type (It.Typ) = Base_Type (T)
260 then
261 return;
263 -- Otherwise keep going
265 else
266 Get_Next_Interp (Index, It);
267 end if;
269 end loop;
271 -- On exit, enter new interpretation. The context, or a preference
272 -- rule, will resolve the ambiguity on the second pass.
274 All_Interp.Table (All_Interp.Last) := (Name, Typ);
275 All_Interp.Increment_Last;
276 All_Interp.Table (All_Interp.Last) := No_Interp;
277 end Add_Entry;
279 ----------------------------
280 -- Is_Universal_Operation --
281 ----------------------------
283 function Is_Universal_Operation (Op : Entity_Id) return Boolean is
284 Arg : Node_Id;
286 begin
287 if Ekind (Op) /= E_Operator then
288 return False;
290 elsif Nkind (N) in N_Binary_Op then
291 return Present (Universal_Interpretation (Left_Opnd (N)))
292 and then Present (Universal_Interpretation (Right_Opnd (N)));
294 elsif Nkind (N) in N_Unary_Op then
295 return Present (Universal_Interpretation (Right_Opnd (N)));
297 elsif Nkind (N) = N_Function_Call then
298 Arg := First_Actual (N);
299 while Present (Arg) loop
300 if No (Universal_Interpretation (Arg)) then
301 return False;
302 end if;
304 Next_Actual (Arg);
305 end loop;
307 return True;
309 else
310 return False;
311 end if;
312 end Is_Universal_Operation;
314 -- Start of processing for Add_One_Interp
316 begin
317 -- If the interpretation is a predefined operator, verify that the
318 -- result type is visible, or that the entity has already been
319 -- resolved (case of an instantiation node that refers to a predefined
320 -- operation, or an internally generated operator node, or an operator
321 -- given as an expanded name). If the operator is a comparison or
322 -- equality, it is the type of the operand that matters to determine
323 -- whether the operator is visible. In an instance, the check is not
324 -- performed, given that the operator was visible in the generic.
326 if Ekind (E) = E_Operator then
328 if Present (Opnd_Type) then
329 Vis_Type := Opnd_Type;
330 else
331 Vis_Type := Base_Type (T);
332 end if;
334 if In_Open_Scopes (Scope (Vis_Type))
335 or else Is_Potentially_Use_Visible (Vis_Type)
336 or else In_Use (Vis_Type)
337 or else (In_Use (Scope (Vis_Type))
338 and then not Is_Hidden (Vis_Type))
339 or else Nkind (N) = N_Expanded_Name
340 or else (Nkind (N) in N_Op and then E = Entity (N))
341 or else In_Instance
342 then
343 null;
345 -- If the node is given in functional notation and the prefix
346 -- is an expanded name, then the operator is visible if the
347 -- prefix is the scope of the result type as well. If the
348 -- operator is (implicitly) defined in an extension of system,
349 -- it is know to be valid (see Defined_In_Scope, sem_ch4.adb).
351 elsif Nkind (N) = N_Function_Call
352 and then Nkind (Name (N)) = N_Expanded_Name
353 and then (Entity (Prefix (Name (N))) = Scope (Base_Type (T))
354 or else Entity (Prefix (Name (N))) = Scope (Vis_Type)
355 or else Scope (Vis_Type) = System_Aux_Id)
356 then
357 null;
359 -- Save type for subsequent error message, in case no other
360 -- interpretation is found.
362 else
363 Candidate_Type := Vis_Type;
364 return;
365 end if;
367 -- In an instance, an abstract non-dispatching operation cannot
368 -- be a candidate interpretation, because it could not have been
369 -- one in the generic (it may be a spurious overloading in the
370 -- instance).
372 elsif In_Instance
373 and then Is_Abstract (E)
374 and then not Is_Dispatching_Operation (E)
375 then
376 return;
377 end if;
379 -- If this is the first interpretation of N, N has type Any_Type.
380 -- In that case place the new type on the node. If one interpretation
381 -- already exists, indicate that the node is overloaded, and store
382 -- both the previous and the new interpretation in All_Interp. If
383 -- this is a later interpretation, just add it to the set.
385 if Etype (N) = Any_Type then
386 if Is_Type (E) then
387 Set_Etype (N, T);
389 else
390 -- Record both the operator or subprogram name, and its type
392 if Nkind (N) in N_Op or else Is_Entity_Name (N) then
393 Set_Entity (N, E);
394 end if;
396 Set_Etype (N, T);
397 end if;
399 -- Either there is no current interpretation in the table for any
400 -- node or the interpretation that is present is for a different
401 -- node. In both cases add a new interpretation to the table.
403 elsif Interp_Map.Last < 0
404 or else
405 (Interp_Map.Table (Interp_Map.Last).Node /= N
406 and then not Is_Overloaded (N))
407 then
408 New_Interps (N);
410 if (Nkind (N) in N_Op or else Is_Entity_Name (N))
411 and then Present (Entity (N))
412 then
413 Add_Entry (Entity (N), Etype (N));
415 elsif (Nkind (N) = N_Function_Call
416 or else Nkind (N) = N_Procedure_Call_Statement)
417 and then (Nkind (Name (N)) = N_Operator_Symbol
418 or else Is_Entity_Name (Name (N)))
419 then
420 Add_Entry (Entity (Name (N)), Etype (N));
422 else
423 -- Overloaded prefix in indexed or selected component,
424 -- or call whose name is an expresion or another call.
426 Add_Entry (Etype (N), Etype (N));
427 end if;
429 Add_Entry (E, T);
431 else
432 Add_Entry (E, T);
433 end if;
434 end Add_One_Interp;
436 -------------------
437 -- All_Overloads --
438 -------------------
440 procedure All_Overloads is
441 begin
442 for J in All_Interp.First .. All_Interp.Last loop
444 if Present (All_Interp.Table (J).Nam) then
445 Write_Entity_Info (All_Interp.Table (J). Nam, " ");
446 else
447 Write_Str ("No Interp");
448 end if;
450 Write_Str ("=================");
451 Write_Eol;
452 end loop;
453 end All_Overloads;
455 ---------------------
456 -- Collect_Interps --
457 ---------------------
459 procedure Collect_Interps (N : Node_Id) is
460 Ent : constant Entity_Id := Entity (N);
461 H : Entity_Id;
462 First_Interp : Interp_Index;
464 begin
465 New_Interps (N);
467 -- Unconditionally add the entity that was initially matched
469 First_Interp := All_Interp.Last;
470 Add_One_Interp (N, Ent, Etype (N));
472 -- For expanded name, pick up all additional entities from the
473 -- same scope, since these are obviously also visible. Note that
474 -- these are not necessarily contiguous on the homonym chain.
476 if Nkind (N) = N_Expanded_Name then
477 H := Homonym (Ent);
478 while Present (H) loop
479 if Scope (H) = Scope (Entity (N)) then
480 Add_One_Interp (N, H, Etype (H));
481 end if;
483 H := Homonym (H);
484 end loop;
486 -- Case of direct name
488 else
489 -- First, search the homonym chain for directly visible entities
491 H := Current_Entity (Ent);
492 while Present (H) loop
493 exit when (not Is_Overloadable (H))
494 and then Is_Immediately_Visible (H);
496 if Is_Immediately_Visible (H)
497 and then H /= Ent
498 then
499 -- Only add interpretation if not hidden by an inner
500 -- immediately visible one.
502 for J in First_Interp .. All_Interp.Last - 1 loop
504 -- Current homograph is not hidden. Add to overloads
506 if not Is_Immediately_Visible (All_Interp.Table (J).Nam) then
507 exit;
509 -- Homograph is hidden, unless it is a predefined operator
511 elsif Type_Conformant (H, All_Interp.Table (J).Nam) then
513 -- A homograph in the same scope can occur within an
514 -- instantiation, the resulting ambiguity has to be
515 -- resolved later.
517 if Scope (H) = Scope (Ent)
518 and then In_Instance
519 and then not Is_Inherited_Operation (H)
520 then
521 All_Interp.Table (All_Interp.Last) := (H, Etype (H));
522 All_Interp.Increment_Last;
523 All_Interp.Table (All_Interp.Last) := No_Interp;
524 goto Next_Homograph;
526 elsif Scope (H) /= Standard_Standard then
527 goto Next_Homograph;
528 end if;
529 end if;
530 end loop;
532 -- On exit, we know that current homograph is not hidden.
534 Add_One_Interp (N, H, Etype (H));
536 if Debug_Flag_E then
537 Write_Str ("Add overloaded Interpretation ");
538 Write_Int (Int (H));
539 Write_Eol;
540 end if;
541 end if;
543 <<Next_Homograph>>
544 H := Homonym (H);
545 end loop;
547 -- Scan list of homographs for use-visible entities only
549 H := Current_Entity (Ent);
551 while Present (H) loop
552 if Is_Potentially_Use_Visible (H)
553 and then H /= Ent
554 and then Is_Overloadable (H)
555 then
556 for J in First_Interp .. All_Interp.Last - 1 loop
558 if not Is_Immediately_Visible (All_Interp.Table (J).Nam) then
559 exit;
561 elsif Type_Conformant (H, All_Interp.Table (J).Nam) then
562 goto Next_Use_Homograph;
563 end if;
564 end loop;
566 Add_One_Interp (N, H, Etype (H));
567 end if;
569 <<Next_Use_Homograph>>
570 H := Homonym (H);
571 end loop;
572 end if;
574 if All_Interp.Last = First_Interp + 1 then
576 -- The original interpretation is in fact not overloaded
578 Set_Is_Overloaded (N, False);
579 end if;
580 end Collect_Interps;
582 ------------
583 -- Covers --
584 ------------
586 function Covers (T1, T2 : Entity_Id) return Boolean is
588 function Full_View_Covers (Typ1, Typ2 : Entity_Id) return Boolean;
589 -- In an instance the proper view may not always be correct for
590 -- private types, but private and full view are compatible. This
591 -- removes spurious errors from nested instantiations that involve,
592 -- among other things, types derived from private types.
594 ----------------------
595 -- Full_View_Covers --
596 ----------------------
598 function Full_View_Covers (Typ1, Typ2 : Entity_Id) return Boolean is
599 begin
600 return
601 Is_Private_Type (Typ1)
602 and then
603 ((Present (Full_View (Typ1))
604 and then Covers (Full_View (Typ1), Typ2))
605 or else Base_Type (Typ1) = Typ2
606 or else Base_Type (Typ2) = Typ1);
607 end Full_View_Covers;
609 -- Start of processing for Covers
611 begin
612 -- If either operand missing, then this is an error, but ignore
613 -- it (and pretend we have a cover) if errors already detected,
614 -- since this may simply mean we have malformed trees.
616 if No (T1) or else No (T2) then
617 if Total_Errors_Detected /= 0 then
618 return True;
619 else
620 raise Program_Error;
621 end if;
622 end if;
624 -- Simplest case: same types are compatible, and types that have the
625 -- same base type and are not generic actuals are compatible. Generic
626 -- actuals belong to their class but are not compatible with other
627 -- types of their class, and in particular with other generic actuals.
628 -- They are however compatible with their own subtypes, and itypes
629 -- with the same base are compatible as well. Similary, constrained
630 -- subtypes obtained from expressions of an unconstrained nominal type
631 -- are compatible with the base type (may lead to spurious ambiguities
632 -- in obscure cases ???)
634 -- Generic actuals require special treatment to avoid spurious ambi-
635 -- guities in an instance, when two formal types are instantiated with
636 -- the same actual, so that different subprograms end up with the same
637 -- signature in the instance.
639 if T1 = T2 then
640 return True;
642 elsif Base_Type (T1) = Base_Type (T2) then
643 if not Is_Generic_Actual_Type (T1) then
644 return True;
645 else
646 return (not Is_Generic_Actual_Type (T2)
647 or else Is_Itype (T1)
648 or else Is_Itype (T2)
649 or else Is_Constr_Subt_For_U_Nominal (T1)
650 or else Is_Constr_Subt_For_U_Nominal (T2)
651 or else Scope (T1) /= Scope (T2));
652 end if;
654 -- Literals are compatible with types in a given "class"
656 elsif (T2 = Universal_Integer and then Is_Integer_Type (T1))
657 or else (T2 = Universal_Real and then Is_Real_Type (T1))
658 or else (T2 = Universal_Fixed and then Is_Fixed_Point_Type (T1))
659 or else (T2 = Any_Fixed and then Is_Fixed_Point_Type (T1))
660 or else (T2 = Any_String and then Is_String_Type (T1))
661 or else (T2 = Any_Character and then Is_Character_Type (T1))
662 or else (T2 = Any_Access and then Is_Access_Type (T1))
663 then
664 return True;
666 -- The context may be class wide
668 elsif Is_Class_Wide_Type (T1)
669 and then Is_Ancestor (Root_Type (T1), T2)
670 then
671 return True;
673 elsif Is_Class_Wide_Type (T1)
674 and then Is_Class_Wide_Type (T2)
675 and then Base_Type (Etype (T1)) = Base_Type (Etype (T2))
676 then
677 return True;
679 -- In a dispatching call the actual may be class-wide
681 elsif Is_Class_Wide_Type (T2)
682 and then Base_Type (Root_Type (T2)) = Base_Type (T1)
683 then
684 return True;
686 -- Some contexts require a class of types rather than a specific type
688 elsif (T1 = Any_Integer and then Is_Integer_Type (T2))
689 or else (T1 = Any_Boolean and then Is_Boolean_Type (T2))
690 or else (T1 = Any_Real and then Is_Real_Type (T2))
691 or else (T1 = Any_Fixed and then Is_Fixed_Point_Type (T2))
692 or else (T1 = Any_Discrete and then Is_Discrete_Type (T2))
693 then
694 return True;
696 -- An aggregate is compatible with an array or record type
698 elsif T2 = Any_Composite
699 and then Ekind (T1) in E_Array_Type .. E_Record_Subtype
700 then
701 return True;
703 -- If the expected type is an anonymous access, the designated
704 -- type must cover that of the expression.
706 elsif Ekind (T1) = E_Anonymous_Access_Type
707 and then Is_Access_Type (T2)
708 and then Covers (Designated_Type (T1), Designated_Type (T2))
709 then
710 return True;
712 -- An Access_To_Subprogram is compatible with itself, or with an
713 -- anonymous type created for an attribute reference Access.
715 elsif (Ekind (Base_Type (T1)) = E_Access_Subprogram_Type
716 or else
717 Ekind (Base_Type (T1)) = E_Access_Protected_Subprogram_Type)
718 and then Is_Access_Type (T2)
719 and then (not Comes_From_Source (T1)
720 or else not Comes_From_Source (T2))
721 and then (Is_Overloadable (Designated_Type (T2))
722 or else
723 Ekind (Designated_Type (T2)) = E_Subprogram_Type)
724 and then
725 Type_Conformant (Designated_Type (T1), Designated_Type (T2))
726 and then
727 Mode_Conformant (Designated_Type (T1), Designated_Type (T2))
728 then
729 return True;
731 -- Ada 2005 (AI-254): An Anonymous_Access_To_Subprogram is compatible
732 -- with itself, or with an anonymous type created for an attribute
733 -- reference Access.
735 elsif (Ekind (Base_Type (T1)) = E_Anonymous_Access_Subprogram_Type
736 or else
737 Ekind (Base_Type (T1))
738 = E_Anonymous_Access_Protected_Subprogram_Type)
739 and then Is_Access_Type (T2)
740 and then (not Comes_From_Source (T1)
741 or else not Comes_From_Source (T2))
742 and then (Is_Overloadable (Designated_Type (T2))
743 or else
744 Ekind (Designated_Type (T2)) = E_Subprogram_Type)
745 and then
746 Type_Conformant (Designated_Type (T1), Designated_Type (T2))
747 and then
748 Mode_Conformant (Designated_Type (T1), Designated_Type (T2))
749 then
750 return True;
752 -- The context can be a remote access type, and the expression the
753 -- corresponding source type declared in a categorized package, or
754 -- viceversa.
756 elsif Is_Record_Type (T1)
757 and then (Is_Remote_Call_Interface (T1)
758 or else Is_Remote_Types (T1))
759 and then Present (Corresponding_Remote_Type (T1))
760 then
761 return Covers (Corresponding_Remote_Type (T1), T2);
763 elsif Is_Record_Type (T2)
764 and then (Is_Remote_Call_Interface (T2)
765 or else Is_Remote_Types (T2))
766 and then Present (Corresponding_Remote_Type (T2))
767 then
768 return Covers (Corresponding_Remote_Type (T2), T1);
770 elsif Ekind (T2) = E_Access_Attribute_Type
771 and then (Ekind (Base_Type (T1)) = E_General_Access_Type
772 or else Ekind (Base_Type (T1)) = E_Access_Type)
773 and then Covers (Designated_Type (T1), Designated_Type (T2))
774 then
775 -- If the target type is a RACW type while the source is an access
776 -- attribute type, we are building a RACW that may be exported.
778 if Is_Remote_Access_To_Class_Wide_Type (Base_Type (T1)) then
779 Set_Has_RACW (Current_Sem_Unit);
780 end if;
782 return True;
784 elsif Ekind (T2) = E_Allocator_Type
785 and then Is_Access_Type (T1)
786 then
787 return Covers (Designated_Type (T1), Designated_Type (T2))
788 or else
789 (From_With_Type (Designated_Type (T1))
790 and then Covers (Designated_Type (T2), Designated_Type (T1)));
792 -- A boolean operation on integer literals is compatible with a
793 -- modular context.
795 elsif T2 = Any_Modular
796 and then Is_Modular_Integer_Type (T1)
797 then
798 return True;
800 -- The actual type may be the result of a previous error
802 elsif Base_Type (T2) = Any_Type then
803 return True;
805 -- A packed array type covers its corresponding non-packed type.
806 -- This is not legitimate Ada, but allows the omission of a number
807 -- of otherwise useless unchecked conversions, and since this can
808 -- only arise in (known correct) expanded code, no harm is done
810 elsif Is_Array_Type (T2)
811 and then Is_Packed (T2)
812 and then T1 = Packed_Array_Type (T2)
813 then
814 return True;
816 -- Similarly an array type covers its corresponding packed array type
818 elsif Is_Array_Type (T1)
819 and then Is_Packed (T1)
820 and then T2 = Packed_Array_Type (T1)
821 then
822 return True;
824 elsif In_Instance
825 and then
826 (Full_View_Covers (T1, T2)
827 or else Full_View_Covers (T2, T1))
828 then
829 return True;
831 -- In the expansion of inlined bodies, types are compatible if they
832 -- are structurally equivalent.
834 elsif In_Inlined_Body
835 and then (Underlying_Type (T1) = Underlying_Type (T2)
836 or else (Is_Access_Type (T1)
837 and then Is_Access_Type (T2)
838 and then
839 Designated_Type (T1) = Designated_Type (T2))
840 or else (T1 = Any_Access
841 and then Is_Access_Type (Underlying_Type (T2))))
842 then
843 return True;
845 -- Ada 2005 (AI-50217): Additional branches to make the shadow entity
846 -- compatible with its real entity.
848 elsif From_With_Type (T1) then
850 -- If the expected type is the non-limited view of a type, the
851 -- expression may have the limited view.
853 if Ekind (T1) = E_Incomplete_Type then
854 return Covers (Non_Limited_View (T1), T2);
856 elsif Ekind (T1) = E_Class_Wide_Type then
857 return
858 Covers (Class_Wide_Type (Non_Limited_View (Etype (T1))), T2);
859 else
860 return False;
861 end if;
863 elsif From_With_Type (T2) then
865 -- If units in the context have Limited_With clauses on each other,
866 -- either type might have a limited view. Checks performed elsewhere
867 -- verify that the context type is the non-limited view.
869 if Ekind (T2) = E_Incomplete_Type then
870 return Covers (T1, Non_Limited_View (T2));
872 elsif Ekind (T2) = E_Class_Wide_Type then
873 return
874 Covers (T1, Class_Wide_Type (Non_Limited_View (Etype (T2))));
875 else
876 return False;
877 end if;
879 -- Otherwise it doesn't cover!
881 else
882 return False;
883 end if;
884 end Covers;
886 ------------------
887 -- Disambiguate --
888 ------------------
890 function Disambiguate
891 (N : Node_Id;
892 I1, I2 : Interp_Index;
893 Typ : Entity_Id)
894 return Interp
896 I : Interp_Index;
897 It : Interp;
898 It1, It2 : Interp;
899 Nam1, Nam2 : Entity_Id;
900 Predef_Subp : Entity_Id;
901 User_Subp : Entity_Id;
903 function Inherited_From_Actual (S : Entity_Id) return Boolean;
904 -- Determine whether one of the candidates is an operation inherited
905 -- by a type that is derived from an actual in an instantiation.
907 function Is_Actual_Subprogram (S : Entity_Id) return Boolean;
908 -- Determine whether a subprogram is an actual in an enclosing
909 -- instance. An overloading between such a subprogram and one
910 -- declared outside the instance is resolved in favor of the first,
911 -- because it resolved in the generic.
913 function Matches (Actual, Formal : Node_Id) return Boolean;
914 -- Look for exact type match in an instance, to remove spurious
915 -- ambiguities when two formal types have the same actual.
917 function Standard_Operator return Boolean;
918 -- Comment required ???
920 function Remove_Conversions return Interp;
921 -- Last chance for pathological cases involving comparisons on
922 -- literals, and user overloadings of the same operator. Such
923 -- pathologies have been removed from the ACVC, but still appear in
924 -- two DEC tests, with the following notable quote from Ben Brosgol:
926 -- [Note: I disclaim all credit/responsibility/blame for coming up with
927 -- this example; Robert Dewar brought it to our attention, since it
928 -- is apparently found in the ACVC 1.5. I did not attempt to find
929 -- the reason in the Reference Manual that makes the example legal,
930 -- since I was too nauseated by it to want to pursue it further.]
932 -- Accordingly, this is not a fully recursive solution, but it handles
933 -- DEC tests c460vsa, c460vsb. It also handles ai00136a, which pushes
934 -- pathology in the other direction with calls whose multiple overloaded
935 -- actuals make them truly unresolvable.
937 ---------------------------
938 -- Inherited_From_Actual --
939 ---------------------------
941 function Inherited_From_Actual (S : Entity_Id) return Boolean is
942 Par : constant Node_Id := Parent (S);
943 begin
944 if Nkind (Par) /= N_Full_Type_Declaration
945 or else Nkind (Type_Definition (Par)) /= N_Derived_Type_Definition
946 then
947 return False;
948 else
949 return Is_Entity_Name (Subtype_Indication (Type_Definition (Par)))
950 and then
951 Is_Generic_Actual_Type (
952 Entity (Subtype_Indication (Type_Definition (Par))));
953 end if;
954 end Inherited_From_Actual;
956 --------------------------
957 -- Is_Actual_Subprogram --
958 --------------------------
960 function Is_Actual_Subprogram (S : Entity_Id) return Boolean is
961 begin
962 return In_Open_Scopes (Scope (S))
963 and then
964 (Is_Generic_Instance (Scope (S))
965 or else Is_Wrapper_Package (Scope (S)));
966 end Is_Actual_Subprogram;
968 -------------
969 -- Matches --
970 -------------
972 function Matches (Actual, Formal : Node_Id) return Boolean is
973 T1 : constant Entity_Id := Etype (Actual);
974 T2 : constant Entity_Id := Etype (Formal);
975 begin
976 return T1 = T2
977 or else
978 (Is_Numeric_Type (T2)
979 and then
980 (T1 = Universal_Real or else T1 = Universal_Integer));
981 end Matches;
983 ------------------------
984 -- Remove_Conversions --
985 ------------------------
987 function Remove_Conversions return Interp is
988 I : Interp_Index;
989 It : Interp;
990 It1 : Interp;
991 F1 : Entity_Id;
992 Act1 : Node_Id;
993 Act2 : Node_Id;
995 begin
996 It1 := No_Interp;
998 Get_First_Interp (N, I, It);
999 while Present (It.Typ) loop
1001 if not Is_Overloadable (It.Nam) then
1002 return No_Interp;
1003 end if;
1005 F1 := First_Formal (It.Nam);
1007 if No (F1) then
1008 return It1;
1010 else
1011 if Nkind (N) = N_Function_Call
1012 or else Nkind (N) = N_Procedure_Call_Statement
1013 then
1014 Act1 := First_Actual (N);
1016 if Present (Act1) then
1017 Act2 := Next_Actual (Act1);
1018 else
1019 Act2 := Empty;
1020 end if;
1022 elsif Nkind (N) in N_Unary_Op then
1023 Act1 := Right_Opnd (N);
1024 Act2 := Empty;
1026 elsif Nkind (N) in N_Binary_Op then
1027 Act1 := Left_Opnd (N);
1028 Act2 := Right_Opnd (N);
1030 else
1031 return It1;
1032 end if;
1034 if Nkind (Act1) in N_Op
1035 and then Is_Overloaded (Act1)
1036 and then (Nkind (Right_Opnd (Act1)) = N_Integer_Literal
1037 or else Nkind (Right_Opnd (Act1)) = N_Real_Literal)
1038 and then Has_Compatible_Type (Act1, Standard_Boolean)
1039 and then Etype (F1) = Standard_Boolean
1040 then
1041 -- If the two candidates are the original ones, the
1042 -- ambiguity is real. Otherwise keep the original,
1043 -- further calls to Disambiguate will take care of
1044 -- others in the list of candidates.
1046 if It1 /= No_Interp then
1047 if It = Disambiguate.It1
1048 or else It = Disambiguate.It2
1049 then
1050 if It1 = Disambiguate.It1
1051 or else It1 = Disambiguate.It2
1052 then
1053 return No_Interp;
1054 else
1055 It1 := It;
1056 end if;
1057 end if;
1059 elsif Present (Act2)
1060 and then Nkind (Act2) in N_Op
1061 and then Is_Overloaded (Act2)
1062 and then (Nkind (Right_Opnd (Act1)) = N_Integer_Literal
1063 or else
1064 Nkind (Right_Opnd (Act1)) = N_Real_Literal)
1065 and then Has_Compatible_Type (Act2, Standard_Boolean)
1066 then
1067 -- The preference rule on the first actual is not
1068 -- sufficient to disambiguate.
1070 goto Next_Interp;
1072 else
1073 It1 := It;
1074 end if;
1075 end if;
1076 end if;
1078 <<Next_Interp>>
1079 Get_Next_Interp (I, It);
1080 end loop;
1082 -- After some error, a formal may have Any_Type and yield
1083 -- a spurious match. To avoid cascaded errors if possible,
1084 -- check for such a formal in either candidate.
1086 if Serious_Errors_Detected > 0 then
1087 declare
1088 Formal : Entity_Id;
1090 begin
1091 Formal := First_Formal (Nam1);
1092 while Present (Formal) loop
1093 if Etype (Formal) = Any_Type then
1094 return Disambiguate.It2;
1095 end if;
1097 Next_Formal (Formal);
1098 end loop;
1100 Formal := First_Formal (Nam2);
1101 while Present (Formal) loop
1102 if Etype (Formal) = Any_Type then
1103 return Disambiguate.It1;
1104 end if;
1106 Next_Formal (Formal);
1107 end loop;
1108 end;
1109 end if;
1111 return It1;
1112 end Remove_Conversions;
1114 -----------------------
1115 -- Standard_Operator --
1116 -----------------------
1118 function Standard_Operator return Boolean is
1119 Nam : Node_Id;
1121 begin
1122 if Nkind (N) in N_Op then
1123 return True;
1125 elsif Nkind (N) = N_Function_Call then
1126 Nam := Name (N);
1128 if Nkind (Nam) /= N_Expanded_Name then
1129 return True;
1130 else
1131 return Entity (Prefix (Nam)) = Standard_Standard;
1132 end if;
1133 else
1134 return False;
1135 end if;
1136 end Standard_Operator;
1138 -- Start of processing for Disambiguate
1140 begin
1141 -- Recover the two legal interpretations
1143 Get_First_Interp (N, I, It);
1144 while I /= I1 loop
1145 Get_Next_Interp (I, It);
1146 end loop;
1148 It1 := It;
1149 Nam1 := It.Nam;
1150 while I /= I2 loop
1151 Get_Next_Interp (I, It);
1152 end loop;
1154 It2 := It;
1155 Nam2 := It.Nam;
1157 -- If the context is universal, the predefined operator is preferred.
1158 -- This includes bounds in numeric type declarations, and expressions
1159 -- in type conversions. If no interpretation yields a universal type,
1160 -- then we must check whether the user-defined entity hides the prede-
1161 -- fined one.
1163 if Chars (Nam1) in Any_Operator_Name
1164 and then Standard_Operator
1165 then
1166 if Typ = Universal_Integer
1167 or else Typ = Universal_Real
1168 or else Typ = Any_Integer
1169 or else Typ = Any_Discrete
1170 or else Typ = Any_Real
1171 or else Typ = Any_Type
1172 then
1173 -- Find an interpretation that yields the universal type, or else
1174 -- a predefined operator that yields a predefined numeric type.
1176 declare
1177 Candidate : Interp := No_Interp;
1179 begin
1180 Get_First_Interp (N, I, It);
1181 while Present (It.Typ) loop
1182 if (Covers (Typ, It.Typ)
1183 or else Typ = Any_Type)
1184 and then
1185 (It.Typ = Universal_Integer
1186 or else It.Typ = Universal_Real)
1187 then
1188 return It;
1190 elsif Covers (Typ, It.Typ)
1191 and then Scope (It.Typ) = Standard_Standard
1192 and then Scope (It.Nam) = Standard_Standard
1193 and then Is_Numeric_Type (It.Typ)
1194 then
1195 Candidate := It;
1196 end if;
1198 Get_Next_Interp (I, It);
1199 end loop;
1201 if Candidate /= No_Interp then
1202 return Candidate;
1203 end if;
1204 end;
1206 elsif Chars (Nam1) /= Name_Op_Not
1207 and then (Typ = Standard_Boolean or else Typ = Any_Boolean)
1208 then
1209 -- Equality or comparison operation. Choose predefined operator
1210 -- if arguments are universal. The node may be an operator, a
1211 -- name, or a function call, so unpack arguments accordingly.
1213 declare
1214 Arg1, Arg2 : Node_Id;
1216 begin
1217 if Nkind (N) in N_Op then
1218 Arg1 := Left_Opnd (N);
1219 Arg2 := Right_Opnd (N);
1221 elsif Is_Entity_Name (N)
1222 or else Nkind (N) = N_Operator_Symbol
1223 then
1224 Arg1 := First_Entity (Entity (N));
1225 Arg2 := Next_Entity (Arg1);
1227 else
1228 Arg1 := First_Actual (N);
1229 Arg2 := Next_Actual (Arg1);
1230 end if;
1232 if Present (Arg2)
1233 and then Present (Universal_Interpretation (Arg1))
1234 and then Universal_Interpretation (Arg2) =
1235 Universal_Interpretation (Arg1)
1236 then
1237 Get_First_Interp (N, I, It);
1238 while Scope (It.Nam) /= Standard_Standard loop
1239 Get_Next_Interp (I, It);
1240 end loop;
1242 return It;
1243 end if;
1244 end;
1245 end if;
1246 end if;
1248 -- If no universal interpretation, check whether user-defined operator
1249 -- hides predefined one, as well as other special cases. If the node
1250 -- is a range, then one or both bounds are ambiguous. Each will have
1251 -- to be disambiguated w.r.t. the context type. The type of the range
1252 -- itself is imposed by the context, so we can return either legal
1253 -- interpretation.
1255 if Ekind (Nam1) = E_Operator then
1256 Predef_Subp := Nam1;
1257 User_Subp := Nam2;
1259 elsif Ekind (Nam2) = E_Operator then
1260 Predef_Subp := Nam2;
1261 User_Subp := Nam1;
1263 elsif Nkind (N) = N_Range then
1264 return It1;
1266 -- If two user defined-subprograms are visible, it is a true ambiguity,
1267 -- unless one of them is an entry and the context is a conditional or
1268 -- timed entry call, or unless we are within an instance and this is
1269 -- results from two formals types with the same actual.
1271 else
1272 if Nkind (N) = N_Procedure_Call_Statement
1273 and then Nkind (Parent (N)) = N_Entry_Call_Alternative
1274 and then N = Entry_Call_Statement (Parent (N))
1275 then
1276 if Ekind (Nam2) = E_Entry then
1277 return It2;
1278 elsif Ekind (Nam1) = E_Entry then
1279 return It1;
1280 else
1281 return No_Interp;
1282 end if;
1284 -- If the ambiguity occurs within an instance, it is due to several
1285 -- formal types with the same actual. Look for an exact match
1286 -- between the types of the formals of the overloadable entities,
1287 -- and the actuals in the call, to recover the unambiguous match
1288 -- in the original generic.
1290 -- The ambiguity can also be due to an overloading between a formal
1291 -- subprogram and a subprogram declared outside the generic. If the
1292 -- node is overloaded, it did not resolve to the global entity in
1293 -- the generic, and we choose the formal subprogram.
1295 -- Finally, the ambiguity can be between an explicit subprogram and
1296 -- one inherited (with different defaults) from an actual. In this
1297 -- case the resolution was to the explicit declaration in the
1298 -- generic, and remains so in the instance.
1300 elsif In_Instance then
1301 if Nkind (N) = N_Function_Call
1302 or else Nkind (N) = N_Procedure_Call_Statement
1303 then
1304 declare
1305 Actual : Node_Id;
1306 Formal : Entity_Id;
1307 Is_Act1 : constant Boolean := Is_Actual_Subprogram (Nam1);
1308 Is_Act2 : constant Boolean := Is_Actual_Subprogram (Nam2);
1310 begin
1311 if Is_Act1 and then not Is_Act2 then
1312 return It1;
1314 elsif Is_Act2 and then not Is_Act1 then
1315 return It2;
1317 elsif Inherited_From_Actual (Nam1)
1318 and then Comes_From_Source (Nam2)
1319 then
1320 return It2;
1322 elsif Inherited_From_Actual (Nam2)
1323 and then Comes_From_Source (Nam1)
1324 then
1325 return It1;
1326 end if;
1328 Actual := First_Actual (N);
1329 Formal := First_Formal (Nam1);
1330 while Present (Actual) loop
1331 if Etype (Actual) /= Etype (Formal) then
1332 return It2;
1333 end if;
1335 Next_Actual (Actual);
1336 Next_Formal (Formal);
1337 end loop;
1339 return It1;
1340 end;
1342 elsif Nkind (N) in N_Binary_Op then
1343 if Matches (Left_Opnd (N), First_Formal (Nam1))
1344 and then
1345 Matches (Right_Opnd (N), Next_Formal (First_Formal (Nam1)))
1346 then
1347 return It1;
1348 else
1349 return It2;
1350 end if;
1352 elsif Nkind (N) in N_Unary_Op then
1353 if Etype (Right_Opnd (N)) = Etype (First_Formal (Nam1)) then
1354 return It1;
1355 else
1356 return It2;
1357 end if;
1359 else
1360 return Remove_Conversions;
1361 end if;
1362 else
1363 return Remove_Conversions;
1364 end if;
1365 end if;
1367 -- an implicit concatenation operator on a string type cannot be
1368 -- disambiguated from the predefined concatenation. This can only
1369 -- happen with concatenation of string literals.
1371 if Chars (User_Subp) = Name_Op_Concat
1372 and then Ekind (User_Subp) = E_Operator
1373 and then Is_String_Type (Etype (First_Formal (User_Subp)))
1374 then
1375 return No_Interp;
1377 -- If the user-defined operator is in an open scope, or in the scope
1378 -- of the resulting type, or given by an expanded name that names its
1379 -- scope, it hides the predefined operator for the type. Exponentiation
1380 -- has to be special-cased because the implicit operator does not have
1381 -- a symmetric signature, and may not be hidden by the explicit one.
1383 elsif (Nkind (N) = N_Function_Call
1384 and then Nkind (Name (N)) = N_Expanded_Name
1385 and then (Chars (Predef_Subp) /= Name_Op_Expon
1386 or else Hides_Op (User_Subp, Predef_Subp))
1387 and then Scope (User_Subp) = Entity (Prefix (Name (N))))
1388 or else Hides_Op (User_Subp, Predef_Subp)
1389 then
1390 if It1.Nam = User_Subp then
1391 return It1;
1392 else
1393 return It2;
1394 end if;
1396 -- Otherwise, the predefined operator has precedence, or if the
1397 -- user-defined operation is directly visible we have a true ambiguity.
1398 -- If this is a fixed-point multiplication and division in Ada83 mode,
1399 -- exclude the universal_fixed operator, which often causes ambiguities
1400 -- in legacy code.
1402 else
1403 if (In_Open_Scopes (Scope (User_Subp))
1404 or else Is_Potentially_Use_Visible (User_Subp))
1405 and then not In_Instance
1406 then
1407 if Is_Fixed_Point_Type (Typ)
1408 and then (Chars (Nam1) = Name_Op_Multiply
1409 or else Chars (Nam1) = Name_Op_Divide)
1410 and then Ada_Version = Ada_83
1411 then
1412 if It2.Nam = Predef_Subp then
1413 return It1;
1414 else
1415 return It2;
1416 end if;
1417 else
1418 return No_Interp;
1419 end if;
1421 elsif It1.Nam = Predef_Subp then
1422 return It1;
1424 else
1425 return It2;
1426 end if;
1427 end if;
1428 end Disambiguate;
1430 ---------------------
1431 -- End_Interp_List --
1432 ---------------------
1434 procedure End_Interp_List is
1435 begin
1436 All_Interp.Table (All_Interp.Last) := No_Interp;
1437 All_Interp.Increment_Last;
1438 end End_Interp_List;
1440 -------------------------
1441 -- Entity_Matches_Spec --
1442 -------------------------
1444 function Entity_Matches_Spec (Old_S, New_S : Entity_Id) return Boolean is
1445 begin
1446 -- Simple case: same entity kinds, type conformance is required.
1447 -- A parameterless function can also rename a literal.
1449 if Ekind (Old_S) = Ekind (New_S)
1450 or else (Ekind (New_S) = E_Function
1451 and then Ekind (Old_S) = E_Enumeration_Literal)
1452 then
1453 return Type_Conformant (New_S, Old_S);
1455 elsif Ekind (New_S) = E_Function
1456 and then Ekind (Old_S) = E_Operator
1457 then
1458 return Operator_Matches_Spec (Old_S, New_S);
1460 elsif Ekind (New_S) = E_Procedure
1461 and then Is_Entry (Old_S)
1462 then
1463 return Type_Conformant (New_S, Old_S);
1465 else
1466 return False;
1467 end if;
1468 end Entity_Matches_Spec;
1470 ----------------------
1471 -- Find_Unique_Type --
1472 ----------------------
1474 function Find_Unique_Type (L : Node_Id; R : Node_Id) return Entity_Id is
1475 T : constant Entity_Id := Etype (L);
1476 I : Interp_Index;
1477 It : Interp;
1478 TR : Entity_Id := Any_Type;
1480 begin
1481 if Is_Overloaded (R) then
1482 Get_First_Interp (R, I, It);
1483 while Present (It.Typ) loop
1484 if Covers (T, It.Typ) or else Covers (It.Typ, T) then
1486 -- If several interpretations are possible and L is universal,
1487 -- apply preference rule.
1489 if TR /= Any_Type then
1491 if (T = Universal_Integer or else T = Universal_Real)
1492 and then It.Typ = T
1493 then
1494 TR := It.Typ;
1495 end if;
1497 else
1498 TR := It.Typ;
1499 end if;
1500 end if;
1502 Get_Next_Interp (I, It);
1503 end loop;
1505 Set_Etype (R, TR);
1507 -- In the non-overloaded case, the Etype of R is already set correctly
1509 else
1510 null;
1511 end if;
1513 -- If one of the operands is Universal_Fixed, the type of the
1514 -- other operand provides the context.
1516 if Etype (R) = Universal_Fixed then
1517 return T;
1519 elsif T = Universal_Fixed then
1520 return Etype (R);
1522 -- Ada 2005 (AI-230): Support the following operators:
1524 -- function "=" (L, R : universal_access) return Boolean;
1525 -- function "/=" (L, R : universal_access) return Boolean;
1527 elsif Ada_Version >= Ada_05
1528 and then Ekind (Etype (L)) = E_Anonymous_Access_Type
1529 and then Is_Access_Type (Etype (R))
1530 then
1531 return Etype (L);
1533 elsif Ada_Version >= Ada_05
1534 and then Ekind (Etype (R)) = E_Anonymous_Access_Type
1535 and then Is_Access_Type (Etype (L))
1536 then
1537 return Etype (R);
1539 else
1540 return Specific_Type (T, Etype (R));
1541 end if;
1543 end Find_Unique_Type;
1545 ----------------------
1546 -- Get_First_Interp --
1547 ----------------------
1549 procedure Get_First_Interp
1550 (N : Node_Id;
1551 I : out Interp_Index;
1552 It : out Interp)
1554 Map_Ptr : Int;
1555 Int_Ind : Interp_Index;
1556 O_N : Node_Id;
1558 begin
1559 -- If a selected component is overloaded because the selector has
1560 -- multiple interpretations, the node is a call to a protected
1561 -- operation or an indirect call. Retrieve the interpretation from
1562 -- the selector name. The selected component may be overloaded as well
1563 -- if the prefix is overloaded. That case is unchanged.
1565 if Nkind (N) = N_Selected_Component
1566 and then Is_Overloaded (Selector_Name (N))
1567 then
1568 O_N := Selector_Name (N);
1569 else
1570 O_N := N;
1571 end if;
1573 Map_Ptr := Headers (Hash (O_N));
1574 while Present (Interp_Map.Table (Map_Ptr).Node) loop
1575 if Interp_Map.Table (Map_Ptr).Node = O_N then
1576 Int_Ind := Interp_Map.Table (Map_Ptr).Index;
1577 It := All_Interp.Table (Int_Ind);
1578 I := Int_Ind;
1579 return;
1580 else
1581 Map_Ptr := Interp_Map.Table (Map_Ptr).Next;
1582 end if;
1583 end loop;
1585 -- Procedure should never be called if the node has no interpretations
1587 raise Program_Error;
1588 end Get_First_Interp;
1590 ---------------------
1591 -- Get_Next_Interp --
1592 ---------------------
1594 procedure Get_Next_Interp (I : in out Interp_Index; It : out Interp) is
1595 begin
1596 I := I + 1;
1597 It := All_Interp.Table (I);
1598 end Get_Next_Interp;
1600 -------------------------
1601 -- Has_Compatible_Type --
1602 -------------------------
1604 function Has_Compatible_Type
1605 (N : Node_Id;
1606 Typ : Entity_Id)
1607 return Boolean
1609 I : Interp_Index;
1610 It : Interp;
1612 begin
1613 if N = Error then
1614 return False;
1615 end if;
1617 if Nkind (N) = N_Subtype_Indication
1618 or else not Is_Overloaded (N)
1619 then
1620 return
1621 Covers (Typ, Etype (N))
1622 or else
1623 (not Is_Tagged_Type (Typ)
1624 and then Ekind (Typ) /= E_Anonymous_Access_Type
1625 and then Covers (Etype (N), Typ));
1627 else
1628 Get_First_Interp (N, I, It);
1629 while Present (It.Typ) loop
1630 if (Covers (Typ, It.Typ)
1631 and then
1632 (Scope (It.Nam) /= Standard_Standard
1633 or else not Is_Invisible_Operator (N, Base_Type (Typ))))
1634 or else (not Is_Tagged_Type (Typ)
1635 and then Ekind (Typ) /= E_Anonymous_Access_Type
1636 and then Covers (It.Typ, Typ))
1637 then
1638 return True;
1639 end if;
1641 Get_Next_Interp (I, It);
1642 end loop;
1644 return False;
1645 end if;
1646 end Has_Compatible_Type;
1648 ----------
1649 -- Hash --
1650 ----------
1652 function Hash (N : Node_Id) return Int is
1653 begin
1654 -- Nodes have a size that is power of two, so to select significant
1655 -- bits only we remove the low-order bits.
1657 return ((Int (N) / 2 ** 5) mod Header_Size);
1658 end Hash;
1660 --------------
1661 -- Hides_Op --
1662 --------------
1664 function Hides_Op (F : Entity_Id; Op : Entity_Id) return Boolean is
1665 Btyp : constant Entity_Id := Base_Type (Etype (First_Formal (F)));
1667 begin
1668 return Operator_Matches_Spec (Op, F)
1669 and then (In_Open_Scopes (Scope (F))
1670 or else Scope (F) = Scope (Btyp)
1671 or else (not In_Open_Scopes (Scope (Btyp))
1672 and then not In_Use (Btyp)
1673 and then not In_Use (Scope (Btyp))));
1674 end Hides_Op;
1676 ------------------------
1677 -- Init_Interp_Tables --
1678 ------------------------
1680 procedure Init_Interp_Tables is
1681 begin
1682 All_Interp.Init;
1683 Interp_Map.Init;
1684 Headers := (others => No_Entry);
1685 end Init_Interp_Tables;
1687 ---------------------
1688 -- Intersect_Types --
1689 ---------------------
1691 function Intersect_Types (L, R : Node_Id) return Entity_Id is
1692 Index : Interp_Index;
1693 It : Interp;
1694 Typ : Entity_Id;
1696 function Check_Right_Argument (T : Entity_Id) return Entity_Id;
1697 -- Find interpretation of right arg that has type compatible with T
1699 --------------------------
1700 -- Check_Right_Argument --
1701 --------------------------
1703 function Check_Right_Argument (T : Entity_Id) return Entity_Id is
1704 Index : Interp_Index;
1705 It : Interp;
1706 T2 : Entity_Id;
1708 begin
1709 if not Is_Overloaded (R) then
1710 return Specific_Type (T, Etype (R));
1712 else
1713 Get_First_Interp (R, Index, It);
1714 loop
1715 T2 := Specific_Type (T, It.Typ);
1717 if T2 /= Any_Type then
1718 return T2;
1719 end if;
1721 Get_Next_Interp (Index, It);
1722 exit when No (It.Typ);
1723 end loop;
1725 return Any_Type;
1726 end if;
1727 end Check_Right_Argument;
1729 -- Start processing for Intersect_Types
1731 begin
1732 if Etype (L) = Any_Type or else Etype (R) = Any_Type then
1733 return Any_Type;
1734 end if;
1736 if not Is_Overloaded (L) then
1737 Typ := Check_Right_Argument (Etype (L));
1739 else
1740 Typ := Any_Type;
1741 Get_First_Interp (L, Index, It);
1742 while Present (It.Typ) loop
1743 Typ := Check_Right_Argument (It.Typ);
1744 exit when Typ /= Any_Type;
1745 Get_Next_Interp (Index, It);
1746 end loop;
1748 end if;
1750 -- If Typ is Any_Type, it means no compatible pair of types was found
1752 if Typ = Any_Type then
1753 if Nkind (Parent (L)) in N_Op then
1754 Error_Msg_N ("incompatible types for operator", Parent (L));
1756 elsif Nkind (Parent (L)) = N_Range then
1757 Error_Msg_N ("incompatible types given in constraint", Parent (L));
1759 else
1760 Error_Msg_N ("incompatible types", Parent (L));
1761 end if;
1762 end if;
1764 return Typ;
1765 end Intersect_Types;
1767 -----------------
1768 -- Is_Ancestor --
1769 -----------------
1771 function Is_Ancestor (T1, T2 : Entity_Id) return Boolean is
1772 Par : Entity_Id;
1774 begin
1775 if Base_Type (T1) = Base_Type (T2) then
1776 return True;
1778 elsif Is_Private_Type (T1)
1779 and then Present (Full_View (T1))
1780 and then Base_Type (T2) = Base_Type (Full_View (T1))
1781 then
1782 return True;
1784 else
1785 Par := Etype (T2);
1787 loop
1788 -- If there was a error on the type declaration, do not recurse
1790 if Error_Posted (Par) then
1791 return False;
1793 elsif Base_Type (T1) = Base_Type (Par)
1794 or else (Is_Private_Type (T1)
1795 and then Present (Full_View (T1))
1796 and then Base_Type (Par) = Base_Type (Full_View (T1)))
1797 then
1798 return True;
1800 elsif Is_Private_Type (Par)
1801 and then Present (Full_View (Par))
1802 and then Full_View (Par) = Base_Type (T1)
1803 then
1804 return True;
1806 elsif Etype (Par) /= Par then
1807 Par := Etype (Par);
1808 else
1809 return False;
1810 end if;
1811 end loop;
1812 end if;
1813 end Is_Ancestor;
1815 ---------------------------
1816 -- Is_Invisible_Operator --
1817 ---------------------------
1819 function Is_Invisible_Operator
1820 (N : Node_Id;
1821 T : Entity_Id)
1822 return Boolean
1824 Orig_Node : constant Node_Id := Original_Node (N);
1826 begin
1827 if Nkind (N) not in N_Op then
1828 return False;
1830 elsif not Comes_From_Source (N) then
1831 return False;
1833 elsif No (Universal_Interpretation (Right_Opnd (N))) then
1834 return False;
1836 elsif Nkind (N) in N_Binary_Op
1837 and then No (Universal_Interpretation (Left_Opnd (N)))
1838 then
1839 return False;
1841 else return
1842 Is_Numeric_Type (T)
1843 and then not In_Open_Scopes (Scope (T))
1844 and then not Is_Potentially_Use_Visible (T)
1845 and then not In_Use (T)
1846 and then not In_Use (Scope (T))
1847 and then
1848 (Nkind (Orig_Node) /= N_Function_Call
1849 or else Nkind (Name (Orig_Node)) /= N_Expanded_Name
1850 or else Entity (Prefix (Name (Orig_Node))) /= Scope (T))
1852 and then not In_Instance;
1853 end if;
1854 end Is_Invisible_Operator;
1856 -------------------
1857 -- Is_Subtype_Of --
1858 -------------------
1860 function Is_Subtype_Of (T1 : Entity_Id; T2 : Entity_Id) return Boolean is
1861 S : Entity_Id;
1863 begin
1864 S := Ancestor_Subtype (T1);
1865 while Present (S) loop
1866 if S = T2 then
1867 return True;
1868 else
1869 S := Ancestor_Subtype (S);
1870 end if;
1871 end loop;
1873 return False;
1874 end Is_Subtype_Of;
1876 ------------------
1877 -- List_Interps --
1878 ------------------
1880 procedure List_Interps (Nam : Node_Id; Err : Node_Id) is
1881 Index : Interp_Index;
1882 It : Interp;
1884 begin
1885 Get_First_Interp (Nam, Index, It);
1886 while Present (It.Nam) loop
1887 if Scope (It.Nam) = Standard_Standard
1888 and then Scope (It.Typ) /= Standard_Standard
1889 then
1890 Error_Msg_Sloc := Sloc (Parent (It.Typ));
1891 Error_Msg_NE (" & (inherited) declared#!", Err, It.Nam);
1893 else
1894 Error_Msg_Sloc := Sloc (It.Nam);
1895 Error_Msg_NE (" & declared#!", Err, It.Nam);
1896 end if;
1898 Get_Next_Interp (Index, It);
1899 end loop;
1900 end List_Interps;
1902 -----------------
1903 -- New_Interps --
1904 -----------------
1906 procedure New_Interps (N : Node_Id) is
1907 Map_Ptr : Int;
1909 begin
1910 All_Interp.Increment_Last;
1911 All_Interp.Table (All_Interp.Last) := No_Interp;
1913 Map_Ptr := Headers (Hash (N));
1915 if Map_Ptr = No_Entry then
1917 -- Place new node at end of table
1919 Interp_Map.Increment_Last;
1920 Headers (Hash (N)) := Interp_Map.Last;
1922 else
1923 -- Place node at end of chain, or locate its previous entry.
1925 loop
1926 if Interp_Map.Table (Map_Ptr).Node = N then
1928 -- Node is already in the table, and is being rewritten.
1929 -- Start a new interp section, retain hash link.
1931 Interp_Map.Table (Map_Ptr).Node := N;
1932 Interp_Map.Table (Map_Ptr).Index := All_Interp.Last;
1933 Set_Is_Overloaded (N, True);
1934 return;
1936 else
1937 exit when Interp_Map.Table (Map_Ptr).Next = No_Entry;
1938 Map_Ptr := Interp_Map.Table (Map_Ptr).Next;
1939 end if;
1940 end loop;
1942 -- Chain the new node.
1944 Interp_Map.Increment_Last;
1945 Interp_Map.Table (Map_Ptr).Next := Interp_Map.Last;
1946 end if;
1948 Interp_Map.Table (Interp_Map.Last) := (N, All_Interp.Last, No_Entry);
1949 Set_Is_Overloaded (N, True);
1950 end New_Interps;
1952 ---------------------------
1953 -- Operator_Matches_Spec --
1954 ---------------------------
1956 function Operator_Matches_Spec (Op, New_S : Entity_Id) return Boolean is
1957 Op_Name : constant Name_Id := Chars (Op);
1958 T : constant Entity_Id := Etype (New_S);
1959 New_F : Entity_Id;
1960 Old_F : Entity_Id;
1961 Num : Int;
1962 T1 : Entity_Id;
1963 T2 : Entity_Id;
1965 begin
1966 -- To verify that a predefined operator matches a given signature,
1967 -- do a case analysis of the operator classes. Function can have one
1968 -- or two formals and must have the proper result type.
1970 New_F := First_Formal (New_S);
1971 Old_F := First_Formal (Op);
1972 Num := 0;
1973 while Present (New_F) and then Present (Old_F) loop
1974 Num := Num + 1;
1975 Next_Formal (New_F);
1976 Next_Formal (Old_F);
1977 end loop;
1979 -- Definite mismatch if different number of parameters
1981 if Present (Old_F) or else Present (New_F) then
1982 return False;
1984 -- Unary operators
1986 elsif Num = 1 then
1987 T1 := Etype (First_Formal (New_S));
1989 if Op_Name = Name_Op_Subtract
1990 or else Op_Name = Name_Op_Add
1991 or else Op_Name = Name_Op_Abs
1992 then
1993 return Base_Type (T1) = Base_Type (T)
1994 and then Is_Numeric_Type (T);
1996 elsif Op_Name = Name_Op_Not then
1997 return Base_Type (T1) = Base_Type (T)
1998 and then Valid_Boolean_Arg (Base_Type (T));
2000 else
2001 return False;
2002 end if;
2004 -- Binary operators
2006 else
2007 T1 := Etype (First_Formal (New_S));
2008 T2 := Etype (Next_Formal (First_Formal (New_S)));
2010 if Op_Name = Name_Op_And or else Op_Name = Name_Op_Or
2011 or else Op_Name = Name_Op_Xor
2012 then
2013 return Base_Type (T1) = Base_Type (T2)
2014 and then Base_Type (T1) = Base_Type (T)
2015 and then Valid_Boolean_Arg (Base_Type (T));
2017 elsif Op_Name = Name_Op_Eq or else Op_Name = Name_Op_Ne then
2018 return Base_Type (T1) = Base_Type (T2)
2019 and then not Is_Limited_Type (T1)
2020 and then Is_Boolean_Type (T);
2022 elsif Op_Name = Name_Op_Lt or else Op_Name = Name_Op_Le
2023 or else Op_Name = Name_Op_Gt or else Op_Name = Name_Op_Ge
2024 then
2025 return Base_Type (T1) = Base_Type (T2)
2026 and then Valid_Comparison_Arg (T1)
2027 and then Is_Boolean_Type (T);
2029 elsif Op_Name = Name_Op_Add or else Op_Name = Name_Op_Subtract then
2030 return Base_Type (T1) = Base_Type (T2)
2031 and then Base_Type (T1) = Base_Type (T)
2032 and then Is_Numeric_Type (T);
2034 -- for division and multiplication, a user-defined function does
2035 -- not match the predefined universal_fixed operation, except in
2036 -- Ada83 mode.
2038 elsif Op_Name = Name_Op_Divide then
2039 return (Base_Type (T1) = Base_Type (T2)
2040 and then Base_Type (T1) = Base_Type (T)
2041 and then Is_Numeric_Type (T)
2042 and then (not Is_Fixed_Point_Type (T)
2043 or else Ada_Version = Ada_83))
2045 -- Mixed_Mode operations on fixed-point types
2047 or else (Base_Type (T1) = Base_Type (T)
2048 and then Base_Type (T2) = Base_Type (Standard_Integer)
2049 and then Is_Fixed_Point_Type (T))
2051 -- A user defined operator can also match (and hide) a mixed
2052 -- operation on universal literals.
2054 or else (Is_Integer_Type (T2)
2055 and then Is_Floating_Point_Type (T1)
2056 and then Base_Type (T1) = Base_Type (T));
2058 elsif Op_Name = Name_Op_Multiply then
2059 return (Base_Type (T1) = Base_Type (T2)
2060 and then Base_Type (T1) = Base_Type (T)
2061 and then Is_Numeric_Type (T)
2062 and then (not Is_Fixed_Point_Type (T)
2063 or else Ada_Version = Ada_83))
2065 -- Mixed_Mode operations on fixed-point types
2067 or else (Base_Type (T1) = Base_Type (T)
2068 and then Base_Type (T2) = Base_Type (Standard_Integer)
2069 and then Is_Fixed_Point_Type (T))
2071 or else (Base_Type (T2) = Base_Type (T)
2072 and then Base_Type (T1) = Base_Type (Standard_Integer)
2073 and then Is_Fixed_Point_Type (T))
2075 or else (Is_Integer_Type (T2)
2076 and then Is_Floating_Point_Type (T1)
2077 and then Base_Type (T1) = Base_Type (T))
2079 or else (Is_Integer_Type (T1)
2080 and then Is_Floating_Point_Type (T2)
2081 and then Base_Type (T2) = Base_Type (T));
2083 elsif Op_Name = Name_Op_Mod or else Op_Name = Name_Op_Rem then
2084 return Base_Type (T1) = Base_Type (T2)
2085 and then Base_Type (T1) = Base_Type (T)
2086 and then Is_Integer_Type (T);
2088 elsif Op_Name = Name_Op_Expon then
2089 return Base_Type (T1) = Base_Type (T)
2090 and then Is_Numeric_Type (T)
2091 and then Base_Type (T2) = Base_Type (Standard_Integer);
2093 elsif Op_Name = Name_Op_Concat then
2094 return Is_Array_Type (T)
2095 and then (Base_Type (T) = Base_Type (Etype (Op)))
2096 and then (Base_Type (T1) = Base_Type (T)
2097 or else
2098 Base_Type (T1) = Base_Type (Component_Type (T)))
2099 and then (Base_Type (T2) = Base_Type (T)
2100 or else
2101 Base_Type (T2) = Base_Type (Component_Type (T)));
2103 else
2104 return False;
2105 end if;
2106 end if;
2107 end Operator_Matches_Spec;
2109 -------------------
2110 -- Remove_Interp --
2111 -------------------
2113 procedure Remove_Interp (I : in out Interp_Index) is
2114 II : Interp_Index;
2116 begin
2117 -- Find end of Interp list and copy downward to erase the discarded one
2119 II := I + 1;
2120 while Present (All_Interp.Table (II).Typ) loop
2121 II := II + 1;
2122 end loop;
2124 for J in I + 1 .. II loop
2125 All_Interp.Table (J - 1) := All_Interp.Table (J);
2126 end loop;
2128 -- Back up interp. index to insure that iterator will pick up next
2129 -- available interpretation.
2131 I := I - 1;
2132 end Remove_Interp;
2134 ------------------
2135 -- Save_Interps --
2136 ------------------
2138 procedure Save_Interps (Old_N : Node_Id; New_N : Node_Id) is
2139 Map_Ptr : Int;
2140 O_N : Node_Id := Old_N;
2142 begin
2143 if Is_Overloaded (Old_N) then
2144 if Nkind (Old_N) = N_Selected_Component
2145 and then Is_Overloaded (Selector_Name (Old_N))
2146 then
2147 O_N := Selector_Name (Old_N);
2148 end if;
2150 Map_Ptr := Headers (Hash (O_N));
2152 while Interp_Map.Table (Map_Ptr).Node /= O_N loop
2153 Map_Ptr := Interp_Map.Table (Map_Ptr).Next;
2154 pragma Assert (Map_Ptr /= No_Entry);
2155 end loop;
2157 New_Interps (New_N);
2158 Interp_Map.Table (Interp_Map.Last).Index :=
2159 Interp_Map.Table (Map_Ptr).Index;
2160 end if;
2161 end Save_Interps;
2163 -------------------
2164 -- Specific_Type --
2165 -------------------
2167 function Specific_Type (T1, T2 : Entity_Id) return Entity_Id is
2168 B1 : constant Entity_Id := Base_Type (T1);
2169 B2 : constant Entity_Id := Base_Type (T2);
2171 function Is_Remote_Access (T : Entity_Id) return Boolean;
2172 -- Check whether T is the equivalent type of a remote access type.
2173 -- If distribution is enabled, T is a legal context for Null.
2175 ----------------------
2176 -- Is_Remote_Access --
2177 ----------------------
2179 function Is_Remote_Access (T : Entity_Id) return Boolean is
2180 begin
2181 return Is_Record_Type (T)
2182 and then (Is_Remote_Call_Interface (T)
2183 or else Is_Remote_Types (T))
2184 and then Present (Corresponding_Remote_Type (T))
2185 and then Is_Access_Type (Corresponding_Remote_Type (T));
2186 end Is_Remote_Access;
2188 -- Start of processing for Specific_Type
2190 begin
2191 if T1 = Any_Type or else T2 = Any_Type then
2192 return Any_Type;
2193 end if;
2195 if B1 = B2 then
2196 return B1;
2198 elsif False
2199 or else (T1 = Universal_Integer and then Is_Integer_Type (T2))
2200 or else (T1 = Universal_Real and then Is_Real_Type (T2))
2201 or else (T1 = Universal_Fixed and then Is_Fixed_Point_Type (T2))
2202 or else (T1 = Any_Fixed and then Is_Fixed_Point_Type (T2))
2203 then
2204 return B2;
2206 elsif False
2207 or else (T2 = Universal_Integer and then Is_Integer_Type (T1))
2208 or else (T2 = Universal_Real and then Is_Real_Type (T1))
2209 or else (T2 = Universal_Fixed and then Is_Fixed_Point_Type (T1))
2210 or else (T2 = Any_Fixed and then Is_Fixed_Point_Type (T1))
2211 then
2212 return B1;
2214 elsif T2 = Any_String and then Is_String_Type (T1) then
2215 return B1;
2217 elsif T1 = Any_String and then Is_String_Type (T2) then
2218 return B2;
2220 elsif T2 = Any_Character and then Is_Character_Type (T1) then
2221 return B1;
2223 elsif T1 = Any_Character and then Is_Character_Type (T2) then
2224 return B2;
2226 elsif T1 = Any_Access
2227 and then (Is_Access_Type (T2) or else Is_Remote_Access (T2))
2228 then
2229 return T2;
2231 elsif T2 = Any_Access
2232 and then (Is_Access_Type (T1) or else Is_Remote_Access (T1))
2233 then
2234 return T1;
2236 elsif T2 = Any_Composite
2237 and then Ekind (T1) in E_Array_Type .. E_Record_Subtype
2238 then
2239 return T1;
2241 elsif T1 = Any_Composite
2242 and then Ekind (T2) in E_Array_Type .. E_Record_Subtype
2243 then
2244 return T2;
2246 elsif T1 = Any_Modular and then Is_Modular_Integer_Type (T2) then
2247 return T2;
2249 elsif T2 = Any_Modular and then Is_Modular_Integer_Type (T1) then
2250 return T1;
2252 -- Special cases for equality operators (all other predefined
2253 -- operators can never apply to tagged types)
2255 elsif Is_Class_Wide_Type (T1)
2256 and then Is_Ancestor (Root_Type (T1), T2)
2257 then
2258 return T1;
2260 elsif Is_Class_Wide_Type (T2)
2261 and then Is_Ancestor (Root_Type (T2), T1)
2262 then
2263 return T2;
2265 elsif (Ekind (B1) = E_Access_Subprogram_Type
2266 or else
2267 Ekind (B1) = E_Access_Protected_Subprogram_Type)
2268 and then Ekind (Designated_Type (B1)) /= E_Subprogram_Type
2269 and then Is_Access_Type (T2)
2270 then
2271 return T2;
2273 elsif (Ekind (B2) = E_Access_Subprogram_Type
2274 or else
2275 Ekind (B2) = E_Access_Protected_Subprogram_Type)
2276 and then Ekind (Designated_Type (B2)) /= E_Subprogram_Type
2277 and then Is_Access_Type (T1)
2278 then
2279 return T1;
2281 elsif (Ekind (T1) = E_Allocator_Type
2282 or else Ekind (T1) = E_Access_Attribute_Type
2283 or else Ekind (T1) = E_Anonymous_Access_Type)
2284 and then Is_Access_Type (T2)
2285 then
2286 return T2;
2288 elsif (Ekind (T2) = E_Allocator_Type
2289 or else Ekind (T2) = E_Access_Attribute_Type
2290 or else Ekind (T2) = E_Anonymous_Access_Type)
2291 and then Is_Access_Type (T1)
2292 then
2293 return T1;
2295 -- If none of the above cases applies, types are not compatible.
2297 else
2298 return Any_Type;
2299 end if;
2300 end Specific_Type;
2302 -----------------------
2303 -- Valid_Boolean_Arg --
2304 -----------------------
2306 -- In addition to booleans and arrays of booleans, we must include
2307 -- aggregates as valid boolean arguments, because in the first pass
2308 -- of resolution their components are not examined. If it turns out not
2309 -- to be an aggregate of booleans, this will be diagnosed in Resolve.
2310 -- Any_Composite must be checked for prior to the array type checks
2311 -- because Any_Composite does not have any associated indexes.
2313 function Valid_Boolean_Arg (T : Entity_Id) return Boolean is
2314 begin
2315 return Is_Boolean_Type (T)
2316 or else T = Any_Composite
2317 or else (Is_Array_Type (T)
2318 and then T /= Any_String
2319 and then Number_Dimensions (T) = 1
2320 and then Is_Boolean_Type (Component_Type (T))
2321 and then (not Is_Private_Composite (T)
2322 or else In_Instance)
2323 and then (not Is_Limited_Composite (T)
2324 or else In_Instance))
2325 or else Is_Modular_Integer_Type (T)
2326 or else T = Universal_Integer;
2327 end Valid_Boolean_Arg;
2329 --------------------------
2330 -- Valid_Comparison_Arg --
2331 --------------------------
2333 function Valid_Comparison_Arg (T : Entity_Id) return Boolean is
2334 begin
2336 if T = Any_Composite then
2337 return False;
2338 elsif Is_Discrete_Type (T)
2339 or else Is_Real_Type (T)
2340 then
2341 return True;
2342 elsif Is_Array_Type (T)
2343 and then Number_Dimensions (T) = 1
2344 and then Is_Discrete_Type (Component_Type (T))
2345 and then (not Is_Private_Composite (T)
2346 or else In_Instance)
2347 and then (not Is_Limited_Composite (T)
2348 or else In_Instance)
2349 then
2350 return True;
2351 elsif Is_String_Type (T) then
2352 return True;
2353 else
2354 return False;
2355 end if;
2356 end Valid_Comparison_Arg;
2358 ---------------------
2359 -- Write_Overloads --
2360 ---------------------
2362 procedure Write_Overloads (N : Node_Id) is
2363 I : Interp_Index;
2364 It : Interp;
2365 Nam : Entity_Id;
2367 begin
2368 if not Is_Overloaded (N) then
2369 Write_Str ("Non-overloaded entity ");
2370 Write_Eol;
2371 Write_Entity_Info (Entity (N), " ");
2373 else
2374 Get_First_Interp (N, I, It);
2375 Write_Str ("Overloaded entity ");
2376 Write_Eol;
2377 Nam := It.Nam;
2379 while Present (Nam) loop
2380 Write_Entity_Info (Nam, " ");
2381 Write_Str ("=================");
2382 Write_Eol;
2383 Get_Next_Interp (I, It);
2384 Nam := It.Nam;
2385 end loop;
2386 end if;
2387 end Write_Overloads;
2389 ----------------------
2390 -- Write_Interp_Ref --
2391 ----------------------
2393 procedure Write_Interp_Ref (Map_Ptr : Int) is
2394 begin
2395 Write_Str (" Node: ");
2396 Write_Int (Int (Interp_Map.Table (Map_Ptr).Node));
2397 Write_Str (" Index: ");
2398 Write_Int (Int (Interp_Map.Table (Map_Ptr).Index));
2399 Write_Str (" Next: ");
2400 Write_Int (Int (Interp_Map.Table (Map_Ptr).Next));
2401 Write_Eol;
2402 end Write_Interp_Ref;
2404 end Sem_Type;