solved some TODOs about Tgeneric type arguments (2)
[hiphop-php.git] / hphp / hack / src / decl / decl_pos_utils.ml
blobe048960f263be2f821662eca1122a4fda69976bb
1 (*
2 * Copyright (c) 2015, 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 Decl_defs
12 open Shallow_decl_defs
13 open Typing_defs
14 module ShapeMap = Nast.ShapeMap
16 (*****************************************************************************)
17 (* Functor traversing a type, but applies a user defined function for
18 * positions. Positions in errors (_decl_errors) are not mapped - entire
19 * field is erased instead. This is safe because there exists a completely
20 * different system for tracking and updating positions in errors
21 * (see ServerTypeCheck.get_files_with_stale_errors)
23 (*****************************************************************************)
24 module TraversePos (ImplementPos : sig
25 val pos : Pos.t -> Pos.t
26 end) =
27 struct
28 open Typing_reason
30 let pos = ImplementPos.pos
32 let string_id (p, x) = (pos p, x)
34 let rec reason = function
35 | Rnone -> Rnone
36 | Rwitness p -> Rwitness (pos p)
37 | Ridx (p, r) -> Ridx (pos p, reason r)
38 | Ridx_vector p -> Ridx_vector (pos p)
39 | Rforeach p -> Rforeach (pos p)
40 | Rasyncforeach p -> Rasyncforeach (pos p)
41 | Rarith p -> Rarith (pos p)
42 | Rarith_ret p -> Rarith_ret (pos p)
43 | Rcomp p -> Rcomp (pos p)
44 | Rconcat_ret p -> Rconcat_ret (pos p)
45 | Rlogic_ret p -> Rlogic_ret (pos p)
46 | Rbitwise p -> Rbitwise (pos p)
47 | Rbitwise_ret p -> Rbitwise_ret (pos p)
48 | Rno_return p -> Rno_return (pos p)
49 | Rno_return_async p -> Rno_return_async (pos p)
50 | Rret_fun_kind (p, k) -> Rret_fun_kind (pos p, k)
51 | Rhint p -> Rhint (pos p)
52 | Rthrow p -> Rthrow (pos p)
53 | Rplaceholder p -> Rplaceholder (pos p)
54 | Rret_div p -> Rret_div (pos p)
55 | Ryield_gen p -> Ryield_gen (pos p)
56 | Ryield_asyncgen p -> Ryield_asyncgen (pos p)
57 | Ryield_asyncnull p -> Ryield_asyncnull (pos p)
58 | Ryield_send p -> Ryield_send (pos p)
59 | Rlost_info (s, r1, Blame (p2, l)) ->
60 Rlost_info (s, reason r1, Blame (pos p2, l))
61 | Rformat (p1, s, r) -> Rformat (pos p1, s, reason r)
62 | Rclass_class (p, s) -> Rclass_class (pos p, s)
63 | Runknown_class p -> Runknown_class (pos p)
64 | Rvar_param p -> Rvar_param (pos p)
65 | Runpack_param (p1, p2, i) -> Runpack_param (pos p1, pos p2, i)
66 | Rinout_param p -> Rinout_param (pos p)
67 | Rinstantiate (r1, x, r2) -> Rinstantiate (reason r1, x, reason r2)
68 | Rarray_filter (p, r) -> Rarray_filter (pos p, reason r)
69 | Rtypeconst (r1, (p, s1), s2, r2) ->
70 Rtypeconst (reason r1, (pos p, s1), s2, reason r2)
71 | Rtype_access (r1, ls) ->
72 Rtype_access (reason r1, List.map ls ~f:(fun (r, s) -> (reason r, s)))
73 | Rexpr_dep_type (r, p, n) -> Rexpr_dep_type (reason r, pos p, n)
74 | Rnullsafe_op p -> Rnullsafe_op (pos p)
75 | Rtconst_no_cstr (p, s) -> Rtconst_no_cstr (pos p, s)
76 | Rpredicated (p, f) -> Rpredicated (pos p, f)
77 | Ris p -> Ris (pos p)
78 | Ras p -> Ras (pos p)
79 | Rvarray_or_darray_key p -> Rvarray_or_darray_key (pos p)
80 | Rusing p -> Rusing (pos p)
81 | Rdynamic_prop p -> Rdynamic_prop (pos p)
82 | Rdynamic_call p -> Rdynamic_call (pos p)
83 | Ridx_dict p -> Ridx_dict (pos p)
84 | Rmissing_required_field (p, n) -> Rmissing_required_field (pos p, n)
85 | Rmissing_optional_field (p, n) -> Rmissing_optional_field (pos p, n)
86 | Runset_field (p, n) -> Runset_field (pos p, n)
87 | Rcontravariant_generic (r1, n) -> Rcontravariant_generic (reason r1, n)
88 | Rinvariant_generic (r1, n) -> Rcontravariant_generic (reason r1, n)
89 | Rregex p -> Rregex (pos p)
90 | Rimplicit_upper_bound (p, s) -> Rimplicit_upper_bound (pos p, s)
91 | Rarith_ret_int p -> Rarith_ret_int (pos p)
92 | Rarith_ret_float (p, r, s) -> Rarith_ret_float (pos p, reason r, s)
93 | Rarith_ret_num (p, r, s) -> Rarith_ret_num (pos p, reason r, s)
94 | Rarith_dynamic p -> Rarith_dynamic (pos p)
95 | Rbitwise_dynamic p -> Rbitwise_dynamic (pos p)
96 | Rincdec_dynamic p -> Rincdec_dynamic (pos p)
97 | Rtype_variable p -> Rtype_variable (pos p)
98 | Rtype_variable_generics (p, t, s) -> Rtype_variable_generics (pos p, t, s)
99 | Rsolve_fail p -> Rsolve_fail (pos p)
100 | Rcstr_on_generics (p, sid) -> Rcstr_on_generics (pos p, string_id sid)
101 | Rlambda_param (p, r) -> Rlambda_param (pos p, reason r)
102 | Rshape (p, fun_name) -> Rshape (pos p, fun_name)
103 | Renforceable p -> Renforceable (pos p)
104 | Rdestructure p -> Rdestructure (pos p)
105 | Rkey_value_collection_key p -> Rkey_value_collection_key (pos p)
106 | Rglobal_class_prop p -> Rglobal_class_prop (pos p)
107 | Rglobal_fun_param p -> Rglobal_fun_param (pos p)
108 | Rglobal_fun_ret p -> Rglobal_fun_ret (pos p)
110 let pos_mapper =
111 object
112 inherit [_] Aast.map
114 method! on_pos _ p = pos p
116 method on_'fb _ fb = fb
118 method on_'en _ en = en
120 method on_'ex _ ex = pos ex
122 method on_'hi _ hi = hi
125 let rec ty t =
126 let (p, x) = deref t in
127 mk (reason p, ty_ x)
129 and ty_ : decl_phase ty_ -> decl_phase ty_ = function
130 | (Tany _ | Tthis | Terr | Tmixed | Tnonnull | Tdynamic | Tvar _) as x -> x
131 | Tarray (ty1, ty2) -> Tarray (ty_opt ty1, ty_opt ty2)
132 | Tdarray (ty1, ty2) -> Tdarray (ty ty1, ty ty2)
133 | Tvarray root_ty -> Tvarray (ty root_ty)
134 | Tvarray_or_darray (ty1, ty2) -> Tvarray_or_darray (ty ty1, ty ty2)
135 | Tprim _ as x -> x
136 | Tgeneric (name, args) -> Tgeneric (name, List.map args ty)
137 | Ttuple tyl -> Ttuple (List.map tyl ty)
138 | Tunion tyl -> Tunion (List.map tyl ty)
139 | Tintersection tyl -> Tintersection (List.map tyl ty)
140 | Toption x -> Toption (ty x)
141 | Tlike x -> Tlike (ty x)
142 | Tfun ft -> Tfun (fun_type ft)
143 | Tapply (sid, xl) -> Tapply (string_id sid, List.map xl ty)
144 | Taccess (root_ty, ids) -> Taccess (ty root_ty, List.map ids string_id)
145 | Tshape (shape_kind, fdm) ->
146 Tshape (shape_kind, ShapeFieldMap.map_and_rekey fdm shape_field_name ty)
147 | Tpu_access (base, sid) -> Tpu_access (ty base, string_id sid)
149 and ty_opt x = Option.map x ty
151 and shape_field_name = function
152 | Ast_defs.SFlit_int s -> Ast_defs.SFlit_int (string_id s)
153 | Ast_defs.SFlit_str s -> Ast_defs.SFlit_str (string_id s)
154 | Ast_defs.SFclass_const (id, s) ->
155 Ast_defs.SFclass_const (string_id id, string_id s)
157 and constraint_ x = List.map ~f:(fun (ck, x) -> (ck, ty x)) x
159 and possibly_enforced_ty et = { et with et_type = ty et.et_type }
161 and fun_type ft =
163 ft with
164 ft_tparams = List.map ~f:type_param ft.ft_tparams;
165 ft_where_constraints = List.map ft.ft_where_constraints where_constraint;
166 ft_params = List.map ft.ft_params fun_param;
167 ft_ret = possibly_enforced_ty ft.ft_ret;
168 ft_arity = fun_arity ft.ft_arity;
169 ft_reactive = fun_reactive ft.ft_reactive;
172 and fun_elt fe =
174 fe with
175 fe_type = ty fe.fe_type;
176 fe_pos = pos fe.fe_pos;
177 fe_decl_errors = None;
180 and fun_reactive = function
181 | Local (Some ty1) -> Local (Some (ty ty1))
182 | Shallow (Some ty1) -> Shallow (Some (ty ty1))
183 | Reactive (Some ty1) -> Reactive (Some (ty ty1))
184 | Pure (Some ty1) -> Pure (Some (ty ty1))
185 | r -> r
187 and where_constraint (ty1, c, ty2) = (ty ty1, c, ty ty2)
189 and fun_arity = function
190 | Fstandard as x -> x
191 | Fvariadic param -> Fvariadic (fun_param param)
193 and fun_param param =
195 param with
196 fp_pos = pos param.fp_pos;
197 fp_type = possibly_enforced_ty param.fp_type;
198 fp_rx_annotation = param_rx_annotation param.fp_rx_annotation;
201 and param_rx_annotation = function
202 | Some (Param_rx_if_impl t) -> Some (Param_rx_if_impl (ty t))
203 | c -> c
205 and class_const cc =
207 cc_synthesized = cc.cc_synthesized;
208 cc_abstract = cc.cc_abstract;
209 cc_pos = pos cc.cc_pos;
210 cc_type = ty cc.cc_type;
211 cc_expr = Option.map ~f:(pos_mapper#on_expr ()) cc.cc_expr;
212 cc_origin = cc.cc_origin;
215 and typeconst_abstract_kind = function
216 | TCAbstract default -> TCAbstract (ty_opt default)
217 | TCPartiallyAbstract -> TCPartiallyAbstract
218 | TCConcrete -> TCConcrete
220 and typeconst tc =
222 ttc_abstract = typeconst_abstract_kind tc.ttc_abstract;
223 ttc_name = string_id tc.ttc_name;
224 ttc_constraint = ty_opt tc.ttc_constraint;
225 ttc_type = ty_opt tc.ttc_type;
226 ttc_origin = tc.ttc_origin;
227 ttc_enforceable = Tuple.T2.map_fst ~f:pos tc.ttc_enforceable;
228 ttc_reifiable = Option.map tc.ttc_reifiable pos;
231 and pu_enum_member pum =
233 tpum_atom = string_id pum.tpum_atom;
234 tpum_origin = pum.tpum_origin;
235 tpum_types =
236 SMap.map
237 begin
238 fun (origin, id, t) ->
239 (origin, string_id id, ty t)
241 pum.tpum_types;
242 tpum_exprs =
243 SMap.map
244 begin
245 fun (origin, id) ->
246 (origin, string_id id)
248 pum.tpum_exprs;
251 and pu_enum pu =
253 tpu_name = string_id pu.tpu_name;
254 tpu_is_final = pu.tpu_is_final;
255 tpu_case_types =
256 SMap.map
257 (fun (origin, tparam) -> (origin, type_param tparam))
258 pu.tpu_case_types;
259 tpu_case_values =
260 SMap.map
261 begin
262 fun (origin, id, declty) ->
263 (origin, string_id id, ty declty)
265 pu.tpu_case_values;
266 tpu_members = SMap.map pu_enum_member pu.tpu_members;
269 and user_attribute ua =
271 Aast.ua_name = string_id ua.Aast.ua_name;
272 ua_params = List.map ~f:(pos_mapper#on_expr ()) ua.Aast.ua_params;
275 and type_param t =
277 t with
278 tp_name = string_id t.tp_name;
279 tp_constraints = constraint_ t.tp_constraints;
280 tp_user_attributes = List.map ~f:user_attribute t.tp_user_attributes;
283 and class_type dc =
285 dc_final = dc.dc_final;
286 dc_const = dc.dc_const;
287 dc_ppl = dc.dc_ppl;
288 dc_need_init = dc.dc_need_init;
289 dc_deferred_init_members = dc.dc_deferred_init_members;
290 dc_abstract = dc.dc_abstract;
291 dc_members_fully_known = dc.dc_members_fully_known;
292 dc_kind = dc.dc_kind;
293 dc_is_xhp = dc.dc_is_xhp;
294 dc_has_xhp_keyword = dc.dc_has_xhp_keyword;
295 dc_is_disposable = dc.dc_is_disposable;
296 dc_name = dc.dc_name;
297 dc_pos = dc.dc_pos;
298 dc_extends = dc.dc_extends;
299 dc_sealed_whitelist = dc.dc_sealed_whitelist;
300 dc_xhp_attr_deps = dc.dc_xhp_attr_deps;
301 dc_req_ancestors = List.map dc.dc_req_ancestors requirement;
302 dc_req_ancestors_extends = dc.dc_req_ancestors_extends;
303 dc_tparams = List.map dc.dc_tparams type_param;
304 dc_where_constraints = List.map dc.dc_where_constraints where_constraint;
305 dc_substs =
306 SMap.map
307 begin
308 fun ({ sc_subst; _ } as sc) ->
309 { sc with sc_subst = SMap.map ty sc_subst }
311 dc.dc_substs;
312 dc_consts = SMap.map class_const dc.dc_consts;
313 dc_typeconsts = SMap.map typeconst dc.dc_typeconsts;
314 dc_pu_enums = SMap.map pu_enum dc.dc_pu_enums;
315 dc_props = dc.dc_props;
316 dc_sprops = dc.dc_sprops;
317 dc_methods = dc.dc_methods;
318 dc_smethods = dc.dc_smethods;
319 dc_construct = dc.dc_construct;
320 dc_ancestors = SMap.map ty dc.dc_ancestors;
321 dc_enum_type = Option.map dc.dc_enum_type enum_type;
322 dc_decl_errors = None;
323 dc_condition_types = dc.dc_condition_types;
326 and requirement (p, t) = (pos p, ty t)
328 and enum_type te =
329 { te_base = ty te.te_base; te_constraint = ty_opt te.te_constraint }
331 and typedef tdef =
333 td_pos = pos tdef.td_pos;
334 td_vis = tdef.td_vis;
335 td_tparams = List.map tdef.td_tparams type_param;
336 td_constraint = ty_opt tdef.td_constraint;
337 td_type = ty tdef.td_type;
338 td_decl_errors = None;
341 and shallow_class sc =
343 sc_mode = sc.sc_mode;
344 sc_final = sc.sc_final;
345 sc_is_xhp = sc.sc_is_xhp;
346 sc_has_xhp_keyword = sc.sc_has_xhp_keyword;
347 sc_kind = sc.sc_kind;
348 sc_name = string_id sc.sc_name;
349 sc_tparams = List.map sc.sc_tparams type_param;
350 sc_where_constraints = List.map sc.sc_where_constraints where_constraint;
351 sc_extends = List.map sc.sc_extends ty;
352 sc_uses = List.map sc.sc_uses ty;
353 sc_method_redeclarations = sc.sc_method_redeclarations;
354 sc_xhp_attr_uses = List.map sc.sc_xhp_attr_uses ty;
355 sc_req_extends = List.map sc.sc_req_extends ty;
356 sc_req_implements = List.map sc.sc_req_implements ty;
357 sc_implements = List.map sc.sc_implements ty;
358 sc_consts = List.map sc.sc_consts shallow_class_const;
359 sc_typeconsts = List.map sc.sc_typeconsts shallow_typeconst;
360 sc_pu_enums = List.map sc.sc_pu_enums shallow_pu_enum;
361 sc_props = List.map sc.sc_props shallow_prop;
362 sc_sprops = List.map sc.sc_sprops shallow_prop;
363 sc_constructor = Option.map sc.sc_constructor shallow_method;
364 sc_static_methods = List.map sc.sc_static_methods shallow_method;
365 sc_methods = List.map sc.sc_methods shallow_method;
366 sc_user_attributes = List.map sc.sc_user_attributes user_attribute;
367 sc_enum_type = Option.map sc.sc_enum_type enum_type;
368 sc_decl_errors = Errors.empty;
371 and shallow_class_const scc =
373 scc_abstract = scc.scc_abstract;
374 scc_expr = Option.map scc.scc_expr (pos_mapper#on_expr ());
375 scc_name = string_id scc.scc_name;
376 scc_type = ty scc.scc_type;
379 and shallow_typeconst stc =
381 stc_abstract = typeconst_abstract_kind stc.stc_abstract;
382 stc_constraint = Option.map stc.stc_constraint ty;
383 stc_name = string_id stc.stc_name;
384 stc_type = Option.map stc.stc_type ty;
385 stc_enforceable = (pos (fst stc.stc_enforceable), snd stc.stc_enforceable);
386 stc_reifiable = Option.map stc.stc_reifiable pos;
389 and shallow_pu_member spum =
391 spum_atom = string_id spum.spum_atom;
392 spum_types = List.map spum.spum_types (fun (s, t) -> (string_id s, ty t));
393 spum_exprs = List.map spum.spum_exprs string_id;
396 and shallow_pu_enum spu =
398 spu_name = string_id spu.spu_name;
399 spu_is_final = spu.spu_is_final;
400 spu_case_types = List.map ~f:type_param spu.spu_case_types;
401 spu_case_values =
402 List.map spu.spu_case_values (fun (s, t) -> (string_id s, ty t));
403 spu_members = List.map spu.spu_members shallow_pu_member;
406 and shallow_prop sp =
408 sp_const = sp.sp_const;
409 sp_xhp_attr = sp.sp_xhp_attr;
410 sp_lateinit = sp.sp_lateinit;
411 sp_lsb = sp.sp_lsb;
412 sp_name = string_id sp.sp_name;
413 sp_needs_init = sp.sp_needs_init;
414 sp_type = Option.map sp.sp_type ty;
415 sp_abstract = sp.sp_abstract;
416 sp_visibility = sp.sp_visibility;
417 sp_fixme_codes = ISet.empty;
420 and shallow_method sm =
422 sm_abstract = sm.sm_abstract;
423 sm_final = sm.sm_final;
424 sm_memoizelsb = sm.sm_memoizelsb;
425 sm_name = string_id sm.sm_name;
426 sm_override = sm.sm_override;
427 sm_dynamicallycallable = sm.sm_dynamicallycallable;
428 sm_reactivity = sm.sm_reactivity;
429 sm_type = ty sm.sm_type;
430 sm_visibility = sm.sm_visibility;
431 sm_fixme_codes = ISet.empty;
432 sm_deprecated = sm.sm_deprecated;
436 (*****************************************************************************)
437 (* Returns a signature with all the positions replaced with Pos.none *)
438 (*****************************************************************************)
439 module NormalizeSig = TraversePos (struct
440 let pos _ = Pos.none
441 end)