Introduce __ReturnsVoidToRx
[hiphop-php.git] / hphp / hack / src / typing / typing_reactivity.ml
blob0956f143c7bcd917073a9d46351d594fd4ff45ca
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 Typing_defs
12 module Phase = Typing_phase
13 module Env = Typing_env
14 module SubType = Typing_subtype
16 let type_to_str: type a. Env.env -> a ty -> string = fun env ty ->
17 (* strip expression dependent types to make error message clearer *)
18 let rec unwrap: type a. a ty -> a ty = function
19 | _, Tabstract (AKdependent (`static, []), Some ty) -> unwrap ty
20 | _, Tabstract (AKdependent (`this, []), Some ty) -> unwrap ty
21 | ty -> ty in
22 Typing_print.full env (unwrap ty)
24 let rec strip_maybe_reactive t =
25 match t with
26 | r, Tfun ({ ft_reactive = MaybeReactive reactive; _ } as ft) ->
27 r, Tfun { ft with ft_reactive = reactive }
28 | r, Toption ty -> r, Toption (strip_maybe_reactive ty)
29 | t -> t
30 let check_call env receiver_type pos reason ft arg_types =
31 let callee_reactivity =
32 (* if function we are about to call is maybe reactive with reactivity flavor R
33 - check its arguments: call to maybe reactive function is treated as reactive
34 if arguments that correspond to parameters marked with <<__OnlyRxIfRxFunc>> are functions
35 with reactivity <: R *)
36 let callee_has_rx_condition_parameters =
37 Core_list.exists ft.ft_params ~f:begin function
38 | { fp_rx_condition; _ } -> Option.is_some fp_rx_condition
39 end in
40 if not callee_has_rx_condition_parameters then ft.ft_reactive
41 else
42 let is_reactive =
43 match Core_list.zip ft.ft_params arg_types with
44 | None -> false
45 | Some l -> Core_list.for_all l ~f:(function
46 | { fp_rx_condition = None; _ }, _ -> true
47 | { fp_rx_condition = Some Param_rx_if_impl ty; _ }, arg_ty ->
48 let _, cond_ty = Phase.localize (Phase.env_with_self env) env ty in
49 SubType.is_sub_type env arg_ty cond_ty
50 | { fp_rx_condition = Some Param_rxfunc; fp_type; _ }, arg_ty ->
51 let param_type = strip_maybe_reactive fp_type in
52 let arg_ty = strip_maybe_reactive arg_ty in
53 SubType.is_sub_type env arg_ty param_type) in
54 if is_reactive then ft.ft_reactive else Nonreactive in
55 (* call is allowed if reactivity of callee is a subtype of reactivity of
56 enlosing environment *)
57 let allow_call =
58 let receiver_type = Option.map receiver_type (fun t -> LoclTy t) in
59 SubType.subtype_reactivity
60 ~extra_info: SubType.({ empty_extra_info with class_ty = receiver_type })
61 ~is_call_site:true
62 env
63 callee_reactivity
64 (Env.env_reactivity env) in
65 let allow_call =
66 if not allow_call && Env.is_checking_lambda () then begin
67 (* if we are inferring reactivity of lambda - now we know it is non-reactive *)
68 Env.not_lambda_reactive ();
69 true
70 end
71 else allow_call in
72 (* call is not allowed, report error *)
73 if not allow_call then begin
74 begin match Env.env_reactivity env, callee_reactivity with
75 | Reactive _, (Shallow _ | Local _ | Nonreactive) ->
76 Errors.nonreactive_function_call pos (Reason.to_pos reason)
77 | Shallow _, Nonreactive ->
78 Errors.nonreactive_call_from_shallow pos (Reason.to_pos reason)
79 | Reactive _, Reactive (Some t)
80 | Shallow _, (Reactive (Some t) | Shallow (Some t) | Local (Some t)) ->
81 let condition_type_str = type_to_str env t in
82 let receiver_type_str =
83 Option.value_map receiver_type ~default:"" ~f:(type_to_str env) in
84 Errors.invalid_conditionally_reactive_call pos (Reason.to_pos reason)
85 condition_type_str
86 receiver_type_str;
87 | _ -> ()
88 end
89 end
91 let rec get_name = function
92 (* name *)
93 | _, Nast.Lvar (_, id) -> Local_id.to_string id
94 (* name = initializer *)
95 | _, Nast.Binop (_, lhs, _) -> get_name lhs
96 | _ -> "_"
98 let disallow_static_or_global_in_reactive_context ~is_static env el =
99 Env.error_if_reactive_context env @@ begin fun () ->
100 (Core_list.hd el) |> Option.iter ~f:(fun n ->
101 let p = fst n in
102 let name = get_name n in
103 if is_static then Errors.static_in_reactive_context p name
104 else Errors.global_in_reactive_context p name)
107 let disallow_onlyrx_if_rxfunc_on_non_functions env param param_ty =
108 let module UA = Naming_special_names.UserAttributes in
109 if Attributes.mem UA.uaOnlyRxIfRxFunc param.Nast.param_user_attributes
110 then begin
111 if param.Nast.param_hint = None
112 then Errors.missing_annotation_for_onlyrx_if_rxfunc_parameter param.Nast.param_pos
113 else match Typing_utils.non_null env param_ty with
114 (* if parameter has <<__OnlyRxIfRxFunc>> annotation then:
115 - parameter should be typed as function *)
116 | _, (_, Tfun _) -> ()
117 | _ ->
118 Errors.invalid_type_for_onlyrx_if_rxfunc_parameter
119 (Reason.to_pos (fst param_ty))
120 (Typing_print.full env param_ty)
123 let verify_void_return_to_rx ~is_expr_statement p env ft =
124 if ft.ft_returns_void_to_rx && not is_expr_statement
125 then Env.error_if_reactive_context env @@ begin fun () ->
126 Errors.returns_void_to_rx_function_as_non_expression_statement p ft.ft_pos