Ban constructor parameter promotion on traits and interfaces
[hiphop-php.git] / hphp / hack / src / errors / errors_sig.ml
blob200c2b9441a7d3647d6e2df7bb8de6feafb63e35
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 module type S = sig
11 type 'a error_
12 type error = Pos.t error_
13 type applied_fixme = Pos.t * int
15 module type Error_category = sig
16 type t
17 val min : int
18 val max : int
19 val of_enum : int -> t option
20 val show : t -> string
21 val err_code : t -> int
22 end
24 (* The analysis phase that the error is coming from. *)
25 type phase = Init | Parsing | Naming | Decl | Typing
26 type severity = Warning | Error
28 module Parsing : Error_category
29 module Naming : Error_category
30 module NastCheck : Error_category
31 module Typing : Error_category
33 (* Error codes that can never be suppressed with a FIXME. *)
34 val default_ignored_fixme_codes : ISet.t
35 (* Error codes that cannot be suppressed with a FIXME based on configuration. *)
36 val ignored_fixme_codes : ISet.t ref
38 val set_allow_errors_in_default_path : bool -> unit
40 val is_hh_fixme : (Pos.t -> int -> bool) ref
41 val get_hh_fixme_pos : (Pos.t -> int -> Pos.t option) ref
42 val to_list : 'a error_ -> ('a * string) list
43 val get_code : 'a error_ -> int
44 val get_pos : error -> Pos.t
45 val get_severity : 'a error_ -> severity
46 val make_error : int -> (Pos.t * string) list -> error
48 val error_code_to_string : int -> string
50 val internal_error : Pos.t -> string -> unit
51 val unimplemented_feature : Pos.t -> string -> unit
52 val experimental_feature : Pos.t -> string -> unit
54 val fixme_format : Pos.t -> unit
55 val typeparam_alok : Pos.t * string -> unit
56 val unexpected_eof : Pos.t -> unit
57 val missing_field : Pos.t -> Pos.t -> string -> unit
58 val explain_constraint :
59 use_pos:Pos.t -> definition_pos:Pos.t -> param_name:string -> error -> unit
60 val explain_where_constraint :
61 use_pos:Pos.t -> definition_pos:Pos.t -> error -> unit
62 val explain_tconst_where_constraint :
63 use_pos:Pos.t -> definition_pos:Pos.t -> error -> unit
64 val explain_type_constant : (Pos.t * string) list -> error -> unit
65 val unexpected_arrow : Pos.t -> string -> unit
66 val missing_arrow : Pos.t -> string -> unit
67 val disallowed_xhp_type : Pos.t -> string -> unit
68 val overflow : Pos.t -> unit
69 val unterminated_comment : Pos.t -> unit
70 val unterminated_xhp_comment : Pos.t -> unit
71 val name_already_bound : string -> Pos.t -> Pos.t -> unit
72 val name_is_reserved : string -> Pos.t -> unit
73 val dollardollar_unused : Pos.t -> unit
74 val assigning_to_const : Pos.t -> unit
75 val self_const_parent_not : Pos.t -> unit
76 val parent_const_self_not : Pos.t -> unit
77 val overriding_prop_const_mismatch : Pos.t -> bool -> Pos.t -> bool -> unit
78 val method_name_already_bound : Pos.t -> string -> unit
79 val error_name_already_bound : string -> string -> Pos.t -> Pos.t -> unit
80 val error_class_attribute_already_bound : string -> string -> Pos.t -> Pos.t -> unit
81 val unbound_name : Pos.t -> string -> [< `cls | `func | `const ] -> unit
82 val different_scope : Pos.t -> string -> Pos.t -> unit
83 val undefined : Pos.t -> string -> unit
84 val this_reserved : Pos.t -> unit
85 val start_with_T : Pos.t -> unit
86 val already_bound : Pos.t -> string -> unit
87 val unexpected_typedef : Pos.t -> Pos.t -> unit
88 val fd_name_already_bound : Pos.t -> unit
89 val primitive_toplevel : Pos.t -> unit
90 val primitive_invalid_alias : Pos.t -> string -> string -> unit
91 val dynamic_new_in_strict_mode : Pos.t -> unit
92 val xhp_optional_required_attr : Pos.t -> string -> unit
93 val xhp_required_with_default : Pos.t -> string -> unit
94 val variable_variables_disallowed : Pos.t -> unit
95 val array_typehints_disallowed : Pos.t -> unit
96 val array_literals_disallowed : Pos.t -> unit
97 val wildcard_disallowed : Pos.t -> unit
98 val void_cast: Pos.t -> unit
99 val object_cast: Pos.t -> string -> unit
100 val unset_cast: Pos.t -> unit
101 val this_no_argument : Pos.t -> unit
102 val this_hint_outside_class : Pos.t -> unit
103 val this_type_forbidden : Pos.t -> unit
104 val lowercase_this : Pos.t -> string -> unit
105 val classname_param : Pos.t -> unit
106 val invalid_instanceof : Pos.t -> unit
107 val tparam_with_tparam : Pos.t -> string -> unit
108 val shadowed_type_param : Pos.t -> Pos.t -> string -> unit
109 val missing_typehint : Pos.t -> unit
110 val expected_variable : Pos.t -> unit
111 val clone_too_many_arguments : Pos.t -> unit
112 val naming_too_few_arguments : Pos.t -> unit
113 val naming_too_many_arguments : Pos.t -> unit
114 val expected_collection : Pos.t -> string -> unit
115 val illegal_CLASS : Pos.t -> unit
116 val illegal_TRAIT : Pos.t -> unit
117 val dynamic_method_call : Pos.t -> unit
118 val nullsafe_property_write_context : Pos.t -> unit
119 val illegal_fun : Pos.t -> unit
120 val illegal_member_variable_class : Pos.t -> unit
121 val illegal_meth_fun : Pos.t -> unit
122 val illegal_inst_meth : Pos.t -> unit
123 val illegal_meth_caller : Pos.t -> unit
124 val illegal_class_meth : Pos.t -> unit
125 val assert_arity : Pos.t -> unit
126 val gena_arity : Pos.t -> unit
127 val genva_arity : Pos.t -> unit
128 val gen_array_rec_arity : Pos.t -> unit
129 val uninstantiable_class : Pos.t -> Pos.t -> string -> (Pos.t * string) list
130 -> unit
131 val abstract_const_usage: Pos.t -> Pos.t -> string -> unit
132 val add_a_typehint : Pos.t -> unit
133 val local_const : Pos.t -> unit
134 val illegal_constant : Pos.t -> unit
135 val parsing_error : Pos.t * string -> unit
136 val format_string :
137 Pos.t -> string -> string -> Pos.t -> string -> string -> unit
138 val expected_literal_format_string : Pos.t -> unit
139 val re_prefixed_non_string : Pos.t -> string -> unit
140 val bad_regex_pattern : Pos.t -> string -> unit
141 val generic_array_strict : Pos.t -> unit
142 val strict_members_not_known : Pos.t -> string -> unit
143 val option_return_only_typehint : Pos.t -> [< `void | `noreturn ] -> unit
144 val tuple_syntax : Pos.t -> unit
145 val class_arity : Pos.t -> Pos.t -> string -> int -> unit
146 val expecting_type_hint : Pos.t -> unit
147 val expecting_type_hint_suggest : Pos.t -> string -> unit
148 val expecting_return_type_hint : Pos.t -> unit
149 val expecting_return_type_hint_suggest : Pos.t -> string -> unit
150 val expecting_awaitable_return_type_hint : Pos.t -> unit
151 val field_kinds : Pos.t -> Pos.t -> unit
152 val unbound_name_typing : Pos.t -> string -> unit
153 val did_you_mean_naming : Pos.t -> string -> Pos.t -> string -> unit
154 val previous_default : Pos.t -> unit
155 val return_only_typehint : Pos.t -> [< `void | `noreturn ] -> unit
156 val unexpected_type_arguments : Pos.t -> unit
157 val too_many_type_arguments : Pos.t -> unit
158 val return_in_void : Pos.t -> Pos.t -> unit
159 val this_in_static : Pos.t -> unit
160 val this_var_outside_class : Pos.t -> unit
161 val unbound_global : Pos.t -> unit
162 val private_inst_meth : Pos.t -> Pos.t -> unit
163 val protected_inst_meth : Pos.t -> Pos.t -> unit
164 val private_class_meth : Pos.t -> Pos.t -> unit
165 val protected_class_meth : Pos.t -> Pos.t -> unit
166 val array_cast : Pos.t -> unit
167 val anonymous_recursive : Pos.t -> unit
168 val static_outside_class : Pos.t -> unit
169 val self_outside_class : Pos.t -> unit
170 val new_inconsistent_construct : Pos.t -> (Pos.t * string)
171 -> [< `static | `classname ] -> unit
172 val pair_arity : Pos.t -> unit
173 val tuple_arity : Pos.t -> int -> Pos.t -> int -> unit
174 val undefined_parent : Pos.t -> unit
175 val parent_outside_class : Pos.t -> unit
176 val parent_abstract_call : string -> Pos.t -> Pos.t -> unit
177 val self_abstract_call : string -> Pos.t -> Pos.t -> unit
178 val classname_abstract_call : string -> string -> Pos.t -> Pos.t -> unit
179 val static_synthetic_method : string -> string -> Pos.t -> Pos.t -> unit
180 val empty_in_strict : Pos.t -> unit
181 val isset_in_strict : Pos.t -> unit
182 val unset_nonidx_in_strict : Pos.t -> (Pos.t * string) list -> unit
183 val unset_nonidx_in_strict_no_varray : Pos.t -> (Pos.t * string) list -> unit
184 val unpacking_disallowed_builtin_function : Pos.t -> string -> unit
185 val array_get_arity : Pos.t -> string -> Pos.t -> unit
186 val typing_error : Pos.t -> string -> unit
187 val typing_error_l : error -> unit
188 val undefined_field :
189 use_pos: Pos.t -> name: string -> shape_type_pos: Pos.t -> unit
190 val array_access : Pos.t -> Pos.t -> string -> unit
191 val keyset_set : Pos.t -> Pos.t -> unit
192 val array_append : Pos.t -> Pos.t -> string -> unit
193 val const_mutation : Pos.t -> Pos.t -> string -> unit
194 val expected_class : ?suffix:string -> Pos.t -> unit
195 val smember_not_found :
196 [< `class_constant | `class_variable | `static_method | `class_typeconst] ->
197 Pos.t ->
198 Pos.t * string ->
199 string ->
200 [< `closest of Pos.t * string
201 | `did_you_mean of Pos.t * string
202 | `no_hint ] ->
203 unit
204 val not_found_hint :
205 [< `closest of 'a * string | `did_you_mean of 'a * string | `no_hint ] ->
206 ('a * string) list
207 val member_not_found :
208 [< `member | `method_ ] ->
209 Pos.t ->
210 Pos.t * string ->
211 string ->
212 [< `closest of Pos.t * string
213 | `did_you_mean of Pos.t * string
214 | `no_hint ] ->
215 (Pos.t * string) list ->
216 unit
217 val parent_in_trait : Pos.t -> unit
218 val parent_undefined : Pos.t -> unit
219 val constructor_no_args : Pos.t -> unit
220 val visibility : Pos.t -> string -> Pos.t -> string -> unit
221 val typing_too_many_args : Pos.t -> Pos.t -> unit
222 val typing_too_few_args : Pos.t -> Pos.t -> unit
223 val anonymous_recursive_call : Pos.t -> unit
224 val bad_call : Pos.t -> string -> unit
225 val sketchy_null_check : Pos.t -> string option -> [< `Coalesce | `Eq | `Neq ] -> unit
226 val sketchy_null_check_primitive : Pos.t -> string option -> [< `Coalesce | `Eq | `Neq ] -> unit
227 val extend_final : Pos.t -> Pos.t -> string -> unit
228 val extend_sealed : Pos.t -> Pos.t -> string -> string -> string -> unit
229 val trait_implement_sealed : Pos.t -> Pos.t -> string -> unit
230 val extend_ppl : Pos.t -> string -> bool -> Pos.t -> string -> string -> string -> unit
231 val sealed_final : Pos.t -> string -> unit
232 val unsealable : Pos.t -> string -> unit
233 val read_before_write : Pos.t * string -> unit
234 val interface_final : Pos.t -> unit
235 val trait_final : Pos.t -> unit
236 val implement_abstract :
237 is_final:bool -> Pos.t -> Pos.t -> string -> string -> unit
238 val generic_static : Pos.t -> string -> unit
239 val fun_too_many_args : Pos.t -> Pos.t -> unit
240 val fun_too_few_args : Pos.t -> Pos.t -> unit
241 val fun_unexpected_nonvariadic : Pos.t -> Pos.t -> unit
242 val fun_variadicity_hh_vs_php56 : Pos.t -> Pos.t -> unit
243 val expected_tparam : Pos.t -> int -> unit
244 val object_string : Pos.t -> Pos.t -> unit
245 val type_param_arity : Pos.t -> string -> string -> unit
246 val cyclic_typedef : Pos.t -> unit
247 val type_arity_mismatch : Pos.t -> string -> Pos.t -> string -> unit
248 val this_final : Pos.t * string -> Pos.t -> error -> unit
249 val exact_class_final : Pos.t * string -> Pos.t -> error -> unit
250 val tuple_arity_mismatch : Pos.t -> string -> Pos.t -> string -> unit
251 val fun_arity_mismatch : Pos.t -> Pos.t -> unit
252 val discarded_awaitable : Pos.t -> Pos.t -> unit
253 val gena_expects_array : Pos.t -> Pos.t -> string -> unit
254 val unify_error : (Pos.t * string) list -> (Pos.t * string) list -> unit
255 val static_dynamic : Pos.t -> Pos.t -> string -> unit
256 val null_member : string -> Pos.t -> (Pos.t * string) list -> unit
257 val non_object_member : string -> Pos.t -> string -> Pos.t -> unit
258 val non_class_member : string -> Pos.t -> string -> Pos.t -> unit
259 val ambiguous_member : string -> Pos.t -> string -> Pos.t -> unit
260 val null_container : Pos.t -> (Pos.t * string) list -> unit
261 val option_mixed : Pos.t -> unit
262 val option_void : Pos.t -> unit
263 val declared_covariant : Pos.t -> Pos.t -> (Pos.t * string) list -> unit
264 val declared_contravariant : Pos.t -> Pos.t -> (Pos.t * string) list -> unit
265 val static_property_type_generic_param :
266 class_pos:Pos.t -> var_type_pos:Pos.t -> generic_pos:Pos.t -> unit
267 val contravariant_this: Pos.t -> string -> string -> unit
268 val wrong_extend_kind : Pos.t -> string -> Pos.t -> string -> unit
269 val unsatisfied_req : Pos.t -> string -> Pos.t -> unit
270 val cyclic_class_def : SSet.t -> Pos.t -> unit
271 val trait_reuse : (Pos.t) -> string -> (Pos.t * string) -> string -> unit
272 val invalid_is_as_expression_hint : string -> Pos.t -> Pos.t -> string -> unit
273 val partially_valid_is_as_expression_hint :
274 string -> Pos.t -> Pos.t -> string -> unit
275 val override_final : parent:Pos.t -> child:Pos.t -> unit
276 val override_memoizelsb : parent:Pos.t -> child:Pos.t -> unit
277 val should_be_override : Pos.t -> string -> string -> unit
278 val override_per_trait : Pos.t * string -> string -> Pos.t -> unit
279 val missing_assign : Pos.t -> unit
280 val private_override : Pos.t -> string -> string -> unit
281 val invalid_memoized_param : Pos.t -> (Pos.t * string) list -> unit
282 val no_construct_parent : Pos.t -> unit
283 val constructor_required : Pos.t * string -> SSet.t -> unit
284 val not_initialized : Pos.t * string -> string list -> unit
285 val call_before_init : Pos.t -> string -> unit
286 val type_arity : Pos.t -> string -> string -> unit
287 val invalid_req_implements : Pos.t -> unit
288 val invalid_req_extends : Pos.t -> unit
289 val abstract_with_body : Pos.t * 'a -> unit
290 val not_abstract_without_body : Pos.t * 'a -> unit
291 val return_in_gen : Pos.t -> unit
292 val return_in_finally : Pos.t -> unit
293 val toplevel_break: Pos.t -> unit
294 val toplevel_continue: Pos.t -> unit
295 val continue_in_switch: Pos.t -> unit
296 val await_in_sync_function : Pos.t -> unit
297 val await_not_allowed : Pos.t -> unit
298 val async_in_interface : Pos.t -> unit
299 val await_in_coroutine : Pos.t -> unit
300 val yield_in_coroutine : Pos.t -> unit
301 val suspend_outside_of_coroutine : Pos.t -> unit
302 val suspend_in_finally : Pos.t -> unit
303 val break_continue_n_not_supported : Pos.t -> unit
304 val static_memoized_function : Pos.t -> unit
305 val magic : Pos.t * string -> unit
306 val non_interface : Pos.t -> string -> string -> unit
307 val toString_returns_string : Pos.t -> unit
308 val toString_visibility : Pos.t -> unit
309 val uses_non_trait : Pos.t -> string -> string -> unit
310 val requires_non_class : Pos.t -> string -> string -> unit
311 val requires_final_class : Pos.t -> string -> unit
312 val abstract_body : Pos.t -> unit
313 val not_public_or_protected_interface : Pos.t -> unit
314 val interface_with_member_variable : Pos.t -> unit
315 val interface_with_static_member_variable : Pos.t -> unit
316 val dangerous_method_name : Pos.t -> unit
317 val illegal_function_name : Pos.t -> string -> unit
318 val case_fallthrough : Pos.t -> Pos.t -> unit
319 val default_fallthrough : Pos.t -> unit
320 val visibility_extends : string -> Pos.t -> Pos.t -> string -> unit
321 val member_not_implemented : string -> Pos.t -> Pos.t -> Pos.t -> unit
322 val bad_decl_override : Pos.t -> string -> Pos.t -> string -> error -> unit
323 val bad_method_override : Pos.t -> string -> error -> unit
324 val bad_enum_decl : Pos.t -> error -> unit
325 val missing_constructor : Pos.t -> unit
326 val enum_constant_type_bad : Pos.t -> Pos.t -> string -> Pos.t list -> unit
327 val enum_type_bad : Pos.t -> string -> Pos.t list -> unit
328 val enum_type_typedef_mixed : Pos.t -> unit
329 val enum_type_typedef_nonnull : Pos.t -> unit
330 val enum_switch_redundant : string -> Pos.t -> Pos.t -> unit
331 val enum_switch_nonexhaustive : Pos.t -> string list -> Pos.t -> unit
332 val enum_switch_redundant_default : Pos.t -> Pos.t -> unit
333 val enum_switch_not_const : Pos.t -> unit
334 val enum_switch_wrong_class : Pos.t -> string -> string -> unit
335 val invalid_shape_field_name : Pos.t -> unit
336 val invalid_shape_field_name_empty : Pos.t -> unit
337 val invalid_shape_field_name_number : Pos.t -> unit
338 val invalid_shape_field_type : Pos.t -> Pos.t -> string -> Pos.t list -> unit
339 val invalid_shape_field_literal : Pos.t -> Pos.t -> unit
340 val invalid_shape_field_const : Pos.t -> Pos.t -> unit
341 val shape_field_class_mismatch : Pos.t -> Pos.t -> string -> string -> unit
342 val shape_field_type_mismatch : Pos.t -> Pos.t -> string -> string -> unit
343 val shape_fields_unknown: Pos.t -> Pos.t -> unit
344 val invalid_shape_remove_key : Pos.t -> unit
345 val shape_field_unset : Pos.t -> Pos.t -> string -> unit
346 val using_internal_class : Pos.t -> string -> unit
347 val nullsafe_not_needed : Pos.t -> (Pos.t * string) list -> unit
348 val trivial_strict_eq : Pos.t -> string -> (Pos.t * string) list
349 -> (Pos.t * string) list -> Pos.t list -> Pos.t list -> unit
350 val trivial_strict_not_nullable_compare_null : Pos.t -> string
351 -> (Pos.t * string) list -> unit
352 val void_usage : Pos.t -> (Pos.t * string) list -> unit
353 val noreturn_usage : Pos.t -> (Pos.t * string) list -> unit
354 val generic_at_runtime : Pos.t -> unit
355 val interface_with_partial_typeconst : Pos.t -> unit
356 val multiple_xhp_category : Pos.t -> unit
357 val not_abstract_without_typeconst : (Pos.t * string) -> unit
358 val typeconst_depends_on_external_tparam : Pos.t -> Pos.t -> string -> unit
359 val typeconst_assigned_tparam : Pos.t -> string -> unit
360 val invalid_type_access_root : (Pos.t * string) -> unit
361 val duplicate_user_attribute : (Pos.t * string) -> Pos.t -> unit
362 val unbound_attribute_name : Pos.t -> string -> unit
363 val attribute_too_many_arguments : Pos.t -> string -> int -> unit
364 val attribute_too_few_arguments : Pos.t -> string -> int -> unit
365 val attribute_param_type : Pos.t -> string -> unit
366 val deprecated_use : Pos.t -> Pos.t -> string -> unit
367 val abstract_with_typeconst : (Pos.t * string) -> unit
368 val cannot_declare_constant:
369 [< `enum | `trait] -> Pos.t -> (Pos.t * string) -> unit
370 val ambiguous_inheritance: Pos.t -> string -> string -> error -> unit
371 val cyclic_typeconst : Pos.t -> string list -> unit
372 val explain_contravariance : Pos.t -> string -> error -> unit
373 val explain_invariance : Pos.t -> string -> string -> error -> unit
374 val this_lvalue : Pos.t -> unit
375 val abstract_concrete_override:
376 Pos.t -> Pos.t -> [< `method_ | `typeconst |`constant]-> unit
377 val local_variable_modified_and_used : Pos.t -> Pos.t list -> unit
378 val local_variable_modified_twice : Pos.t -> Pos.t list -> unit
379 val assign_during_case : Pos.t -> unit
380 val cyclic_enum_constraint : Pos.t -> unit
381 val invalid_classname : Pos.t -> unit
382 val illegal_type_structure : Pos.t -> string -> unit
383 val illegal_typeconst_direct_access : Pos.t -> unit
384 val class_property_only_static_literal : Pos.t -> unit
385 val reference_expr : Pos.t -> unit
386 val unification_cycle : Pos.t -> string -> unit
387 val eq_incompatible_types : Pos.t -> (Pos.t * string) list
388 -> (Pos.t * string) list -> unit
389 val comparison_invalid_types : Pos.t -> (Pos.t * string) list
390 -> (Pos.t * string) list -> unit
391 val instanceof_generic_classname : Pos.t -> string -> unit
392 val final_property : Pos.t -> unit
393 val pass_by_ref_annotation_missing : Pos.t -> Pos.t -> unit
394 val reffiness_invariant : Pos.t -> Pos.t -> [< `normal | `inout ] -> unit
395 val pass_by_ref_annotation_unexpected : Pos.t -> Pos.t -> bool -> unit
396 val invalid_new_disposable : Pos.t -> unit
397 val invalid_disposable_hint : Pos.t -> string -> unit
398 val invalid_disposable_return_hint : Pos.t -> string -> unit
399 val invalid_return_disposable : Pos.t -> unit
400 val unsupported_feature : Pos.t -> string -> unit
401 val invalid_switch_case_value_type : Pos.t -> string -> string -> unit
402 val to_json : Pos.absolute error_ -> Hh_json.json
403 val to_string : ?indent:bool -> Pos.absolute error_ -> string
404 val try_ : (unit -> 'a) -> (error -> 'a) -> 'a
405 val try_with_error : (unit -> 'a) -> (unit -> 'a) -> 'a
406 val try_add_err : Pos.t -> string -> (unit -> 'a) -> (unit -> 'a) -> 'a
408 (* The type of collections of errors *)
409 type t
411 val do_ : (unit -> 'a) -> t * 'a
412 val do_with_context :
413 Relative_path.t -> phase -> (unit -> 'a) -> t * 'a
415 val run_in_context : Relative_path.t -> phase -> (unit -> 'a) -> 'a
416 val run_in_decl_mode : Relative_path.t -> (unit -> 'a) -> 'a
417 val ignore_ : (unit -> 'a) -> 'a
418 val try_when :
419 (unit -> 'a) -> when_:(unit -> bool) -> do_:(error -> unit) -> 'a
420 val has_no_errors : (unit -> 'a) -> bool
421 val currently_has_errors : unit -> bool
422 val must_error : (unit -> unit) -> (unit -> unit) -> unit
423 val to_absolute : error -> Pos.absolute error_
425 val merge : t -> t -> t
426 val merge_into_current : t -> unit
428 val incremental_update_set:
429 old:t -> new_:t -> rechecked:Relative_path.Set.t -> phase -> t
430 val incremental_update_map:
431 old:t -> new_:t -> rechecked:'a Relative_path.Map.t -> phase -> t
433 val empty : t
434 val is_empty : t -> bool
435 val count : t -> int
436 val get_error_list : t -> error list
437 val get_sorted_error_list : t -> error list
438 val from_error_list : error list -> t
439 val iter_error_list : (error -> unit) -> t -> unit
440 val fold_errors :
441 ?phase:phase ->
442 t ->
443 init:'a ->
444 f:(Relative_path.t -> error -> 'a -> 'a) ->
446 val fold_errors_in :
447 ?phase:phase ->
448 t ->
449 source:Relative_path.t ->
450 init:'a ->
451 f:(error -> 'a -> 'a) ->
453 val get_failed_files : t -> phase -> Relative_path.Set.t
454 val sort : error list -> error list
455 val get_applied_fixmes : t -> applied_fixme list
456 val darray_not_supported : Pos.t -> unit
457 val varray_not_supported : Pos.t -> unit
458 val nonnull_not_supported : Pos.t -> unit
459 val too_few_type_arguments : Pos.t -> unit
460 val required_field_is_optional : Pos.t -> Pos.t -> string -> unit
461 val array_get_with_optional_field : Pos.t -> Pos.t -> string -> unit
462 val goto_label_already_defined : string -> Pos.t -> Pos.t -> unit
463 val goto_label_undefined : Pos.t -> string -> unit
464 val goto_label_defined_in_finally : Pos.t -> unit
465 val goto_invoked_in_finally : Pos.t -> unit
466 val method_needs_visibility : Pos.t -> unit
467 val dynamic_class_property_name_in_strict_mode : Pos.t -> unit
468 val dynamic_class_name_in_strict_mode : Pos.t -> unit
469 val reading_from_append: Pos.t -> unit
470 val const_attribute_prohibited: Pos.t -> string -> unit
471 val varray_or_darray_not_supported : Pos.t -> unit
472 val unknown_field_disallowed_in_shape : Pos.t -> Pos.t -> string -> unit
473 val nullable_cast : Pos.t -> string -> Pos.t -> unit
474 val non_call_argument_in_suspend : Pos.t -> (Pos.t * string) list -> unit
475 val non_coroutine_call_in_suspend : Pos.t -> (Pos.t * string) list -> unit
476 val coroutine_call_outside_of_suspend : Pos.t -> unit
477 val function_is_not_coroutine : Pos.t -> string -> unit
478 val coroutinness_mismatch : bool -> Pos.t -> Pos.t -> unit
479 val invalid_ppl_call : Pos.t -> string -> unit
480 val invalid_ppl_static_call : Pos.t -> string -> unit
481 val ppl_meth_pointer : Pos.t -> string -> unit
482 val coroutine_outside_experimental : Pos.t -> unit
483 val return_disposable_mismatch : bool -> Pos.t -> Pos.t -> unit
484 val fun_reactivity_mismatch : Pos.t -> string -> Pos.t -> string -> unit
485 val frozen_in_incorrect_scope : Pos.t -> unit
486 val reassign_mutable_var : Pos.t -> unit
487 val mutable_call_on_immutable : Pos.t -> Pos.t -> unit
488 val mutable_argument_mismatch : Pos.t -> Pos.t -> unit
489 val invalid_mutable_return_result: Pos.t -> Pos.t -> string -> unit
490 val mutable_return_result_mismatch: bool -> Pos.t -> Pos.t -> unit
491 val mutable_params_outside_of_sync : Pos.t -> Pos.t -> string -> string -> unit
492 val mutable_async_method : Pos.t -> unit
493 val mutable_attribute_on_function : Pos.t -> unit
494 val mutable_methods_must_be_reactive : Pos.t -> string -> unit
495 val mutable_return_annotated_decls_must_be_reactive : string -> Pos.t -> string -> unit
496 val invalid_freeze_target : Pos.t -> Pos.t -> string -> unit
497 val invalid_freeze_use : Pos.t -> unit
498 val freeze_in_nonreactive_context : Pos.t -> unit
499 val this_as_lexical_variable : Pos.t -> unit
500 val dollardollar_lvalue : Pos.t -> unit
501 val duplicate_using_var : Pos.t -> unit
502 val illegal_disposable : Pos.t -> string -> unit
503 val escaping_disposable : Pos.t -> unit
504 val escaping_disposable_parameter : Pos.t -> unit
505 val escaping_this : Pos.t -> unit
506 val must_extend_disposable : Pos.t -> unit
507 val accept_disposable_invariant : Pos.t -> Pos.t -> unit
508 val inout_params_outside_of_sync : Pos.t -> unit
509 val inout_params_special : Pos.t -> unit
510 val inout_params_mix_byref : Pos.t -> Pos.t -> unit
511 val inout_params_memoize : Pos.t -> Pos.t -> unit
512 val obj_set_reactive : Pos.t -> unit
513 val global_in_reactive_context : Pos.t -> string -> unit
514 val static_property_in_reactive_context : Pos.t -> unit
515 val inout_annotation_missing : Pos.t -> Pos.t -> unit
516 val inout_annotation_unexpected : Pos.t -> Pos.t -> bool -> unit
517 val inoutness_mismatch : Pos.t -> Pos.t -> unit
518 val inout_params_ret_by_ref : Pos.t -> Pos.t -> unit
519 val xhp_required : Pos.t -> string -> (Pos.t * string) list -> unit
520 val illegal_xhp_child : Pos.t -> (Pos.t * string) list -> unit
521 val nonreactive_function_call : Pos.t -> Pos.t -> string -> Pos.t option -> unit
522 val nonreactive_append : Pos.t -> unit
523 val inout_argument_bad_expr : Pos.t -> unit
524 val inout_argument_bad_type : Pos.t -> (Pos.t * string) list -> unit
525 val nonreactive_call_from_shallow : Pos.t -> Pos.t -> string -> Pos.t option -> unit
526 val illegal_destructor : Pos.t -> unit
527 val rx_enabled_in_non_rx_context : Pos.t -> unit
528 val rx_enabled_in_lambdas : Pos.t -> unit
529 val ambiguous_lambda : Pos.t -> (Pos.t * string) list -> unit
530 val ellipsis_strict_mode :
531 require:[< `Param_name | `Type | `Type_and_param_name ] -> Pos.t -> unit
532 val untyped_lambda_strict_mode : Pos.t -> unit
533 val binding_ref_in_array : Pos.t -> unit
534 val return_ref_in_array : Pos.t -> unit
535 val passing_array_cell_by_ref : Pos.t -> unit
536 val conditionally_reactive_function : Pos.t -> unit
537 val multiple_conditionally_reactive_annotations : Pos.t -> string -> unit
538 val conditionally_reactive_annotation_invalid_arguments : is_method:bool -> Pos.t -> unit
539 val echo_in_reactive_context : Pos.t -> unit
540 val superglobal_in_reactive_context : Pos.t -> string -> unit
541 val static_in_reactive_context : Pos.t -> string -> unit
542 val missing_reactivity_for_condition: Pos.t -> unit
543 val multiple_reactivity_annotations: Pos.t -> unit
544 val rx_is_enabled_invalid_location: Pos.t -> unit
545 val wrong_expression_kind_attribute: string -> Pos.t -> string -> Pos.t -> string -> string -> unit
546 val attribute_class_no_constructor_args: Pos.t -> Pos.t -> unit
547 val cannot_return_borrowed_value_as_immutable: Pos.t -> Pos.t -> unit
548 val decl_override_missing_hint: Pos.t -> unit
549 val let_var_immutability_violation : Pos.t -> string -> unit
550 val atmost_rx_as_rxfunc_invalid_location: Pos.t -> unit
551 val no_atmost_rx_as_rxfunc_for_rx_if_args: Pos.t -> unit
552 val coroutine_in_constructor: Pos.t -> unit
553 val illegal_return_by_ref: Pos.t -> unit
554 val illegal_by_ref_expr: Pos.t -> string -> unit
555 val variadic_byref_param: Pos.t -> unit
556 val reference_in_strict_mode: Pos.t -> unit
557 val invalid_type_for_atmost_rx_as_rxfunc_parameter: Pos.t -> string -> unit
558 val missing_annotation_for_atmost_rx_as_rxfunc_parameter: Pos.t -> unit
559 val mutable_in_nonreactive_context: Pos.t -> unit
560 val invalid_argument_of_rx_mutable_function: Pos.t -> unit
561 val return_void_to_rx_mismatch: pos1_has_attribute:bool -> Pos.t -> Pos.t -> unit
562 val returns_void_to_rx_function_as_non_expression_statement: Pos.t -> Pos.t -> unit
563 val non_awaited_awaitable_in_rx: Pos.t -> unit
564 val shapes_key_exists_always_true: Pos.t -> string -> Pos.t -> unit
565 val shapes_key_exists_always_false: Pos.t -> string -> Pos.t -> [< `Undefined | `Unset] -> unit
566 val shapes_idx_with_non_existent_field: Pos.t -> string -> Pos.t -> [< `Undefined | `Unset] -> unit
567 val ambiguous_object_access: Pos.t -> string -> Pos.t -> string -> Pos.t -> string -> string -> unit
568 val forward_compatibility_not_current: Pos.t -> ForwardCompatibilityLevel.t -> unit
569 val forward_compatibility_below_minimum: Pos.t -> ForwardCompatibilityLevel.t -> unit
570 val invalid_argument_type_for_condition_in_rx:
571 is_receiver: bool -> Pos.t -> Pos.t -> Pos.t -> string -> string -> unit
572 val invalid_function_type_for_condition_in_rx:
573 Pos.t -> Pos.t -> Pos.t -> string -> string -> unit
574 val callsite_reactivity_mismatch: Pos.t -> Pos.t -> string -> Pos.t option -> string -> unit
575 val rx_parameter_condition_mismatch: string -> Pos.t -> Pos.t -> unit
576 val maybe_mutable_attribute_on_function: Pos.t -> unit
577 val conflicting_mutable_and_maybe_mutable_attributes: Pos.t -> unit
578 val maybe_mutable_methods_must_be_reactive: Pos.t -> string -> unit
579 val reassign_maybe_mutable_var: Pos.t -> unit
580 val immutable_argument_mismatch : Pos.t -> Pos.t -> unit
581 val maybe_mutable_argument_mismatch : Pos.t -> Pos.t -> unit
582 val immutable_call_on_mutable: Pos.t -> Pos.t -> unit
583 val invalid_call_on_maybe_mutable: fun_is_mutable:bool -> Pos.t -> Pos.t -> unit
584 val mutability_mismatch: is_receiver: bool -> Pos.t -> string -> Pos.t -> string -> unit
585 val invalid_traversable_in_rx: Pos.t -> unit
586 val reference_in_rx: Pos.t -> unit
587 val reassign_mutable_this: Pos.t -> unit
588 val mutable_expression_as_multiple_mutable_arguments: Pos.t -> string -> Pos.t -> string -> unit
589 val invalid_unset_target_rx: Pos.t -> unit
590 val declare_statement_in_hack : Pos.t -> unit
591 val misplaced_rx_of_scope: Pos.t -> unit
592 val rx_of_scope_and_explicit_rx: Pos.t -> unit
593 val lateinit_with_default: Pos.t -> unit
594 val interface_use_trait: Pos.t -> unit
595 val nonstatic_method_in_abstract_final_class: Pos.t -> unit
596 val mutable_on_static: Pos.t -> unit
597 val trait_interface_constructor_promo: Pos.t -> unit