Support ~ types on XHP attributes that are enum {'x', 'y'}
[hiphop-php.git] / hphp / hack / src / decl / decl_pos_utils.ml
blobd546e3089e9b9537210619cfd9eb177fd1cf308d
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
15 (*****************************************************************************)
16 (* Functor traversing a type, but applies a user defined function for
17 * positions. Positions in errors (_decl_errors) are not mapped - entire
18 * field is erased instead. This is safe because there exists a completely
19 * different system for tracking and updating positions in errors
20 * (see ServerTypeCheck.get_files_with_stale_errors)
22 (*****************************************************************************)
23 module TraversePos (ImplementPos : sig
24 val pos : Pos.t -> Pos.t
26 val pos_or_decl : Pos_or_decl.t -> Pos_or_decl.t
27 end) =
28 struct
29 open Typing_reason
31 let pos = ImplementPos.pos
33 let pos_or_decl = ImplementPos.pos_or_decl
35 let positioned_id : Typing_defs.pos_id -> Typing_defs.pos_id =
36 (fun (p, x) -> (pos_or_decl p, x))
38 let rec reason : type ph. ph Typing_reason.t_ -> ph Typing_reason.t_ =
39 function
40 | Rnone -> Rnone
41 | Rwitness p -> Rwitness (pos p)
42 | Rwitness_from_decl p -> Rwitness_from_decl (pos_or_decl p)
43 | Ridx (p, r) -> Ridx (pos p, reason r)
44 | Ridx_vector p -> Ridx_vector (pos p)
45 | Ridx_vector_from_decl p -> Ridx_vector_from_decl (pos_or_decl p)
46 | Rforeach p -> Rforeach (pos p)
47 | Rasyncforeach p -> Rasyncforeach (pos p)
48 | Rarith p -> Rarith (pos p)
49 | Rarith_ret p -> Rarith_ret (pos p)
50 | Rcomp p -> Rcomp (pos p)
51 | Rconcat_ret p -> Rconcat_ret (pos p)
52 | Rlogic_ret p -> Rlogic_ret (pos p)
53 | Rbitwise p -> Rbitwise (pos p)
54 | Rbitwise_ret p -> Rbitwise_ret (pos p)
55 | Rno_return p -> Rno_return (pos p)
56 | Rno_return_async p -> Rno_return_async (pos p)
57 | Rret_fun_kind (p, k) -> Rret_fun_kind (pos p, k)
58 | Rret_fun_kind_from_decl (p, k) ->
59 Rret_fun_kind_from_decl (pos_or_decl p, k)
60 | Rhint p -> Rhint (pos_or_decl p)
61 | Rthrow p -> Rthrow (pos p)
62 | Rplaceholder p -> Rplaceholder (pos p)
63 | Rret_div p -> Rret_div (pos p)
64 | Ryield_gen p -> Ryield_gen (pos p)
65 | Ryield_asyncgen p -> Ryield_asyncgen (pos p)
66 | Ryield_asyncnull p -> Ryield_asyncnull (pos p)
67 | Ryield_send p -> Ryield_send (pos p)
68 | Rlost_info (s, r1, Blame (p2, l)) ->
69 Rlost_info (s, reason r1, Blame (pos p2, l))
70 | Rformat (p1, s, r) -> Rformat (pos p1, s, reason r)
71 | Rclass_class (p, s) -> Rclass_class (pos_or_decl p, s)
72 | Runknown_class p -> Runknown_class (pos p)
73 | Rvar_param p -> Rvar_param (pos p)
74 | Rvar_param_from_decl p -> Rvar_param_from_decl (pos_or_decl p)
75 | Runpack_param (p1, p2, i) -> Runpack_param (pos p1, pos_or_decl p2, i)
76 | Rinout_param p -> Rinout_param (pos_or_decl p)
77 | Rinstantiate (r1, x, r2) -> Rinstantiate (reason r1, x, reason r2)
78 | Rtypeconst (r1, (p, s1), s2, r2) ->
79 Rtypeconst (reason r1, (pos_or_decl p, s1), s2, reason r2)
80 | Rtype_access (r1, ls) ->
81 Rtype_access (reason r1, List.map ls ~f:(fun (r, s) -> (reason r, s)))
82 | Rexpr_dep_type (r, p, n) -> Rexpr_dep_type (reason r, pos_or_decl p, n)
83 | Rnullsafe_op p -> Rnullsafe_op (pos p)
84 | Rtconst_no_cstr id -> Rtconst_no_cstr (positioned_id id)
85 | Rpredicated (p, f) -> Rpredicated (pos p, f)
86 | Ris p -> Ris (pos p)
87 | Ras p -> Ras (pos p)
88 | Rvarray_or_darray_key p -> Rvarray_or_darray_key (pos_or_decl p)
89 | Rvec_or_dict_key p -> Rvec_or_dict_key (pos_or_decl p)
90 | Rusing p -> Rusing (pos p)
91 | Rdynamic_prop p -> Rdynamic_prop (pos p)
92 | Rdynamic_call p -> Rdynamic_call (pos p)
93 | Rdynamic_construct p -> Rdynamic_construct (pos p)
94 | Ridx_dict p -> Ridx_dict (pos p)
95 | Rset_element p -> Rset_element (pos p)
96 | Rmissing_optional_field (p, n) ->
97 Rmissing_optional_field (pos_or_decl p, n)
98 | Runset_field (p, n) -> Runset_field (pos p, n)
99 | Rcontravariant_generic (r1, n) -> Rcontravariant_generic (reason r1, n)
100 | Rinvariant_generic (r1, n) -> Rcontravariant_generic (reason r1, n)
101 | Rregex p -> Rregex (pos p)
102 | Rimplicit_upper_bound (p, s) -> Rimplicit_upper_bound (pos_or_decl p, s)
103 | Rarith_ret_int p -> Rarith_ret_int (pos p)
104 | Rarith_ret_float (p, r, s) -> Rarith_ret_float (pos p, reason r, s)
105 | Rarith_ret_num (p, r, s) -> Rarith_ret_num (pos p, reason r, s)
106 | Rarith_dynamic p -> Rarith_dynamic (pos p)
107 | Rbitwise_dynamic p -> Rbitwise_dynamic (pos p)
108 | Rincdec_dynamic p -> Rincdec_dynamic (pos p)
109 | Rtype_variable p -> Rtype_variable (pos p)
110 | Rtype_variable_generics (p, t, s) -> Rtype_variable_generics (pos p, t, s)
111 | Rglobal_type_variable_generics (p, t, s) ->
112 Rglobal_type_variable_generics (pos_or_decl p, t, s)
113 | Rsolve_fail p -> Rsolve_fail (pos_or_decl p)
114 | Rcstr_on_generics (p, sid) ->
115 Rcstr_on_generics (pos_or_decl p, positioned_id sid)
116 | Rlambda_param (p, r) -> Rlambda_param (pos p, reason r)
117 | Rshape (p, fun_name) -> Rshape (pos p, fun_name)
118 | Renforceable p -> Renforceable (pos_or_decl p)
119 | Rdestructure p -> Rdestructure (pos p)
120 | Rkey_value_collection_key p -> Rkey_value_collection_key (pos p)
121 | Rglobal_class_prop p -> Rglobal_class_prop (pos_or_decl p)
122 | Rglobal_fun_param p -> Rglobal_fun_param (pos_or_decl p)
123 | Rglobal_fun_ret p -> Rglobal_fun_ret (pos_or_decl p)
124 | Rsplice p -> Rsplice (pos p)
125 | Ret_boolean p -> Ret_boolean (pos p)
126 | Rdefault_capability p -> Rdefault_capability (pos_or_decl p)
127 | Rconcat_operand p -> Rconcat_operand (pos p)
128 | Rinterp_operand p -> Rinterp_operand (pos p)
129 | Rdynamic_coercion r -> Rdynamic_coercion (reason r)
130 | Rsupport_dynamic_type p -> Rsupport_dynamic_type (pos_or_decl p)
131 | Rdynamic_partial_enforcement (p, cn, r) ->
132 Rdynamic_partial_enforcement (pos_or_decl p, cn, reason r)
133 | Rrigid_tvar_escape (p, v, w, r) ->
134 Rrigid_tvar_escape (pos p, v, w, reason r)
136 let rec ty t =
137 let (p, x) = deref t in
138 mk (reason p, ty_ x)
140 and ty_ : decl_phase ty_ -> decl_phase ty_ = function
141 | (Tany _ | Tthis | Terr | Tmixed | Tnonnull | Tdynamic | Tvar _) as x -> x
142 | Tvec_or_dict (ty1, ty2) -> Tvec_or_dict (ty ty1, ty ty2)
143 | Tprim _ as x -> x
144 | Tgeneric (name, args) -> Tgeneric (name, List.map args ~f:ty)
145 | Ttuple tyl -> Ttuple (List.map tyl ~f:ty)
146 | Tunion tyl -> Tunion (List.map tyl ~f:ty)
147 | Tintersection tyl -> Tintersection (List.map tyl ~f:ty)
148 | Toption x -> Toption (ty x)
149 | Tlike x -> Tlike (ty x)
150 | Tfun ft -> Tfun (fun_type ft)
151 | Tapply (sid, xl) -> Tapply (positioned_id sid, List.map xl ~f:ty)
152 | Taccess (root_ty, id) -> Taccess (ty root_ty, positioned_id id)
153 | Tshape (shape_kind, fdm) ->
154 Tshape (shape_kind, ShapeFieldMap.map_and_rekey fdm shape_field_name ty)
156 and ty_opt x = Option.map x ~f:ty
158 and shape_field_name = function
159 | Typing_defs.TSFlit_int (p, s) -> Typing_defs.TSFlit_int (pos_or_decl p, s)
160 | Typing_defs.TSFlit_str (p, s) -> Typing_defs.TSFlit_str (pos_or_decl p, s)
161 | Typing_defs.TSFclass_const (id, s) ->
162 Typing_defs.TSFclass_const (positioned_id id, positioned_id s)
164 and constraint_ x = List.map ~f:(fun (ck, x) -> (ck, ty x)) x
166 and possibly_enforced_ty et = { et with et_type = ty et.et_type }
168 and capability = function
169 | CapTy cap -> CapTy (ty cap)
170 | CapDefaults p -> CapDefaults (pos_or_decl p)
172 and fun_implicit_params implicit =
173 { capability = capability implicit.capability }
175 and fun_type ft =
177 ft with
178 ft_tparams = List.map ~f:type_param ft.ft_tparams;
179 ft_where_constraints =
180 List.map ft.ft_where_constraints ~f:where_constraint;
181 ft_params = List.map ft.ft_params ~f:fun_param;
182 ft_implicit_params = fun_implicit_params ft.ft_implicit_params;
183 ft_ret = possibly_enforced_ty ft.ft_ret;
184 ft_arity = fun_arity ft.ft_arity;
187 and fun_elt fe =
188 { fe with fe_type = ty fe.fe_type; fe_pos = pos_or_decl fe.fe_pos }
190 and where_constraint (ty1, c, ty2) = (ty ty1, c, ty ty2)
192 and fun_arity = function
193 | Fstandard as x -> x
194 | Fvariadic param -> Fvariadic (fun_param param)
196 and fun_param param =
198 param with
199 fp_pos = pos_or_decl param.fp_pos;
200 fp_type = possibly_enforced_ty param.fp_type;
203 and class_const cc =
205 cc_synthesized = cc.cc_synthesized;
206 cc_abstract = cc.cc_abstract;
207 cc_pos = pos_or_decl cc.cc_pos;
208 cc_type = ty cc.cc_type;
209 cc_origin = cc.cc_origin;
210 cc_refs = cc.cc_refs;
213 and typeconst = function
214 | TCAbstract { atc_as_constraint; atc_super_constraint; atc_default } ->
215 TCAbstract
217 atc_as_constraint = ty_opt atc_as_constraint;
218 atc_super_constraint = ty_opt atc_super_constraint;
219 atc_default = ty_opt atc_default;
221 | TCConcrete { tc_type } -> TCConcrete { tc_type = ty tc_type }
223 and typeconst_type tc =
225 ttc_synthesized = tc.ttc_synthesized;
226 ttc_name = positioned_id tc.ttc_name;
227 ttc_kind = typeconst tc.ttc_kind;
228 ttc_origin = tc.ttc_origin;
229 ttc_enforceable = Tuple.T2.map_fst ~f:pos_or_decl tc.ttc_enforceable;
230 ttc_reifiable = Option.map tc.ttc_reifiable ~f:pos_or_decl;
231 ttc_concretized = tc.ttc_concretized;
232 ttc_is_ctx = tc.ttc_is_ctx;
235 and user_attribute { ua_name; ua_classname_params } =
236 { ua_name = positioned_id ua_name; ua_classname_params }
238 and type_param t =
240 tp_name = positioned_id t.tp_name;
241 tp_variance = t.tp_variance;
242 tp_reified = t.tp_reified;
243 tp_tparams = List.map ~f:type_param t.tp_tparams;
244 tp_constraints = constraint_ t.tp_constraints;
245 tp_user_attributes = List.map ~f:user_attribute t.tp_user_attributes;
248 and class_type dc =
250 dc_final = dc.dc_final;
251 dc_const = dc.dc_const;
252 dc_internal = dc.dc_internal;
253 dc_need_init = dc.dc_need_init;
254 dc_deferred_init_members = dc.dc_deferred_init_members;
255 dc_abstract = dc.dc_abstract;
256 dc_kind = dc.dc_kind;
257 dc_is_xhp = dc.dc_is_xhp;
258 dc_has_xhp_keyword = dc.dc_has_xhp_keyword;
259 dc_module = dc.dc_module;
260 dc_name = dc.dc_name;
261 dc_pos = dc.dc_pos;
262 dc_extends = dc.dc_extends;
263 dc_sealed_whitelist = dc.dc_sealed_whitelist;
264 dc_xhp_attr_deps = dc.dc_xhp_attr_deps;
265 dc_xhp_enum_values = dc.dc_xhp_enum_values;
266 dc_req_ancestors = List.map dc.dc_req_ancestors ~f:requirement;
267 dc_req_ancestors_extends = dc.dc_req_ancestors_extends;
268 dc_tparams = List.map dc.dc_tparams ~f:type_param;
269 dc_where_constraints =
270 List.map dc.dc_where_constraints ~f:where_constraint;
271 dc_substs =
272 SMap.map
273 begin
274 fun ({ sc_subst; _ } as sc) ->
275 { sc with sc_subst = SMap.map ty sc_subst }
277 dc.dc_substs;
278 dc_consts = SMap.map class_const dc.dc_consts;
279 dc_typeconsts = SMap.map typeconst_type dc.dc_typeconsts;
280 dc_props = dc.dc_props;
281 dc_sprops = dc.dc_sprops;
282 dc_methods = dc.dc_methods;
283 dc_smethods = dc.dc_smethods;
284 dc_construct = dc.dc_construct;
285 dc_ancestors = SMap.map ty dc.dc_ancestors;
286 dc_support_dynamic_type = dc.dc_support_dynamic_type;
287 dc_enum_type = Option.map dc.dc_enum_type ~f:enum_type;
288 dc_decl_errors = None;
289 dc_condition_types = dc.dc_condition_types;
292 and requirement (p, t) = (pos_or_decl p, ty t)
294 and enum_type te =
296 te_base = ty te.te_base;
297 te_constraint = ty_opt te.te_constraint;
298 te_includes = List.map te.te_includes ~f:ty;
301 and typedef tdef =
303 td_module = tdef.td_module;
304 td_pos = pos_or_decl tdef.td_pos;
305 td_vis = tdef.td_vis;
306 td_tparams = List.map tdef.td_tparams ~f:type_param;
307 td_constraint = ty_opt tdef.td_constraint;
308 td_type = ty tdef.td_type;
309 td_is_ctx = tdef.td_is_ctx;
310 td_attributes = List.map tdef.td_attributes ~f:user_attribute;
313 and shallow_class sc =
315 sc_mode = sc.sc_mode;
316 sc_final = sc.sc_final;
317 sc_abstract = sc.sc_abstract;
318 sc_is_xhp = sc.sc_is_xhp;
319 sc_has_xhp_keyword = sc.sc_has_xhp_keyword;
320 sc_kind = sc.sc_kind;
321 sc_module = sc.sc_module;
322 sc_name = positioned_id sc.sc_name;
323 sc_tparams = List.map sc.sc_tparams ~f:type_param;
324 sc_where_constraints =
325 List.map sc.sc_where_constraints ~f:where_constraint;
326 sc_extends = List.map sc.sc_extends ~f:ty;
327 sc_uses = List.map sc.sc_uses ~f:ty;
328 sc_xhp_attr_uses = List.map sc.sc_xhp_attr_uses ~f:ty;
329 sc_xhp_enum_values = sc.sc_xhp_enum_values;
330 sc_req_extends = List.map sc.sc_req_extends ~f:ty;
331 sc_req_implements = List.map sc.sc_req_implements ~f:ty;
332 sc_implements = List.map sc.sc_implements ~f:ty;
333 sc_support_dynamic_type = sc.sc_support_dynamic_type;
334 sc_consts = List.map sc.sc_consts ~f:shallow_class_const;
335 sc_typeconsts = List.map sc.sc_typeconsts ~f:shallow_typeconst;
336 sc_props = List.map sc.sc_props ~f:shallow_prop;
337 sc_sprops = List.map sc.sc_sprops ~f:shallow_prop;
338 sc_constructor = Option.map sc.sc_constructor ~f:shallow_method;
339 sc_static_methods = List.map sc.sc_static_methods ~f:shallow_method;
340 sc_methods = List.map sc.sc_methods ~f:shallow_method;
341 sc_user_attributes = List.map sc.sc_user_attributes ~f:user_attribute;
342 sc_enum_type = Option.map sc.sc_enum_type ~f:enum_type;
345 and shallow_class_const scc =
347 scc_abstract = scc.scc_abstract;
348 scc_name = positioned_id scc.scc_name;
349 scc_type = ty scc.scc_type;
350 scc_refs = scc.scc_refs;
353 and shallow_typeconst stc =
355 stc_kind = typeconst stc.stc_kind;
356 stc_name = positioned_id stc.stc_name;
357 stc_enforceable =
358 (pos_or_decl (fst stc.stc_enforceable), snd stc.stc_enforceable);
359 stc_reifiable = Option.map stc.stc_reifiable ~f:pos_or_decl;
360 stc_is_ctx = stc.stc_is_ctx;
363 and shallow_prop sp =
365 sp_name = positioned_id sp.sp_name;
366 sp_xhp_attr = sp.sp_xhp_attr;
367 sp_type = Option.map sp.sp_type ~f:ty;
368 sp_visibility = sp.sp_visibility;
369 sp_flags = sp.sp_flags;
372 and shallow_method sm =
374 sm_name = positioned_id sm.sm_name;
375 sm_type = ty sm.sm_type;
376 sm_visibility = sm.sm_visibility;
377 sm_deprecated = sm.sm_deprecated;
378 sm_flags = sm.sm_flags;
379 sm_attributes = sm.sm_attributes;
383 (*****************************************************************************)
384 (* Returns a signature with all the positions replaced with Pos.none *)
385 (*****************************************************************************)
386 module NormalizeSig = TraversePos (struct
387 let pos _ = Pos.none
389 let pos_or_decl _ = Pos_or_decl.none
390 end)