1------------------------------------------------------------------------------
2--                                                                          --
3--                         GNAT COMPILER COMPONENTS                         --
4--                                                                          --
5--                             S E M _ T Y P E                              --
6--                                                                          --
7--                                 S p e c                                  --
8--                                                                          --
9--          Copyright (C) 1992-2013, 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 3,  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 COPYING3.  If not, go to --
19-- http://www.gnu.org/licenses for a complete copy of the license.          --
20--                                                                          --
21-- GNAT was originally developed  by the GNAT team at  New York University. --
22-- Extensive contributions were provided by Ada Core Technologies Inc.      --
23--                                                                          --
24------------------------------------------------------------------------------
25
26--  This unit contains the routines used to handle type determination,
27--  including the routine used to support overload resolution.
28
29with Types; use Types;
30
31package Sem_Type is
32
33   ---------------------------------------------
34   -- Data Structures for Overload Resolution --
35   ---------------------------------------------
36
37   --  To determine the unique meaning of an identifier, overload resolution
38   --  may have to be performed if the visibility rules alone identify more
39   --  than one possible entity as the denotation of a given identifier. When
40   --  the visibility rules find such a potential ambiguity, the set of
41   --  possible interpretations must be attached to the identifier, and
42   --  overload resolution must be performed over the innermost enclosing
43   --  complete context. At the end of the resolution, either a single
44   --  interpretation is found for all identifiers in the context, or else a
45   --  type error (invalid type or ambiguous reference) must be signalled.
46
47   --  The set of interpretations of a given name is stored in a data structure
48   --  that is separate from the syntax tree, because it corresponds to
49   --  transient information. The interpretations themselves are stored in
50   --  table All_Interp. A mapping from tree nodes to sets of interpretations
51   --  called Interp_Map, is maintained by the overload resolution routines.
52   --  Both these structures are initialized at the beginning of every complete
53   --  context.
54
55   --  Corresponding to the set of interpretations for a given overloadable
56   --  identifier, there is a set of possible types corresponding to the types
57   --  that the overloaded call may return. We keep a 1-to-1 correspondence
58   --  between interpretations and types: for user-defined subprograms the type
59   --  is the declared return type. For operators, the type is determined by
60   --  the type of the arguments. If the arguments themselves are overloaded,
61   --  we enter the operator name in the names table for each possible result
62   --  type. In most cases, arguments are not overloaded and only one
63   --  interpretation is present anyway.
64
65   type Interp is record
66      Nam         : Entity_Id;
67      Typ         : Entity_Id;
68      Abstract_Op : Entity_Id := Empty;
69   end record;
70
71   --  Entity Abstract_Op is set to the abstract operation which potentially
72   --  disables the interpretation in Ada 2005 mode.
73
74   No_Interp : constant Interp := (Empty, Empty, Empty);
75
76   type Interp_Index is new Int;
77
78   ---------------------
79   -- Error Reporting --
80   ---------------------
81
82   --  A common error is the use of an operator in infix notation on arguments
83   --  of a type that is not directly visible. Rather than diagnosing a type
84   --  mismatch, it is better to indicate that the type can be made use-visible
85   --  with the appropriate use clause. The global variable Candidate_Type is
86   --  set in Add_One_Interp whenever an interpretation might be legal for an
87   --  operator if the type were directly visible. This variable is used in
88   --  sem_ch4 when no legal interpretation is found.
89
90   Candidate_Type : Entity_Id;
91
92   -----------------
93   -- Subprograms --
94   -----------------
95
96   procedure Init_Interp_Tables;
97   --  Invoked by gnatf when processing multiple files
98
99   procedure Collect_Interps (N : Node_Id);
100   --  Invoked when the name N has more than one visible interpretation. This
101   --  is the high level routine which accumulates the possible interpretations
102   --  of the node. The first meaning and type of N have already been stored
103   --  in N. If the name is an expanded name, the homonyms are only those that
104   --  belong to the same scope.
105
106   function Is_Invisible_Operator (N : Node_Id; T : Entity_Id) return Boolean;
107   --  Check whether a predefined operation with universal operands appears in
108   --  a context in which the operators of the expected type are not visible.
109
110   procedure List_Interps (Nam : Node_Id; Err : Node_Id);
111   --  List candidate interpretations of an overloaded name. Used for various
112   --  error reports.
113
114   procedure Add_One_Interp
115     (N         : Node_Id;
116      E         : Entity_Id;
117      T         : Entity_Id;
118      Opnd_Type : Entity_Id := Empty);
119   --  Add (E, T) to the list of interpretations of the node being resolved.
120   --  For calls and operators, i.e. for nodes that have a name field, E is an
121   --  overloadable entity, and T is its type. For constructs such as indexed
122   --  expressions, the caller sets E equal to T, because the overloading comes
123   --  from other fields, and the node itself has no name to resolve. Hidden
124   --  denotes whether an interpretation has been disabled by an abstract
125   --  operator. Add_One_Interp includes semantic processing to deal with
126   --  adding entries that hide one another etc.
127   --
128   --  For operators, the legality of the operation depends on the visibility
129   --  of T and its scope. If the operator is an equality or comparison, T is
130   --  always Boolean, and we use Opnd_Type, which is a candidate type for one
131   --  of the operands of N, to check visibility.
132
133   procedure End_Interp_List;
134   --  End the list of interpretations of current node
135
136   procedure Get_First_Interp
137     (N  : Node_Id;
138      I  : out Interp_Index;
139      It : out Interp);
140   --  Initialize iteration over set of interpretations for Node N. The first
141   --  interpretation is placed in It, and I is initialized for subsequent
142   --  calls to Get_Next_Interp.
143
144   procedure Get_Next_Interp (I : in out Interp_Index; It : out Interp);
145   --  Iteration step over set of interpretations. Using the value in I, which
146   --  was set by a previous call to Get_First_Interp or Get_Next_Interp, the
147   --  next interpretation is placed in It, and I is updated for the next call.
148   --  The end of the list of interpretations is signalled by It.Nam = Empty.
149
150   procedure Remove_Interp (I : in out Interp_Index);
151   --  Remove an interpretation that is hidden by another, or that does not
152   --  match the context. The value of I on input was set by a call to either
153   --  Get_First_Interp or Get_Next_Interp and references the interpretation
154   --  to be removed. The only allowed use of the exit value of I is as input
155   --  to a subsequent call to Get_Next_Interp, which yields the interpretation
156   --  following the removed one.
157
158   procedure Save_Interps (Old_N : Node_Id; New_N : Node_Id);
159   --  If an overloaded node is rewritten during semantic analysis, its
160   --  possible interpretations must be linked to the copy. This procedure
161   --  transfers the overload information (Is_Overloaded flag, and list of
162   --  interpretations) from Old_N, the old node, to New_N, its new copy.
163   --  It has no effect in the non-overloaded case.
164
165   function Covers (T1, T2 : Entity_Id) return Boolean;
166   --  This is the basic type compatibility routine. T1 is the expected type,
167   --  imposed by context, and T2 is the actual type. The processing reflects
168   --  both the definition of type coverage and the rules for operand matching;
169   --  that is, this does not exactly match the RM definition of "covers".
170
171   function Disambiguate
172     (N      : Node_Id;
173      I1, I2 : Interp_Index;
174      Typ    : Entity_Id) return Interp;
175   --  If more than one interpretation of a name in a call is legal, apply
176   --  preference rules (universal types first) and operator visibility in
177   --  order to remove ambiguity. I1 and I2 are the first two interpretations
178   --  that are compatible with the context, but there may be others.
179
180   function Entity_Matches_Spec (Old_S,  New_S : Entity_Id) return Boolean;
181   --  To resolve subprogram renaming and default formal subprograms in generic
182   --  definitions. Old_S is a possible interpretation of the entity being
183   --  renamed, New_S has an explicit signature. If Old_S is a subprogram, as
184   --  opposed to an operator, type and mode conformance are required.
185
186   function Find_Unique_Type (L : Node_Id; R : Node_Id) return Entity_Id;
187   --  Used in second pass of resolution, for equality and comparison nodes. L
188   --  is the left operand, whose type is known to be correct, and R is the
189   --  right operand, which has one interpretation compatible with that of L.
190   --  Return the type intersection of the two.
191
192   function Has_Compatible_Type (N : Node_Id; Typ : Entity_Id) return Boolean;
193   --  Verify that some interpretation of the node N has a type compatible with
194   --  Typ. If N is not overloaded, then its unique type must be compatible
195   --  with Typ. Otherwise iterate through the interpretations of N looking for
196   --  a compatible one.
197
198   function Hides_Op (F : Entity_Id; Op : Entity_Id) return Boolean;
199   --  A user-defined function hides a predefined operator if it is matches the
200   --  signature of the operator, and is declared in an open scope, or in the
201   --  scope of the result type.
202
203   function Interface_Present_In_Ancestor
204     (Typ   : Entity_Id;
205      Iface : Entity_Id) return Boolean;
206   --  Ada 2005 (AI-251): Typ must be a tagged record type/subtype and Iface
207   --  must be an abstract interface type (or a class-wide abstract interface).
208   --  This function is used to check if Typ or some ancestor of Typ implements
209   --  Iface (returning True only if so).
210
211   function Intersect_Types (L, R : Node_Id) return Entity_Id;
212   --  Find the common interpretation to two analyzed nodes. If one of the
213   --  interpretations is universal, choose the non-universal one. If either
214   --  node is overloaded, find single common interpretation.
215
216   function In_Generic_Actual (Exp : Node_Id) return Boolean;
217   --  Determine whether the expression is part of a generic actual. At the
218   --  time the actual is resolved the scope is already that of the instance,
219   --  but conceptually the resolution of the actual takes place in the
220   --  enclosing context and no special disambiguation rules should be applied.
221
222   function Is_Ancestor
223     (T1            : Entity_Id;
224      T2            : Entity_Id;
225      Use_Full_View : Boolean := False) return Boolean;
226   --  T1 is a tagged type (not class-wide). Verify that it is one of the
227   --  ancestors of type T2 (which may or not be class-wide). If Use_Full_View
228   --  is True then the full-view of private parents is used when climbing
229   --  through the parents of T2.
230   --
231   --  Note: For analysis purposes the flag Use_Full_View must be set to False
232   --  (otherwise we break the privacy contract since this routine returns true
233   --  for hidden ancestors of private types). For expansion purposes this flag
234   --  is generally set to True since the expander must know with precision the
235   --  ancestors of a tagged type. For example, if a private type derives from
236   --  an interface type then the interface may not be an ancestor of its full
237   --  view since the full-view is only required to cover the interface (RM 7.3
238   --  (7.3/2))) and this knowledge affects construction of dispatch tables.
239
240   function Is_Progenitor
241     (Iface : Entity_Id;
242      Typ   : Entity_Id) return Boolean;
243   --  Determine whether the interface Iface is implemented by Typ. It requires
244   --  traversing the list of abstract interfaces of the type, as well as that
245   --  of the ancestor types. The predicate is used to determine when a formal
246   --  in the signature of an inherited operation must carry the derived type.
247
248   function Is_Subtype_Of (T1 : Entity_Id; T2 : Entity_Id) return Boolean;
249   --  Checks whether T1 is any subtype of T2 directly or indirectly. Applies
250   --  only to scalar subtypes???
251
252   function Operator_Matches_Spec (Op, New_S : Entity_Id) return Boolean;
253   --  Used to resolve subprograms renaming operators, and calls to user
254   --  defined operators. Determines whether a given operator Op, matches
255   --  a specification, New_S.
256
257   procedure Set_Abstract_Op (I : Interp_Index; V : Entity_Id);
258   --  Set the abstract operation field of an interpretation
259
260   function Valid_Comparison_Arg (T : Entity_Id) return Boolean;
261   --  A valid argument to an ordering operator must be a discrete type, a
262   --  real type, or a one dimensional array with a discrete component type.
263
264   function Valid_Boolean_Arg (T : Entity_Id) return Boolean;
265   --  A valid argument of a boolean operator is either some boolean type, or a
266   --  one-dimensional array of boolean type.
267
268   procedure Write_Interp (It : Interp);
269   --  Debugging procedure to display an Interp
270
271   procedure Write_Interp_Ref (Map_Ptr : Int);
272   --  Debugging procedure to display entry in Interp_Map. Would not be needed
273   --  if it were possible to debug instantiations of Table.
274
275   procedure Write_Overloads (N : Node_Id);
276   --  Debugging procedure to output info on possibly overloaded entities for
277   --  specified node.
278
279end Sem_Type;
280