Refactor env_with_self
[hiphop-php.git] / hphp / hack / src / typing / tast_env.ml
blob90ee4a92e8c955380535e190540ee01c6344b554
1 (*
2 * Copyright (c) 2018, Facebook, Inc.
3 * All rights reserved.
5 * This source code is licensed under the MIT license found in the
6 * LICENSE file in the "hack" directory of this source tree.
8 *)
10 open Hh_prelude
11 open Aast
13 type class_or_typedef_result =
14 | ClassResult of Decl_provider.class_decl
15 | TypedefResult of Typing_defs.typedef_type
17 (** {!Tast_env.env} is just an alias to {!Typing_env.env}, and the functions we
18 provide for it are largely just aliases to functions that take a
19 {!Typing_env.env}.
21 If you find that you need to add a new alias here, please take care to
22 ensure that it always works with the information available in the {!env}
23 constructed by {!Tast_visitor} classes. Only a subset of the information
24 available in the inference phase ({!module:Typing}) will be persisted in a
25 {!Tast.program} (and thus available to {!Tast_visitor}). Most of the
26 persisted information comes from {!Typing_env.save}. *)
28 let show_env _ = "<env>"
30 let pp_env _ _ = Printf.printf "%s\n" "<env>"
32 type env = Typing_env_types.env
34 type t = env [@@deriving show]
36 exception Not_in_class
38 let print_ty = Typing_print.full_strip_ns
40 let print_decl_ty = Typing_print.full_strip_ns_decl
42 let print_error_ty = Typing_print.error
44 let print_ty_with_identity env phase_ty sym_occurrence sym_definition =
45 match phase_ty with
46 | Typing_defs.DeclTy ty ->
47 let (env, ty) =
48 Typing_phase.localize_with_self env ~ignore_errors:true ty
50 Typing_print.full_with_identity env ty sym_occurrence sym_definition
51 | Typing_defs.LoclTy ty ->
52 Typing_print.full_with_identity env ty sym_occurrence sym_definition
54 let ty_to_json = Typing_print.to_json
56 let json_to_locl_ty = Typing_print.json_to_locl_ty
58 let get_self_id = Typing_env.get_self_id
60 let get_self_ty = Typing_env.get_self_ty
62 let get_parent_id = Typing_env.get_parent_id
64 let get_self_ty_exn env =
65 match get_self_ty env with
66 | Some self_ty -> self_ty
67 | None -> raise Not_in_class
69 let get_class = Typing_env.get_class
71 let get_class_or_typedef env x =
72 match Typing_env.get_class_or_typedef env x with
73 | Some (Typing_env.ClassResult cd) -> Some (ClassResult cd)
74 | Some (Typing_env.TypedefResult td) -> Some (TypedefResult td)
75 | None -> None
77 let is_static = Typing_env.is_static
79 let is_strict = Typing_env.is_strict
81 let get_mode = Typing_env.get_mode
83 let get_tcopt = Typing_env.get_tcopt
85 let get_ctx = Typing_env.get_ctx
87 let expand_type = Typing_env.expand_type
89 let set_static = Typing_env.set_static
91 let set_val_kind = Typing_env.set_val_kind
93 let set_inside_constructor env =
94 { env with Typing_env_types.inside_constructor = true }
96 let get_inside_constructor env = env.Typing_env_types.inside_constructor
98 let get_decl_env env = env.Typing_env_types.decl_env
100 let get_val_kind = Typing_env.get_val_kind
102 let get_file = Typing_env.get_file
104 let get_deps_mode = Typing_env.get_deps_mode
106 let fully_expand = Typing_expand.fully_expand
108 (*****************************************************************************)
109 (* Given some class type or unresolved union of class types, return the
110 * identifiers of all classes the type may represent.
112 * Intended for uses like constructing call graphs and finding references, where
113 * we have the statically known class type of some runtime value or class ID and
114 * we would like the name of that class. *)
115 (*****************************************************************************)
116 let get_class_ids env ty =
117 let open Typing_defs in
118 let rec aux seen acc ty =
119 match get_node ty with
120 | Tclass ((_, cid), _, _) -> cid :: acc
121 | Toption ty
122 | Tdependent (_, ty)
123 | Tnewtype (_, _, ty) ->
124 aux seen acc ty
125 | Tunion tys
126 | Tintersection tys ->
127 List.fold tys ~init:acc ~f:(aux seen)
128 | Tgeneric (name, targs) when not (List.mem ~equal:String.equal seen name)
130 let seen = name :: seen in
131 let upper_bounds = Typing_env.get_upper_bounds env name targs in
132 Typing_set.fold (fun ty acc -> aux seen acc ty) upper_bounds acc
133 | _ -> acc
135 List.rev (aux [] [] (Typing_expand.fully_expand env ty))
137 let non_null = Typing_solver.non_null
139 let get_concrete_supertypes = Typing_utils.get_concrete_supertypes
141 let is_visible = Typing_visibility.is_visible
143 let assert_nontrivial = Typing_equality_check.assert_nontrivial
145 let assert_nullable = Typing_equality_check.assert_nullable
147 let hint_to_ty env = Decl_hint.hint env.Typing_env_types.decl_env
149 let localize env ety_env = Typing_phase.localize ~ety_env env
151 let localize_with_self = Typing_phase.localize_with_self
153 let get_upper_bounds = Typing_env.get_upper_bounds
155 let is_fresh_generic_parameter = Typing_env.is_fresh_generic_parameter
157 let simplify_unions env ty = Typing_union.simplify_unions env ty
159 let union_list env r tyl = Typing_union.union_list env r tyl
161 let get_reified = Typing_env.get_reified
163 let get_enforceable = Typing_env.get_enforceable
165 let get_newable = Typing_env.get_newable
167 let assert_subtype p reason env ty_have ty_expect on_error =
168 Typing_ops.sub_type p reason env ty_have ty_expect on_error
170 let is_sub_type env ty_sub ty_super =
171 Typing_subtype.is_sub_type env ty_sub ty_super
173 let can_subtype env ty_sub ty_super =
174 Typing_subtype.can_sub_type env ty_sub ty_super
176 let is_sub_type_for_union env ty_sub ty_super =
177 Typing_subtype.is_sub_type_for_union env ty_sub ty_super
179 let referenced_typeconsts env root ids =
180 let root = hint_to_ty env root in
181 let ety_env = Typing_defs.empty_expand_env in
182 Typing_taccess.referenced_typeconsts env ety_env (root, ids)
184 let empty ctx = Typing_env.empty ctx Relative_path.default ~droot:None
186 let restore_saved_env env saved_env =
187 let module Env = Typing_env_types in
188 let ctx =
189 Provider_context.map_tcopt env.Env.decl_env.Decl_env.ctx ~f:(fun _tcopt ->
190 saved_env.Tast.tcopt)
192 let decl_env = { env.Env.decl_env with Decl_env.ctx } in
194 env with
195 Env.decl_env;
196 Env.pessimize = saved_env.Tast.pessimize;
197 Env.genv =
199 env.Env.genv with
200 Env.tcopt = saved_env.Tast.tcopt;
201 Env.condition_types = saved_env.Tast.condition_types;
203 Env.inference_env =
204 Typing_inference_env.simple_merge
205 env.Env.inference_env
206 saved_env.Tast.inference_env;
207 Env.global_tpenv = saved_env.Tast.tpenv;
208 Env.fun_tast_info = saved_env.Tast.fun_tast_info;
211 module EnvFromDef = Typing_env_from_def
212 open Tast
214 let check_fun_tast_info_present env = function
215 | Some _ -> ()
216 | None ->
217 Errors.internal_error
218 env.Typing_env_types.function_pos
219 "fun_tast_info of a function or method was not filled in before TAST checking"
221 let restore_method_env env m =
222 let se = m.m_annotation in
223 restore_saved_env env se
225 let restore_fun_env env f =
226 let se = f.f_annotation in
227 restore_saved_env env se
229 let fun_env ctx f =
230 let ctx =
231 Provider_context.map_tcopt ctx ~f:(fun _tcopt -> f.f_annotation.tcopt)
233 let env = EnvFromDef.fun_env ~origin:Decl_counters.Tast ctx f in
234 restore_fun_env env f
236 let class_env ctx c =
237 let ctx =
238 Provider_context.map_tcopt ctx ~f:(fun _tcopt -> c.c_annotation.tcopt)
240 let env = EnvFromDef.class_env ~origin:Decl_counters.Tast ctx c in
241 restore_saved_env env c.c_annotation
243 let typedef_env ctx t =
244 let ctx =
245 Provider_context.map_tcopt ctx ~f:(fun _tcopt -> t.t_annotation.tcopt)
247 let env = EnvFromDef.typedef_env ~origin:Decl_counters.Tast ctx t in
248 restore_saved_env env t.t_annotation
250 let gconst_env ctx cst =
251 let ctx =
252 Provider_context.map_tcopt ctx ~f:(fun _tcopt -> cst.cst_annotation.tcopt)
254 let env = EnvFromDef.gconst_env ~origin:Decl_counters.Tast ctx cst in
255 restore_saved_env env cst.cst_annotation
257 let def_env ctx d =
258 match d with
259 | Fun x -> fun_env ctx x
260 | Class x -> class_env ctx x
261 | Typedef x -> typedef_env ctx x
262 | Constant x -> gconst_env ctx x
263 | RecordDef _ -> empty ctx
264 (* TODO T44306013 *)
265 (* The following nodes are included in the TAST, but are not typechecked.
266 * However, we need to return an env here so for now create an empty env using
267 * the default typechecker options.
269 | Stmt _
270 | Namespace _
271 | NamespaceUse _
272 | SetNamespaceEnv _
273 | FileAttributes _ ->
274 empty ctx
276 let typing_env_as_tast_env env = env
278 let tast_env_as_typing_env env = env
280 let is_xhp_child = Typing_xhp.is_xhp_child
282 let get_enum = Typing_env.get_enum
284 let is_typedef = Typing_env.is_typedef
286 let get_typedef = Typing_env.get_typedef
288 let is_enum = Typing_env.is_enum
290 let get_fun = Typing_env.get_fun
292 let set_allow_wildcards env =
293 { env with Typing_env_types.allow_wildcards = true }
295 let get_allow_wildcards env = env.Typing_env_types.allow_wildcards
297 let is_enum_class env c = Typing_env.is_enum_class env c
299 let extract_from_fun_tast_info env extractor default_value =
300 let fun_tast_info = env.Typing_env_types.fun_tast_info in
301 check_fun_tast_info_present env fun_tast_info;
302 match fun_tast_info with
303 | Some fun_tast_info -> extractor fun_tast_info
304 | None ->
305 (* In this case, check_fun_tast_info_present reported an error already *)
306 default_value
308 let fun_has_implicit_return (env : t) =
309 extract_from_fun_tast_info env (fun info -> info.has_implicit_return) false
311 let named_fun_body_is_unsafe (env : t) =
312 extract_from_fun_tast_info env (fun info -> info.named_body_is_unsafe) false
314 let get_const env cls name = Typing_env.get_const env cls name
316 let consts env cls = Typing_env.consts env cls
318 let fill_in_pos_filename_if_in_current_decl =
319 Typing_env.fill_in_pos_filename_if_in_current_decl