Introduce Terr in place of Tany for type errors
[hiphop-php.git] / hphp / hack / src / typing / typing_defs.ml
blobb5b1c1a26d36df2b2444027c0f0ba63229f8b051
1 (**
2 * Copyright (c) 2015, Facebook, Inc.
3 * All rights reserved.
5 * This source code is licensed under the BSD-style license found in the
6 * LICENSE file in the "hack" directory of this source tree. An additional grant
7 * of patent rights can be found in the PATENTS file in the same directory.
9 *)
11 open Core
13 module Reason = Typing_reason
14 module SN = Naming_special_names
16 type visibility =
17 | Vpublic
18 | Vprivate of string
19 | Vprotected of string
21 (* All the possible types, reason is a trace of why a type
22 was inferred in a certain way.
24 Types exists in two phases. Phase one is 'decl', meaning it is a type that
25 was declared in user code. Phase two is 'locl', meaning it is a type that is
26 inferred via local inference.
28 (* create private types to represent the different type phases *)
29 type decl = private DeclPhase
30 type locl = private LoclPhase
32 type 'phase ty = Reason.t * 'phase ty_
33 and _ ty_ =
34 (*========== Following Types Exist Only in the Declared Phase ==========*)
35 (* The late static bound type of a class *)
36 | Tthis : decl ty_
38 (* Either an object type or a type alias, ty list are the arguments *)
39 | Tapply : Nast.sid * decl ty list -> decl ty_
41 (* The type of a generic parameter. The constraints on a generic parameter
42 * are accessed through the lenv.tpenv component of the environment, which
43 * is set up when checking the body of a function or method. See uses of
44 * Typing_phase.localize_generic_parameters_with_bounds.
46 | Tgeneric : string -> decl ty_
48 (* Name of class, name of type const, remaining names of type consts *)
49 | Taccess : taccess_type -> decl ty_
51 (* The type of the various forms of "array":
52 * Tarray (None, None) => "array"
53 * Tarray (Some ty, None) => "array<ty>"
54 * Tarray (Some ty1, Some ty2) => "array<ty1, ty2>"
55 * Tarray (None, Some ty) => [invalid]
57 | Tarray : decl ty option * decl ty option -> decl ty_
59 (*========== Following Types Exist in Both Phases ==========*)
60 (* "Any" is the type of a variable with a missing annotation, and "mixed" is
61 * the type of a variable annotated as "mixed". THESE TWO ARE VERY DIFFERENT!
62 * Any unifies with anything, i.e., it is both a supertype and subtype of any
63 * other type. You can do literally anything to it; it's the "trust me" type.
64 * Mixed, on the other hand, is only a supertype of everything. You need to do
65 * a case analysis to figure out what it is (i.e., its elimination form).
67 * Here's an example to demonstrate:
69 * function f($x): int {
70 * return $x + 1;
71 * }
73 * In that example, $x has type Tany. This unifies with anything, so adding
74 * one to it is allowed, and returning that as int is allowed.
76 * In contrast, if $x were annotated as mixed, adding one to that would be
77 * a type error -- mixed is not a subtype of int, and you must be a subtype
78 * of int to take part in addition. (The converse is true though -- int is a
79 * subtype of mixed.) A case analysis would need to be done on $x, via
80 * is_int or similar.
82 | Tany
83 | Tmixed
85 | Terr
87 (* Nullable, called "option" in the ML parlance. *)
88 | Toption : 'phase ty -> 'phase ty_
90 (* All the primitive types: int, string, void, etc. *)
91 | Tprim : Nast.tprim -> 'phase ty_
93 (* A wrapper around fun_type, which contains the full type information for a
94 * function, method, lambda, etc. Note that lambdas have an additional layer
95 * of indirection before you get to Tfun -- see Tanon below. *)
96 | Tfun : 'phase fun_type -> 'phase ty_
99 (* Tuple, with ordered list of the types of the elements of the tuple. *)
100 | Ttuple : 'phase ty list -> 'phase ty_
102 (* Whether all fields of this shape are known, types of each of the
103 * known arms.
105 | Tshape : shape_fields_known * ('phase ty Nast.ShapeMap.t) -> 'phase ty_
107 (*========== Below Are Types That Cannot Be Declared In User Code ==========*)
109 (* A type variable (not to be confused with a type parameter). This is the
110 * core of how type inference works. If you aren't familiar with it, a
111 * suitable explanation couldn't possibly fit here; terms to google for
112 * include "Hindley-Milner type inference", "unification", and "algorithm W".
114 | Tvar : Ident.t -> locl ty_
116 (* The type of an opaque type (e.g. a "newtype" outside of the file where it
117 * was defined). They are "opaque", which means that they only unify with
118 * themselves. However, it is possible to have a constraint that allows us to
119 * relax this. For example:
121 * newtype my_type as int = ...
123 * Outside of the file where the type was defined, this translates to:
125 * Tabstract (AKnewtype (pos, "my_type", []), Some (Tprim Tint))
127 * Which means that my_type is abstract, but is subtype of int as well.
129 * We also create abstract types for generic parameters of a function, i.e.
131 * function foo<T>(T $x): void {
132 * // Body
135 * The type 'T' will be represented as an abstract type when type checking
136 * the body of 'foo'.
138 * Finally abstract types are also derived from the 'this' type and
139 * accessing type constants on it, resulting in a dependent type.
141 | Tabstract : abstract_kind * locl ty option -> locl ty_
143 (* An anonymous function, including the fun arity, and the identifier to
144 * type the body of the function. (The actual closure is stored in
145 * Typing_env.env.genv.anons) *)
146 | Tanon : locl fun_arity * Ident.t -> locl ty_
148 (* This is a kinda-union-type we use in order to defer picking which common
149 * ancestor for a type we should use until we hit a type annotation.
150 * For example:
152 * interface I {}
153 * class C implements I {}
154 * class D extends C {}
155 * function f(): I {
156 * if (...) {
157 * $x = new C();
158 * } else {
159 * $x = new D();
161 * return $x;
164 * What is the type of $x? We need to pick some common ancestor, but which
165 * one? Both C and I would be acceptable, which do we mean? This is where
166 * Tunresolved comes in -- after the if/else, the type of $x is
167 * Unresolved[C, D] -- it could be *either one*, and we defer the check until
168 * we hit an annotation. In particular, when we hit the "return", we make sure
169 * that it is compatible with both C and D, and then we know we've found the
170 * right supertype. Since we don't do global inference, we'll always either
171 * hit an annotation to check, or hit a place an annotation is missing in
172 * which case we can just throw away the type.
174 * Note that this is *not* really a union type -- most notably, it's allowed
175 * to grow as inference goes on, which union types don't. For example:
177 * function f(): Vector<num> {
178 * $v = Vector {};
179 * $v[] = 1;
180 * $v[] = 3.14;
181 * return $v;
184 * (Eliding some Tvar for clarity) On the first line, $v is
185 * Vector<Unresolved[]>. On the second, Vector<Unresolved[int]>. On the third,
186 * Vector<Unresolved[int,float]> -- it grows! Then when we finally return $v,
187 * we see that int and float are both compatible with num, and we have found
188 * our suitable supertype.
190 * One final implication of this growing is that if an unresolved is used in
191 * a contravariant position, we must collapse it down to whatever is annotated
192 * right then, in order to be sound.
194 | Tunresolved : locl ty list -> locl ty_
196 (* Tobject is an object type compatible with all objects. This type is also
197 * compatible with some string operations (since a class might implement
198 * __toString), but not with string type hints. In a similar way, Tobject
199 * is compatible with some array operations (since a class might implement
200 * ArrayAccess), but not with array type hints.
202 * Tobject is currently used to type code like:
203 * ../test/typecheck/return_unknown_class.php
205 | Tobject : locl ty_
207 (* An instance of a class or interface, ty list are the arguments *)
208 | Tclass : Nast.sid * locl ty list -> locl ty_
210 (* Localized version of Tarray *)
211 | Tarraykind : array_kind -> locl ty_
213 and array_kind =
214 (* Those three types directly correspond to their decl level counterparts:
215 * array, array<_> and array<_, _> *)
216 | AKany
217 | AKvec of locl ty
218 | AKmap of locl ty * locl ty
219 (* This is a type created when we see array() literal *)
220 | AKempty
221 (* Array "used like a shape" - initialized and indexed with keys that are
222 * only string/class constants *)
223 | AKshape of (locl ty * locl ty) Nast.ShapeMap.t
224 (* Array "used like a tuple" - initialized without keys and indexed with
225 * integers that are within initialized range *)
226 | AKtuple of (locl ty) IMap.t
228 (* An abstract type derived from either a newtype, a type parameter, or some
229 * dependent type
231 and abstract_kind =
232 (* newtype foo<T1, T2> ... *)
233 | AKnewtype of string * locl ty list
234 (* enum foo ... *)
235 | AKenum of string
236 (* <T super C> ; None if 'as' constrained *)
237 | AKgeneric of string
238 (* see dependent_type *)
239 | AKdependent of dependent_type
241 (* A dependent type consists of a base kind which indicates what the type is
242 * dependent on. It is either dependent on:
243 * - The type 'this'
244 * - The class context (what 'static' is resolved to in a class)
245 * - A class
246 * - An expression
248 * Dependent types also have a path component (derived from accessing a type
249 * constant). Thus the dependent type (`expr 0, ['A', 'B', 'C']) roughly means
250 * "The type resulting from accessing the type constant A then the type constant
251 * B and then the type constant C on the expression reference by 0"
253 and dependent_type =
254 (* Type that is the subtype of the late bound type within a class. *)
255 [ `this
256 (* The late bound type within a class. It is the type of 'new static()' and
257 * '$this'. This is different from the 'this' type. The 'this' type isn't
258 * quite strong enough in some cases. It means you are a subtype of the late
259 * bound class, but there are instances where you need the exact type.
260 * We may not need both since the only way to make something of type 'this'
261 * that is not 'static' is with 'instanceof static'.
263 | `static
264 (* A class name, new type, or generic, i.e.
266 * abstract class C { abstract const type T }
268 * The type C::T is (`cls '\C', ['T'])
270 | `cls of string
271 (* A reference to some expression. For example:
273 * $x->foo()
275 * The expression $x would have a reference Ident.t
276 * The expression $x->foo() would have a different one
278 | `expr of Ident.t
279 ] * string list
281 and taccess_type = decl ty * Nast.sid list
283 (* Local shape constructed using "shape" keyword has all the fields
284 * known:
286 * $s = shape('x' => 4, 'y' => 4);
288 * It has fields 'x' and 'y' and definitely no other fields. On the other
289 * hand, shape types that come from typehints may (due to structural
290 * subtyping of shapes) have some other, unlisted fields:
292 * type s = shape('x' => int);
294 * function f(s $s) {
297 * f(shape('x' => 4, 'y' => 5));
299 * The call to f is valid because of structural subtyping - shapes are
300 * permitted to "forget" fields. But the 'y' field still exists at runtime,
301 * and we cannot say inside the body of $f that we know that 'x' is the only
302 * field. This is relevant when deciding if it's safe to omit optional fields
303 * - if shape fields are not fully known, even optional fields have to be
304 * explicitly set/unset.
306 * We also track in additional map of FieldsPartiallyKnown names of fields
307 * that are known to not exist (because they were explicitly unset).
309 and shape_fields_known =
310 | FieldsFullyKnown
311 | FieldsPartiallyKnown of Pos.t Nast.ShapeMap.t
313 (* The type of a function AND a method.
314 * A function has a min and max arity because of optional arguments *)
315 and 'phase fun_type = {
316 ft_pos : Pos.t ;
317 ft_deprecated : string option ;
318 ft_abstract : bool ;
319 ft_arity : 'phase fun_arity ;
320 ft_tparams : 'phase tparam list ;
321 ft_where_constraints : 'phase where_constraint list ;
322 ft_params : 'phase fun_params ;
323 ft_ret : 'phase ty ;
326 (* Arity information for a fun_type; indicating the minimum number of
327 * args expected by the function and the maximum number of args for
328 * standard, non-variadic functions or the type of variadic argument taken *)
329 and 'phase fun_arity =
330 | Fstandard of int * int (* min ; max *)
331 (* PHP5.6-style ...$args finishes the func declaration *)
332 | Fvariadic of int * 'phase fun_param (* min ; variadic param type *)
333 (* HH-style ... anonymous variadic arg; body presumably uses func_get_args *)
334 | Fellipsis of int (* min *)
337 and 'phase fun_param = (string option * 'phase ty)
339 and 'phase fun_params = 'phase fun_param list
341 and class_elt = {
342 ce_final : bool;
343 ce_is_xhp_attr : bool;
344 ce_override : bool;
345 (* true if this elt arose from require-extends or other mechanisms
346 of hack "synthesizing" methods that were not written by the
347 programmer. The eventual purpose of this is to make sure that
348 elts that *are* written by the programmer take precedence over
349 synthesized elts. *)
350 ce_synthesized : bool;
351 ce_visibility : visibility;
352 ce_type : decl ty Lazy.t;
353 (* identifies the class from which this elt originates *)
354 ce_origin : string;
357 and class_const = {
358 cc_synthesized : bool;
359 cc_abstract : bool;
360 cc_pos : Pos.t;
361 cc_type : decl ty;
362 cc_expr : Nast.expr option;
363 (* identifies the class from which this const originates *)
364 cc_origin : string;
367 (* The position is that of the hint in the `use` / `implements` AST node
368 * that causes a class to have this requirement applied to it. E.g.
370 * class Foo {}
372 * interface Bar {
373 * require extends Foo; <- position of the decl ty
376 * class Baz extends Foo implements Bar { <- position of the `implements`
379 and requirement = Pos.t * decl ty
381 and class_type = {
382 tc_need_init : bool;
383 (* Whether the typechecker knows of all (non-interface) ancestors
384 * and thus known all accessible members of this class *)
385 tc_members_fully_known : bool;
386 tc_abstract : bool;
387 tc_final : bool;
388 (* When a class is abstract (or in a trait) the initialization of
389 * a protected member can be delayed *)
390 tc_deferred_init_members : SSet.t;
391 tc_kind : Ast.class_kind;
392 tc_name : string ;
393 tc_pos : Pos.t ;
394 tc_tparams : decl tparam list ;
395 tc_consts : class_const SMap.t;
396 tc_typeconsts : typeconst_type SMap.t;
397 tc_props : class_elt SMap.t;
398 tc_sprops : class_elt SMap.t;
399 tc_methods : class_elt SMap.t;
400 tc_smethods : class_elt SMap.t;
401 tc_construct : class_elt option * bool;
402 (* This includes all the classes, interfaces and traits this class is
403 * using. *)
404 tc_ancestors : decl ty SMap.t ;
405 tc_req_ancestors : requirement list;
406 tc_req_ancestors_extends : SSet.t; (* the extends of req_ancestors *)
407 tc_extends : SSet.t;
408 tc_enum_type : enum_type option;
411 and typeconst_type = {
412 ttc_name : Nast.sid;
413 ttc_constraint : decl ty option;
414 ttc_type : decl ty option;
415 ttc_origin : string;
418 and enum_type = {
419 te_base : decl ty;
420 te_constraint : decl ty option;
423 and typedef_type = {
424 td_pos: Pos.t;
425 td_vis: Nast.typedef_visibility;
426 td_tparams: decl tparam list;
427 td_constraint: decl ty option;
428 td_type: decl ty;
431 and 'phase tparam =
432 Ast.variance * Ast.id * (Ast.constraint_kind * 'phase ty) list
434 and 'phase where_constraint =
435 'phase ty * Ast.constraint_kind * 'phase ty
437 type phase_ty =
438 | DeclTy of decl ty
439 | LoclTy of locl ty
441 (* Tracks information about how a type was expanded *)
442 type expand_env = {
443 (* A list of the type defs and type access we have expanded thus far. Used
444 * to prevent entering into a cycle when expanding these types
446 type_expansions : (Pos.t * string) list;
447 substs : locl ty SMap.t;
448 this_ty : locl ty;
449 (* The class that the type is extracted from. Used for creating expression
450 * dependent types for type constants.
452 from_class : Nast.class_id option;
455 type ety = expand_env * locl ty
457 let has_expanded {type_expansions; _} x =
458 List.exists type_expansions begin function
459 | (_, x') when x = x' -> true
460 | _ -> false
463 (* The identifier for this *)
464 let this = Local_id.make "$this"
466 let arity_min ft_arity : int = match ft_arity with
467 | Fstandard (min, _) | Fvariadic (min, _) | Fellipsis min -> min
469 module AbstractKind = struct
470 let to_string = function
471 | AKnewtype (name, _) -> name
472 | AKgeneric name -> name
473 | AKenum name -> "enum "^(Utils.strip_ns name)
474 | AKdependent (dt, ids) ->
475 let dt =
476 match dt with
477 | `this -> SN.Typehints.this
478 | `static -> "<"^SN.Classes.cStatic^">"
479 | `cls c -> c
480 | `expr i ->
481 let display_id = Reason.get_expr_display_id i in
482 "<expr#"^string_of_int display_id^">" in
483 String.concat "::" (dt::ids)
486 (*****************************************************************************)
487 (* Suggest mode *)
488 (*****************************************************************************)
490 (* Set to true when we are trying to infer the missing type hints. *)
491 let is_suggest_mode = ref false