OSDN Git Service

* sysdep.c: Problem discovered during IA64 VMS port.
[pf3gnuchains/gcc-fork.git] / gcc / ada / sem_type.adb
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-2003 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 ------------------------------------------------------------------------------
26
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;
44
45 package body Sem_Type is
46
47    ---------------------
48    -- Data Structures --
49    ---------------------
50
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.
60
61    --              Headers        Interp_Map          All_Interp
62    --
63    --                 _            -------             ----------
64    --                |_|           |_____|         --->|interp1 |
65    --                |_|---------->|node |         |   |interp2 |
66    --                |_|           |index|---------|   |nointerp|
67    --                |_|           |next |             |        |
68    --                              |-----|             |        |
69    --                              -------             ----------
70
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???
75
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");
83
84    type Interp_Ref is record
85       Node  : Node_Id;
86       Index : Interp_Index;
87       Next  : Int;
88    end record;
89
90    Header_Size : constant Int := 2 ** 12;
91    No_Entry    : constant Int := -1;
92    Headers     : array (0 .. Header_Size) of Int := (others => No_Entry);
93
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");
101
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.
105
106    -------------------------------------
107    -- Handling of Overload Resolution --
108    -------------------------------------
109
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.
117
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).
124
125    --------------------------
126    -- Operator Overloading --
127    --------------------------
128
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.)
139
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.
144    --
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.
150
151    -----------------------
152    -- Local Subprograms --
153    -----------------------
154
155    procedure All_Overloads;
156    pragma Warnings (Off, All_Overloads);
157    --  Debugging procedure: list full contents of Overloads table.
158
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.
164
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).
168
169    --------------------
170    -- Add_One_Interp --
171    --------------------
172
173    procedure Add_One_Interp
174      (N         : Node_Id;
175       E         : Entity_Id;
176       T         : Entity_Id;
177       Opnd_Type : Entity_Id := Empty)
178    is
179       Vis_Type : Entity_Id;
180
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.
185
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.
189
190       ---------------
191       -- Add_Entry --
192       ---------------
193
194       procedure Add_Entry (Name :  Entity_Id; Typ : Entity_Id) is
195          Index : Interp_Index;
196          It    : Interp;
197
198       begin
199          Get_First_Interp (N, Index, It);
200
201          while Present (It.Nam) loop
202
203             --  A user-defined subprogram hides another declared at an outer
204             --  level, or one that is use-visible. So return if previous
205             --  definition hides new one (which is either in an outer
206             --  scope, or use-visible). Note that for functions use-visible
207             --  is the same as potentially use-visible. If new one hides
208             --  previous one, replace entry in table of interpretations.
209             --  If this is a universal operation, retain the operator in case
210             --  preference rule applies.
211
212             if (((Ekind (Name) = E_Function or else Ekind (Name) = E_Procedure)
213                  and then Ekind (Name) = Ekind (It.Nam))
214                 or else (Ekind (Name) = E_Operator
215               and then Ekind (It.Nam) = E_Function))
216
217               and then Is_Immediately_Visible (It.Nam)
218               and then Type_Conformant (Name, It.Nam)
219               and then Base_Type (It.Typ) = Base_Type (T)
220             then
221                if Is_Universal_Operation (Name) then
222                   exit;
223
224                --  If node is an operator symbol, we have no actuals with
225                --  which to check hiding, and this is done in full in the
226                --  caller (Analyze_Subprogram_Renaming) so we include the
227                --  predefined operator in any case.
228
229                elsif Nkind (N) = N_Operator_Symbol
230                  or else (Nkind (N) = N_Expanded_Name
231                             and then
232                           Nkind (Selector_Name (N)) = N_Operator_Symbol)
233                then
234                   exit;
235
236                elsif not In_Open_Scopes (Scope (Name))
237                  or else Scope_Depth (Scope (Name))
238                    <= Scope_Depth (Scope (It.Nam))
239                then
240                   --  If ambiguity within instance, and entity is not an
241                   --  implicit operation, save for later disambiguation.
242
243                   if Scope (Name) = Scope (It.Nam)
244                     and then not Is_Inherited_Operation (Name)
245                     and then In_Instance
246                   then
247                      exit;
248                   else
249                      return;
250                   end if;
251
252                else
253                   All_Interp.Table (Index).Nam := Name;
254                   return;
255                end if;
256
257             --  Avoid making duplicate entries in overloads
258
259             elsif Name = It.Nam
260               and then Base_Type (It.Typ) = Base_Type (T)
261             then
262                return;
263
264             --  Otherwise keep going
265
266             else
267                Get_Next_Interp (Index, It);
268             end if;
269
270          end loop;
271
272          --  On exit, enter new interpretation. The context, or a preference
273          --  rule, will resolve the ambiguity on the second pass.
274
275          All_Interp.Table (All_Interp.Last) := (Name, Typ);
276          All_Interp.Increment_Last;
277          All_Interp.Table (All_Interp.Last) := No_Interp;
278       end Add_Entry;
279
280       ----------------------------
281       -- Is_Universal_Operation --
282       ----------------------------
283
284       function Is_Universal_Operation (Op : Entity_Id) return Boolean is
285          Arg : Node_Id;
286
287       begin
288          if Ekind (Op) /= E_Operator then
289             return False;
290
291          elsif Nkind (N) in N_Binary_Op then
292             return Present (Universal_Interpretation (Left_Opnd (N)))
293               and then Present (Universal_Interpretation (Right_Opnd (N)));
294
295          elsif Nkind (N) in N_Unary_Op then
296             return Present (Universal_Interpretation (Right_Opnd (N)));
297
298          elsif Nkind (N) = N_Function_Call then
299             Arg := First_Actual (N);
300
301             while Present (Arg) loop
302
303                if No (Universal_Interpretation (Arg)) then
304                   return False;
305                end if;
306
307                Next_Actual (Arg);
308             end loop;
309
310             return True;
311
312          else
313             return False;
314          end if;
315       end Is_Universal_Operation;
316
317    --  Start of processing for Add_One_Interp
318
319    begin
320       --  If the interpretation is a predefined operator, verify that the
321       --  result type is visible, or that the entity has already been
322       --  resolved (case of an instantiation node that refers to a predefined
323       --  operation, or an internally generated operator node, or an operator
324       --  given as an expanded name). If the operator is a comparison or
325       --  equality, it is the type of the operand that matters to determine
326       --  whether the operator is visible. In an instance, the check is not
327       --  performed, given that the operator was visible in the generic.
328
329       if Ekind (E) = E_Operator then
330
331          if Present (Opnd_Type) then
332             Vis_Type := Opnd_Type;
333          else
334             Vis_Type := Base_Type (T);
335          end if;
336
337          if In_Open_Scopes (Scope (Vis_Type))
338            or else Is_Potentially_Use_Visible (Vis_Type)
339            or else In_Use (Vis_Type)
340            or else (In_Use (Scope (Vis_Type))
341                      and then not Is_Hidden (Vis_Type))
342            or else Nkind (N) = N_Expanded_Name
343            or else (Nkind (N) in N_Op and then E = Entity (N))
344            or else In_Instance
345          then
346             null;
347
348          --  If the node is given in functional notation and the prefix
349          --  is an expanded name, then the operator is visible if the
350          --  prefix is the scope of the result type as well. If the
351          --  operator is (implicitly) defined in an extension of system,
352          --  it is know to be valid (see Defined_In_Scope, sem_ch4.adb).
353
354          elsif Nkind (N) = N_Function_Call
355            and then Nkind (Name (N)) = N_Expanded_Name
356            and then (Entity (Prefix (Name (N))) = Scope (Base_Type (T))
357                       or else Entity (Prefix (Name (N))) = Scope (Vis_Type)
358                       or else Scope (Vis_Type) = System_Aux_Id)
359          then
360             null;
361
362          --  Save type for subsequent error message, in case no other
363          --  interpretation is found.
364
365          else
366             Candidate_Type := Vis_Type;
367             return;
368          end if;
369
370       --  In an instance, an abstract non-dispatching operation cannot
371       --  be a candidate interpretation, because it could not have been
372       --  one in the generic (it may be a spurious overloading in the
373       --  instance).
374
375       elsif In_Instance
376         and then Is_Abstract (E)
377         and then not Is_Dispatching_Operation (E)
378       then
379          return;
380       end if;
381
382       --  If this is the first interpretation of N, N has type Any_Type.
383       --  In that case place the new type on the node. If one interpretation
384       --  already exists, indicate that the node is overloaded, and store
385       --  both the previous and the new interpretation in All_Interp. If
386       --  this is a later interpretation, just add it to the set.
387
388       if Etype (N) = Any_Type then
389          if Is_Type (E) then
390             Set_Etype (N, T);
391
392          else
393             --  Record both the operator or subprogram name, and its type.
394
395             if Nkind (N) in N_Op or else Is_Entity_Name (N) then
396                Set_Entity (N, E);
397             end if;
398
399             Set_Etype (N, T);
400          end if;
401
402       --  Either there is no current interpretation in the table for any
403       --  node or the interpretation that is present is for a different
404       --  node. In both cases add a new interpretation to the table.
405
406       elsif Interp_Map.Last < 0
407         or else
408           (Interp_Map.Table (Interp_Map.Last).Node /= N
409              and then not Is_Overloaded (N))
410       then
411          New_Interps (N);
412
413          if (Nkind (N) in N_Op or else Is_Entity_Name (N))
414            and then Present (Entity (N))
415          then
416             Add_Entry (Entity (N), Etype (N));
417
418          elsif (Nkind (N) = N_Function_Call
419                  or else Nkind (N) = N_Procedure_Call_Statement)
420            and then (Nkind (Name (N)) = N_Operator_Symbol
421                       or else Is_Entity_Name (Name (N)))
422          then
423             Add_Entry (Entity (Name (N)), Etype (N));
424
425          else
426             --  Overloaded prefix in indexed or selected component,
427             --  or call whose name is an expresion or another call.
428
429             Add_Entry (Etype (N), Etype (N));
430          end if;
431
432          Add_Entry (E, T);
433
434       else
435          Add_Entry (E, T);
436       end if;
437    end Add_One_Interp;
438
439    -------------------
440    -- All_Overloads --
441    -------------------
442
443    procedure All_Overloads is
444    begin
445       for J in All_Interp.First .. All_Interp.Last loop
446
447          if Present (All_Interp.Table (J).Nam) then
448             Write_Entity_Info (All_Interp.Table (J). Nam, " ");
449          else
450             Write_Str ("No Interp");
451          end if;
452
453          Write_Str ("=================");
454          Write_Eol;
455       end loop;
456    end All_Overloads;
457
458    ---------------------
459    -- Collect_Interps --
460    ---------------------
461
462    procedure Collect_Interps (N : Node_Id) is
463       Ent          : constant Entity_Id := Entity (N);
464       H            : Entity_Id;
465       First_Interp : Interp_Index;
466
467    begin
468       New_Interps (N);
469
470       --  Unconditionally add the entity that was initially matched
471
472       First_Interp := All_Interp.Last;
473       Add_One_Interp (N, Ent, Etype (N));
474
475       --  For expanded name, pick up all additional entities from the
476       --  same scope, since these are obviously also visible. Note that
477       --  these are not necessarily contiguous on the homonym chain.
478
479       if Nkind (N) = N_Expanded_Name then
480          H := Homonym (Ent);
481          while Present (H) loop
482             if Scope (H) = Scope (Entity (N)) then
483                Add_One_Interp (N, H, Etype (H));
484             end if;
485
486             H := Homonym (H);
487          end loop;
488
489       --  Case of direct name
490
491       else
492          --  First, search the homonym chain for directly visible entities
493
494          H := Current_Entity (Ent);
495          while Present (H) loop
496             exit when (not Is_Overloadable (H))
497               and then Is_Immediately_Visible (H);
498
499             if Is_Immediately_Visible (H)
500               and then H /= Ent
501             then
502                --  Only add interpretation if not hidden by an inner
503                --  immediately visible one.
504
505                for J in First_Interp .. All_Interp.Last - 1 loop
506
507                   --  Current homograph is not hidden. Add to overloads.
508
509                   if not Is_Immediately_Visible (All_Interp.Table (J).Nam) then
510                      exit;
511
512                   --  Homograph is hidden, unless it is a predefined operator.
513
514                   elsif Type_Conformant (H, All_Interp.Table (J).Nam) then
515
516                      --  A homograph in the same scope can occur within an
517                      --  instantiation, the resulting ambiguity has to be
518                      --  resolved later.
519
520                      if Scope (H) = Scope (Ent)
521                         and then In_Instance
522                         and then not Is_Inherited_Operation (H)
523                      then
524                         All_Interp.Table (All_Interp.Last) := (H, Etype (H));
525                         All_Interp.Increment_Last;
526                         All_Interp.Table (All_Interp.Last) := No_Interp;
527                         goto Next_Homograph;
528
529                      elsif Scope (H) /= Standard_Standard then
530                         goto Next_Homograph;
531                      end if;
532                   end if;
533                end loop;
534
535                --  On exit, we know that current homograph is not hidden.
536
537                Add_One_Interp (N, H, Etype (H));
538
539                if Debug_Flag_E then
540                   Write_Str ("Add overloaded Interpretation ");
541                   Write_Int (Int (H));
542                   Write_Eol;
543                end if;
544             end if;
545
546             <<Next_Homograph>>
547                H := Homonym (H);
548          end loop;
549
550          --  Scan list of homographs for use-visible entities only.
551
552          H := Current_Entity (Ent);
553
554          while Present (H) loop
555             if Is_Potentially_Use_Visible (H)
556               and then H /= Ent
557               and then Is_Overloadable (H)
558             then
559                for J in First_Interp .. All_Interp.Last - 1 loop
560
561                   if not Is_Immediately_Visible (All_Interp.Table (J).Nam) then
562                      exit;
563
564                   elsif Type_Conformant (H, All_Interp.Table (J).Nam) then
565                      goto Next_Use_Homograph;
566                   end if;
567                end loop;
568
569                Add_One_Interp (N, H, Etype (H));
570             end if;
571
572             <<Next_Use_Homograph>>
573                H := Homonym (H);
574          end loop;
575       end if;
576
577       if All_Interp.Last = First_Interp + 1 then
578
579          --  The original interpretation is in fact not overloaded.
580
581          Set_Is_Overloaded (N, False);
582       end if;
583    end Collect_Interps;
584
585    ------------
586    -- Covers --
587    ------------
588
589    function Covers (T1, T2 : Entity_Id) return Boolean is
590
591       function Full_View_Covers (Typ1, Typ2 : Entity_Id) return Boolean;
592       --  In an instance the proper view may not always be correct for
593       --  private types, but private and full view are compatible. This
594       --  removes spurious errors from nested instantiations that involve,
595       --  among other things, types derived from private types.
596
597       ----------------------
598       -- Full_View_Covers --
599       ----------------------
600
601       function Full_View_Covers (Typ1, Typ2 : Entity_Id) return Boolean is
602       begin
603          return
604            Is_Private_Type (Typ1)
605              and then
606               ((Present (Full_View (Typ1))
607                     and then Covers (Full_View (Typ1), Typ2))
608                  or else Base_Type (Typ1) = Typ2
609                  or else Base_Type (Typ2) = Typ1);
610       end Full_View_Covers;
611
612    --  Start of processing for Covers
613
614    begin
615       --  If either operand missing, then this is an error, but ignore
616       --  it (and pretend we have a cover) if errors already detected,
617       --  since this may simply mean we have malformed trees.
618
619       if No (T1) or else No (T2) then
620          if Total_Errors_Detected /= 0 then
621             return True;
622          else
623             raise Program_Error;
624          end if;
625       end if;
626
627       --  Simplest case: same types are compatible, and types that have the
628       --  same base type and are not generic actuals are compatible. Generic
629       --  actuals  belong to their class but are not compatible with other
630       --  types of their class, and in particular with other generic actuals.
631       --  They are however compatible with their own subtypes, and itypes
632       --  with the same base are compatible as well. Similary, constrained
633       --  subtypes obtained from expressions of an unconstrained nominal type
634       --  are compatible with the base type (may lead to spurious ambiguities
635       --  in obscure cases ???)
636
637       --  Generic actuals require special treatment to avoid spurious ambi-
638       --  guities in an instance, when two formal types are instantiated with
639       --  the same actual, so that different subprograms end up with the same
640       --  signature in the instance.
641
642       if T1 = T2 then
643          return True;
644
645       elsif Base_Type (T1) = Base_Type (T2) then
646          if not Is_Generic_Actual_Type (T1) then
647             return True;
648          else
649             return (not Is_Generic_Actual_Type (T2)
650                      or else Is_Itype (T1)
651                      or else Is_Itype (T2)
652                      or else Is_Constr_Subt_For_U_Nominal (T1)
653                      or else Is_Constr_Subt_For_U_Nominal (T2)
654                      or else Scope (T1) /= Scope (T2));
655          end if;
656
657       --  Literals are compatible with types in  a given "class"
658
659       elsif (T2 = Universal_Integer and then Is_Integer_Type (T1))
660         or else (T2 = Universal_Real    and then Is_Real_Type (T1))
661         or else (T2 = Universal_Fixed   and then Is_Fixed_Point_Type (T1))
662         or else (T2 = Any_Fixed         and then Is_Fixed_Point_Type (T1))
663         or else (T2 = Any_String        and then Is_String_Type (T1))
664         or else (T2 = Any_Character     and then Is_Character_Type (T1))
665         or else (T2 = Any_Access        and then Is_Access_Type (T1))
666       then
667          return True;
668
669       --  The context may be class wide.
670
671       elsif Is_Class_Wide_Type (T1)
672         and then Is_Ancestor (Root_Type (T1), T2)
673       then
674          return True;
675
676       elsif Is_Class_Wide_Type (T1)
677         and then Is_Class_Wide_Type (T2)
678         and then Base_Type (Etype (T1)) = Base_Type (Etype (T2))
679       then
680          return True;
681
682       --  In a dispatching call the actual may be class-wide
683
684       elsif Is_Class_Wide_Type (T2)
685         and then Base_Type (Root_Type (T2)) = Base_Type (T1)
686       then
687          return True;
688
689       --  Some contexts require a class of types rather than a specific type
690
691       elsif (T1 = Any_Integer and then Is_Integer_Type (T2))
692         or else (T1 = Any_Boolean and then Is_Boolean_Type (T2))
693         or else (T1 = Any_Real and then Is_Real_Type (T2))
694         or else (T1 = Any_Fixed and then Is_Fixed_Point_Type (T2))
695         or else (T1 = Any_Discrete and then Is_Discrete_Type (T2))
696       then
697          return True;
698
699       --  An aggregate is compatible with an array or record type
700
701       elsif T2 = Any_Composite
702         and then Ekind (T1) in E_Array_Type .. E_Record_Subtype
703       then
704          return True;
705
706       --  If the expected type is an anonymous access, the designated
707       --  type must cover that of the expression.
708
709       elsif Ekind (T1) = E_Anonymous_Access_Type
710         and then Is_Access_Type (T2)
711         and then Covers (Designated_Type (T1), Designated_Type (T2))
712       then
713          return True;
714
715       --  An Access_To_Subprogram is compatible with itself, or with an
716       --  anonymous type created for an attribute reference Access.
717
718       elsif (Ekind (Base_Type (T1)) = E_Access_Subprogram_Type
719                or else
720              Ekind (Base_Type (T1)) = E_Access_Protected_Subprogram_Type)
721         and then Is_Access_Type (T2)
722         and then (not Comes_From_Source (T1)
723                    or else not Comes_From_Source (T2))
724         and then (Is_Overloadable (Designated_Type (T2))
725                     or else
726                   Ekind (Designated_Type (T2)) = E_Subprogram_Type)
727         and then
728           Type_Conformant (Designated_Type (T1), Designated_Type (T2))
729         and then
730           Mode_Conformant (Designated_Type (T1), Designated_Type (T2))
731       then
732          return True;
733
734       --  The context can be a remote access type, and the expression the
735       --  corresponding source type declared in a categorized package, or
736       --  viceversa.
737
738       elsif Is_Record_Type (T1)
739         and then (Is_Remote_Call_Interface (T1)
740                    or else Is_Remote_Types (T1))
741         and then Present (Corresponding_Remote_Type (T1))
742       then
743          return Covers (Corresponding_Remote_Type (T1), T2);
744
745       elsif Is_Record_Type (T2)
746         and then (Is_Remote_Call_Interface (T2)
747                    or else Is_Remote_Types (T2))
748         and then Present (Corresponding_Remote_Type (T2))
749       then
750          return Covers (Corresponding_Remote_Type (T2), T1);
751
752       elsif Ekind (T2) = E_Access_Attribute_Type
753         and then (Ekind (Base_Type (T1)) = E_General_Access_Type
754               or else Ekind (Base_Type (T1)) = E_Access_Type)
755         and then Covers (Designated_Type (T1), Designated_Type (T2))
756       then
757          --  If the target type is a RACW type while the source is an access
758          --  attribute type, we are building a RACW that may be exported.
759
760          if Is_Remote_Access_To_Class_Wide_Type (Base_Type (T1)) then
761             Set_Has_RACW (Current_Sem_Unit);
762          end if;
763
764          return True;
765
766       elsif Ekind (T2) = E_Allocator_Type
767         and then Is_Access_Type (T1)
768       then
769          return Covers (Designated_Type (T1), Designated_Type (T2))
770           or else
771             (From_With_Type (Designated_Type (T1))
772               and then Covers (Designated_Type (T2), Designated_Type (T1)));
773
774       --  A boolean operation on integer literals is compatible with a
775       --  modular context.
776
777       elsif T2 = Any_Modular
778         and then Is_Modular_Integer_Type (T1)
779       then
780          return True;
781
782       --  The actual type may be the result of a previous error
783
784       elsif Base_Type (T2) = Any_Type then
785          return True;
786
787       --  A packed array type covers its corresponding non-packed type.
788       --  This is not legitimate Ada, but allows the omission of a number
789       --  of otherwise useless unchecked conversions, and since this can
790       --  only arise in (known correct) expanded code, no harm is done
791
792       elsif Is_Array_Type (T2)
793         and then Is_Packed (T2)
794         and then T1 = Packed_Array_Type (T2)
795       then
796          return True;
797
798       --  Similarly an array type covers its corresponding packed array type
799
800       elsif Is_Array_Type (T1)
801         and then Is_Packed (T1)
802         and then T2 = Packed_Array_Type (T1)
803       then
804          return True;
805
806       elsif In_Instance
807         and then
808           (Full_View_Covers (T1, T2)
809             or else Full_View_Covers (T2, T1))
810       then
811          return True;
812
813       --  In the expansion of inlined bodies, types are compatible if they
814       --  are structurally equivalent.
815
816       elsif In_Inlined_Body
817         and then (Underlying_Type (T1) = Underlying_Type (T2)
818                    or else (Is_Access_Type (T1)
819                               and then Is_Access_Type (T2)
820                               and then
821                                 Designated_Type (T1) = Designated_Type (T2))
822                    or else (T1 = Any_Access
823                               and then Is_Access_Type (Underlying_Type (T2))))
824       then
825          return True;
826
827       elsif From_With_Type (T1) then
828
829          --  If the expected type is the non-limited view of a type, the
830          --  expression may have the limited view.
831
832          if Ekind (T1) = E_Incomplete_Type then
833             return Covers (Non_Limited_View (T1), T2);
834
835          elsif Ekind (T1) = E_Class_Wide_Type then
836             return
837               Covers (Class_Wide_Type (Non_Limited_View (Etype (T1))), T2);
838          else
839             return False;
840          end if;
841
842       elsif From_With_Type (T2) then
843
844          --  If units in the context have Limited_With clauses on each other,
845          --  either type might have a limited view. Checks performed elsewhere
846          --  verify that the context type is the non-limited view.
847
848          if Ekind (T2) = E_Incomplete_Type then
849             return Covers (T1, Non_Limited_View (T2));
850
851          elsif Ekind (T2) = E_Class_Wide_Type then
852             return
853               Covers (T1, Class_Wide_Type (Non_Limited_View (Etype (T2))));
854          else
855             return False;
856          end if;
857
858       --  Otherwise it doesn't cover!
859
860       else
861          return False;
862       end if;
863    end Covers;
864
865    ------------------
866    -- Disambiguate --
867    ------------------
868
869    function Disambiguate
870      (N      : Node_Id;
871       I1, I2 : Interp_Index;
872       Typ    : Entity_Id)
873       return   Interp
874    is
875       I           : Interp_Index;
876       It          : Interp;
877       It1, It2    : Interp;
878       Nam1, Nam2  : Entity_Id;
879       Predef_Subp : Entity_Id;
880       User_Subp   : Entity_Id;
881
882       function Is_Actual_Subprogram (S : Entity_Id) return Boolean;
883       --  Determine whether a subprogram is an actual in an enclosing
884       --  instance. An overloading between such a subprogram and one
885       --  declared outside the instance is resolved in favor of the first,
886       --  because it resolved in the generic.
887
888       function Matches (Actual, Formal : Node_Id) return Boolean;
889       --  Look for exact type match in an instance, to remove spurious
890       --  ambiguities when two formal types have the same actual.
891
892       function Standard_Operator return Boolean;
893
894       function Remove_Conversions return Interp;
895       --  Last chance for pathological cases involving comparisons on
896       --  literals, and user overloadings of the same operator. Such
897       --  pathologies have been removed from the ACVC, but still appear in
898       --  two DEC tests, with the following notable quote from Ben Brosgol:
899       --
900       --  [Note: I disclaim all credit/responsibility/blame for coming up with
901       --  this example;  Robert Dewar brought it to our attention, since it
902       --  is apparently found in the ACVC 1.5. I did not attempt to find
903       --  the reason in the Reference Manual that makes the example legal,
904       --  since I was too nauseated by it to want to pursue it further.]
905       --
906       --  Accordingly, this is not a fully recursive solution, but it handles
907       --  DEC tests c460vsa, c460vsb. It also handles ai00136a, which pushes
908       --  pathology in the other direction with calls whose multiple overloaded
909       --  actuals make them truly unresolvable.
910
911       function Is_Actual_Subprogram (S : Entity_Id) return Boolean is
912       begin
913          return In_Open_Scopes (Scope (S))
914            and then
915              (Is_Generic_Instance (Scope (S))
916                 or else Is_Wrapper_Package (Scope (S)));
917       end Is_Actual_Subprogram;
918
919       -------------
920       -- Matches --
921       -------------
922
923       function Matches (Actual, Formal : Node_Id) return Boolean is
924          T1 : constant Entity_Id := Etype (Actual);
925          T2 : constant Entity_Id := Etype (Formal);
926
927       begin
928          return T1 = T2
929            or else
930              (Is_Numeric_Type (T2)
931                and then
932              (T1 = Universal_Real or else T1 = Universal_Integer));
933       end Matches;
934
935       ------------------------
936       -- Remove_Conversions --
937       ------------------------
938
939       function Remove_Conversions return Interp is
940          I    : Interp_Index;
941          It   : Interp;
942          It1  : Interp;
943          F1   : Entity_Id;
944          Act1 : Node_Id;
945          Act2 : Node_Id;
946
947       begin
948          It1   := No_Interp;
949          Get_First_Interp (N, I, It);
950
951          while Present (It.Typ) loop
952
953             if not Is_Overloadable (It.Nam) then
954                return No_Interp;
955             end if;
956
957             F1 := First_Formal (It.Nam);
958
959             if No (F1) then
960                return It1;
961
962             else
963                if Nkind (N) = N_Function_Call
964                  or else Nkind (N) = N_Procedure_Call_Statement
965                then
966                   Act1 := First_Actual (N);
967
968                   if Present (Act1) then
969                      Act2 := Next_Actual (Act1);
970                   else
971                      Act2 := Empty;
972                   end if;
973
974                elsif Nkind (N) in N_Unary_Op then
975                   Act1 := Right_Opnd (N);
976                   Act2 := Empty;
977
978                elsif Nkind (N) in N_Binary_Op then
979                   Act1 := Left_Opnd (N);
980                   Act2 := Right_Opnd (N);
981
982                else
983                   return It1;
984                end if;
985
986                if Nkind (Act1) in N_Op
987                  and then Is_Overloaded (Act1)
988                  and then (Nkind (Right_Opnd (Act1)) = N_Integer_Literal
989                             or else Nkind (Right_Opnd (Act1)) = N_Real_Literal)
990                  and then Has_Compatible_Type (Act1, Standard_Boolean)
991                  and then Etype (F1) = Standard_Boolean
992                then
993                   --  If the two candidates are the original ones, the
994                   --  ambiguity is real. Otherwise keep the original,
995                   --  further calls to Disambiguate will take care of
996                   --  others in the list of candidates.
997
998                   if It1 /= No_Interp then
999                      if It = Disambiguate.It1
1000                        or else It = Disambiguate.It2
1001                      then
1002                         if It1 = Disambiguate.It1
1003                           or else It1 = Disambiguate.It2
1004                         then
1005                            return No_Interp;
1006                         else
1007                            It1 := It;
1008                         end if;
1009                      end if;
1010
1011                   elsif Present (Act2)
1012                     and then Nkind (Act2) in N_Op
1013                     and then Is_Overloaded (Act2)
1014                     and then (Nkind (Right_Opnd (Act1)) = N_Integer_Literal
1015                                 or else
1016                               Nkind (Right_Opnd (Act1)) = N_Real_Literal)
1017                     and then Has_Compatible_Type (Act2, Standard_Boolean)
1018                   then
1019                      --  The preference rule on the first actual is not
1020                      --  sufficient to disambiguate.
1021
1022                      goto Next_Interp;
1023
1024                   else
1025                      It1 := It;
1026                   end if;
1027                end if;
1028             end if;
1029
1030             <<Next_Interp>>
1031                Get_Next_Interp (I, It);
1032          end loop;
1033
1034          if Serious_Errors_Detected > 0 then
1035
1036             --  After some error, a formal may have Any_Type and yield
1037             --  a spurious match. To avoid cascaded errors if possible,
1038             --  check for such a formal in either candidate.
1039
1040             declare
1041                Formal : Entity_Id;
1042
1043             begin
1044                Formal := First_Formal (Nam1);
1045                while Present (Formal) loop
1046                   if Etype (Formal) = Any_Type then
1047                      return Disambiguate.It2;
1048                   end if;
1049
1050                   Next_Formal (Formal);
1051                end loop;
1052
1053                Formal := First_Formal (Nam2);
1054                while Present (Formal) loop
1055                   if Etype (Formal) = Any_Type then
1056                      return Disambiguate.It1;
1057                   end if;
1058
1059                   Next_Formal (Formal);
1060                end loop;
1061             end;
1062          end if;
1063
1064          return It1;
1065       end Remove_Conversions;
1066
1067       -----------------------
1068       -- Standard_Operator --
1069       -----------------------
1070
1071       function Standard_Operator return Boolean is
1072          Nam : Node_Id;
1073
1074       begin
1075          if Nkind (N) in N_Op then
1076             return True;
1077
1078          elsif Nkind (N) = N_Function_Call then
1079             Nam := Name (N);
1080
1081             if Nkind (Nam) /= N_Expanded_Name then
1082                return True;
1083             else
1084                return Entity (Prefix (Nam)) = Standard_Standard;
1085             end if;
1086          else
1087             return False;
1088          end if;
1089       end Standard_Operator;
1090
1091    --  Start of processing for Disambiguate
1092
1093    begin
1094       --  Recover the two legal interpretations.
1095
1096       Get_First_Interp (N, I, It);
1097
1098       while I /= I1 loop
1099          Get_Next_Interp (I, It);
1100       end loop;
1101
1102       It1  := It;
1103       Nam1 := It.Nam;
1104
1105       while I /= I2 loop
1106          Get_Next_Interp (I, It);
1107       end loop;
1108
1109       It2  := It;
1110       Nam2 := It.Nam;
1111
1112       --  If the context is universal, the predefined operator is preferred.
1113       --  This includes bounds in numeric type declarations, and expressions
1114       --  in type conversions. If no interpretation yields a universal type,
1115       --  then we must check whether the user-defined entity hides the prede-
1116       --  fined one.
1117
1118       if Chars (Nam1) in  Any_Operator_Name
1119         and then Standard_Operator
1120       then
1121          if        Typ = Universal_Integer
1122            or else Typ = Universal_Real
1123            or else Typ = Any_Integer
1124            or else Typ = Any_Discrete
1125            or else Typ = Any_Real
1126            or else Typ = Any_Type
1127          then
1128             --  Find an interpretation that yields the universal type, or else
1129             --  a predefined operator that yields a predefined numeric type.
1130
1131             declare
1132                Candidate : Interp := No_Interp;
1133             begin
1134                Get_First_Interp (N, I, It);
1135
1136                while Present (It.Typ) loop
1137                   if (Covers (Typ, It.Typ)
1138                        or else Typ = Any_Type)
1139                     and then
1140                      (It.Typ = Universal_Integer
1141                        or else It.Typ = Universal_Real)
1142                   then
1143                      return It;
1144
1145                   elsif Covers (Typ, It.Typ)
1146                     and then Scope (It.Typ) = Standard_Standard
1147                     and then Scope (It.Nam) = Standard_Standard
1148                     and then Is_Numeric_Type (It.Typ)
1149                   then
1150                      Candidate := It;
1151                   end if;
1152
1153                   Get_Next_Interp (I, It);
1154                end loop;
1155
1156                if Candidate /= No_Interp then
1157                   return Candidate;
1158                end if;
1159             end;
1160
1161          elsif Chars (Nam1) /= Name_Op_Not
1162            and then (Typ = Standard_Boolean
1163              or else Typ = Any_Boolean)
1164          then
1165             --  Equality or comparison operation. Choose predefined operator
1166             --  if arguments are universal. The node may be an operator, a
1167             --  name, or a function call, so unpack arguments accordingly.
1168
1169             declare
1170                Arg1, Arg2 : Node_Id;
1171
1172             begin
1173                if Nkind (N) in N_Op then
1174                   Arg1 := Left_Opnd  (N);
1175                   Arg2 := Right_Opnd (N);
1176
1177                elsif Is_Entity_Name (N)
1178                  or else Nkind (N) = N_Operator_Symbol
1179                then
1180                   Arg1 := First_Entity (Entity (N));
1181                   Arg2 := Next_Entity (Arg1);
1182
1183                else
1184                   Arg1 := First_Actual (N);
1185                   Arg2 := Next_Actual (Arg1);
1186                end if;
1187
1188                if Present (Arg2)
1189                  and then Present (Universal_Interpretation (Arg1))
1190                  and then Universal_Interpretation (Arg2) =
1191                           Universal_Interpretation (Arg1)
1192                then
1193                   Get_First_Interp (N, I, It);
1194
1195                   while Scope (It.Nam) /= Standard_Standard loop
1196                      Get_Next_Interp (I, It);
1197                   end loop;
1198
1199                   return It;
1200                end if;
1201             end;
1202          end if;
1203       end if;
1204
1205       --  If no universal interpretation, check whether user-defined operator
1206       --  hides predefined one, as well as other special cases. If the node
1207       --  is a range, then one or both bounds are ambiguous. Each will have
1208       --  to be disambiguated w.r.t. the context type. The type of the range
1209       --  itself is imposed by the context, so we can return either legal
1210       --  interpretation.
1211
1212       if Ekind (Nam1) = E_Operator then
1213          Predef_Subp := Nam1;
1214          User_Subp   := Nam2;
1215
1216       elsif Ekind (Nam2) = E_Operator then
1217          Predef_Subp := Nam2;
1218          User_Subp   := Nam1;
1219
1220       elsif Nkind (N) = N_Range then
1221          return It1;
1222
1223       --  If two user defined-subprograms are visible, it is a true ambiguity,
1224       --  unless one of them is an entry and the context is a conditional or
1225       --  timed entry call, or unless we are within an instance and this is
1226       --  results from two formals types with the same actual.
1227
1228       else
1229          if Nkind (N) = N_Procedure_Call_Statement
1230            and then Nkind (Parent (N)) = N_Entry_Call_Alternative
1231            and then N = Entry_Call_Statement (Parent (N))
1232          then
1233             if Ekind (Nam2) = E_Entry then
1234                return It2;
1235             elsif Ekind (Nam1) = E_Entry then
1236                return It1;
1237             else
1238                return No_Interp;
1239             end if;
1240
1241          --  If the ambiguity occurs within an instance, it is due to several
1242          --  formal types with the same actual. Look for an exact match
1243          --  between the types of the formals of the overloadable entities,
1244          --  and the actuals in the call, to recover the unambiguous match
1245          --  in the original generic.
1246
1247          --  The ambiguity can also be due to an overloading between a formal
1248          --  subprogram and a subprogram declared outside the generic. If the
1249          --  node is overloaded, it did not resolve to the global entity in
1250          --  the generic, and we choose the formal subprogram.
1251
1252          elsif In_Instance then
1253             if Nkind (N) = N_Function_Call
1254               or else Nkind (N) = N_Procedure_Call_Statement
1255             then
1256                declare
1257                   Actual  : Node_Id;
1258                   Formal  : Entity_Id;
1259                   Is_Act1 : constant Boolean := Is_Actual_Subprogram (Nam1);
1260                   Is_Act2 : constant Boolean := Is_Actual_Subprogram (Nam2);
1261
1262                begin
1263                   if Is_Act1 and then not Is_Act2 then
1264                      return It1;
1265
1266                   elsif Is_Act2 and then not Is_Act1 then
1267                      return It2;
1268                   end if;
1269
1270                   Actual := First_Actual (N);
1271                   Formal := First_Formal (Nam1);
1272                   while Present (Actual) loop
1273                      if Etype (Actual) /= Etype (Formal) then
1274                         return It2;
1275                      end if;
1276
1277                      Next_Actual (Actual);
1278                      Next_Formal (Formal);
1279                   end loop;
1280
1281                   return It1;
1282                end;
1283
1284             elsif Nkind (N) in N_Binary_Op then
1285
1286                if Matches (Left_Opnd (N), First_Formal (Nam1))
1287                  and then
1288                    Matches (Right_Opnd (N), Next_Formal (First_Formal (Nam1)))
1289                then
1290                   return It1;
1291                else
1292                   return It2;
1293                end if;
1294
1295             elsif Nkind (N) in  N_Unary_Op then
1296
1297                if Etype (Right_Opnd (N)) = Etype (First_Formal (Nam1)) then
1298                   return It1;
1299                else
1300                   return It2;
1301                end if;
1302
1303             else
1304                return Remove_Conversions;
1305             end if;
1306          else
1307             return Remove_Conversions;
1308          end if;
1309       end if;
1310
1311       --  an implicit concatenation operator on a string type cannot be
1312       --  disambiguated from the predefined concatenation. This can only
1313       --  happen with concatenation of string literals.
1314
1315       if Chars (User_Subp) = Name_Op_Concat
1316         and then Ekind (User_Subp) = E_Operator
1317         and then Is_String_Type (Etype (First_Formal (User_Subp)))
1318       then
1319          return No_Interp;
1320
1321       --  If the user-defined operator is in  an open scope, or in the scope
1322       --  of the resulting type, or given by an expanded name that names its
1323       --  scope, it hides the predefined operator for the type. Exponentiation
1324       --  has to be special-cased because the implicit operator does not have
1325       --  a symmetric signature, and may not be hidden by the explicit one.
1326
1327       elsif (Nkind (N) = N_Function_Call
1328               and then Nkind (Name (N)) = N_Expanded_Name
1329               and then (Chars (Predef_Subp) /= Name_Op_Expon
1330                           or else Hides_Op (User_Subp, Predef_Subp))
1331               and then Scope (User_Subp) = Entity (Prefix (Name (N))))
1332         or else Hides_Op (User_Subp, Predef_Subp)
1333       then
1334          if It1.Nam = User_Subp then
1335             return It1;
1336          else
1337             return It2;
1338          end if;
1339
1340       --  Otherwise, the predefined operator has precedence, or if the
1341       --  user-defined operation is directly visible we have a true ambiguity.
1342       --  If this is a fixed-point multiplication and division in Ada83 mode,
1343       --  exclude the universal_fixed operator, which often causes ambiguities
1344       --  in legacy code.
1345
1346       else
1347          if (In_Open_Scopes (Scope (User_Subp))
1348            or else Is_Potentially_Use_Visible (User_Subp))
1349            and then not In_Instance
1350          then
1351             if Is_Fixed_Point_Type (Typ)
1352               and then (Chars (Nam1) = Name_Op_Multiply
1353                          or else Chars (Nam1) = Name_Op_Divide)
1354               and then Ada_83
1355             then
1356                if It2.Nam = Predef_Subp then
1357                   return It1;
1358
1359                else
1360                   return It2;
1361                end if;
1362             else
1363                return No_Interp;
1364             end if;
1365
1366          elsif It1.Nam = Predef_Subp then
1367             return It1;
1368
1369          else
1370             return It2;
1371          end if;
1372       end if;
1373
1374    end Disambiguate;
1375
1376    ---------------------
1377    -- End_Interp_List --
1378    ---------------------
1379
1380    procedure End_Interp_List is
1381    begin
1382       All_Interp.Table (All_Interp.Last) := No_Interp;
1383       All_Interp.Increment_Last;
1384    end End_Interp_List;
1385
1386    -------------------------
1387    -- Entity_Matches_Spec --
1388    -------------------------
1389
1390    function Entity_Matches_Spec (Old_S, New_S : Entity_Id) return Boolean is
1391    begin
1392       --  Simple case: same entity kinds, type conformance is required.
1393       --  A parameterless function can also rename a literal.
1394
1395       if Ekind (Old_S) = Ekind (New_S)
1396         or else (Ekind (New_S) = E_Function
1397                   and then Ekind (Old_S) = E_Enumeration_Literal)
1398       then
1399          return Type_Conformant (New_S, Old_S);
1400
1401       elsif Ekind (New_S) = E_Function
1402         and then Ekind (Old_S) = E_Operator
1403       then
1404          return Operator_Matches_Spec (Old_S, New_S);
1405
1406       elsif Ekind (New_S) = E_Procedure
1407         and then Is_Entry (Old_S)
1408       then
1409          return Type_Conformant (New_S, Old_S);
1410
1411       else
1412          return False;
1413       end if;
1414    end Entity_Matches_Spec;
1415
1416    ----------------------
1417    -- Find_Unique_Type --
1418    ----------------------
1419
1420    function Find_Unique_Type (L : Node_Id; R : Node_Id) return Entity_Id is
1421       T  : constant Entity_Id := Etype (L);
1422       I  : Interp_Index;
1423       It : Interp;
1424       TR : Entity_Id := Any_Type;
1425
1426    begin
1427       if Is_Overloaded (R) then
1428          Get_First_Interp (R, I, It);
1429
1430          while Present (It.Typ) loop
1431             if Covers (T, It.Typ) or else Covers (It.Typ, T) then
1432
1433                --  If several interpretations are possible and L is universal,
1434                --  apply preference rule.
1435
1436                if TR /= Any_Type then
1437
1438                   if (T = Universal_Integer or else T = Universal_Real)
1439                     and then It.Typ = T
1440                   then
1441                      TR := It.Typ;
1442                   end if;
1443
1444                else
1445                   TR := It.Typ;
1446                end if;
1447             end if;
1448
1449             Get_Next_Interp (I, It);
1450          end loop;
1451
1452          Set_Etype (R, TR);
1453
1454       --  In the non-overloaded case, the Etype of R is already set
1455       --  correctly.
1456
1457       else
1458          null;
1459       end if;
1460
1461       --  If one of the operands is Universal_Fixed, the type of the
1462       --  other operand provides the context.
1463
1464       if Etype (R) = Universal_Fixed then
1465          return T;
1466
1467       elsif T = Universal_Fixed then
1468          return Etype (R);
1469
1470       else
1471          return Specific_Type (T, Etype (R));
1472       end if;
1473
1474    end Find_Unique_Type;
1475
1476    ----------------------
1477    -- Get_First_Interp --
1478    ----------------------
1479
1480    procedure Get_First_Interp
1481      (N  : Node_Id;
1482       I  : out Interp_Index;
1483       It : out Interp)
1484    is
1485       Map_Ptr : Int;
1486       Int_Ind : Interp_Index;
1487       O_N     : Node_Id;
1488
1489    begin
1490       --  If a selected component is overloaded because the selector has
1491       --  multiple interpretations, the node is a call to a protected
1492       --  operation or an indirect call. Retrieve the interpretation from
1493       --  the selector name. The selected component may be overloaded as well
1494       --  if the prefix is overloaded. That case is unchanged.
1495
1496       if Nkind (N) = N_Selected_Component
1497         and then Is_Overloaded (Selector_Name (N))
1498       then
1499          O_N := Selector_Name (N);
1500       else
1501          O_N := N;
1502       end if;
1503
1504       Map_Ptr := Headers (Hash (O_N));
1505
1506       while Present (Interp_Map.Table (Map_Ptr).Node) loop
1507          if Interp_Map.Table (Map_Ptr).Node = O_N then
1508             Int_Ind := Interp_Map.Table (Map_Ptr).Index;
1509             It := All_Interp.Table (Int_Ind);
1510             I := Int_Ind;
1511             return;
1512          else
1513             Map_Ptr := Interp_Map.Table (Map_Ptr).Next;
1514          end if;
1515       end loop;
1516
1517       --  Procedure should never be called if the node has no interpretations
1518
1519       raise Program_Error;
1520    end Get_First_Interp;
1521
1522    ----------------------
1523    --  Get_Next_Interp --
1524    ----------------------
1525
1526    procedure Get_Next_Interp (I : in out Interp_Index; It : out Interp) is
1527    begin
1528       I  := I + 1;
1529       It := All_Interp.Table (I);
1530    end Get_Next_Interp;
1531
1532    -------------------------
1533    -- Has_Compatible_Type --
1534    -------------------------
1535
1536    function Has_Compatible_Type
1537      (N    : Node_Id;
1538       Typ  : Entity_Id)
1539       return Boolean
1540    is
1541       I  : Interp_Index;
1542       It : Interp;
1543
1544    begin
1545       if N = Error then
1546          return False;
1547       end if;
1548
1549       if Nkind (N) = N_Subtype_Indication
1550         or else not Is_Overloaded (N)
1551       then
1552          return
1553            Covers (Typ, Etype (N))
1554            or else
1555              (not Is_Tagged_Type (Typ)
1556                 and then Ekind (Typ) /= E_Anonymous_Access_Type
1557                 and then Covers (Etype (N), Typ));
1558
1559       else
1560          Get_First_Interp (N, I, It);
1561
1562          while Present (It.Typ) loop
1563             if (Covers (Typ, It.Typ)
1564                 and then
1565                   (Scope (It.Nam) /= Standard_Standard
1566                      or else not Is_Invisible_Operator (N, Base_Type (Typ))))
1567
1568               or else (not Is_Tagged_Type (Typ)
1569                         and then Ekind (Typ) /= E_Anonymous_Access_Type
1570                         and then Covers (It.Typ, Typ))
1571             then
1572                return True;
1573             end if;
1574
1575             Get_Next_Interp (I, It);
1576          end loop;
1577
1578          return False;
1579       end if;
1580    end Has_Compatible_Type;
1581
1582    ----------
1583    -- Hash --
1584    ----------
1585
1586    function Hash (N : Node_Id) return Int is
1587    begin
1588       --  Nodes have a size that is power of two, so to select significant
1589       --  bits only we remove the low-order bits.
1590
1591       return ((Int (N) / 2 ** 5) mod Header_Size);
1592    end Hash;
1593
1594    --------------
1595    -- Hides_Op --
1596    --------------
1597
1598    function Hides_Op (F : Entity_Id; Op : Entity_Id) return Boolean is
1599       Btyp : constant Entity_Id := Base_Type (Etype (First_Formal (F)));
1600
1601    begin
1602       return Operator_Matches_Spec (Op, F)
1603         and then (In_Open_Scopes (Scope (F))
1604                     or else Scope (F) = Scope (Btyp)
1605                     or else (not In_Open_Scopes (Scope (Btyp))
1606                               and then not In_Use (Btyp)
1607                               and then not In_Use (Scope (Btyp))));
1608    end Hides_Op;
1609
1610    ------------------------
1611    -- Init_Interp_Tables --
1612    ------------------------
1613
1614    procedure Init_Interp_Tables is
1615    begin
1616       All_Interp.Init;
1617       Interp_Map.Init;
1618       Headers := (others => No_Entry);
1619    end Init_Interp_Tables;
1620
1621    ---------------------
1622    -- Intersect_Types --
1623    ---------------------
1624
1625    function Intersect_Types (L, R : Node_Id) return Entity_Id is
1626       Index : Interp_Index;
1627       It    : Interp;
1628       Typ   : Entity_Id;
1629
1630       function Check_Right_Argument (T : Entity_Id) return Entity_Id;
1631       --  Find interpretation of right arg that has type compatible with T
1632
1633       --------------------------
1634       -- Check_Right_Argument --
1635       --------------------------
1636
1637       function Check_Right_Argument (T : Entity_Id) return Entity_Id is
1638          Index : Interp_Index;
1639          It    : Interp;
1640          T2    : Entity_Id;
1641
1642       begin
1643          if not Is_Overloaded (R) then
1644             return Specific_Type (T, Etype (R));
1645
1646          else
1647             Get_First_Interp (R, Index, It);
1648
1649             loop
1650                T2 := Specific_Type (T, It.Typ);
1651
1652                if T2 /= Any_Type then
1653                   return T2;
1654                end if;
1655
1656                Get_Next_Interp (Index, It);
1657                exit when No (It.Typ);
1658             end loop;
1659
1660             return Any_Type;
1661          end if;
1662       end Check_Right_Argument;
1663
1664    --  Start processing for Intersect_Types
1665
1666    begin
1667       if Etype (L) = Any_Type or else Etype (R) = Any_Type then
1668          return Any_Type;
1669       end if;
1670
1671       if not Is_Overloaded (L) then
1672          Typ := Check_Right_Argument (Etype (L));
1673
1674       else
1675          Typ := Any_Type;
1676          Get_First_Interp (L, Index, It);
1677
1678          while Present (It.Typ) loop
1679             Typ := Check_Right_Argument (It.Typ);
1680             exit when Typ /= Any_Type;
1681             Get_Next_Interp (Index, It);
1682          end loop;
1683
1684       end if;
1685
1686       --  If Typ is Any_Type, it means no compatible pair of types was found
1687
1688       if Typ = Any_Type then
1689
1690          if Nkind (Parent (L)) in N_Op then
1691             Error_Msg_N ("incompatible types for operator", Parent (L));
1692
1693          elsif Nkind (Parent (L)) = N_Range then
1694             Error_Msg_N ("incompatible types given in constraint", Parent (L));
1695
1696          else
1697             Error_Msg_N ("incompatible types", Parent (L));
1698          end if;
1699       end if;
1700
1701       return Typ;
1702    end Intersect_Types;
1703
1704    -----------------
1705    -- Is_Ancestor --
1706    -----------------
1707
1708    function Is_Ancestor (T1, T2 : Entity_Id) return Boolean is
1709       Par : Entity_Id;
1710
1711    begin
1712       if Base_Type (T1) = Base_Type (T2) then
1713          return True;
1714
1715       elsif Is_Private_Type (T1)
1716         and then Present (Full_View (T1))
1717         and then Base_Type (T2) = Base_Type (Full_View (T1))
1718       then
1719          return True;
1720
1721       else
1722          Par := Etype (T2);
1723
1724          loop
1725             --  If there was a error on the type declaration, do not recurse
1726
1727             if Error_Posted (Par) then
1728                return False;
1729
1730             elsif Base_Type (T1) = Base_Type (Par)
1731               or else (Is_Private_Type (T1)
1732                          and then Present (Full_View (T1))
1733                          and then Base_Type (Par) = Base_Type (Full_View (T1)))
1734             then
1735                return True;
1736
1737             elsif Is_Private_Type (Par)
1738               and then Present (Full_View (Par))
1739               and then Full_View (Par) = Base_Type (T1)
1740             then
1741                return True;
1742
1743             elsif Etype (Par) /= Par then
1744                Par := Etype (Par);
1745             else
1746                return False;
1747             end if;
1748          end loop;
1749       end if;
1750    end Is_Ancestor;
1751
1752    ---------------------------
1753    -- Is_Invisible_Operator --
1754    ---------------------------
1755
1756    function Is_Invisible_Operator
1757      (N    : Node_Id;
1758       T    : Entity_Id)
1759       return Boolean
1760    is
1761       Orig_Node : constant Node_Id := Original_Node (N);
1762
1763    begin
1764       if Nkind (N) not in N_Op then
1765          return False;
1766
1767       elsif not Comes_From_Source (N) then
1768          return False;
1769
1770       elsif No (Universal_Interpretation (Right_Opnd (N))) then
1771          return False;
1772
1773       elsif Nkind (N) in N_Binary_Op
1774         and then No (Universal_Interpretation (Left_Opnd (N)))
1775       then
1776          return False;
1777
1778       else return
1779         Is_Numeric_Type (T)
1780           and then not In_Open_Scopes (Scope (T))
1781           and then not Is_Potentially_Use_Visible (T)
1782           and then not In_Use (T)
1783           and then not In_Use (Scope (T))
1784           and then
1785             (Nkind (Orig_Node) /= N_Function_Call
1786               or else Nkind (Name (Orig_Node)) /= N_Expanded_Name
1787               or else Entity (Prefix (Name (Orig_Node))) /= Scope (T))
1788
1789           and then not In_Instance;
1790       end if;
1791    end Is_Invisible_Operator;
1792
1793    -------------------
1794    -- Is_Subtype_Of --
1795    -------------------
1796
1797    function Is_Subtype_Of (T1 : Entity_Id; T2 : Entity_Id) return Boolean is
1798       S : Entity_Id;
1799
1800    begin
1801       S := Ancestor_Subtype (T1);
1802       while Present (S) loop
1803          if S = T2 then
1804             return True;
1805          else
1806             S := Ancestor_Subtype (S);
1807          end if;
1808       end loop;
1809
1810       return False;
1811    end Is_Subtype_Of;
1812
1813    ------------------
1814    -- List_Interps --
1815    ------------------
1816
1817    procedure List_Interps (Nam : Node_Id; Err : Node_Id) is
1818       Index : Interp_Index;
1819       It    : Interp;
1820
1821    begin
1822       Get_First_Interp (Nam, Index, It);
1823       while Present (It.Nam) loop
1824          if Scope (It.Nam) = Standard_Standard
1825            and then Scope (It.Typ) /= Standard_Standard
1826          then
1827             Error_Msg_Sloc := Sloc (Parent (It.Typ));
1828             Error_Msg_NE ("   & (inherited) declared#!", Err, It.Nam);
1829
1830          else
1831             Error_Msg_Sloc := Sloc (It.Nam);
1832             Error_Msg_NE ("   & declared#!", Err, It.Nam);
1833          end if;
1834
1835          Get_Next_Interp (Index, It);
1836       end loop;
1837    end List_Interps;
1838
1839    -----------------
1840    -- New_Interps --
1841    -----------------
1842
1843    procedure New_Interps (N : Node_Id)  is
1844       Map_Ptr : Int;
1845
1846    begin
1847       All_Interp.Increment_Last;
1848       All_Interp.Table (All_Interp.Last) := No_Interp;
1849
1850       Map_Ptr := Headers (Hash (N));
1851
1852       if Map_Ptr = No_Entry then
1853
1854          --  Place new node at end of table
1855
1856          Interp_Map.Increment_Last;
1857          Headers (Hash (N)) := Interp_Map.Last;
1858
1859       else
1860          --   Place node at end of chain, or locate its previous entry.
1861
1862          loop
1863             if Interp_Map.Table (Map_Ptr).Node = N then
1864
1865                --  Node is already in the table, and is being rewritten.
1866                --  Start a new interp section, retain hash link.
1867
1868                Interp_Map.Table (Map_Ptr).Node  := N;
1869                Interp_Map.Table (Map_Ptr).Index := All_Interp.Last;
1870                Set_Is_Overloaded (N, True);
1871                return;
1872
1873             else
1874                exit when Interp_Map.Table (Map_Ptr).Next = No_Entry;
1875                Map_Ptr := Interp_Map.Table (Map_Ptr).Next;
1876             end if;
1877          end loop;
1878
1879          --  Chain the new node.
1880
1881          Interp_Map.Increment_Last;
1882          Interp_Map.Table (Map_Ptr).Next := Interp_Map.Last;
1883       end if;
1884
1885       Interp_Map.Table (Interp_Map.Last) := (N, All_Interp.Last, No_Entry);
1886       Set_Is_Overloaded (N, True);
1887    end New_Interps;
1888
1889    ---------------------------
1890    -- Operator_Matches_Spec --
1891    ---------------------------
1892
1893    function Operator_Matches_Spec (Op, New_S : Entity_Id) return Boolean is
1894       Op_Name : constant Name_Id   := Chars (Op);
1895       T       : constant Entity_Id := Etype (New_S);
1896       New_F   : Entity_Id;
1897       Old_F   : Entity_Id;
1898       Num     : Int;
1899       T1      : Entity_Id;
1900       T2      : Entity_Id;
1901
1902    begin
1903       --  To verify that a predefined operator matches a given signature,
1904       --  do a case analysis of the operator classes. Function can have one
1905       --  or two formals and must have the proper result type.
1906
1907       New_F := First_Formal (New_S);
1908       Old_F := First_Formal (Op);
1909       Num := 0;
1910
1911       while Present (New_F) and then Present (Old_F) loop
1912          Num := Num + 1;
1913          Next_Formal (New_F);
1914          Next_Formal (Old_F);
1915       end loop;
1916
1917       --  Definite mismatch if different number of parameters
1918
1919       if Present (Old_F) or else Present (New_F) then
1920          return False;
1921
1922       --  Unary operators
1923
1924       elsif Num = 1 then
1925          T1 := Etype (First_Formal (New_S));
1926
1927          if Op_Name = Name_Op_Subtract
1928            or else Op_Name = Name_Op_Add
1929            or else Op_Name = Name_Op_Abs
1930          then
1931             return Base_Type (T1) = Base_Type (T)
1932               and then Is_Numeric_Type (T);
1933
1934          elsif Op_Name = Name_Op_Not then
1935             return Base_Type (T1) = Base_Type (T)
1936               and then Valid_Boolean_Arg (Base_Type (T));
1937
1938          else
1939             return False;
1940          end if;
1941
1942       --  Binary operators
1943
1944       else
1945          T1 := Etype (First_Formal (New_S));
1946          T2 := Etype (Next_Formal (First_Formal (New_S)));
1947
1948          if Op_Name =  Name_Op_And or else Op_Name = Name_Op_Or
1949            or else Op_Name = Name_Op_Xor
1950          then
1951             return Base_Type (T1) = Base_Type (T2)
1952               and then Base_Type (T1) = Base_Type (T)
1953               and then Valid_Boolean_Arg (Base_Type (T));
1954
1955          elsif Op_Name = Name_Op_Eq or else Op_Name = Name_Op_Ne then
1956             return Base_Type (T1) = Base_Type (T2)
1957               and then not Is_Limited_Type (T1)
1958               and then Is_Boolean_Type (T);
1959
1960          elsif Op_Name = Name_Op_Lt or else Op_Name = Name_Op_Le
1961            or else Op_Name = Name_Op_Gt or else Op_Name = Name_Op_Ge
1962          then
1963             return Base_Type (T1) = Base_Type (T2)
1964               and then Valid_Comparison_Arg (T1)
1965               and then Is_Boolean_Type (T);
1966
1967          elsif Op_Name = Name_Op_Add or else Op_Name = Name_Op_Subtract then
1968             return Base_Type (T1) = Base_Type (T2)
1969               and then Base_Type (T1) = Base_Type (T)
1970               and then Is_Numeric_Type (T);
1971
1972          --  for division and multiplication, a user-defined function does
1973          --  not match the predefined universal_fixed operation, except in
1974          --  Ada83 mode.
1975
1976          elsif Op_Name = Name_Op_Divide then
1977             return (Base_Type (T1) = Base_Type (T2)
1978               and then Base_Type (T1) = Base_Type (T)
1979               and then Is_Numeric_Type (T)
1980               and then (not Is_Fixed_Point_Type (T)
1981                          or else Ada_83))
1982
1983             --  Mixed_Mode operations on fixed-point types.
1984
1985               or else (Base_Type (T1) = Base_Type (T)
1986                         and then Base_Type (T2) = Base_Type (Standard_Integer)
1987                         and then Is_Fixed_Point_Type (T))
1988
1989             --  A user defined operator can also match (and hide) a mixed
1990             --  operation on universal literals.
1991
1992               or else (Is_Integer_Type (T2)
1993                         and then Is_Floating_Point_Type (T1)
1994                         and then Base_Type (T1) = Base_Type (T));
1995
1996          elsif Op_Name = Name_Op_Multiply then
1997             return (Base_Type (T1) = Base_Type (T2)
1998               and then Base_Type (T1) = Base_Type (T)
1999               and then Is_Numeric_Type (T)
2000               and then (not Is_Fixed_Point_Type (T)
2001                          or else Ada_83))
2002
2003             --  Mixed_Mode operations on fixed-point types.
2004
2005               or else (Base_Type (T1) = Base_Type (T)
2006                         and then Base_Type (T2) = Base_Type (Standard_Integer)
2007                         and then Is_Fixed_Point_Type (T))
2008
2009               or else (Base_Type (T2) = Base_Type (T)
2010                         and then Base_Type (T1) = Base_Type (Standard_Integer)
2011                         and then Is_Fixed_Point_Type (T))
2012
2013               or else (Is_Integer_Type (T2)
2014                         and then Is_Floating_Point_Type (T1)
2015                         and then Base_Type (T1) = Base_Type (T))
2016
2017               or else (Is_Integer_Type (T1)
2018                         and then Is_Floating_Point_Type (T2)
2019                         and then Base_Type (T2) = Base_Type (T));
2020
2021          elsif Op_Name = Name_Op_Mod or else Op_Name = Name_Op_Rem then
2022             return Base_Type (T1) = Base_Type (T2)
2023               and then Base_Type (T1) = Base_Type (T)
2024               and then Is_Integer_Type (T);
2025
2026          elsif Op_Name = Name_Op_Expon then
2027             return Base_Type (T1) = Base_Type (T)
2028               and then Is_Numeric_Type (T)
2029               and then Base_Type (T2) = Base_Type (Standard_Integer);
2030
2031          elsif Op_Name = Name_Op_Concat then
2032             return Is_Array_Type (T)
2033               and then (Base_Type (T) = Base_Type (Etype (Op)))
2034               and then (Base_Type (T1) = Base_Type (T)
2035                          or else
2036                         Base_Type (T1) = Base_Type (Component_Type (T)))
2037               and then (Base_Type (T2) = Base_Type (T)
2038                          or else
2039                         Base_Type (T2) = Base_Type (Component_Type (T)));
2040
2041          else
2042             return False;
2043          end if;
2044       end if;
2045    end Operator_Matches_Spec;
2046
2047    -------------------
2048    -- Remove_Interp --
2049    -------------------
2050
2051    procedure Remove_Interp (I : in out Interp_Index) is
2052       II : Interp_Index;
2053
2054    begin
2055       --  Find end of Interp list and copy downward to erase the discarded one
2056
2057       II := I + 1;
2058
2059       while Present (All_Interp.Table (II).Typ) loop
2060          II := II + 1;
2061       end loop;
2062
2063       for J in I + 1 .. II loop
2064          All_Interp.Table (J - 1) := All_Interp.Table (J);
2065       end loop;
2066
2067       --  Back up interp. index to insure that iterator will pick up next
2068       --  available interpretation.
2069
2070       I := I - 1;
2071    end Remove_Interp;
2072
2073    ------------------
2074    -- Save_Interps --
2075    ------------------
2076
2077    procedure Save_Interps (Old_N : Node_Id; New_N : Node_Id) is
2078       Map_Ptr : Int;
2079       O_N     : Node_Id := Old_N;
2080
2081    begin
2082       if Is_Overloaded (Old_N) then
2083          if Nkind (Old_N) = N_Selected_Component
2084            and then Is_Overloaded (Selector_Name (Old_N))
2085          then
2086             O_N := Selector_Name (Old_N);
2087          end if;
2088
2089          Map_Ptr := Headers (Hash (O_N));
2090
2091          while Interp_Map.Table (Map_Ptr).Node /= O_N loop
2092             Map_Ptr := Interp_Map.Table (Map_Ptr).Next;
2093             pragma Assert (Map_Ptr /= No_Entry);
2094          end loop;
2095
2096          New_Interps (New_N);
2097          Interp_Map.Table (Interp_Map.Last).Index :=
2098            Interp_Map.Table (Map_Ptr).Index;
2099       end if;
2100    end Save_Interps;
2101
2102    -------------------
2103    -- Specific_Type --
2104    -------------------
2105
2106    function Specific_Type (T1, T2 : Entity_Id) return Entity_Id is
2107       B1 : constant Entity_Id := Base_Type (T1);
2108       B2 : constant Entity_Id := Base_Type (T2);
2109
2110       function Is_Remote_Access (T : Entity_Id) return Boolean;
2111       --  Check whether T is the equivalent type of a remote access type.
2112       --  If distribution is enabled, T is a legal context for Null.
2113
2114       ----------------------
2115       -- Is_Remote_Access --
2116       ----------------------
2117
2118       function Is_Remote_Access (T : Entity_Id) return Boolean is
2119       begin
2120          return Is_Record_Type (T)
2121            and then (Is_Remote_Call_Interface (T)
2122                       or else Is_Remote_Types (T))
2123            and then Present (Corresponding_Remote_Type (T))
2124            and then Is_Access_Type (Corresponding_Remote_Type (T));
2125       end Is_Remote_Access;
2126
2127    --  Start of processing for Specific_Type
2128
2129    begin
2130       if T1 = Any_Type or else T2 = Any_Type then
2131          return Any_Type;
2132       end if;
2133
2134       if B1 = B2 then
2135          return B1;
2136
2137       elsif False
2138         or else (T1 = Universal_Integer and then Is_Integer_Type (T2))
2139         or else (T1 = Universal_Real    and then Is_Real_Type (T2))
2140         or else (T1 = Universal_Fixed   and then Is_Fixed_Point_Type (T2))
2141         or else (T1 = Any_Fixed         and then Is_Fixed_Point_Type (T2))
2142       then
2143          return B2;
2144
2145       elsif False
2146         or else (T2 = Universal_Integer and then Is_Integer_Type (T1))
2147         or else (T2 = Universal_Real    and then Is_Real_Type (T1))
2148         or else (T2 = Universal_Fixed   and then Is_Fixed_Point_Type (T1))
2149         or else (T2 = Any_Fixed         and then Is_Fixed_Point_Type (T1))
2150       then
2151          return B1;
2152
2153       elsif T2 = Any_String and then Is_String_Type (T1) then
2154          return B1;
2155
2156       elsif T1 = Any_String and then Is_String_Type (T2) then
2157          return B2;
2158
2159       elsif T2 = Any_Character and then Is_Character_Type (T1) then
2160          return B1;
2161
2162       elsif T1 = Any_Character and then Is_Character_Type (T2) then
2163          return B2;
2164
2165       elsif T1 = Any_Access
2166         and then (Is_Access_Type (T2) or else Is_Remote_Access (T2))
2167       then
2168          return T2;
2169
2170       elsif T2 = Any_Access
2171         and then (Is_Access_Type (T1) or else Is_Remote_Access (T1))
2172       then
2173          return T1;
2174
2175       elsif T2 = Any_Composite
2176         and then Ekind (T1) in E_Array_Type .. E_Record_Subtype
2177       then
2178          return T1;
2179
2180       elsif T1 = Any_Composite
2181         and then Ekind (T2) in E_Array_Type .. E_Record_Subtype
2182       then
2183          return T2;
2184
2185       elsif T1 = Any_Modular and then Is_Modular_Integer_Type (T2) then
2186          return T2;
2187
2188       elsif T2 = Any_Modular and then Is_Modular_Integer_Type (T1) then
2189          return T1;
2190
2191       --  Special cases for equality operators (all other predefined
2192       --  operators can never apply to tagged types)
2193
2194       elsif Is_Class_Wide_Type (T1)
2195         and then Is_Ancestor (Root_Type (T1), T2)
2196       then
2197          return T1;
2198
2199       elsif Is_Class_Wide_Type (T2)
2200         and then Is_Ancestor (Root_Type (T2), T1)
2201       then
2202          return T2;
2203
2204       elsif (Ekind (B1) = E_Access_Subprogram_Type
2205                or else
2206              Ekind (B1) = E_Access_Protected_Subprogram_Type)
2207         and then Ekind (Designated_Type (B1)) /= E_Subprogram_Type
2208         and then Is_Access_Type (T2)
2209       then
2210          return T2;
2211
2212       elsif (Ekind (B2) = E_Access_Subprogram_Type
2213                or else
2214              Ekind (B2) = E_Access_Protected_Subprogram_Type)
2215         and then Ekind (Designated_Type (B2)) /= E_Subprogram_Type
2216         and then Is_Access_Type (T1)
2217       then
2218          return T1;
2219
2220       elsif (Ekind (T1) = E_Allocator_Type
2221               or else Ekind (T1) = E_Access_Attribute_Type
2222               or else Ekind (T1) = E_Anonymous_Access_Type)
2223         and then Is_Access_Type (T2)
2224       then
2225          return T2;
2226
2227       elsif (Ekind (T2) = E_Allocator_Type
2228               or else Ekind (T2) = E_Access_Attribute_Type
2229               or else Ekind (T2) = E_Anonymous_Access_Type)
2230         and then Is_Access_Type (T1)
2231       then
2232          return T1;
2233
2234       --  If none of the above cases applies, types are not compatible.
2235
2236       else
2237          return Any_Type;
2238       end if;
2239    end Specific_Type;
2240
2241    -----------------------
2242    -- Valid_Boolean_Arg --
2243    -----------------------
2244
2245    --  In addition to booleans and arrays of booleans, we must include
2246    --  aggregates as valid boolean arguments, because in the first pass
2247    --  of resolution their components are not examined. If it turns out not
2248    --  to be an aggregate of booleans, this will be diagnosed in Resolve.
2249    --  Any_Composite must be checked for prior to the array type checks
2250    --  because Any_Composite does not have any associated indexes.
2251
2252    function Valid_Boolean_Arg (T : Entity_Id) return Boolean is
2253    begin
2254       return Is_Boolean_Type (T)
2255         or else T = Any_Composite
2256         or else (Is_Array_Type (T)
2257                   and then T /= Any_String
2258                   and then Number_Dimensions (T) = 1
2259                   and then Is_Boolean_Type (Component_Type (T))
2260                   and then (not Is_Private_Composite (T)
2261                              or else In_Instance)
2262                   and then (not Is_Limited_Composite (T)
2263                              or else In_Instance))
2264         or else Is_Modular_Integer_Type (T)
2265         or else T = Universal_Integer;
2266    end Valid_Boolean_Arg;
2267
2268    --------------------------
2269    -- Valid_Comparison_Arg --
2270    --------------------------
2271
2272    function Valid_Comparison_Arg (T : Entity_Id) return Boolean is
2273    begin
2274
2275       if T = Any_Composite then
2276          return False;
2277       elsif Is_Discrete_Type (T)
2278         or else Is_Real_Type (T)
2279       then
2280          return True;
2281       elsif Is_Array_Type (T)
2282           and then Number_Dimensions (T) = 1
2283           and then Is_Discrete_Type (Component_Type (T))
2284           and then (not Is_Private_Composite (T)
2285                      or else In_Instance)
2286           and then (not Is_Limited_Composite (T)
2287                      or else In_Instance)
2288       then
2289          return True;
2290       elsif Is_String_Type (T) then
2291          return True;
2292       else
2293          return False;
2294       end if;
2295    end Valid_Comparison_Arg;
2296
2297    ---------------------
2298    -- Write_Overloads --
2299    ---------------------
2300
2301    procedure Write_Overloads (N : Node_Id) is
2302       I   : Interp_Index;
2303       It  : Interp;
2304       Nam : Entity_Id;
2305
2306    begin
2307       if not Is_Overloaded (N) then
2308          Write_Str ("Non-overloaded entity ");
2309          Write_Eol;
2310          Write_Entity_Info (Entity (N), " ");
2311
2312       else
2313          Get_First_Interp (N, I, It);
2314          Write_Str ("Overloaded entity ");
2315          Write_Eol;
2316          Nam := It.Nam;
2317
2318          while Present (Nam) loop
2319             Write_Entity_Info (Nam,  "      ");
2320             Write_Str ("=================");
2321             Write_Eol;
2322             Get_Next_Interp (I, It);
2323             Nam := It.Nam;
2324          end loop;
2325       end if;
2326    end Write_Overloads;
2327
2328    -----------------------
2329    --  Write_Interp_Ref --
2330    -----------------------
2331
2332    procedure Write_Interp_Ref (Map_Ptr : Int) is
2333    begin
2334       Write_Str (" Node:  ");
2335       Write_Int (Int (Interp_Map.Table (Map_Ptr).Node));
2336       Write_Str (" Index: ");
2337       Write_Int (Int (Interp_Map.Table (Map_Ptr).Index));
2338       Write_Str (" Next:  ");
2339       Write_Int (Int (Interp_Map.Table (Map_Ptr).Next));
2340       Write_Eol;
2341    end Write_Interp_Ref;
2342
2343 end Sem_Type;