Handle condition types for intersections
[hiphop-php.git] / hphp / hack / src / typing / typing_reactivity.ml
blobe92ba0e75eaf41ace336363e937fb0218217a5be
1 (*
2 * Copyright (c) 2017, 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 Core_kernel
11 open Typing_defs
13 module Phase = Typing_phase
14 module Env = Typing_env
15 module SubType = Typing_subtype
16 module TU = Typing_utils
17 module CT = SubType.ConditionTypes
18 module MakeType = Typing_make_type
20 type method_call_info = {
21 receiver_type: locl ty;
22 receiver_is_self: bool;
23 is_static: bool;
24 method_name: string;
27 let make_call_info ~receiver_is_self ~is_static receiver_type method_name =
28 { receiver_type; receiver_is_self; is_static; method_name; }
30 let type_to_str: type a. Env.env -> a ty -> string = fun env ty ->
31 (* strip expression dependent types to make error message clearer *)
32 let rec unwrap: type a. a ty -> a ty = function
33 | _, Tabstract (AKdependent DTthis, Some ty) -> unwrap ty
34 | ty -> ty in
35 Typing_print.full env (unwrap ty)
37 let localize env ty =
38 let _, t = Phase.localize (Phase.env_with_self env) env ty in
41 let rec condition_type_from_reactivity r =
42 match r with
43 | Reactive (Some t) | Shallow (Some t) | Local (Some t) -> Some t
44 | MaybeReactive r -> condition_type_from_reactivity r
45 | RxVar v -> Option.bind v condition_type_from_reactivity
46 | _ -> None
48 (* Obtains condition type associated with ty
49 - for types in [$this; self; static] it tries to extract condition type from the
50 current reactivity context
51 - for parameter types with OnlyRxIfImpl annotation it will get associated condition
52 type that was specified as parameter in attribute
53 - for all other cases return None *)
54 let get_associated_condition_type env ~is_self ty =
55 match ty with
56 | _, Tabstract (AKgeneric n, _) ->
57 Env.get_condition_type env n
58 | _, Tabstract (AKdependent DTthis, _) ->
59 condition_type_from_reactivity (Env.env_reactivity env)
60 | _ when is_self ->
61 condition_type_from_reactivity (Env.env_reactivity env)
62 | _ -> None
64 (* removes condition type from given reactivity flavor *)
65 let rec strip_conditional_reactivity r =
66 match r with
67 | Reactive (Some _) -> Reactive None
68 | Shallow (Some _) -> Shallow None
69 | Local (Some _) -> Local None
70 | MaybeReactive r -> MaybeReactive (strip_conditional_reactivity r)
71 | RxVar v -> RxVar (Option.map v strip_conditional_reactivity)
72 | r -> r
74 (* checks if condition type associated with ty matches the condition
75 specified by cond_ty *)
76 let condition_type_matches ~is_self env ty cond_ty =
77 get_associated_condition_type ~is_self env ty
78 |> Option.value_map ~default:false ~f:(fun arg_cond_ty ->
79 let arg_cond_ty = CT.localize_condition_type env arg_cond_ty in
80 SubType.is_sub_type_LEGACY_DEPRECATED env arg_cond_ty cond_ty)
82 (* checks if ty matches the criteria specified by argument of __OnlyRxIfImpl *)
83 let check_only_rx_if_impl env ~is_receiver ~is_self pos reason ty cond_ty =
84 (* __OnlyRxIfImpl condition is true if either
85 - ty is a subtype of condition type
86 - type has linked condition type which is a subtype of condition type *)
87 let cond_ty = CT.localize_condition_type env cond_ty in
88 let rec check env ty =
89 (* TODO: move caller to be TAST check *)
90 match Env.expand_type env ty with
91 | env, (_, Tintersection tyl) -> List.exists tyl ~f:(check env)
92 | env, ty ->
93 SubType.is_sub_type_LEGACY_DEPRECATED env ty cond_ty ||
94 condition_type_matches ~is_self env ty cond_ty
96 let ok = check env ty in
97 if not ok
98 then begin
99 let condition_type_str = type_to_str env cond_ty in
100 let arg_type_str = type_to_str env ty in
101 let arg_pos = Reason.to_pos (fst ty) in
102 Errors.invalid_argument_type_for_condition_in_rx ~is_receiver
103 pos (Reason.to_pos reason) arg_pos condition_type_str arg_type_str
104 end;
107 let bind o ~f = Option.bind o f
109 let try_get_method_from_condition_type env receiver_info =
110 receiver_info
111 |> bind ~f:begin
112 fun { receiver_type; receiver_is_self = is_self; is_static; method_name; _ } ->
113 get_associated_condition_type ~is_self env receiver_type
114 |> Option.map ~f:(fun t -> t, is_static, method_name)
116 |> bind ~f:begin
117 fun (t, is_static, method_name) ->
118 CT.try_get_method_from_condition_type env t is_static method_name
120 |> bind ~f:begin
121 function
122 | { ce_type = lazy (_, Typing_defs.Tfun f); _ } -> Some f
123 | _ -> None
126 let try_get_reactivity_from_condition_type env receiver_info =
127 try_get_method_from_condition_type env receiver_info
128 |> Option.map ~f:begin
129 function
130 | { ft_reactive = Nonreactive; _ } -> Nonreactive
131 | { ft_reactive = MaybeReactive _ as r; _ } -> r
132 | { ft_reactive = r; _ } -> MaybeReactive r
135 let check_reactivity_matches env pos reason caller_reactivity (callee_reactivity, cause_pos) =
136 let callee_reactivity = strip_conditional_reactivity callee_reactivity in
137 let ok = SubType.subtype_reactivity ~is_call_site:true env callee_reactivity caller_reactivity in
138 if ok then true
139 else begin
140 (* for better error reporting remove rxvar from caller reactivity *)
141 let caller_reactivity =
142 match caller_reactivity with
143 | MaybeReactive (RxVar (Some r)) -> MaybeReactive r
144 | RxVar (Some r) -> r
145 | r -> r in
146 begin match caller_reactivity, callee_reactivity with
147 | (MaybeReactive (Reactive _) | Reactive _),
148 (MaybeReactive (Shallow _ | Local _ | Nonreactive) | (Shallow _ | Local _ | Nonreactive)) ->
149 Errors.nonreactive_function_call pos
150 (Reason.to_pos reason)
151 (TU.reactivity_to_string env callee_reactivity)
152 cause_pos
153 | (MaybeReactive (Shallow _) | Shallow _), Nonreactive ->
154 Errors.nonreactive_call_from_shallow pos
155 (Reason.to_pos reason)
156 (TU.reactivity_to_string env callee_reactivity)
157 cause_pos
158 | _ ->
159 Errors.callsite_reactivity_mismatch
160 pos (Reason.to_pos reason)
161 (TU.reactivity_to_string env callee_reactivity)
162 cause_pos
163 (TU.reactivity_to_string env caller_reactivity)
164 end;
165 false
168 let get_effective_reactivity env r ft arg_types =
169 let go ((res, _) as acc) (p, arg_ty) =
170 if p.fp_rx_annotation = Some Param_rx_var
171 then begin
172 match arg_ty with
173 | reason, Tfun { ft_reactive = r; _ } ->
174 if SubType.subtype_reactivity env ~is_call_site:true r res
175 then acc
176 else r, Some (Reason.to_pos reason)
177 | _ -> acc
179 else acc in
180 match r with
181 | RxVar (Some rx) | MaybeReactive (RxVar (Some rx)) | rx ->
182 begin match List.zip ft.ft_params arg_types with
183 | Some l -> List.fold ~init:(rx, None) ~f:go l
184 | None -> r, None
187 let check_call env method_info pos reason ft arg_types =
188 (* do nothing if unsafe_rx is set *)
189 if TypecheckerOptions.unsafe_rx (Env.get_tcopt env) then ()
190 else
191 match Env.env_reactivity env with
192 (* non reactive and locally reactive functions can call pretty much anything
193 - do nothing *)
194 | Nonreactive | Local _ -> ()
195 | _ ->
196 (* check steps:
197 1. ensure that conditions for all parameters (including receiver) are met
198 2. check that reactivity of the callee matches reactivity of the caller with
199 stripped condition types (they were checked on step 1) *)
200 let caller_reactivity =
201 let rec go = function
202 | Reactive (Some _)
203 | MaybeReactive (Reactive (Some _)) -> MaybeReactive (Reactive None)
204 | Shallow (Some _)
205 | MaybeReactive (Shallow (Some _)) -> MaybeReactive (Shallow None)
206 | Local (Some _)
207 | MaybeReactive (Local (Some _)) -> MaybeReactive (Local None)
208 | MaybeReactive (RxVar (Some v)) -> MaybeReactive (RxVar (Some (go v)))
209 | r -> r in
210 go (Env.env_reactivity env) in
211 (* check that all conditions are met if we are calling something
212 conditionally reactive *)
213 let callee_is_conditionally_reactive =
214 (* receiver is conditionally reactive *)
215 Option.is_some (condition_type_from_reactivity ft.ft_reactive) ||
216 (* one of arguments is conditionally reactive *)
217 List.exists ft.ft_params ~f:begin function
218 | { fp_rx_annotation = Some (Param_rx_if_impl _); _ } -> true
219 | _ -> false
220 end in
221 let allow_call =
222 if callee_is_conditionally_reactive then begin
223 let allow_call =
224 (* check that condition for receiver is met *)
225 match condition_type_from_reactivity ft.ft_reactive, method_info with
226 | Some cond_ty, Some { receiver_type; receiver_is_self = is_self; _ } ->
227 check_only_rx_if_impl env
228 ~is_receiver:true
229 ~is_self
230 pos reason
231 receiver_type cond_ty
232 | _ ->
233 true in
234 allow_call &&
235 (* check that conditions for all arguments are met *)
236 begin
237 let rec check_params ft_params arg_types =
238 match ft_params, arg_types with
239 | [], _ -> true
240 | { fp_rx_annotation = Some Param_rx_if_impl ty; fp_type; _ } :: tl, arg_ty::arg_tl ->
241 let ty =
242 if Typing_utils.is_option env fp_type.et_type
243 then MakeType.nullable (fst ty) ty
244 else ty
246 (* check if argument type matches condition *)
247 check_only_rx_if_impl env ~is_receiver:false ~is_self:false pos reason arg_ty ty &&
248 (* check the rest of arguments *)
249 check_params tl arg_tl
250 | { fp_rx_annotation = Some Param_rx_if_impl ty; fp_type; _ } :: tl, []
251 when Typing_utils.is_option env fp_type.et_type ->
252 (* if there are more parameters than actual arguments - assume that remaining parameters
253 have default values (actual arity check is performed elsewhere). *)
254 let ty = MakeType.nullable (fst ty) ty in
255 (* Treat missing arguments as if null was provided explicitly *)
256 let arg_ty = (MakeType.null Reason.none) in
257 check_only_rx_if_impl env ~is_receiver:false ~is_self:false pos reason arg_ty ty &&
258 check_params tl []
259 | { fp_rx_annotation = Some Param_rx_if_impl _; _ } :: _, [] ->
260 (* Missing argument for non-nulalble RxIfImpl parameter - no reasonable defaults are expected.
261 TODO: add check that type of parameter annotated with RxIfImpl is class or interface *)
262 false
263 | _::tl, _::arg_tl -> check_params tl arg_tl
264 | _:: tl, [] -> check_params tl []
266 check_params ft.ft_params arg_types
269 else true in
270 (* if call is not allowed - this means that that at least one of conditions
271 was not met and since errors were already reported we can bail out. Otherwise
272 we need to verify that reactivities for callee and caller are in agreement. *)
273 if allow_call then begin
274 (* pick the function we are trying to invoke *)
275 let ok =
276 Option.value_map (try_get_reactivity_from_condition_type env method_info)
277 ~f:(fun r -> check_reactivity_matches env pos reason caller_reactivity (r, None))
278 ~default: false in
279 if not ok then
280 check_reactivity_matches env pos reason caller_reactivity
281 (get_effective_reactivity env ft.ft_reactive ft arg_types)
282 |> ignore
285 let disallow_atmost_rx_as_rxfunc_on_non_functions env param param_ty =
286 let module UA = Naming_special_names.UserAttributes in
287 if Attributes.mem UA.uaAtMostRxAsFunc param.Aast.param_user_attributes
288 then begin
289 if param.Aast.param_hint = None
290 then Errors.missing_annotation_for_atmost_rx_as_rxfunc_parameter param.Aast.param_pos
291 else
292 let rec err_if_not_fun ty =
293 match snd ty with
294 (* if parameter has <<__AtMostRxAsFunc>> annotation then:
295 - parameter should be typed as function or a like function *)
296 | Tfun _ -> ()
297 | Tunion [ty; (_, Tdynamic)]
298 | Tunion [(_, Tdynamic); ty]
299 | Toption ty -> err_if_not_fun ty
300 | _ ->
301 Errors.invalid_type_for_atmost_rx_as_rxfunc_parameter
302 (Reason.to_pos (fst param_ty))
303 (Typing_print.full env param_ty) in
304 err_if_not_fun param_ty
307 (* generate a name that uniquely identifies pair target_type * condition_type *)
308 let generate_fresh_name_for_target_of_condition_type env target_type condition_type =
309 match condition_type with
310 | _, Tapply ((_, cond_name), _) ->
311 Some ((Typing_print.full env target_type) ^ "#" ^ cond_name)
312 | _, Taccess _ ->
313 Some ((Typing_print.full env target_type) ^ "#" ^ (Typing_print.full env condition_type))
314 | _ -> None
316 let try_substitute_type_with_condition env cond_ty ty =
317 generate_fresh_name_for_target_of_condition_type env ty cond_ty
318 |> Option.map ~f:begin fun fresh_type_argument_name ->
319 let param_ty =
320 (Reason.Rwitness (Reason.to_pos (fst ty))),
321 Tabstract ((AKgeneric fresh_type_argument_name), None) in
322 (* if generic type is already registered this means we already saw
323 parameter with the same pair (declared type * condition type) so there
324 is no need to add condition type to env again *)
325 if Env.is_generic_parameter env fresh_type_argument_name
326 then env, param_ty
327 else begin
328 let param_ty, ty =
329 match ty with
330 | _, Toption ty -> ((fst param_ty), Toption param_ty), ty
331 | _ -> param_ty, ty in
332 (* constraint type argument to hint *)
333 let env = Env.add_upper_bound_global env fresh_type_argument_name ty in
334 (* link type argument name to condition type *)
335 let env = Env.set_condition_type env fresh_type_argument_name cond_ty in
336 env, param_ty
340 (* for cases like
341 <<__OnlyRxIfImpl(Rx::class)>>
342 function f(): this::T {
343 if (Rx_ENABLED {
344 return get_rx();
346 else {
347 return get_cached_rx(); // returns this::T
350 return type of f will be represented as (<TFresh>#Rx) as this::T
351 so we can use name of fresh parameter to track condition type. This in turn will
352 lead to error in else branch of if statement because get_cached_rx will return this::T
353 and it is not assignable to fresh type parameter. To handle this for returns we reduce
354 return type to its upper bound if return type is TFresh and current context is non-reactive *)
355 let strip_condition_type_in_return env ty =
356 if Env.env_reactivity env <> Nonreactive then ty
357 else begin match ty with
358 | _, Tabstract ((AKgeneric n), _)
359 when Option.is_some (Env.get_condition_type env n) ->
360 let upper_bounds = Env.get_upper_bounds env n in
361 begin match Typing_set.elements upper_bounds with
362 | [ty] -> ty
363 | _ -> ty
365 | _ -> ty
367 let get_adjusted_return_type env receiver_info ret_ty =
368 match try_get_method_from_condition_type env receiver_info with
369 | None -> env, ret_ty
370 | Some cond_fty ->
371 try_substitute_type_with_condition env cond_fty.ft_ret.et_type ret_ty
372 |> Option.value ~default:(env, ret_ty)