parser ban by-ref on construct calls and definition
[hiphop-php.git] / hphp / hack / src / errors / errors.ml
blob29b1ce2d57b548e9744fe8f388d064c32f3dc138
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 Core_kernel
11 open Utils
12 open Reordered_argument_collections
13 open String_utils
15 type error_code = int
16 (* We use `Pos.t message` on the server and convert to `Pos.absolute message`
17 * before sending it to the client *)
18 type 'a message = 'a * string
20 type phase = Init | Parsing | Naming | Decl | Typing
21 type severity = Warning | Error
22 type format = Context | Raw
24 (* The file and phase of analysis being currently performed *)
25 let current_context : (Relative_path.t * phase) ref = ref (Relative_path.default, Typing)
27 let allow_errors_in_default_path = ref true
29 module PhaseMap = Reordered_argument_map(MyMap.Make(struct
30 type t = phase
32 let rank = function
33 | Init -> 0
34 | Parsing -> 1
35 | Naming -> 2
36 | Decl -> 3
37 | Typing -> 4
39 let compare x y = (rank x) - (rank y)
40 end))
42 (* Results of single file analysis. *)
43 type 'a file_t = 'a list PhaseMap.t
44 (* Results of multi-file analysis. *)
45 type 'a files_t = ('a file_t) Relative_path.Map.t
47 let files_t_fold v ~f ~init =
48 Relative_path.Map.fold v ~init ~f:begin fun path v acc ->
49 PhaseMap.fold v ~init:acc ~f:begin fun phase v acc ->
50 f path phase v acc
51 end
52 end
54 let files_t_map v ~f =
55 Relative_path.Map.map v ~f:begin fun v ->
56 PhaseMap.map v ~f
57 end
59 let files_t_merge ~f x y =
60 (* Using fold instead of merge to make the runtime proportional to the size
61 * of first argument (like List.rev_append ) *)
62 Relative_path.Map.fold x ~init:y ~f:begin fun k x acc ->
63 let y = Option.value (Relative_path.Map.get y k) ~default:PhaseMap.empty in
64 Relative_path.Map.add acc k (
65 PhaseMap.merge x y ~f:(fun phase x y -> f phase k x y)
67 end
69 let files_t_to_list x =
70 files_t_fold x ~f:(fun _ _ x acc -> List.rev_append x acc) ~init:[] |>
71 List.rev
73 let list_to_files_t = function
74 | [] -> Relative_path.Map.empty
75 | x ->
76 (* Values constructed here should not be used with incremental mode.
77 * See assert in incremental_update. *)
78 Relative_path.Map.singleton Relative_path.default
79 (PhaseMap.singleton Typing x)
81 let get_code_severity code =
82 if code = Error_codes.Init.err_code Error_codes.Init.ForwardCompatibilityNotCurrent
83 then Warning
84 else Error
86 (* Get most recently-ish added error. *)
87 let get_last error_map =
88 (* If this map has more than one element, we pick an arbitrary file. Because
89 * of that, we might not end up with the most recent error and generate a
90 * less-specific error message. This should be rare. *)
91 match Relative_path.Map.max_binding error_map with
92 | None -> None
93 | Some (_, phase_map) -> begin
94 let error_list = PhaseMap.max_binding phase_map
95 |> Option.value_map ~f:snd ~default:[]
97 match List.rev error_list with
98 | [] -> None
99 | e::_ -> Some e
102 type 'a error_ = error_code * 'a message list
103 type error = Pos.t error_
104 type applied_fixme = Pos.t * int
106 let applied_fixmes : applied_fixme files_t ref = ref Relative_path.Map.empty
108 let (error_map : error files_t ref) = ref Relative_path.Map.empty
110 let accumulate_errors = ref false
111 (* Some filename when declaring *)
112 let in_lazy_decl = ref None
114 let try_with_result f1 f2 =
115 let error_map_copy = !error_map in
116 let accumulate_errors_copy = !accumulate_errors in
117 error_map := Relative_path.Map.empty;
118 accumulate_errors := true;
119 let result, errors = Utils.try_finally
120 ~f:begin fun () ->
121 let result = f1 () in
122 result, !error_map
124 ~finally:begin fun () ->
125 error_map := error_map_copy;
126 accumulate_errors := accumulate_errors_copy;
129 match get_last errors with
130 | None -> result
131 | Some (code,l) ->
132 (* Remove bad position sentinel if present: we might be about to add a new primary
133 * error position*)
134 let l = match l with
135 | (_, msg) :: l when msg = Badpos_sentinel.message -> l
136 | _ -> l in
137 f2 result (code,l)
139 let do_ f =
140 let error_map_copy = !error_map in
141 let accumulate_errors_copy = !accumulate_errors in
142 let applied_fixmes_copy = !applied_fixmes in
143 error_map := Relative_path.Map.empty;
144 applied_fixmes := Relative_path.Map.empty;
145 accumulate_errors := true;
146 let result, out_errors, out_applied_fixmes = Utils.try_finally
147 ~f:begin fun () ->
148 let result = f () in
149 result, !error_map, !applied_fixmes
151 ~finally:begin fun () ->
152 error_map := error_map_copy;
153 applied_fixmes := applied_fixmes_copy;
154 accumulate_errors := accumulate_errors_copy;
157 let out_errors = files_t_map ~f:(List.rev) out_errors in
158 (out_errors, out_applied_fixmes), result
160 let run_in_context path phase f =
161 let context_copy = !current_context in
162 current_context := (path, phase);
163 Utils.try_finally ~f ~finally:begin fun () ->
164 current_context := context_copy;
167 (* Log important data if lazy_decl triggers a crash *)
168 let lazy_decl_error_logging error error_map to_absolute to_string =
169 let error_list = files_t_to_list !error_map in
170 (* Print the current error list, which should be empty *)
171 Printf.eprintf "%s" "Error list(should be empty):\n";
172 List.iter error_list ~f:(fun err ->
173 let msg = err |> to_absolute |> to_string in Printf.eprintf "%s\n" msg);
174 Printf.eprintf "%s" "Offending error:\n";
175 Printf.eprintf "%s" error;
177 (* Print out a larger stack trace *)
178 Printf.eprintf "%s" "Callstack:\n";
179 Printf.eprintf "%s" (Caml.Printexc.raw_backtrace_to_string
180 (Caml.Printexc.get_callstack 500));
181 (* Exit with special error code so we can see the log after *)
182 Exit_status.exit Exit_status.Lazy_decl_bug
184 (*****************************************************************************)
185 (* Error code printing. *)
186 (*****************************************************************************)
188 let error_kind error_code =
189 match error_code / 1000 with
190 | 1 -> "Parsing"
191 | 2 -> "Naming"
192 | 3 -> "NastCheck"
193 | 4 -> "Typing"
194 | 5 -> "Lint"
195 | 8 -> "Init"
196 | _ -> "Other"
198 let error_code_to_string error_code =
199 let error_kind = error_kind error_code in
200 let error_number = Printf.sprintf "%04d" error_code in
201 error_kind^"["^error_number^"]"
203 let phase_to_string (phase : phase) : string =
204 match phase with
205 | Init -> "Init"
206 | Parsing -> "Parsing"
207 | Naming -> "Naming"
208 | Decl -> "Decl"
209 | Typing -> "Typing"
211 let rec get_pos (error : error) = fst (List.hd_exn (snd error))
213 and sort err =
214 List.sort ~compare:begin fun x y ->
215 Pos.compare (get_pos x) (get_pos y)
216 end err
217 |> List.remove_consecutive_duplicates ~equal:(=)
219 and get_sorted_error_list (err,_) =
220 sort (files_t_to_list err)
222 (* Getters and setter for passed-in map, based on current context *)
223 let get_current_file_t file_t_map =
224 let current_file = fst !current_context in
225 Relative_path.Map.get file_t_map current_file |>
226 Option.value ~default:PhaseMap.empty
228 let get_current_list file_t_map =
229 let current_phase = snd !current_context in
230 get_current_file_t file_t_map |> fun x ->
231 PhaseMap.get x current_phase |>
232 Option.value ~default:[]
234 let set_current_list file_t_map new_list =
235 let current_file, current_phase = !current_context in
236 file_t_map := Relative_path.Map.add
237 !file_t_map
238 current_file
239 (PhaseMap.add
240 (get_current_file_t !file_t_map)
241 current_phase
242 new_list
245 let do_with_context path phase f = run_in_context path phase (fun () -> do_ f)
247 (* Turn on lazy decl mode for the duration of the closure.
248 This runs without returning the original state,
249 since we collect it later in do_with_lazy_decls_
251 let run_in_decl_mode filename f =
252 let old_in_lazy_decl = !in_lazy_decl in
253 in_lazy_decl := Some filename;
254 Utils.try_finally ~f ~finally:begin fun () ->
255 in_lazy_decl := old_in_lazy_decl;
258 and make_error code (x : (Pos.t * string) list) : error = (code, x)
260 (*****************************************************************************)
261 (* Accessors. *)
262 (*****************************************************************************)
264 and get_code (error: 'a error_) = ((fst error): error_code)
266 let get_severity (error: 'a error_) = get_code_severity (get_code error)
268 let to_list (error : 'a error_) = snd error
269 let to_absolute error =
270 let code, msg_l = (get_code error), (to_list error) in
271 let msg_l = List.map msg_l (fun (p, s) -> Pos.to_absolute p, s) in
272 code, msg_l
274 let read_lines path = In_channel.read_lines path
276 let line_margin (line_num : int option) col_width: string =
277 let padded_num = match line_num with
278 | Some line_num -> Printf.sprintf "%*d" col_width line_num
279 | None -> String.make col_width ' '
281 Tty.apply_color (Tty.Normal Tty.Cyan) (padded_num ^ " |")
283 (* Get the lines of source code associated with this position. *)
284 let load_context_lines (pos : Pos.absolute): string list =
285 let path = Pos.filename pos in
286 let line = Pos.line pos in
287 let end_line = Pos.end_line pos in
288 let lines =
289 try read_lines path
290 with (Sys_error _) -> []
292 (* Line numbers are 1-indexed. *)
293 List.filteri lines ~f:(fun i _ -> (i + 1 >= line) && (i + 1 <= end_line))
295 let format_context_lines (pos : Pos.absolute) (lines : string list) col_width: string =
296 let lines = (match lines with
297 | [] -> [Tty.apply_color (Tty.Dim Tty.White) "No source found"]
298 | ls -> ls) in
299 let line_num = Pos.line pos in
300 let format_line i (line : string) =
301 Printf.sprintf "%s %s" (line_margin (Some (line_num + i)) col_width) line in
302 let formatted_lines = List.mapi ~f:format_line lines in
303 (* TODO: display all the lines, showing the underline on all of them. *)
304 List.hd_exn formatted_lines
306 (* Format this message as " ^^^ You did something wrong here". *)
307 let format_substring_underline (pos: Pos.absolute) (msg: string) (first_context_line: string option) is_first col_width: string =
308 let start_line, start_column = Pos.line_column pos in
309 let end_line, end_column = Pos.end_line_column pos in
310 let underline_width = match first_context_line with
311 | None -> 4 (* Arbitrary choice when source isn't available. *)
312 | Some first_context_line ->
313 if start_line = end_line then
314 end_column - start_column
315 else
316 (String.length first_context_line) - start_column
318 let underline = String.make underline_width '^' in
319 let underline_padding = if Option.is_some first_context_line then
320 (String.make start_column ' ')
321 else
324 let color = if is_first then Tty.Bold Tty.Red else Tty.Dim Tty.Default in
325 Printf.sprintf "%s %s%s"
326 (line_margin None col_width)
327 underline_padding
328 (Tty.apply_color color
329 (if is_first then underline else (underline ^ " " ^ msg)))
331 let format_filename (pos: Pos.absolute): string =
332 let relative_path path =
333 let cwd = Filename.concat (Sys.getcwd ()) "" in
334 lstrip path cwd
336 let filename = relative_path (Pos.filename pos) in
337 Printf.sprintf " %s %s"
338 (Tty.apply_color (Tty.Normal Tty.Cyan) "-->")
339 (Tty.apply_color (Tty.Normal Tty.Green) filename)
341 let column_width line_number =
342 let num_digits x = int_of_float (Float.log10 (float_of_int x)) + 1 in
343 (max 3 (num_digits line_number))
345 (* Format the line of code associated with this message, and the message itself. *)
346 let format_message (msg: string) (pos: Pos.absolute) ~is_first ~col_width : string * string =
347 let col_width = Option.value col_width ~default:(column_width (Pos.line pos)) in
349 let context_lines = load_context_lines pos in
350 let pretty_ctx = format_context_lines pos context_lines col_width in
351 let pretty_msg = format_substring_underline pos msg (List.hd context_lines) is_first col_width in
352 (pretty_ctx, pretty_msg)
354 (** Sort messages such that messages in the same file are together.
355 Do not reorder the files or messages within a file.
357 let group_by_file (msgs : Pos.absolute message list): Pos.absolute message list =
358 let rec build_map msgs grouped filenames =
359 match msgs with
360 | msg::msgs ->
361 (let filename = (Pos.filename (fst msg)) in
362 match String.Map.find grouped filename with
363 | Some file_msgs ->
364 let grouped = String.Map.set grouped ~key:filename ~data:(file_msgs @ [msg]) in
365 build_map msgs grouped filenames
366 | None ->
367 let grouped = String.Map.set grouped ~key:filename ~data:[msg] in
368 build_map msgs grouped (filename::filenames))
369 | [] -> (grouped, filenames)
371 let grouped, filenames = build_map msgs String.Map.empty [] in
372 List.concat_map (List.rev filenames) ~f:(fun fn -> String.Map.find_exn grouped fn)
374 (* Work out the column width needed for each file. Files with many
375 lines need a wider column due to the higher line numbers. *)
376 let col_widths (msgs: Pos.absolute message list): int Core_kernel.String.Map.t =
377 (* Find the longest line number for every file in msgs. *)
378 let longest_lines =
379 List.fold msgs ~init:String.Map.empty
380 ~f:(fun acc msg ->
381 let filename = Pos.filename (fst msg) in
382 let current_max = Option.value (String.Map.find acc filename) ~default:0 in
383 String.Map.set acc ~key:filename ~data:(max current_max (Pos.line (fst msg))))
385 String.Map.map longest_lines ~f:column_width
387 (** Given a list of error messages, format them with context.
388 The list may not be ordered, and multiple messages may occur on one line.
390 let format_messages (msgs: Pos.absolute message list): string =
391 let msgs = group_by_file msgs in
392 (* The first message is the 'primary' message, so add a boolean to distinguish it. *)
393 let rec label_first msgs is_first =
394 match msgs with
395 | msg::msgs -> (msg, is_first)::label_first msgs false
396 | [] -> []
398 let labelled_msgs = label_first msgs true in
400 (* Sort messages by line number, so we can display with context. *)
401 let cmp (m1, _) (m2, _) =
402 match compare (Pos.filename (fst m1)) (Pos.filename (fst m2)) with
403 | 0 -> compare (Pos.line (fst m1)) (Pos.line (fst m2))
404 | _ -> 0 in
405 let sorted_msgs = List.stable_sort cmp labelled_msgs in
407 (* For every message, show it alongside the relevant line. If there
408 are multiple messages associated with the line, only show it once. *)
409 let col_widths = col_widths msgs in
410 let rec aux msgs prev : string list =
411 match msgs with
412 | (msg, is_first)::msgs ->
413 let (pos, err_msg) = msg in
414 let filename = Pos.filename pos in
415 let line = Pos.line pos in
416 let col_width = String.Map.find col_widths filename in
417 let pretty_ctx, pretty_msg = format_message err_msg pos ~is_first ~col_width in
418 let formatted : string list = (match prev with
419 | Some (prev_filename, prev_line) when prev_filename = filename && prev_line = line ->
420 (* Previous message was on this line too, just show the message itself*)
421 [pretty_msg]
422 | Some (prev_filename, _) when prev_filename = filename ->
423 (* Previous message was this file, but an earlier line. *)
424 [pretty_ctx; pretty_msg]
425 | _ ->
426 [format_filename pos; pretty_ctx; pretty_msg])
428 formatted @ aux msgs (Some (filename, line))
429 | [] -> []
431 String.concat ~sep:"\n" (aux sorted_msgs None) ^ "\n"
433 (* E.g. "10 errors found." *)
434 let format_summary format errors max_errors : string option =
435 match format with
436 | Context ->
437 let total = List.length errors in
438 let formatted_total =
439 Printf.sprintf "%d error%s found"
440 total
441 (if total = 1 then "" else "s")
443 let truncated = match max_errors with
444 | Some max_errors when total > max_errors ->
445 Printf.sprintf " (only showing first %d).\n" max_errors
446 | _ -> ".\n"
448 Some (formatted_total ^ truncated)
449 | Raw -> None
451 let to_contextual_string (error : Pos.absolute error_) : string =
452 let error_code = get_code error in
453 let msgl = to_list error in
454 let buf = Buffer.create 50 in
455 (match msgl with
456 | [] -> failwith "Impossible: an error always has non-empty list of messages"
457 | (_, msg) :: _ ->
458 Buffer.add_string buf begin
459 Printf.sprintf "%s %s\n"
460 (Tty.apply_color (Tty.Bold Tty.Red) (error_code_to_string error_code))
461 (Tty.apply_color (Tty.Bold Tty.White) msg)
462 end);
463 (try Buffer.add_string buf (format_messages msgl)
464 with _ -> Buffer.add_string buf "Error could not be pretty-printed. Please file a bug.");
465 Buffer.add_string buf "\n";
466 Buffer.contents buf
468 let to_absolute_for_test error =
469 let code, msg_l = (get_code error), (to_list error) in
470 let msg_l = List.map msg_l (fun (p, s) ->
471 let path = Pos.filename p in
472 let path_without_prefix = Relative_path.suffix path in
473 let p = Pos.set_file
474 (Relative_path.create Relative_path.Dummy path_without_prefix)
475 p in
476 Pos.to_absolute p, s) in
477 code, msg_l
479 let to_string ?(indent=false) (error : Pos.absolute error_) : string =
480 let error_code, msgl = (get_code error), (to_list error) in
481 let buf = Buffer.create 50 in
482 (match msgl with
483 | [] -> assert false
484 | (pos1, msg1) :: rest_of_error ->
485 Buffer.add_string buf begin
486 let error_code = error_code_to_string error_code in
487 Printf.sprintf "%s\n%s (%s)\n"
488 (Pos.string pos1) msg1 error_code
489 end;
490 let indentstr = if indent then " " else "" in
491 List.iter rest_of_error begin fun (p, w) ->
492 let msg = Printf.sprintf "%s%s\n%s%s\n"
493 indentstr (Pos.string p) indentstr w in
494 Buffer.add_string buf msg
497 Buffer.contents buf
499 let add_error error =
500 if !accumulate_errors then
501 let () = match !current_context with
502 | (path, _) when path = Relative_path.default &&
503 (not !allow_errors_in_default_path) ->
504 Hh_logger.log "WARNING: adding an error in default path\n%s\n"
505 (Caml.Printexc.raw_backtrace_to_string (Caml.Printexc.get_callstack 100))
506 | _ -> ()
508 (* Cheap test to avoid duplicating most recent error *)
509 let error_list = get_current_list !error_map in
510 match error_list with
511 | old_error :: _ when error = old_error -> ()
512 | _ -> set_current_list error_map (error :: error_list)
513 else
514 (* We have an error, but haven't handled it in any way *)
515 let msg = error |> to_absolute |> to_string in
516 match !in_lazy_decl with
517 | Some _ ->
518 lazy_decl_error_logging msg error_map to_absolute to_string
519 | None -> assert_false_log_backtrace (Some msg)
521 (* Whether we've found at least one error *)
522 let currently_has_errors () = get_current_list !error_map <> []
524 module Parsing = Error_codes.Parsing
525 module Naming = Error_codes.Naming
526 module NastCheck = Error_codes.NastCheck
527 module Typing = Error_codes.Typing
529 (*****************************************************************************)
530 (* Types *)
531 (*****************************************************************************)
533 type t = error files_t * applied_fixme files_t
535 module type Error_category = sig
536 type t
537 val min : int
538 val max : int
539 val of_enum : int -> t option
540 val show : t -> string
541 val err_code : t -> int
543 (*****************************************************************************)
544 (* HH_FIXMEs hook *)
545 (*****************************************************************************)
547 let error_codes_treated_strictly = ref (ISet.of_list [])
548 let is_strict_code code = ISet.mem code !error_codes_treated_strictly
550 let default_ignored_fixme_codes = ISet.of_list [
551 Typing.err_code Typing.InvalidIsAsExpressionHint;
552 Typing.err_code Typing.InvalidEnforceableTypeArgument;
553 Typing.err_code Typing.RequireArgsReify;
554 Typing.err_code Typing.InvalidReifiedArgument;
555 Typing.err_code Typing.GenericsNotAllowed;
556 Typing.err_code Typing.InvalidNewableTypeArgument;
557 Typing.err_code Typing.InvalidNewableTypeParamConstraints;
558 Typing.err_code Typing.NewWithoutNewable;
559 Typing.err_code Typing.NewStaticClassReified;
560 Typing.err_code Typing.MemoizeReified;
561 Typing.err_code Typing.ReifiedTparamVariadic;
563 let ignored_fixme_codes = ref default_ignored_fixme_codes
565 let set_allow_errors_in_default_path x = allow_errors_in_default_path := x
567 let is_ignored_code code = ISet.mem code !ignored_fixme_codes
569 let is_ignored_fixme code = is_ignored_code code
571 let (is_hh_fixme: (Pos.t -> error_code -> bool) ref) = ref (fun _ _ -> false)
572 let (get_hh_fixme_pos: (Pos.t -> error_code -> Pos.t option) ref) =
573 ref (fun _ _ -> None)
575 let add_ignored_fixme_code_error pos code =
576 if !is_hh_fixme pos code && is_ignored_code code then
577 let pos = Option.value (!get_hh_fixme_pos pos code) ~default:pos in
578 add_error (make_error code
579 [pos,
580 Printf.sprintf "You cannot use HH_FIXME or HH_IGNORE_ERROR comments to suppress error %d" code])
582 (*****************************************************************************)
583 (* Errors accumulator. *)
584 (*****************************************************************************)
586 (* If primary position in error list isn't in current file, wrap with a sentinel error *)
587 let check_pos_msg pos_msg_l =
588 let pos = fst (List.hd_exn pos_msg_l) in
589 let current_file = fst !current_context in
590 if current_file <> Relative_path.default && Pos.filename pos <> current_file
591 then (Pos.make_from current_file, Badpos_sentinel.message) :: pos_msg_l
592 else pos_msg_l
594 let rec add_applied_fixme code pos =
595 if ServerLoadFlag.get_no_load () then
596 let applied_fixmes_list = get_current_list !applied_fixmes in
597 set_current_list applied_fixmes ((pos, code) :: applied_fixmes_list)
598 else ()
600 and add code pos msg =
601 let pos_msg_l = check_pos_msg [pos, msg] in
602 if not (is_ignored_fixme code) && !is_hh_fixme pos code
603 then add_applied_fixme code pos
604 else add_error (make_error code pos_msg_l);
605 add_ignored_fixme_code_error pos code
607 and add_list code pos_msg_l =
608 let pos = fst (List.hd_exn pos_msg_l) in
609 let pos_msg_l = check_pos_msg pos_msg_l in
610 if not (is_ignored_fixme code) && !is_hh_fixme pos code
611 then add_applied_fixme code pos
612 else add_error (make_error code pos_msg_l);
613 add_ignored_fixme_code_error pos code;
615 and merge (err',fixmes') (err,fixmes) =
616 let append = fun _ _ x y ->
617 let x = Option.value x ~default: [] in
618 let y = Option.value y ~default: [] in
619 Some (List.rev_append x y)
621 files_t_merge ~f:append err' err,
622 files_t_merge ~f:append fixmes' fixmes
624 and merge_into_current errors =
625 let merged = merge errors (!error_map, !applied_fixmes) in
626 error_map := fst merged;
627 applied_fixmes := snd merged
629 and incremental_update :
630 (* Need to write out the entire ugly type to convince OCaml it's polymorphic
631 * and can update both error_map as well as applied_fixmes map *)
632 type a .
633 a files_t ->
634 a files_t ->
635 (* function folding over paths of rechecked files *)
636 (a files_t -> (Relative_path.t -> a files_t -> a files_t) -> a files_t) ->
637 phase ->
638 a files_t
639 = fun old new_ fold phase ->
640 (* Helper to remove acc[path][phase]. If acc[path] becomes empty afterwards,
641 * remove it too (i.e do not store empty maps or lists ever). *)
642 let remove path phase acc =
643 let new_phase_map = match Relative_path.Map.get acc path with
644 | None -> None
645 | Some phase_map ->
646 let new_phase_map = PhaseMap.remove phase_map phase in
647 if PhaseMap.is_empty new_phase_map then None else Some new_phase_map
649 match new_phase_map with
650 | None -> Relative_path.Map.remove acc path
651 | Some x -> Relative_path.Map.add acc path x
653 (* Replace old errors with new *)
654 let res = files_t_merge new_ old ~f:begin fun phase path new_ old ->
655 if path = Relative_path.default then begin
656 let phase = match phase with
657 | Init -> "Init"
658 | Parsing -> "Parsing"
659 | Naming -> "Naming"
660 | Decl -> "Decl"
661 | Typing -> "Typing"
663 Utils.assert_false_log_backtrace (Some(
664 "Default (untracked) error sources should not get into incremental " ^
665 "mode. There might be a missing call to Errors.do_with_context/" ^
666 "run_in_context somwhere or incorrectly used Errors.from_error_list." ^
667 "Phase: " ^ phase
669 end;
670 match new_ with
671 | Some new_ -> Some (List.rev new_)
672 | None -> old
673 end in
674 (* For files that were rechecked, but had no errors - remove them from maps *)
675 fold res begin fun path acc ->
676 let has_errors =
677 match Relative_path.Map.get new_ path with
678 | None -> false
679 | Some phase_map -> PhaseMap.mem phase_map phase
681 if has_errors then acc
682 else remove path phase acc
685 and incremental_update_set ~old ~new_ ~rechecked phase =
686 let fold = fun init g -> Relative_path.Set.fold ~f:begin fun path acc ->
687 g path acc
688 end ~init rechecked in
689 (incremental_update (fst old) (fst new_) fold phase),
690 (incremental_update (snd old) (snd new_) fold phase)
692 and incremental_update_map ~old ~new_ ~rechecked phase =
693 let fold = fun init g -> Relative_path.Map.fold ~f:begin fun path _ acc ->
694 g path acc
695 end ~init rechecked in
696 (incremental_update (fst old) (fst new_) fold phase),
697 (incremental_update (snd old) (snd new_) fold phase)
699 and empty = (Relative_path.Map.empty, Relative_path.Map.empty)
700 and is_empty (err, _fixmes) = Relative_path.Map.is_empty err
702 and count (err, _fixmes) = files_t_fold err ~f:(fun _ _ x acc -> acc + List.length x) ~init:0
703 and get_error_list (err, _fixmes) = files_t_to_list err
704 and get_applied_fixmes (_err, fixmes) = files_t_to_list fixmes
705 and from_error_list err = (list_to_files_t err, Relative_path.Map.empty)
707 (*****************************************************************************)
708 (* Accessors. (All methods delegated to the parameterized module.) *)
709 (*****************************************************************************)
711 let iter_error_list f err = List.iter ~f:f (get_sorted_error_list err)
713 let fold_errors ?phase err ~init ~f =
714 match phase with
715 | None ->
716 files_t_fold (fst err)
717 ~init
718 ~f:begin fun source _ errors acc ->
719 List.fold_right errors ~init:acc ~f:(f source)
721 | Some phase ->
722 Relative_path.Map.fold (fst err) ~init ~f:begin fun source phases acc ->
723 match PhaseMap.get phases phase with
724 | None -> acc
725 | Some errors -> List.fold_right errors ~init:acc ~f:(f source)
728 let fold_errors_in ?phase err ~source ~init ~f =
729 Relative_path.Map.get (fst err) source |>
730 Option.value ~default:PhaseMap.empty |>
731 PhaseMap.fold ~init ~f:begin fun p errors acc ->
732 if phase <> None && phase <> Some p then acc
733 else List.fold_right errors ~init:acc ~f
736 let get_failed_files err phase =
737 files_t_fold (fst err)
738 ~init:Relative_path.Set.empty
739 ~f:begin fun source p _ acc ->
740 if phase <> p then acc else Relative_path.Set.add acc source
743 (*****************************************************************************)
744 (* Error code printing. *)
745 (*****************************************************************************)
747 let internal_error pos msg =
748 add 0 pos ("Internal error: "^msg)
750 let unimplemented_feature pos msg =
751 add 0 pos ("Feature not implemented: " ^ msg)
753 let experimental_feature pos msg =
754 add 0 pos ("Cannot use experimental feature: " ^ msg)
756 (*****************************************************************************)
757 (* Parsing errors. *)
758 (*****************************************************************************)
760 let fixme_format pos =
761 add (Parsing.err_code Parsing.FixmeFormat) pos
762 "HH_FIXME wrong format, expected '/* HH_FIXME[ERROR_NUMBER] */'"
764 let parsing_error (p, msg) =
765 add (Parsing.err_code Parsing.ParsingError) p msg
767 (*****************************************************************************)
768 (* Legacy AST / AAST errors *)
769 (*****************************************************************************)
771 let unsupported_trait_use_as pos =
772 add (Naming.err_code Naming.UnsupportedTraitUseAs) pos
773 "Trait use as is a PHP feature that is unsupported in Hack"
775 let unsupported_instead_of pos =
776 add (Naming.err_code Naming.UnsupportedInsteadOf) pos
777 "insteadof is a PHP feature that is unsupported in Hack"
779 let invalid_trait_use_as_visibility pos =
780 add (Naming.err_code Naming.InvalidTraitUseAsVisibility) pos
781 "Cannot redeclare trait method's visibility in this manner"
783 (*****************************************************************************)
784 (* Naming errors *)
785 (*****************************************************************************)
788 let unexpected_arrow pos cname =
789 add (Naming.err_code Naming.UnexpectedArrow) pos (
790 "Keys may not be specified for "^cname^" initialization"
793 let missing_arrow pos cname =
794 add (Naming.err_code Naming.MissingArrow) pos (
795 "Keys must be specified for "^cname^" initialization"
798 let disallowed_xhp_type pos name =
799 add (Naming.err_code Naming.DisallowedXhpType) pos (
800 name^" is not a valid type. Use :xhp or XHPChild."
803 let name_is_reserved name pos =
804 let name = Utils.strip_all_ns name in
805 add (Naming.err_code Naming.NameIsReserved) pos (
806 name^" cannot be used as it is reserved."
809 let dollardollar_unused pos =
810 add (Naming.err_code Naming.DollardollarUnused) pos ("This expression does not contain a "^
811 "usage of the special pipe variable. Did you forget to use the ($$) "^
812 "variable?")
814 let method_name_already_bound pos name =
815 add (Naming.err_code Naming.MethodNameAlreadyBound) pos (
816 "Method name already bound: "^name
819 let reference_in_rx pos =
820 add (Naming.err_code Naming.ReferenceInRx) pos (
821 "References are not allowed in reactive code."
823 let error_name_already_bound name name_prev p p_prev =
824 let name = Utils.strip_ns name in
825 let name_prev = Utils.strip_ns name_prev in
826 let errs = [
827 p, "Name already bound: "^name;
828 p_prev, (if String.compare name name_prev = 0
829 then "Previous definition is here"
830 else "Previous definition "^name_prev^" differs only in capitalization ")
831 ] in
832 let hhi_msg =
833 "This appears to be defined in an hhi file included in your project "^
834 "root. The hhi files for the standard library are now a part of the "^
835 "typechecker and must be removed from your project. Typically, you can "^
836 "do this by deleting the \"hhi\" directory you copied into your "^
837 "project when first starting with Hack." in
838 let errs =
839 if (Relative_path.prefix (Pos.filename p)) = Relative_path.Hhi
840 then errs @ [p_prev, hhi_msg]
841 else if (Relative_path.prefix (Pos.filename p_prev)) = Relative_path.Hhi
842 then errs @ [p, hhi_msg]
843 else errs in
844 add_list (Naming.err_code Naming.ErrorNameAlreadyBound) errs
846 let error_class_attribute_already_bound name name_prev p p_prev =
847 let name = Utils.strip_ns name in
848 let name_prev = Utils.strip_ns name_prev in
849 let errs = [
850 p, "A class and an attribute class cannot share the same name. Conflicting class: "^name;
851 p_prev, "Previous definition: "^name_prev
852 ] in
853 add_list (Naming.err_code Naming.AttributeClassNameConflict) errs
855 let unbound_name pos name kind =
856 let kind_str = match kind with
857 | `cls -> "an object type"
858 | `func -> "a global function"
859 | `const -> "a global constant"
861 add (Naming.err_code Naming.UnboundName) pos
862 ("Unbound name: "^(strip_ns name)^" ("^kind_str^")")
864 let rx_move_invalid_location pos =
865 add (Naming.err_code Naming.RxMoveInvalidLocation) pos
866 "Rx\\move is only allowed in argument position or as right hand side of the assignment."
868 let undefined ~in_rx_scope pos var_name =
869 let rx_scope_clarification =
870 if in_rx_scope then "or unsets "
871 else "" in
872 add (Naming.err_code Naming.Undefined) pos ("Variable "^var_name^
873 " is undefined, "^
874 "or there exists at least one control flow path reaching this point which "^
875 "does not define " ^ rx_scope_clarification ^ var_name ^".")
877 let this_reserved pos =
878 add (Naming.err_code Naming.ThisReserved) pos
879 "The type parameter \"this\" is reserved"
881 let start_with_T pos =
882 add (Naming.err_code Naming.StartWith_T) pos
883 "Please make your type parameter start with the letter T (capital)"
885 let already_bound pos name =
886 add (Naming.err_code Naming.NameAlreadyBound) pos ("Argument already bound: "^name)
888 let unexpected_typedef pos def_pos =
889 add_list (Naming.err_code Naming.UnexpectedTypedef) [
890 pos, "Unexpected typedef";
891 def_pos, "Definition is here";
894 let fd_name_already_bound pos =
895 add (Naming.err_code Naming.FdNameAlreadyBound) pos
896 "Field name already bound"
898 let primitive_toplevel pos =
899 add (Naming.err_code Naming.PrimitiveToplevel) pos (
900 "Primitive type annotations are always available and may no \
901 longer be referred to in the toplevel namespace."
904 let primitive_invalid_alias pos used valid =
905 add (Naming.err_code Naming.PrimitiveInvalidAlias) pos
906 ("Invalid Hack type. Using '"^used^"' in Hack is considered \
907 an error. Use '"^valid^"' instead, to keep the codebase \
908 consistent.")
910 let dynamic_new_in_strict_mode pos =
911 add (Naming.err_code Naming.DynamicNewInStrictMode) pos
912 "Cannot use dynamic new in strict mode"
914 let invalid_type_access_root (pos, id) =
915 add (Naming.err_code Naming.InvalidTypeAccessRoot) pos
916 (id^" must be an identifier for a class, \"self\", or \"this\"")
918 let duplicate_user_attribute (pos, name) existing_attr_pos =
919 add_list (Naming.err_code Naming.DuplicateUserAttribute) [
920 pos, "You cannot reuse the attribute "^name;
921 existing_attr_pos, name^" was already used here";
924 let unbound_attribute_name pos name =
925 let reason = if (string_starts_with name "__")
926 then "starts with __ but is not a standard attribute"
927 else "does not have a class. Please declare a class for the attribute."
928 in add (Naming.err_code Naming.UnboundName) pos
929 ("Unrecognized user attribute: "^(Utils.strip_ns name)^" "^reason)
931 let this_no_argument pos =
932 add (Naming.err_code Naming.ThisNoArgument) pos "\"this\" expects no arguments"
934 let void_cast pos =
935 add (Naming.err_code Naming.VoidCast) pos "Cannot cast to void."
937 let unset_cast pos =
938 add (Naming.err_code Naming.UnsetCast) pos "Don't use (unset), just assign null!"
940 let object_cast pos cls_opt =
941 let msg1 = "Object casts are unsupported." in
942 let msg2 =
943 match cls_opt with
944 | Some c ->
945 " Try 'if ($var instanceof "^c^")' or 'invariant($var instanceof "^c^", ...)'."
946 | None -> ""
948 add (Naming.err_code Naming.ObjectCast) pos (msg1 ^ msg2)
950 let this_hint_outside_class pos =
951 add (Naming.err_code Naming.ThisHintOutsideClass) pos
952 "Cannot use \"this\" outside of a class"
954 let this_type_forbidden pos =
955 add (Naming.err_code Naming.ThisMustBeReturn) pos
956 "The type \"this\" cannot be used as a constraint on a class' generic, \
957 or as the type of a static member variable"
959 let nonstatic_property_with_lsb pos =
960 add (Naming.err_code Naming.NonstaticPropertyWithLSB) pos
961 "__LSB attribute may only be used on static properties"
963 let lowercase_this pos type_ =
964 add (Naming.err_code Naming.LowercaseThis) pos (
965 "Invalid Hack type \""^type_^"\". Use \"this\" instead"
968 let classname_param pos =
969 add (Naming.err_code Naming.ClassnameParam) pos
970 ("Missing type parameter to classname; classname is entirely"
971 ^" meaningless without one")
973 let invalid_instanceof pos =
974 add (Naming.err_code Naming.InvalidInstanceof) pos
975 "This instanceof has an invalid right operand. Only class identifiers, \
976 local variables, accesses of objects / classes / arrays, and function / \
977 method calls are allowed."
979 let tparam_with_tparam pos x =
980 add (Naming.err_code Naming.TparamWithTparam) pos (
981 Printf.sprintf "%s is a type parameter. Type parameters cannot \
982 themselves take type parameters (e.g. %s<int> doesn't make sense)" x x
985 let shadowed_type_param p pos name =
986 add_list (Naming.err_code Naming.ShadowedTypeParam) [
987 p, Printf.sprintf "You cannot re-bind the type parameter %s" name;
988 pos, Printf.sprintf "%s is already bound here" name
991 let missing_typehint pos =
992 add (Naming.err_code Naming.MissingTypehint) pos
993 "Please add a type hint"
995 let expected_variable pos =
996 add (Naming.err_code Naming.ExpectedVariable) pos
997 "Was expecting a variable name"
999 let clone_too_many_arguments pos =
1000 add (Naming.err_code Naming.NamingTooManyArguments) pos
1001 "__clone method cannot take arguments"
1003 let naming_too_few_arguments pos =
1004 add (Naming.err_code Naming.NamingTooFewArguments) pos
1005 "Too few arguments"
1007 let naming_too_many_arguments pos =
1008 add (Naming.err_code Naming.NamingTooManyArguments) pos
1009 "Too many arguments"
1011 let expected_collection pos cn =
1012 add (Naming.err_code Naming.ExpectedCollection) pos (
1013 "Unexpected collection type " ^ (Utils.strip_ns cn)
1016 let illegal_CLASS pos =
1017 add (Naming.err_code Naming.IllegalClass) pos
1018 "Using __CLASS__ outside a class or trait"
1020 let illegal_TRAIT pos =
1021 add (Naming.err_code Naming.IllegalTrait) pos
1022 "Using __TRAIT__ outside a trait"
1024 let lvar_in_obj_get pos =
1025 add (Naming.err_code Naming.LvarInObjGet) pos
1026 "Dynamic method or attribute access is not allowed on a non-dynamic value."
1028 let nullsafe_property_write_context pos =
1029 add (Typing.err_code Typing.NullsafePropertyWriteContext) pos
1030 "?-> syntax not supported here, this function effectively does a write"
1032 let illegal_fun pos =
1033 let msg = "The argument to fun() must be a single-quoted, constant "^
1034 "literal string representing a valid function name." in
1035 add (Naming.err_code Naming.IllegalFun) pos msg
1037 let illegal_member_variable_class pos =
1038 let msg = "Cannot declare a constant named 'class'. \
1039 The name 'class' is reserved for the class \
1040 constant that represents the name of the class" in
1041 add (Naming.err_code Naming.IllegalMemberVariableClass) pos msg
1043 let illegal_meth_fun pos =
1044 let msg = "String argument to fun() contains ':';"^
1045 " for static class methods, use"^
1046 " class_meth(Cls::class, 'method_name'), not fun('Cls::method_name')" in
1047 add (Naming.err_code Naming.IllegalMethFun) pos msg
1049 let illegal_inst_meth pos =
1050 let msg = "The argument to inst_meth() must be an expression and a "^
1051 "constant literal string representing a valid method name." in
1052 add (Naming.err_code Naming.IllegalInstMeth) pos msg
1054 let illegal_meth_caller pos =
1055 let msg =
1056 "The two arguments to meth_caller() must be:"
1057 ^"\n - first: ClassOrInterface::class"
1058 ^"\n - second: a single-quoted string literal containing the name"
1059 ^" of a non-static method of that class" in
1060 add (Naming.err_code Naming.IllegalMethCaller) pos msg
1062 let illegal_class_meth pos =
1063 let msg =
1064 "The two arguments to class_meth() must be:"
1065 ^"\n - first: ValidClassname::class"
1066 ^"\n - second: a single-quoted string literal containing the name"
1067 ^" of a static method of that class" in
1068 add (Naming.err_code Naming.IllegalClassMeth) pos msg
1070 let assert_arity pos =
1071 add (Naming.err_code Naming.AssertArity) pos
1072 "assert expects exactly one argument"
1074 let genva_arity pos =
1075 add (Naming.err_code Naming.GenvaArity) pos
1076 "genva() expects at least 1 argument"
1078 let unexpected_ty_in_tast pos ~actual_ty ~expected_ty =
1079 add (Typing.err_code Typing.UnexpectedTy) pos (
1080 "Unexpected type in TAST: expected " ^ expected_ty ^ ", got " ^ actual_ty
1083 let uninstantiable_class usage_pos decl_pos name reason_msgl =
1084 let name = strip_ns name in
1085 let msgl = [
1086 usage_pos, (name^" is uninstantiable");
1087 decl_pos, "Declaration is here"
1088 ] in
1089 let msgl = match reason_msgl with
1090 | (reason_pos, reason_str) :: tail ->
1091 (reason_pos, reason_str^" which must be instantiable") :: tail @ msgl
1092 | _ -> msgl in
1093 add_list (Typing.err_code Typing.UninstantiableClass) msgl
1095 let abstract_const_usage usage_pos decl_pos name =
1096 let name = strip_ns name in
1097 add_list (Typing.err_code Typing.AbstractConstUsage) [
1098 usage_pos, ("Cannot reference abstract constant "^name^" directly");
1099 decl_pos, "Declaration is here"
1102 let add_a_typehint pos =
1103 add (Naming.err_code Naming.AddATypehint) pos
1104 "Please add a type hint"
1106 let illegal_constant pos =
1107 add (Naming.err_code Naming.IllegalConstant) pos
1108 "Illegal constant value"
1110 let invalid_req_implements pos =
1111 add (Naming.err_code Naming.InvalidReqImplements) pos
1112 "Only traits may use 'require implements'"
1114 let invalid_req_extends pos =
1115 add (Naming.err_code Naming.InvalidReqExtends) pos
1116 "Only traits and interfaces may use 'require extends'"
1118 let did_you_mean_naming pos name suggest_pos suggest_name =
1119 add_list (Naming.err_code Naming.DidYouMeanNaming) [
1120 pos, "Could not find "^(strip_ns name);
1121 suggest_pos, "Did you mean "^(strip_ns suggest_name)^"?"
1124 let using_internal_class pos name =
1125 add (Naming.err_code Naming.UsingInternalClass) pos (
1126 name^" is an implementation internal class that cannot be used directly"
1129 let too_few_type_arguments p =
1130 add (Naming.err_code Naming.TooFewTypeArguments) p
1131 ("Too few type arguments for this type")
1133 let goto_label_already_defined
1134 label_name
1135 redeclaration_pos
1136 original_delcaration_pos =
1137 add_list
1138 (Naming.err_code Naming.GotoLabelAlreadyDefined)
1140 redeclaration_pos, "Cannot redeclare the goto label '" ^ label_name ^ "'";
1141 original_delcaration_pos, "Declaration is here";
1144 let goto_label_undefined pos label_name =
1145 add (Naming.err_code Naming.GotoLabelUndefined) pos ("Undefined goto label: " ^ label_name)
1147 let goto_label_defined_in_finally pos =
1148 add (Naming.err_code Naming.GotoLabelDefinedInFinally)
1150 "It is illegal to define a goto label within a finally block."
1152 let goto_invoked_in_finally pos =
1153 add (Naming.err_code Naming.GotoInvokedInFinally)
1155 "It is illegal to invoke goto within a finally block."
1157 let method_needs_visibility pos =
1158 add (Naming.err_code Naming.MethodNeedsVisibility)
1159 pos ("Methods need to be marked public, private, or protected.")
1161 let dynamic_class_name_in_strict_mode pos =
1162 add (Naming.err_code Naming.DynamicClassNameInStrictMode)
1164 "Cannot use dynamic class name in strict mode"
1166 let xhp_optional_required_attr pos id =
1167 add (Naming.err_code Naming.XhpOptionalRequiredAttr)
1169 ("XHP attribute " ^ id ^ " cannot be marked as nullable and required")
1171 let xhp_required_with_default pos id =
1172 add (Naming.err_code Naming.XhpRequiredWithDefault)
1174 ("XHP attribute " ^ id ^ " cannot be marked as required and provide a default")
1176 let array_typehints_disallowed pos =
1177 add (Naming.err_code Naming.ArrayTypehintsDisallowed) pos
1178 "Array typehints are no longer legal; use varray or darray instead"
1180 let array_literals_disallowed pos =
1181 add (Naming.err_code Naming.ArrayLiteralsDisallowed) pos
1182 "Array literals are no longer legal; use varray or darray instead"
1184 let wildcard_disallowed pos =
1185 add (Naming.err_code Naming.WildcardDisallowed) pos
1186 "Wildcard typehints are not allowed in this position"
1188 let reference_in_strict_mode pos =
1189 add (Naming.err_code Naming.ReferenceInStrictMode) pos
1190 "Don't use references!"
1192 let misplaced_mutability_hint pos =
1193 add (Naming.err_code Naming.MisplacedMutabilityHint) pos
1194 "Setting mutability via type hints is only allowed for parameters of reactive function types. \
1195 For other cases consider using attributes."
1197 let mutability_hint_in_non_rx_function pos =
1198 add (Naming.err_code Naming.MutabilityHintInNonRx) pos
1199 "Parameter with mutability hint cannot appear in non-reactive function type."
1201 let invalid_mutability_in_return_type_hint pos =
1202 add (Naming.err_code Naming.InvalidReturnMutableHint) pos
1203 "OwnedMutable is the only mutability related hint allowed in return type annotation \
1204 for reactive function types."
1206 let pu_duplication pos name kind =
1207 add (Naming.err_code Naming.PocketUniversesDuplication) pos
1208 (sprintf "[PocketUniverses] %s (%s) is declared multiple times" name kind)
1210 (*****************************************************************************)
1211 (* Init check errors *)
1212 (*****************************************************************************)
1214 let no_construct_parent pos =
1215 add (NastCheck.err_code NastCheck.NoConstructParent) pos (
1216 sl["You are extending a class that needs to be initialized\n";
1217 "Make sure you call parent::__construct.\n"
1221 let nonstatic_method_in_abstract_final_class pos =
1222 add (NastCheck.err_code NastCheck.NonstaticMethodInAbstractFinalClass) pos (
1223 "Abstract final classes cannot have nonstatic methods or constructors."
1226 let constructor_required (pos, name) prop_names =
1227 let name = Utils.strip_ns name in
1228 let props_str = SSet.fold ~f:(fun x acc -> x^" "^acc) prop_names ~init:"" in
1229 add (NastCheck.err_code NastCheck.ConstructorRequired) pos
1230 ("Lacking __construct, class "^name^" does not initialize its private member(s): "^props_str)
1232 let not_initialized (pos, cname) prop_names =
1233 let cname = Utils.strip_ns cname in
1234 let props_str = List.fold_right prop_names
1235 ~f:(fun x acc -> x^" "^acc) ~init:"" in
1236 let members, verb =
1237 if 1 = List.length prop_names
1238 then "member", "is"
1239 else "members", "are" in
1240 let setters_str = List.fold_right prop_names
1241 ~f:(fun x acc -> "$this->"^x^" "^acc) ~init:"" in
1242 add (NastCheck.err_code NastCheck.NotInitialized) pos (
1244 "Class "; cname ; " does not initialize all of its members; ";
1245 props_str; verb; " not always initialized.";
1246 "\nMake sure you systematically set "; setters_str;
1247 "when the method __construct is called.";
1248 "\nAlternatively, you can define the "; members ;" as optional (?...)\n"
1251 let call_before_init pos cv =
1252 add (NastCheck.err_code NastCheck.CallBeforeInit) pos (
1253 sl([
1254 "Until the initialization of $this is over,";
1255 " you can only call private methods\n";
1256 "The initialization is not over because ";
1258 if cv = "parent::__construct"
1259 then ["you forgot to call parent::__construct"]
1260 else ["$this->"; cv; " can still potentially be null"])
1263 (*****************************************************************************)
1264 (* Nast errors check *)
1265 (*****************************************************************************)
1267 let type_arity pos name nargs =
1268 add (Typing.err_code Typing.TypeArityMismatch) pos (
1269 sl["The type ";(Utils.strip_ns name);
1270 " expects ";nargs;" type parameter(s)"]
1273 let abstract_with_body (p, _) =
1274 add (NastCheck.err_code NastCheck.AbstractWithBody) p
1275 "This method is declared as abstract, but has a body"
1277 let not_abstract_without_body (p, _) =
1278 add (NastCheck.err_code NastCheck.NotAbstractWithoutBody) p
1279 "This method is not declared as abstract, it must have a body"
1281 let not_abstract_without_typeconst (p, _) =
1282 add (NastCheck.err_code NastCheck.NotAbstractWithoutTypeconst) p
1283 ("This type constant is not declared as abstract, it must have"^
1284 " an assigned type")
1286 let typeconst_depends_on_external_tparam pos ext_pos ext_name =
1287 add_list (NastCheck.err_code NastCheck.TypeconstDependsOnExternalTparam) [
1288 pos, ("A type constant can only use type parameters declared in its own"^
1289 " type parameter list");
1290 ext_pos, (ext_name ^ " was declared as a type parameter here");
1293 let interface_with_partial_typeconst tconst_pos =
1294 add (NastCheck.err_code NastCheck.InterfaceWithPartialTypeconst) tconst_pos
1295 "An interface cannot contain a partially abstract type constant"
1297 let multiple_xhp_category pos =
1298 add (NastCheck.err_code NastCheck.MultipleXhpCategory) pos
1299 "XHP classes can only contain one category declaration"
1301 let return_in_gen p =
1302 add (NastCheck.err_code NastCheck.ReturnInGen) p
1303 ("You cannot return a value in a generator (a generator"^
1304 " is a function that uses yield)")
1306 let return_in_finally p =
1307 add (NastCheck.err_code NastCheck.ReturnInFinally) p
1308 ("Don't use return in a finally block;"^
1309 " there's nothing to receive the return value")
1311 let toplevel_break p =
1312 add (NastCheck.err_code NastCheck.ToplevelBreak) p
1313 "break can only be used inside loops or switch statements"
1315 let toplevel_continue p =
1316 add (NastCheck.err_code NastCheck.ToplevelContinue) p
1317 "continue can only be used inside loops"
1319 let continue_in_switch p =
1320 add (NastCheck.err_code NastCheck.ContinueInSwitch) p
1321 ("In PHP, 'continue;' inside a switch \
1322 statement is equivalent to 'break;'."^
1323 " Hack does not support this; use 'break' if that is what you meant.")
1325 let await_in_sync_function p =
1326 add (NastCheck.err_code NastCheck.AwaitInSyncFunction) p
1327 "await can only be used inside async functions"
1329 let interface_use_trait p =
1330 add (NastCheck.err_code NastCheck.InterfaceUsesTrait) p
1331 "Interfaces cannot use traits"
1333 let await_not_allowed p =
1334 add (NastCheck.err_code NastCheck.AwaitNotAllowed) p
1335 "await is only permitted as a statement, expression in a return statement \
1336 or as a right hand side in top level assignment."
1338 let await_in_coroutine p =
1339 add (NastCheck.err_code NastCheck.AwaitInCoroutine) p
1340 "await is not allowed in coroutines."
1342 let yield_in_coroutine p =
1343 add (NastCheck.err_code NastCheck.YieldInCoroutine) p
1344 "yield is not allowed in coroutines."
1346 let suspend_outside_of_coroutine p =
1347 add (NastCheck.err_code NastCheck.SuspendOutsideOfCoroutine) p
1348 "suspend is only allowed in coroutines."
1350 let suspend_in_finally p =
1351 add (NastCheck.err_code NastCheck.SuspendInFinally) p
1352 "suspend is not allowed inside finally blocks."
1354 let break_continue_n_not_supported p =
1355 add (NastCheck.err_code NastCheck.BreakContinueNNotSupported) p
1356 "Break/continue N operators are not supported."
1358 let static_memoized_function p =
1359 add (NastCheck.err_code NastCheck.StaticMemoizedFunction) p
1360 "memoize is not allowed on static methods in classes that aren't final "
1362 let magic (p, s) =
1363 add (NastCheck.err_code NastCheck.Magic) p
1364 (s^" is a magic method and cannot be called directly")
1366 let non_interface (p : Pos.t) (c2: string) (verb: string): 'a =
1367 add (NastCheck.err_code NastCheck.NonInterface) p
1368 ("Cannot " ^ verb ^ " " ^ (strip_ns c2) ^ " - it is not an interface")
1370 let toString_returns_string pos =
1371 add (NastCheck.err_code NastCheck.ToStringReturnsString) pos "__toString should return a string"
1373 let toString_visibility pos =
1374 add (NastCheck.err_code NastCheck.ToStringVisibility) pos
1375 "__toString must have public visibility and cannot be static"
1377 let uses_non_trait (p: Pos.t) (n: string) (t: string) =
1378 add (NastCheck.err_code NastCheck.UsesNonTrait) p
1379 ((Utils.strip_ns n) ^ " is not a trait. It is " ^ t ^ ".")
1381 let requires_non_class (p: Pos.t) (n: string) (t: string) =
1382 add (NastCheck.err_code NastCheck.RequiresNonClass) p
1383 ((Utils.strip_ns n) ^ " is not a class. It is " ^ t ^ ".")
1385 let requires_final_class (p: Pos.t) (n: string) =
1386 add (NastCheck.err_code NastCheck.RequiresFinalClass) p
1387 ((Utils.strip_ns n) ^ " is not an extendable class.")
1389 let abstract_body pos =
1390 add (NastCheck.err_code NastCheck.AbstractBody) pos "This method shouldn't have a body"
1392 let not_public_or_protected_interface pos =
1393 add (NastCheck.err_code NastCheck.NotPublicInterface) pos
1394 "Access type for interface method must be public or protected."
1396 let interface_with_member_variable pos =
1397 add (NastCheck.err_code NastCheck.InterfaceWithMemberVariable) pos
1398 "Interfaces cannot have member variables"
1400 let interface_with_static_member_variable pos =
1401 add (NastCheck.err_code NastCheck.InterfaceWithStaticMemberVariable) pos
1402 "Interfaces cannot have static variables"
1404 let illegal_function_name pos mname =
1405 add (NastCheck.err_code NastCheck.IllegalFunctionName) pos
1406 ("Illegal function name: " ^ strip_ns mname)
1408 let dangerous_method_name pos =
1409 add (NastCheck.err_code NastCheck.DangerousMethodName) pos (
1410 "This is a dangerous method name, "^
1411 "if you want to define a constructor, use "^
1412 "__construct"
1415 let inout_params_outside_of_sync pos =
1416 add (NastCheck.err_code NastCheck.InoutParamsOutsideOfSync) pos (
1417 "Inout parameters cannot be defined on async functions, "^
1418 "generators or coroutines."
1421 let mutable_attribute_on_function pos =
1422 add (NastCheck.err_code NastCheck.MutableAttributeOnFunction) pos (
1423 "<<__Mutable>> only makes sense on methods, or parameters on functions or methods."
1426 let maybe_mutable_attribute_on_function pos =
1427 add (NastCheck.err_code NastCheck.MaybeMutableAttributeOnFunction) pos (
1428 "<<__MaybeMutable>> only makes sense on methods, or parameters on functions or methods."
1431 let conflicting_mutable_and_maybe_mutable_attributes pos =
1432 add (NastCheck.err_code NastCheck.ConflictingMutableAndMaybeMutableAttributes) pos (
1433 "Declaration cannot have both <<__Mutable>> and <<__MaybeMutable>> attributtes."
1436 let mutable_methods_must_be_reactive pos name =
1437 add (NastCheck.err_code NastCheck.MutableMethodsMustBeReactive) pos (
1438 "The method " ^ (strip_ns name) ^ " has a mutable parameter" ^
1439 " (or mutable this), so it must be marked reactive with <<__Rx>>."
1442 let mutable_return_annotated_decls_must_be_reactive kind pos name =
1443 add (NastCheck.err_code NastCheck.MutableReturnAnnotatedDeclsMustBeReactive) pos (
1444 "The " ^ kind ^ " " ^ (strip_ns name) ^ " is annotated with <<__MutableReturn>>, " ^
1445 " so it must be marked reactive with <<__Rx>>."
1448 let maybe_mutable_methods_must_be_reactive pos name =
1449 add (NastCheck.err_code NastCheck.MaybeMutableMethodsMustBeReactive) pos (
1450 "The method " ^ (strip_ns name) ^ " is annotated with <<__MaybeMutable> attribute, \
1451 or has this attribute on one of parameters so it must be marked reactive."
1455 let inout_params_special pos =
1456 add (NastCheck.err_code NastCheck.InoutParamsSpecial) pos
1457 "Methods with special semantics cannot have inout parameters."
1459 let inout_params_mix_byref pos1 pos2 =
1460 if pos1 <> pos2 then begin
1461 let msg1 = pos1, "Cannot mix inout and byRef parameters" in
1462 let msg2 = pos2, "This parameter is passed by reference" in
1463 add_list (NastCheck.err_code NastCheck.InoutParamsMixByref) [msg1; msg2]
1466 let inout_params_memoize fpos pos =
1467 let msg1 = fpos, "Functions with inout parameters cannot be memoized" in
1468 let msg2 = pos, "This is an inout parameter" in
1469 add_list (NastCheck.err_code NastCheck.InoutParamsMemoize) [msg1; msg2]
1471 let reading_from_append pos =
1472 add (NastCheck.err_code NastCheck.ReadingFromAppend) pos "Cannot use [] for reading"
1474 let const_attribute_prohibited pos kind =
1475 add (NastCheck.err_code NastCheck.ConstAttributeProhibited) pos
1476 ("Cannot apply __Const attribute to " ^ kind)
1478 let inout_argument_bad_expr pos =
1479 add (NastCheck.err_code NastCheck.InoutArgumentBadExpr) pos (
1480 "Arguments for inout parameters must be local variables or simple " ^
1481 "subscript expressions on vecs, dicts, keysets, or arrays"
1484 let illegal_destructor pos =
1485 add (NastCheck.err_code NastCheck.IllegalDestructor) pos (
1486 "Destructors are not supported in Hack; use other patterns like " ^
1487 "IDisposable/using or try/catch instead."
1490 let multiple_conditionally_reactive_annotations pos name =
1491 add (NastCheck.err_code NastCheck.MultipleConditionallyReactiveAnnotations) pos (
1492 "Method '" ^ name ^ "' has multiple <<__OnlyRxIfImpl>> annotations."
1495 let rx_is_enabled_invalid_location pos =
1496 add (NastCheck.err_code NastCheck.RxIsEnabledInvalidLocation) pos (
1497 "HH\\Rx\\IS_ENABLED must be the only condition in an if-statement, " ^
1498 "and that if-statement must be the only statement in the function body."
1501 let atmost_rx_as_rxfunc_invalid_location pos =
1502 add (NastCheck.err_code NastCheck.MaybeRxInvalidLocation) pos (
1503 "<<__AtMostRxAsFunc>> attribute can only be put on parameters of \
1504 conditionally reactive function or method annotated with \
1505 <<__AtMostRxAsArgs>> attribute."
1508 let no_atmost_rx_as_rxfunc_for_rx_if_args pos =
1509 add (NastCheck.err_code NastCheck.NoOnlyrxIfRxfuncForRxIfArgs) pos (
1510 "Function or method annotated with <<__AtMostRxAsArgs>> attribute \
1511 should have at least one parameter with <<__AtMostRxAsFunc>> or \
1512 <<__OnlyRxIfImpl>> annotations."
1515 let conditionally_reactive_annotation_invalid_arguments ~is_method pos =
1516 let loc = if is_method then "Method" else "Parameter" in
1517 add (NastCheck.err_code NastCheck.ConditionallyReactiveAnnotationInvalidArguments) pos (
1518 loc ^ " is marked with <<__OnlyRxIfImpl>> attribute that have " ^
1519 "invalid arguments. This attribute must have one argument and it should be " ^
1520 "'::class' class constant."
1523 let coroutine_in_constructor pos =
1524 add (NastCheck.err_code NastCheck.CoroutineInConstructor) pos
1525 "A class constructor may not be a coroutine"
1527 let illegal_by_ref_expr pos str verb =
1528 add (NastCheck.err_code NastCheck.IllegalByRefExpr) pos
1529 (str ^ " cannot be " ^ verb ^ " by reference")
1531 let variadic_byref_param pos =
1532 add (NastCheck.err_code NastCheck.VariadicByRefParam) pos
1533 "Variadic parameters should not be taken by reference"
1535 let byref_dynamic_call pos =
1536 add (NastCheck.err_code NastCheck.ByRefDynamicCall) pos
1537 "Arguments can not be passed by reference to dynamic function calls"
1539 let classname_const_instanceof class_name pos =
1540 add (NastCheck.err_code NastCheck.ClassnameConstInstanceOf) pos
1541 (class_name^"::class is redundant in an instanceof, just write '"^class_name^"'.")
1543 let byref_on_property pos =
1544 add (NastCheck.err_code NastCheck.ByRefProperty) pos
1545 "Properties cannot be passed by reference"
1547 (*****************************************************************************)
1548 (* Nast terminality *)
1549 (*****************************************************************************)
1551 let case_fallthrough pos1 pos2 =
1552 add_list (NastCheck.err_code NastCheck.CaseFallthrough) [
1553 pos1, ("This switch has a case that implicitly falls through and is "^
1554 "not annotated with // FALLTHROUGH");
1555 pos2, "This case implicitly falls through"
1558 let default_fallthrough pos =
1559 add (NastCheck.err_code NastCheck.DefaultFallthrough) pos
1560 ("This switch has a default case that implicitly falls "^
1561 "through and is not annotated with // FALLTHROUGH")
1563 (*****************************************************************************)
1564 (* Typing errors *)
1565 (*****************************************************************************)
1567 let visibility_extends vis pos parent_pos parent_vis =
1568 let msg1 = pos, "This member visibility is: " ^ vis in
1569 let msg2 = parent_pos, parent_vis ^ " was expected" in
1570 add_list (Typing.err_code Typing.VisibilityExtends) [msg1; msg2]
1572 let member_not_implemented member_name parent_pos pos defn_pos =
1573 let msg1 = pos, "This type doesn't implement the method "^member_name in
1574 let msg2 = parent_pos, "Which is required by this interface" in
1575 let msg3 = defn_pos, "As defined here" in
1576 add_list (Typing.err_code Typing.MemberNotImplemented) [msg1; msg2; msg3]
1578 let bad_decl_override parent_pos parent_name pos name (error: error) =
1579 let msg1 = pos, ("Class " ^ (strip_ns name)
1580 ^ " does not correctly implement all required members ") in
1581 let msg2 = parent_pos,
1582 ("Some members are incompatible with those declared in type "
1583 ^ (strip_ns parent_name) ^
1584 "\nRead the following to see why:"
1585 ) in
1586 (* This is a cascading error message *)
1587 let code, msgl = (get_code error), (to_list error) in
1588 add_list code (msg1 :: msg2 :: msgl)
1590 let bad_method_override pos member_name (error: error) =
1591 let msg = pos, ("Member " ^ (strip_ns member_name)
1592 ^ " has the wrong type") in
1593 (* This is a cascading error message *)
1594 let code, msgl = (get_code error), (to_list error) in
1595 add_list code (msg :: msgl)
1597 let bad_enum_decl pos (error: error) =
1598 let msg = pos,
1599 "This enum declaration is invalid.\n\
1600 Read the following to see why:"
1602 (* This is a cascading error message *)
1603 let code, msgl = (get_code error), (to_list error) in
1604 add_list code (msg :: msgl)
1606 let missing_constructor pos =
1607 add (Typing.err_code Typing.MissingConstructor) pos
1608 "The constructor is not implemented"
1610 let typedef_trail_entry pos =
1611 pos, "Typedef definition comes from here"
1613 let add_with_trail code errs trail =
1614 add_list code (errs @ List.map trail typedef_trail_entry)
1616 let enum_constant_type_bad pos ty_pos ty trail =
1617 add_with_trail (Typing.err_code Typing.EnumConstantTypeBad)
1618 [pos, "Enum constants must be an int or string";
1619 ty_pos, "Not " ^ ty]
1620 trail
1622 let enum_type_bad pos ty trail =
1623 add_with_trail (Typing.err_code Typing.EnumTypeBad)
1624 [pos, "Enums must be int or string, not " ^ ty]
1625 trail
1627 let enum_type_typedef_nonnull pos =
1628 add (Typing.err_code Typing.EnumTypeTypedefNonnull) pos
1629 "Can't use typedef that resolves to nonnull in enum"
1631 let enum_switch_redundant const first_pos second_pos =
1632 add_list (Typing.err_code Typing.EnumSwitchRedundant) [
1633 second_pos, "Redundant case statement";
1634 first_pos, const ^ " already handled here"
1637 let enum_switch_nonexhaustive pos missing enum_pos =
1638 add_list (Typing.err_code Typing.EnumSwitchNonexhaustive) [
1639 pos, "Switch statement nonexhaustive; the following cases are missing: " ^
1640 String.concat ~sep:", " missing;
1641 enum_pos, "Enum declared here"
1644 let enum_switch_redundant_default pos enum_pos =
1645 add_list (Typing.err_code Typing.EnumSwitchRedundantDefault) [
1646 pos, "All cases already covered; a redundant default case prevents "^
1647 "detecting future errors";
1648 enum_pos, "Enum declared here"
1651 let enum_switch_not_const pos =
1652 add (Typing.err_code Typing.EnumSwitchNotConst) pos
1653 "Case in switch on enum is not an enum constant"
1655 let enum_switch_wrong_class pos expected got =
1656 add (Typing.err_code Typing.EnumSwitchWrongClass) pos
1657 ("Switching on enum " ^ expected ^ " but using constant from " ^ got)
1659 let invalid_shape_field_name p =
1660 add (Typing.err_code Typing.InvalidShapeFieldName) p
1661 "Was expecting a constant string, class constant, or int (for shape access)"
1663 let invalid_shape_field_name_empty p =
1664 add (Typing.err_code Typing.InvalidShapeFieldNameEmpty) p
1665 "A shape field name cannot be an empty string"
1667 let invalid_shape_field_type pos ty_pos ty trail =
1668 add_with_trail (Typing.err_code Typing.InvalidShapeFieldType)
1669 [pos, "A shape field name must be an int or string";
1670 ty_pos, "Not " ^ ty]
1671 trail
1673 let invalid_shape_field_literal key_pos witness_pos =
1674 add_list (Typing.err_code Typing.InvalidShapeFieldLiteral)
1675 [key_pos, "Shape uses literal string as field name";
1676 witness_pos, "But expected a class constant"]
1678 let invalid_shape_field_const key_pos witness_pos =
1679 add_list (Typing.err_code Typing.InvalidShapeFieldConst)
1680 [key_pos, "Shape uses class constant as field name";
1681 witness_pos, "But expected a literal string"]
1683 let shape_field_class_mismatch key_pos witness_pos key_class witness_class =
1684 add_list (Typing.err_code Typing.ShapeFieldClassMismatch)
1685 [key_pos, "Shape field name is class constant from " ^ key_class;
1686 witness_pos, "But expected constant from " ^ witness_class]
1688 let shape_field_type_mismatch key_pos witness_pos key_ty witness_ty =
1689 add_list (Typing.err_code Typing.ShapeFieldTypeMismatch)
1690 [key_pos, "Shape field name is " ^ key_ty ^ " class constant";
1691 witness_pos, "But expected " ^ witness_ty]
1693 let missing_field pos1 pos2 name =
1694 add_list (Typing.err_code Typing.MissingField) (
1695 (pos1, "The field '"^name^"' is missing")::
1696 [pos2, "The field '"^name^"' is defined"])
1698 let unknown_field_disallowed_in_shape pos1 pos2 name =
1699 add_list
1700 (Typing.err_code Typing.UnknownFieldDisallowedInShape)
1702 pos1,
1703 "The field '" ^ name ^ "' is not defined in this shape type, and \
1704 this shape type does not allow unknown fields.";
1705 pos2,
1706 "The field '" ^ name ^ "' is set in the shape.";
1709 let shape_fields_unknown pos1 pos2 =
1710 add_list (Typing.err_code Typing.ShapeFieldsUnknown)
1712 pos1,
1713 "This shape type allows unknown fields, and so it may contain fields \
1714 other than those explicitly declared in its declaration.";
1715 pos2,
1716 "It is incompatible with a shape that does not allow unknown fields.";
1719 let shape_field_unset pos1 pos2 name =
1720 add_list (Typing.err_code Typing.ShapeFieldUnset) (
1721 [(pos1, "The field '"^name^"' was unset here");
1722 (pos2, "The field '"^name^"' might be present in this shape because of " ^
1723 "structural subtyping")]
1726 let invalid_shape_remove_key p =
1727 add (Typing.err_code Typing.InvalidShapeRemoveKey) p
1728 "You can only unset fields of local variables"
1730 let unification_cycle pos ty =
1731 add_list (Typing.err_code Typing.UnificationCycle)
1732 [pos, "Type circularity: in order to type-check this expression it " ^
1733 "is necessary for a type [rec] to be equal to type " ^ ty]
1735 let violated_constraint p_cstr (p_tparam, tparam) left right =
1736 add_list (Typing.err_code Typing.UnifyError)
1737 ([(p_cstr, "Some type constraint(s) are violated here");
1738 (p_tparam, Printf.sprintf "%s is a constrained type parameter" tparam)]
1739 @ left
1740 @ right)
1742 let method_variance pos =
1743 add (Typing.err_code Typing.MethodVariance) pos
1744 ("Covariance or contravariance is not allowed in type parameter of \
1745 method or function.")
1747 let explain_constraint ~use_pos ~definition_pos ~param_name (error : error) =
1748 let inst_msg = "Some type constraint(s) here are violated" in
1749 let code, msgl = (get_code error), (to_list error) in
1750 (* There may be multiple constraints instantiated at one spot; avoid
1751 * duplicating the instantiation message *)
1752 let msgl = match msgl with
1753 | (p, x) :: rest when x = inst_msg && p = use_pos -> rest
1754 | _ -> msgl in
1755 let name = Utils.strip_ns param_name in
1756 add_list code begin
1757 [use_pos, inst_msg;
1758 definition_pos, "'" ^ name ^ "' is a constrained type parameter"] @ msgl
1761 let explain_where_constraint ~use_pos ~definition_pos (error : error) =
1762 let inst_msg = "A 'where' type constraint is violated here" in
1763 let code, msgl = (get_code error), (to_list error) in
1764 add_list code begin
1765 [use_pos, inst_msg;
1766 definition_pos, "This is the method with 'where' type constraints"] @ msgl
1769 let explain_tconst_where_constraint ~use_pos ~definition_pos (error: error) =
1770 let inst_msg = "A 'where' type constraint is violated here" in
1771 let code, msgl = (get_code error), (to_list error) in
1772 add_list code begin
1773 [use_pos, inst_msg;
1774 definition_pos,
1775 "This method's where constraints contain a generic type access"] @ msgl
1778 let format_string pos snippet s class_pos fname class_suggest =
1779 add_list (Typing.err_code Typing.FormatString) [
1780 (pos, "I don't understand the format string " ^ snippet ^ " in " ^ s);
1781 (class_pos,
1782 "You can add a new format specifier by adding "
1783 ^fname^"() to "^class_suggest)]
1785 let expected_literal_format_string pos =
1786 add (Typing.err_code Typing.ExpectedLiteralFormatString) pos
1787 "This argument must be a literal format string"
1789 let re_prefixed_non_string pos non_strings =
1790 add (Typing.err_code Typing.RePrefixedNonString) pos
1791 (non_strings^" are not allowed to be to be `re`-prefixed")
1793 let bad_regex_pattern pos s =
1794 add (Typing.err_code Typing.BadRegexPattern) pos
1795 ("Bad regex pattern; "^s^".")
1797 let generic_array_strict p =
1798 add (Typing.err_code Typing.GenericArrayStrict) p
1799 "You cannot have an array without generics in strict mode"
1801 let strict_members_not_known p name =
1802 let name = Utils.strip_ns name in
1803 add (Typing.err_code Typing.StrictMembersNotKnown) p
1804 (name^" has a non-<?hh grandparent; this is not allowed in strict mode"
1805 ^" because that parent may define methods of unknowable name and type")
1807 let option_return_only_typehint p kind =
1808 let (typehint, reason) = match kind with
1809 | `void -> ("?void", "only return implicitly")
1810 | `noreturn -> ("?noreturn", "never return")
1812 add (Typing.err_code Typing.OptionReturnOnlyTypehint) p
1813 (typehint^" is a nonsensical typehint; a function cannot both "^reason
1814 ^" and return null.")
1816 let tuple_syntax p =
1817 add (Typing.err_code Typing.TupleSyntax) p
1818 ("Did you want a tuple? Try (X,Y), not tuple<X,Y>")
1820 let class_arity usage_pos class_pos class_name arity =
1821 add_list (Typing.err_code Typing.ClassArity)
1822 [usage_pos, ("The class "^(Utils.strip_ns class_name)^" expects "^
1823 soi arity^" arguments");
1824 class_pos, "Definition is here"]
1826 let redeclaring_missing_method p trait_method =
1827 add (Typing.err_code Typing.RedeclaringMissingMethod) p
1828 ("Attempting to redeclare a trait method " ^ trait_method ^ " which was never inherited. " ^
1829 "You might be trying to redeclare a non-static method as static or vice-versa.")
1831 let expecting_type_hint p =
1832 add (Typing.err_code Typing.ExpectingTypeHint) p "Was expecting a type hint"
1834 let expecting_type_hint_suggest p ty =
1835 add (Typing.err_code Typing.ExpectingTypeHintSuggest) p
1836 ("Was expecting a type hint (what about: "^ty^")")
1838 let expecting_return_type_hint p =
1839 add (Typing.err_code Typing.ExpectingReturnTypeHint) p
1840 "Was expecting a return type hint"
1842 let expecting_return_type_hint_suggest p ty =
1843 add (Typing.err_code Typing.ExpectingReturnTypeHintSuggest) p
1844 ("Was expecting a return type hint (what about: ': "^ty^"')")
1846 let expecting_awaitable_return_type_hint p =
1847 add (Typing.err_code Typing.ExpectingAwaitableReturnTypeHint) p
1848 "Was expecting an Awaitable return type hint"
1850 let duplicate_using_var pos =
1851 add (Typing.err_code Typing.DuplicateUsingVar) pos
1852 "Local variable already used in 'using' statement"
1854 let illegal_disposable pos verb =
1855 add (Typing.err_code Typing.IllegalDisposable) pos
1856 ("Disposable objects must only be " ^ verb ^ " in a 'using' statement")
1858 let escaping_disposable pos =
1859 add (Typing.err_code Typing.EscapingDisposable) pos
1860 "Variable from 'using' clause may only be used as receiver in method invocation or \
1861 passed to function with <<__AcceptDisposable>> parameter attribute"
1863 let escaping_disposable_parameter pos =
1864 add (Typing.err_code Typing.EscapingDisposableParameter) pos
1865 "Parameter with <<__AcceptDisposable>> attribute may only be used as receiver in method \
1866 invocation or passed to another function with <<__AcceptDisposable>> parameter attribute"
1868 let escaping_this pos =
1869 add (Typing.err_code Typing.EscapingThis) pos
1870 "$this implementing IDisposable or IAsyncDisposable may only be used as receiver in method \
1871 invocation or passed to another function with <<__AcceptDisposable>> parameter attribute"
1873 let escaping_mutable_object pos =
1874 add (Typing.err_code Typing.EscapingMutableObject) pos
1875 "Neither a Mutable nor MaybeMutable object may be captured by an \
1876 anonymous function."
1878 let must_extend_disposable pos =
1879 add (Typing.err_code Typing.MustExtendDisposable) pos
1880 "A disposable type may not extend a class or use a trait that is not disposable"
1882 let accept_disposable_invariant pos1 pos2 =
1883 let msg1 = pos1, "This parameter is marked <<__AcceptDisposable>>" in
1884 let msg2 = pos2, "This parameter is not marked <<__AcceptDisposable>>" in
1885 add_list (Typing.err_code Typing.AcceptDisposableInvariant) [msg1; msg2]
1887 let field_kinds pos1 pos2 =
1888 add_list (Typing.err_code Typing.FieldKinds)
1889 [pos1, "You cannot use this kind of field (value)";
1890 pos2, "Mixed with this kind of field (key => value)"]
1892 let unbound_name_typing pos name =
1893 add (Typing.err_code Typing.UnboundNameTyping) pos
1894 ("Unbound name (typing): "^(strip_ns name))
1896 let previous_default p =
1897 add (Typing.err_code Typing.PreviousDefault) p
1898 ("A previous parameter has a default value.\n"^
1899 "Remove all the default values for the preceding parameters,\n"^
1900 "or add a default value to this one.")
1902 let return_only_typehint p kind =
1903 let msg = match kind with
1904 | `void -> "void"
1905 | `noreturn -> "noreturn" in
1906 add (Naming.err_code Naming.ReturnOnlyTypehint) p
1907 ("The "^msg^" typehint can only be used to describe a function return type")
1909 let unexpected_type_arguments p =
1910 add (Naming.err_code Naming.UnexpectedTypeArguments) p
1911 ("Type arguments are not expected for this type")
1913 let too_many_type_arguments p =
1914 add (Naming.err_code Naming.TooManyTypeArguments) p
1915 ("Too many type arguments for this type")
1917 let return_in_void pos1 pos2 =
1918 add_list (Typing.err_code Typing.ReturnInVoid) [
1919 pos1,
1920 "You cannot return a value";
1921 pos2,
1922 "This is a void function"
1925 let this_var_outside_class p =
1926 add (Typing.err_code Typing.ThisVarOutsideClass) p "Can't use $this outside of a class"
1928 let unbound_global cst_pos =
1929 add (Typing.err_code Typing.UnboundGlobal) cst_pos "Unbound global constant (Typing)"
1931 let private_inst_meth ~def_pos ~use_pos =
1932 add_list (Typing.err_code Typing.PrivateInstMeth) [
1933 use_pos, "You cannot use this method with inst_meth \
1934 (whether you are in the same class or not).";
1935 def_pos, "It is declared as private here";
1938 let protected_inst_meth ~def_pos ~use_pos =
1939 add_list (Typing.err_code Typing.ProtectedInstMeth) [
1940 use_pos, "You cannot use this method with inst_meth \
1941 (whether you are in the same class hierarchy or not).";
1942 def_pos, "It is declared as protected here";
1945 let private_class_meth ~def_pos ~use_pos =
1946 add_list (Typing.err_code Typing.PrivateClassMeth) [
1947 use_pos, "You cannot use this method with class_meth \
1948 (whether you are in the same class or not).";
1949 def_pos, "It is declared as private here";
1952 let protected_class_meth ~def_pos ~use_pos =
1953 add_list (Typing.err_code Typing.ProtectedClassMeth) [
1954 use_pos, "You cannot use this method with class_meth \
1955 (whether you are in the same class hierarchy or not).";
1956 def_pos, "It is declared as protected here";
1959 let array_cast pos =
1960 add (Typing.err_code Typing.ArrayCast) pos
1961 "(array) cast forbidden; arrays with unspecified \
1962 key and value types are not allowed"
1964 let string_cast pos ty =
1965 add (Typing.err_code Typing.StringCast) pos @@
1966 Printf.sprintf
1967 "Cannot cast a value of type %s to string.\n\
1968 Only primitives may be used in a (string) cast.\n\
1969 If you are trying to cast a Stringish type, please use `stringish_cast`.\n\
1970 This functionality is being removed from HHVM."
1973 let nullable_cast pos ty ty_pos =
1974 add_list (Typing.err_code Typing.NullableCast) [
1975 pos, "Casting from a nullable type is forbidden";
1976 ty_pos, "This is "^ty;
1979 let anonymous_recursive pos =
1980 add (Typing.err_code Typing.AnonymousRecursive) pos
1981 "Anonymous functions cannot be recursive"
1983 let static_outside_class pos =
1984 add (Typing.err_code Typing.StaticOutsideClass) pos
1985 "'static' is undefined outside of a class"
1987 let self_outside_class pos =
1988 add (Typing.err_code Typing.SelfOutsideClass) pos
1989 "'self' is undefined outside of a class"
1991 let new_inconsistent_construct new_pos (cpos, cname) kind =
1992 let name = Utils.strip_ns cname in
1993 let preamble = match kind with
1994 | `static -> "Can't use new static() for "^name
1995 | `classname -> "Can't use new on classname<"^name^">"
1997 add_list (Typing.err_code Typing.NewStaticInconsistent) [
1998 new_pos, preamble^"; __construct arguments are not \
1999 guaranteed to be consistent in child classes";
2000 cpos, ("This declaration is neither final nor uses \
2001 the <<__ConsistentConstruct>> attribute")]
2003 let pair_arity pos =
2004 add (Typing.err_code Typing.PairArity) pos "A pair has exactly 2 elements"
2006 let undefined_parent pos =
2007 add (Typing.err_code Typing.UndefinedParent) pos
2008 "The parent class is undefined"
2010 let parent_outside_class pos =
2011 add (Typing.err_code Typing.ParentOutsideClass) pos
2012 "'parent' is undefined outside of a class"
2014 let parent_abstract_call meth_name call_pos decl_pos =
2015 add_list (Typing.err_code Typing.AbstractCall) [
2016 call_pos, ("Cannot call parent::"^meth_name^"(); it is abstract");
2017 decl_pos, "Declaration is here"
2020 let self_abstract_call meth_name call_pos decl_pos =
2021 add_list (Typing.err_code Typing.AbstractCall) [
2022 call_pos, ("Cannot call self::"^meth_name^"(); it is abstract. Did you mean static::"^meth_name^"()?");
2023 decl_pos, "Declaration is here"
2026 let classname_abstract_call cname meth_name call_pos decl_pos =
2027 let cname = Utils.strip_ns cname in
2028 add_list (Typing.err_code Typing.AbstractCall) [
2029 call_pos, ("Cannot call "^cname^"::"^meth_name^"(); it is abstract");
2030 decl_pos, "Declaration is here"
2033 let static_synthetic_method cname meth_name call_pos decl_pos =
2034 let cname = Utils.strip_ns cname in
2035 add_list (Typing.err_code Typing.StaticSyntheticMethod) [
2036 call_pos, ("Cannot call "^cname^"::"^meth_name^"(); "^meth_name^" is not defined in "^cname);
2037 decl_pos, "Declaration is here"
2040 let isset_in_strict pos =
2041 add (Typing.err_code Typing.IssetEmptyInStrict) pos
2042 ("isset tends to hide errors due to variable typos and so is limited to dynamic checks in "
2043 ^"strict mode")
2045 let unset_nonidx_in_strict pos msgs =
2046 add_list (Typing.err_code Typing.UnsetNonidxInStrict)
2047 ([pos, "In strict mode, unset is banned except on array, keyset, "^
2048 "or dict indexing"] @
2049 msgs)
2051 let unset_nonidx_in_strict_no_varray pos msgs =
2052 add_list (Typing.err_code Typing.UnsetNonidxInStrict)
2053 ([pos, "In strict mode, unset is banned except on dict-like array, "^
2054 "darray, keyset, or dict indexing"] @
2055 msgs)
2057 let unpacking_disallowed_builtin_function pos name =
2058 let name = Utils.strip_ns name in
2059 add (Typing.err_code Typing.UnpackingDisallowed) pos
2060 ("Arg unpacking is disallowed for "^name)
2062 let array_get_arity pos1 name pos2 =
2063 add_list (Typing.err_code Typing.ArrayGetArity) [
2064 pos1, "You cannot use this "^(Utils.strip_ns name);
2065 pos2, "It is missing its type parameters"
2068 let typing_error pos msg =
2069 add (Typing.err_code Typing.GenericUnify) pos msg
2071 let undefined_field ~use_pos ~name ~shape_type_pos =
2072 add_list (Typing.err_code Typing.UndefinedField) [
2073 use_pos, "The field "^name^" is undefined";
2074 shape_type_pos, "Definition is here"
2077 let array_access pos1 pos2 ty =
2078 add_list (Typing.err_code Typing.ArrayAccess)
2079 ((pos1, "This is not an object of type KeyedContainer, this is "^ty) ::
2080 if not (phys_equal pos2 Pos.none)
2081 then [pos2, "Definition is here"]
2082 else [])
2084 let keyset_set pos1 pos2 =
2085 add_list (Typing.err_code Typing.KeysetSet)
2086 ((pos1, "Elements in a keyset cannot be assigned, use append instead.") ::
2087 if not (phys_equal pos2 Pos.none)
2088 then [pos2, "Definition is here"]
2089 else [])
2091 let array_append pos1 pos2 ty =
2092 add_list (Typing.err_code Typing.ArrayAppend)
2093 ((pos1, ty^" does not allow array append") ::
2094 if not (phys_equal pos2 Pos.none)
2095 then [pos2, "Definition is here"]
2096 else [])
2098 let const_mutation pos1 pos2 ty =
2099 add_list (Typing.err_code Typing.ConstMutation)
2100 ((pos1, "You cannot mutate this") ::
2101 if not (phys_equal pos2 Pos.none)
2102 then [(pos2, "This is " ^ ty)]
2103 else [])
2105 let expected_class ?(suffix="") pos =
2106 add (Typing.err_code Typing.ExpectedClass) pos ("Was expecting a class"^suffix)
2108 let unknown_type description pos r =
2109 let msg = ("Was expecting " ^ description ^ " but type is unknown") in
2110 add_list (Typing.err_code Typing.UnknownType)
2111 ([pos, msg] @ r)
2113 let snot_found_hint = function
2114 | `no_hint ->
2116 | `closest (pos, v) ->
2117 [pos, "The closest thing is "^v^" but it's not a static method"]
2118 | `did_you_mean (pos, v) ->
2119 [pos, "Did you mean: "^v]
2121 let string_of_class_member_kind = function
2122 | `class_constant -> "class constant"
2123 | `static_method -> "static method"
2124 | `class_variable -> "class variable"
2125 | `class_typeconst -> "type constant"
2127 let smember_not_found kind pos (cpos, class_name) member_name hint =
2128 let kind = string_of_class_member_kind kind in
2129 let class_name = strip_ns class_name in
2130 let msg = "Could not find "^kind^" "^member_name^" in type "^class_name in
2131 add_list (Typing.err_code Typing.SmemberNotFound)
2132 ((pos, msg) :: (snot_found_hint hint
2133 @ [(cpos, "Declaration of "^class_name^" is here")]))
2135 let not_found_hint = function
2136 | `no_hint ->
2138 | `closest (pos, v) ->
2139 [pos, "The closest thing is "^v^" but it's a static method"]
2140 | `did_you_mean (pos, v) ->
2141 [pos, "Did you mean: "^v]
2143 let member_not_found kind pos (cpos, type_name) member_name hint reason =
2144 let type_name = strip_ns type_name in
2145 let kind =
2146 match kind with
2147 | `method_ -> "method"
2148 | `member -> "member"
2150 let msg = "Could not find "^kind^" "^member_name^" in an object of type "^
2151 type_name in
2152 add_list (Typing.err_code Typing.MemberNotFound)
2153 ((pos, msg) :: (not_found_hint hint @ reason
2154 @ [(cpos, "Declaration of "^type_name^" is here")]))
2156 let parent_in_trait pos =
2157 add (Typing.err_code Typing.ParentInTrait) pos
2158 ("parent:: inside a trait is undefined"
2159 ^" without 'require extends' of a class defined in <?hh")
2161 let parent_undefined pos =
2162 add (Typing.err_code Typing.ParentUndefined) pos
2163 "parent is undefined"
2165 let constructor_no_args pos =
2166 add (Typing.err_code Typing.ConstructorNoArgs) pos
2167 "This constructor expects no argument"
2169 let visibility p msg1 p_vis msg2 =
2170 add_list (Typing.err_code Typing.Visibility) [p, msg1; p_vis, msg2]
2172 let typing_too_many_args expected actual pos pos_def =
2173 add_list (Typing.err_code Typing.TypingTooManyArgs)
2174 [(pos,
2175 Printf.sprintf "Too many arguments (expected %d but got %d)" expected actual);
2176 (pos_def, "Definition is here")]
2178 let typing_too_few_args required actual pos pos_def =
2179 add_list (Typing.err_code Typing.TypingTooFewArgs)
2180 [(pos,
2181 Printf.sprintf "Too few arguments (required %d but got %d)" required actual);
2182 (pos_def, "Definition is here")]
2184 let anonymous_recursive_call pos =
2185 add (Typing.err_code Typing.AnonymousRecursiveCall) pos
2186 "recursive call to anonymous function"
2188 let bad_call pos ty =
2189 add (Typing.err_code Typing.BadCall) pos
2190 ("This call is invalid, this is not a function, it is "^ty)
2192 let extend_final extend_pos decl_pos name =
2193 let name = (strip_ns name) in
2194 add_list (Typing.err_code Typing.ExtendFinal) [
2195 extend_pos, ("You cannot extend final class "^name);
2196 decl_pos, "Declaration is here"
2199 let extend_sealed child_pos parent_pos parent_name parent_kind verb =
2200 let name = (strip_ns parent_name) in
2201 add_list (Typing.err_code Typing.ExtendSealed) [
2202 child_pos, ("You cannot "^verb^" sealed "^parent_kind^" "^name);
2203 parent_pos, "Declaration is here"
2206 let extend_ppl
2207 child_pos child_class_type child_is_ppl parent_pos parent_class_type parent_name verb =
2208 let name = (strip_ns parent_name) in
2209 let warning =
2210 if child_is_ppl
2211 then child_class_type^" annotated with <<__PPL>> cannot "^verb^
2212 " non <<__PPL>> "^parent_class_type^": "^name
2213 else child_class_type^" must be annotated with <<__PPL>> to "^verb^
2214 " <<__PPL>> "^parent_class_type^": "^name in
2215 add_list (Typing.err_code Typing.ExtendPPL) [
2216 child_pos, warning;
2217 parent_pos, "Declaration is here";
2220 let read_before_write (pos, v) =
2221 add (Typing.err_code Typing.ReadBeforeWrite) pos (
2223 "Read access to $this->"; v; " before initialization"
2226 let interface_final pos =
2227 add (Typing.err_code Typing.InterfaceFinal) pos
2228 "Interfaces cannot be final"
2230 let trait_final pos =
2231 add (Typing.err_code Typing.TraitFinal) pos
2232 "Traits cannot be final"
2234 let final_property pos =
2235 add (Typing.err_code Typing.FinalProperty) pos "Properties cannot be declared final"
2237 let implement_abstract ~is_final pos1 pos2 kind x =
2238 let name = "abstract "^kind^" '"^x^"'" in
2239 let msg1 =
2240 if is_final then
2241 "This class was declared as final. It must provide an implementation \
2242 for the "^name
2243 else
2244 "This class must be declared abstract, or provide an implementation \
2245 for the "^name in
2246 add_list (Typing.err_code Typing.ImplementAbstract) [
2247 pos1, msg1;
2248 pos2, "Declaration is here";
2251 let generic_static pos x =
2252 add (Typing.err_code Typing.GenericStatic) pos (
2253 "This static variable cannot use the type parameter "^x^"."
2256 let fun_too_many_args pos1 pos2 =
2257 add_list (Typing.err_code Typing.FunTooManyArgs) [
2258 pos1, "Too many mandatory arguments";
2259 pos2, "Because of this definition";
2262 let fun_too_few_args pos1 pos2 =
2263 add_list (Typing.err_code Typing.FunTooFewArgs) [
2264 pos1, "Too few arguments";
2265 pos2, "Because of this definition";
2268 let fun_unexpected_nonvariadic pos1 pos2 =
2269 add_list (Typing.err_code Typing.FunUnexpectedNonvariadic) [
2270 pos1, "Should have a variadic argument";
2271 pos2, "Because of this definition";
2274 let fun_variadicity_hh_vs_php56 pos1 pos2 =
2275 add_list (Typing.err_code Typing.FunVariadicityHhVsPhp56) [
2276 pos1, "Variadic arguments: ...-style is not a subtype of ...$args";
2277 pos2, "Because of this definition";
2280 let ellipsis_strict_mode ~require pos =
2281 let msg = match require with
2282 | `Type -> "Cannot use ... without a type hint in strict mode. Please add a type hint."
2283 | `Param_name ->
2284 "Cannot use ... without a parameter name in strict mode. Please add a parameter name."
2285 | `Type_and_param_name ->
2286 "Cannot use ... without a type hint and parameter name in strict mode. \
2287 Please add a type hint and parameter name."
2289 add (Typing.err_code Typing.EllipsisStrictMode) pos msg
2291 let untyped_lambda_strict_mode pos =
2292 let msg =
2293 "Cannot determine types of lambda parameters in strict mode. \
2294 Please add type hints on parameters."
2296 add (Typing.err_code Typing.UntypedLambdaStrictMode) pos msg
2298 let echo_in_reactive_context pos =
2299 add (Typing.err_code Typing.EchoInReactiveContext) pos (
2300 "'echo' or 'print' are not allowed in reactive functions."
2303 let expected_tparam ~use_pos ~definition_pos n =
2304 add_list (Typing.err_code Typing.ExpectedTparam)
2306 use_pos, "Expected " ^
2307 (match n with
2308 | 0 -> "no type parameter"
2309 | 1 -> "a type parameter"
2310 | n -> string_of_int n ^ " type parameters"
2312 definition_pos, "Definition is here"
2315 let object_string pos1 pos2 =
2316 add_list (Typing.err_code Typing.ObjectString) [
2317 pos1, "You cannot use this object as a string";
2318 pos2, "This object doesn't implement __toString";
2321 let object_string_deprecated pos =
2322 add (Typing.err_code Typing.ObjectString) pos
2323 "You cannot use this object as a string\n\
2324 Implicit conversions of Stringish objects to string are deprecated."
2326 let type_param_arity pos x n =
2327 add (Typing.err_code Typing.TypeParamArity) pos (
2328 "The type "^x^" expects "^n^" parameters"
2331 let cyclic_typedef p =
2332 add (Typing.err_code Typing.CyclicTypedef) p
2333 "Cyclic typedef"
2335 let type_arity_mismatch pos1 n1 pos2 n2 =
2336 add_list (Typing.err_code Typing.TypeArityMismatch) [
2337 pos1, "This type has "^n1^" arguments";
2338 pos2, "This one has "^n2;
2341 let this_final id pos2 (error: error) =
2342 let n = Utils.strip_ns (snd id) in
2343 let message1 = "Since "^n^" is not final" in
2344 let message2 = "this might not be a "^n in
2345 let code, msgl = (get_code error), (to_list error) in
2346 add_list code (msgl @ [(fst id, message1); (pos2, message2)])
2348 let exact_class_final id pos2 (error: error) =
2349 let n = Utils.strip_ns (snd id) in
2350 let message1 = "This requires the late-bound type to be exactly "^n in
2351 let message2 =
2352 "Since " ^n^" is not final this might be an instance of a child class" in
2353 let code, msgl = (get_code error), (to_list error) in
2354 add_list code (msgl @ [(fst id, message1); (pos2, message2)])
2356 let fun_arity_mismatch pos1 pos2 =
2357 add_list (Typing.err_code Typing.FunArityMismatch) [
2358 pos1, "Number of arguments doesn't match";
2359 pos2, "Because of this definition";
2362 let fun_reactivity_mismatch pos1 kind1 pos2 kind2 =
2363 let f k = "This function is " ^ k ^ "." in
2364 add_list
2365 (Typing.err_code Typing.FunReactivityMismatch)
2367 pos1, f kind1;
2368 pos2, f kind2
2371 let inconsistent_mutability pos1 mut1 p2_opt =
2372 match p2_opt with
2373 | Some (pos2, mut2) ->
2374 add_list (Typing.err_code Typing.InconsistentMutability) [
2375 pos1, "Inconsistent mutability of local variable, here local is " ^ mut1;
2376 pos2, "But here it is " ^ mut2;
2378 | None ->
2379 add (Typing.err_code Typing.InconsistentMutability) pos1
2380 ("Local is " ^ mut1 ^ " in one scope and immutable in another.")
2382 let inconsistent_mutability_for_conditional p_mut p_other =
2383 add_list (Typing.err_code Typing.InconsistentMutability) [
2384 p_mut, "Inconsistent mutability of conditional expression, this branch returns owned \
2385 mutable value";
2386 p_other, "But this one does not.";
2389 let invalid_mutability_flavor pos mut1 mut2 =
2390 add (Typing.err_code Typing.InvalidMutabilityFlavorInAssignment) pos
2391 ("Cannot assign " ^ mut2 ^ " value to " ^ mut1 ^ " local variable. \
2392 Mutability flavor of local variable cannot be altered.")
2394 let reassign_mutable_var ~in_collection pos1 =
2395 let msg =
2396 if in_collection
2397 then "This variable is mutable. You cannot create a new reference to it \
2398 by putting it into the collection."
2399 else "This variable is mutable. You cannot create a new reference to it." in
2400 add (Typing.err_code Typing.ReassignMutableVar) pos1 msg
2402 let reassign_mutable_this ~in_collection ~is_maybe_mutable pos1 =
2403 let kind =
2404 if is_maybe_mutable
2405 then "maybe mutable"
2406 else "mutable" in
2407 let msg =
2408 if in_collection
2409 then "$this here is " ^ kind ^ ". You cannot create a new reference to it \
2410 by putting it into the collection."
2411 else "$this here is " ^ kind ^ ". You cannot create a new reference to it." in
2412 add (Typing.err_code Typing.ReassignMutableThis) pos1 msg
2414 let mutable_expression_as_multiple_mutable_arguments pos param_kind prev_pos prev_param_kind =
2415 add_list (Typing.err_code Typing.MutableExpressionAsMultipleMutableArguments) [
2416 pos, "A mutable expression may not be passed as multiple arguments where \
2417 at least one matching parameter is mutable. Matching parameter here is " ^ param_kind;
2418 prev_pos, "This is where it was used before, being passed as " ^ prev_param_kind
2421 let reassign_maybe_mutable_var ~in_collection pos1 =
2422 let msg =
2423 if in_collection
2424 then "This variable is maybe mutable. You cannot create a new reference to it \
2425 by putting it into the collection."
2426 else "This variable is maybe mutable. You cannot create a new reference to it." in
2427 add (Typing.err_code Typing.ReassignMaybeMutableVar) pos1 msg
2429 let mutable_call_on_immutable fpos pos1 rx_mutable_hint_pos =
2430 let l =
2431 match rx_mutable_hint_pos with
2432 | Some p ->
2433 [p, "Consider wrapping this expression with Rx\\mutable to forward mutability."]
2434 | None -> []
2436 let l =
2437 (pos1, "Cannot call mutable function on immutable expression") ::
2438 (fpos, "This function is marked <<__Mutable>>, so it has a mutable $this.") ::
2441 add_list (Typing.err_code Typing.MutableCallOnImmutable) l
2443 let immutable_call_on_mutable fpos pos1 =
2444 add_list (Typing.err_code Typing.ImmutableCallOnMutable)
2446 pos1, "Cannot call non-mutable function on mutable expression";
2447 fpos, "This function is not marked as <<__Mutable>>.";
2450 let mutability_mismatch ~is_receiver pos1 mut1 pos2 mut2 =
2451 let msg mut =
2452 let msg = if is_receiver then "Receiver of this function" else "This parameter" in
2453 msg ^ " is " ^ mut in
2454 add_list (Typing.err_code Typing.MutabilityMismatch)
2456 pos1, "Incompatible mutabilities:";
2457 pos1, msg mut1;
2458 pos2, msg mut2;
2461 let invalid_call_on_maybe_mutable ~fun_is_mutable pos fpos =
2462 let msg =
2463 "Cannot call " ^ (if fun_is_mutable then "mutable" else "non-mutable") ^ " \
2464 function on maybe mutable value." in
2465 add_list (Typing.err_code Typing.InvalidCallMaybeMutable)
2467 pos, msg;
2468 fpos, "This function is not marked as <<__MaybeMutable>>."
2471 let mutable_argument_mismatch param_pos arg_pos =
2472 add_list (Typing.err_code Typing.MutableArgumentMismatch)
2474 arg_pos, "Invalid argument";
2475 param_pos, "This parameter is marked mutable";
2476 arg_pos, "But this expression is not";
2479 let immutable_argument_mismatch param_pos arg_pos =
2480 add_list (Typing.err_code Typing.ImmutableArgumentMismatch)
2482 arg_pos, "Invalid argument";
2483 param_pos, "This parameter is not marked as mutable";
2484 arg_pos, "But this expression is mutable";
2487 let mutably_owned_argument_mismatch ~arg_is_owned_local param_pos arg_pos =
2488 let arg_msg =
2489 if arg_is_owned_local
2490 then "Owned mutable locals used as argument should be passed via \
2491 Rx\\move function"
2492 else "But this expression is not owned mutable" in
2493 add_list (Typing.err_code Typing.ImmutableArgumentMismatch)
2495 arg_pos, "Invalid argument";
2496 param_pos, "This parameter is marked with <<__OwnedMutable>>";
2497 arg_pos, arg_msg;
2500 let maybe_mutable_argument_mismatch param_pos arg_pos =
2501 add_list (Typing.err_code Typing.MaybeMutableArgumentMismatch)
2503 arg_pos, "Invalid argument";
2504 param_pos, "This parameter is not marked <<__MaybeMutable>>";
2505 arg_pos, "But this expression is maybe mutable"
2508 let invalid_mutable_return_result error_pos function_pos value_kind =
2509 add_list (Typing.err_code Typing.InvalidMutableReturnResult)
2511 error_pos, "Functions marked <<__MutableReturn>> must return mutably owned values: \
2512 mutably owned local variables and results of calling Rx\\mutable.";
2513 function_pos, "This function is marked <<__MutableReturn>>";
2514 error_pos, "This expression is " ^ value_kind
2517 let freeze_in_nonreactive_context pos1 =
2518 add (Typing.err_code Typing.FreezeInNonreactiveContext) pos1
2519 ("\\HH\\Rx\\freeze can only be used in reactive functions")
2521 let mutable_in_nonreactive_context pos =
2522 add (Typing.err_code Typing.MutableInNonreactiveContext) pos
2523 ("\\HH\\Rx\\mutable can only be used in reactive functions")
2525 let move_in_nonreactive_context pos =
2526 add (Typing.err_code Typing.MoveInNonreactiveContext) pos
2527 ("\\HH\\Rx\\move can only be used in reactive functions")
2530 let invalid_argument_type_for_condition_in_rx
2531 ~is_receiver f_pos def_pos arg_pos expected_type actual_type =
2532 let arg_msg =
2533 if is_receiver then "Receiver type" else "Argument type" in
2534 let arg_msg =
2535 arg_msg ^ " must be a subtype of " ^ expected_type ^
2536 ", now " ^ actual_type ^ "." in
2537 add_list (Typing.err_code Typing.InvalidConditionallyReactiveCall) [
2538 f_pos, "Cannot invoke conditionally reactive function in reactive context, \
2539 because at least one reactivity condition is not met.";
2540 arg_pos, arg_msg;
2541 def_pos, "This is the function declaration";
2544 let callsite_reactivity_mismatch f_pos def_pos callee_reactivity cause_pos_opt caller_reactivity =
2545 add_list (Typing.err_code Typing.CallSiteReactivityMismatch) ([
2546 f_pos, "Reactivity mismatch: " ^ caller_reactivity ^ " function cannot call " ^
2547 callee_reactivity ^ " function.";
2548 def_pos, "This is declaration of the function being called."
2549 ] @ Option.value_map cause_pos_opt ~default:[] ~f:(fun cause_pos ->
2550 [cause_pos, "Reactivity of this argument was used as reactivity of the callee."]
2553 let invalid_argument_of_rx_mutable_function pos =
2554 add (Typing.err_code Typing.InvalidArgumentOfRxMutableFunction) pos (
2555 "Single argument to \\HH\\Rx\\mutable should be an expression that yields new \
2556 mutably-owned value, like 'new A()', Hack collection literal or 'f()' where f is function \
2557 annotated with <<__MutableReturn>> attribute."
2560 let invalid_freeze_use pos1 =
2561 add (Typing.err_code Typing.InvalidFreezeUse) pos1
2562 ("freeze takes a single mutably-owned local variable as an argument")
2564 let invalid_move_use pos1 =
2565 add (Typing.err_code Typing.InvalidMoveUse) pos1
2566 ("move takes a single mutably-owned local variable as an argument")
2568 let require_args_reify def_pos arg_pos =
2569 add_list (Typing.err_code Typing.RequireArgsReify) [
2570 arg_pos, "All type arguments must be specified because a type parameter is reified";
2571 def_pos, "Definition is here"
2574 let invalid_reified_argument (def_pos, def_name) arg_pos arg_kind =
2575 add_list (Typing.err_code Typing.InvalidReifiedArgument) [
2576 arg_pos, "This is " ^ arg_kind ^ ", it cannot be used as a reified type argument";
2577 def_pos, def_name ^ " is reified"
2580 let new_static_class_reified pos =
2581 add (Typing.err_code Typing.NewStaticClassReified) pos
2582 "Cannot call new static because the current class has reified generics"
2584 let consistent_construct_reified pos =
2585 add (Typing.err_code Typing.ConsistentConstructReified) pos
2586 "This class or one of its ancestors is annotated with <<__ConsistentConstruct>>. \
2587 It cannot have reified generics."
2589 let new_without_newable pos name =
2590 add (Typing.err_code Typing.NewWithoutNewable) pos
2591 (name ^ " cannot be used with `new` because it does not have the <<__Newable>> attribute")
2593 let reified_tparam_variadic pos =
2594 add (Typing.err_code Typing.NewWithoutNewable) pos
2595 ("A function or method that has a reified type parameter cannot take reified arguments")
2597 let invalid_freeze_target pos1 var_pos var_mutability_str =
2598 add_list (Typing.err_code Typing.InvalidFreezeTarget)
2600 pos1, "Invalid argument - freeze() takes a single mutable variable";
2601 var_pos, "This variable is "^var_mutability_str;
2604 let invalid_move_target pos1 var_pos var_mutability_str =
2605 add_list (Typing.err_code Typing.InvalidMoveTarget)
2607 pos1, "Invalid argument - move() takes a single mutably-owned variable";
2608 var_pos, "This variable is "^var_mutability_str;
2611 let discarded_awaitable pos1 pos2 =
2612 add_list (Typing.err_code Typing.DiscardedAwaitable) [
2613 pos1, "This expression is of type Awaitable, but it's "^
2614 "either being discarded or used in a dangerous way before "^
2615 "being awaited";
2616 pos2, "This is why I think it is Awaitable"
2619 let unify_error left right =
2620 add_list (Typing.err_code Typing.UnifyError) (left @ right)
2623 let elt_type_to_string = function
2624 | `Method -> "method"
2625 | `Property -> "property"
2627 let static_redeclared_as_dynamic dyn_position static_position member_name ~elt_type =
2628 let dollar = match elt_type with `Property -> "$" | _ -> "" in
2629 let elt_type = elt_type_to_string elt_type in
2630 let msg_dynamic = "The "^elt_type^" "^dollar^member_name^" is declared here as non-static" in
2631 let msg_static = "But it conflicts with an inherited static declaration here" in
2632 add_list (Typing.err_code Typing.StaticDynamic) [
2633 dyn_position, msg_dynamic;
2634 static_position, msg_static
2637 let dynamic_redeclared_as_static static_position dyn_position member_name ~elt_type =
2638 let dollar = match elt_type with `Property -> "$" | _ -> "" in
2639 let elt_type = elt_type_to_string elt_type in
2640 let msg_static = "The "^elt_type^" "^dollar^member_name^" is declared here as static" in
2641 let msg_dynamic = "But it conflicts with an inherited non-static declaration here" in
2642 add_list (Typing.err_code Typing.StaticDynamic) [
2643 static_position, msg_static;
2644 dyn_position, msg_dynamic
2647 let null_member s pos r =
2648 add_list (Typing.err_code Typing.NullMember) ([
2649 pos,
2650 "You are trying to access the member "^s^
2651 " but this object can be null. "
2652 ] @ r
2655 let non_object_member s pos1 ty pos2 =
2656 let msg_start = ("You are trying to access the member "^s^
2657 " but this is not an object, it is "^ty) in
2658 let msg =
2659 if ty = "a shape" then
2660 msg_start ^ ". Did you mean $foo['" ^ s ^ "'] instead?"
2661 else
2662 msg_start in
2663 add_list (Typing.err_code Typing.NonObjectMember) [
2664 pos1, msg;
2665 pos2, "Definition is here"
2668 let unknown_object_member s pos r =
2669 let msg = ("You are trying to access the member " ^ s ^ " on a value whose class is unknown") in
2670 add_list (Typing.err_code Typing.UnknownObjectMember)
2671 ([pos, msg] @ r)
2673 let non_class_member s pos1 ty pos2 =
2674 add_list (Typing.err_code Typing.NonClassMember) [
2675 pos1,
2676 ("You are trying to access the member "^s^
2677 " but this is not a class, it is "^
2678 ty);
2679 pos2,
2680 "Definition is here"
2683 let ambiguous_member s pos1 ty pos2 =
2684 add_list (Typing.err_code Typing.AmbiguousMember) [
2685 pos1,
2686 ("You are trying to access the member "^s^
2687 " but there is more than one implementation on "^
2688 ty);
2689 pos2,
2690 "Definition is here"
2693 let null_container p null_witness =
2694 add_list (Typing.err_code Typing.NullContainer) (
2697 "You are trying to access an element of this container"^
2698 " but the container could be null. "
2699 ] @ null_witness)
2701 let option_mixed pos =
2702 add (Typing.err_code Typing.OptionMixed) pos
2703 "?mixed is a redundant typehint - just use mixed"
2705 let option_null pos =
2706 add (Typing.err_code Typing.OptionNull) pos
2707 "?null is a redundant typehint - just use null"
2709 let declared_covariant pos1 pos2 emsg =
2710 add_list (Typing.err_code Typing.DeclaredCovariant) (
2711 [pos2, "Illegal usage of a covariant type parameter";
2712 pos1, "This is where the parameter was declared as covariant (+)"
2713 ] @ emsg
2716 let declared_contravariant pos1 pos2 emsg =
2717 add_list (Typing.err_code Typing.DeclaredContravariant) (
2718 [pos2, "Illegal usage of a contravariant type parameter";
2719 pos1, "This is where the parameter was declared as contravariant (-)"
2720 ] @ emsg
2723 let static_property_type_generic_param ~class_pos ~var_type_pos ~generic_pos =
2724 add_list (Typing.err_code Typing.ClassVarTypeGenericParam)
2725 [generic_pos, "A generic parameter cannot be used in the type of a static property";
2726 var_type_pos, "This is where the type of the static property was declared";
2727 class_pos, "This is the class containing the static property"]
2729 let contravariant_this pos class_name tp =
2730 add (Typing.err_code Typing.ContravariantThis) pos (
2731 "The \"this\" type cannot be used in this " ^
2732 "contravariant position because its enclosing class \"" ^ class_name ^
2733 "\" " ^ "is final and has a variant type parameter \"" ^ tp ^ "\"")
2735 let cyclic_typeconst pos sl =
2736 let sl = List.map sl strip_ns in
2737 add (Typing.err_code Typing.CyclicTypeconst) pos
2738 ("Cyclic type constant:\n "^String.concat ~sep:" -> " sl)
2740 let abstract_concrete_override pos parent_pos kind =
2741 let kind_str = match kind with
2742 | `method_ -> "method"
2743 | `typeconst -> "type constant"
2744 | `constant -> "constant" in
2745 add_list (Typing.err_code Typing.AbstractConcreteOverride) ([
2746 pos, "Cannot re-declare this " ^ kind_str ^ " as abstract";
2747 parent_pos, "Previously defined here"
2750 let instanceof_generic_classname pos name =
2751 add (Typing.err_code Typing.InstanceofGenericClassname) pos
2752 ("'instanceof' cannot be used on 'classname<" ^ name ^ ">' because '" ^
2753 name ^ "' may be instantiated with a type such as \
2754 'C<int>' that cannot be checked at runtime")
2756 let required_field_is_optional pos1 pos2 name =
2757 add_list (Typing.err_code Typing.RequiredFieldIsOptional)
2759 pos1, "The field '"^name^"' is optional";
2760 pos2, "The field '"^name^"' is defined as required"
2763 let array_get_with_optional_field pos1 pos2 name =
2764 add_list
2765 (Typing.err_code Typing.ArrayGetWithOptionalField)
2767 pos1,
2768 "Invalid index operation: '" ^ name ^ "' is marked as an optional shape \
2769 field. It may not be present in the shape. Use the `??` operator \
2770 instead.";
2771 pos2,
2772 "This is where the field was declared as optional."
2775 let non_call_argument_in_suspend pos msgs =
2776 add_list
2777 (Typing.err_code Typing.NonCallArgumentInSuspend) (
2779 pos,
2780 "'suspend' operator expects call to a coroutine as an argument."
2781 ] @ msgs
2783 let non_coroutine_call_in_suspend pos msgs =
2784 add_list
2785 (Typing.err_code Typing.NonCoroutineCallInSuspend) (
2787 pos,
2788 "Only coroutine functions are allowed to be called in \
2789 'suspend' operator."
2790 ] @ msgs
2793 let coroutine_call_outside_of_suspend pos =
2794 add_list
2795 (Typing.err_code Typing.CoroutineCallOutsideOfSuspend)
2797 pos,
2798 "Coroutine calls are only allowed when they are arguments to \
2799 'suspend' operator"
2802 let function_is_not_coroutine pos name =
2803 add_list
2804 (Typing.err_code Typing.FunctionIsNotCoroutine)
2806 pos,
2807 "Function '" ^ name ^ "' is not a coroutine and cannot be \
2808 used in as an argument of 'suspend' operator."
2811 let coroutinness_mismatch pos1_is_coroutine pos1 pos2 =
2812 let m1 = "This is a coroutine." in
2813 let m2 = "This is not a coroutine." in
2814 add_list
2815 (Typing.err_code Typing.CoroutinnessMismatch)
2817 pos1, if pos1_is_coroutine then m1 else m2;
2818 pos2, if pos1_is_coroutine then m2 else m1;
2821 let invalid_ppl_call pos context =
2822 let error_msg = "Cannot call a method on an object of a <<__PPL>> class "^context in
2823 add (Typing.err_code Typing.InvalidPPLCall) pos error_msg
2825 let invalid_ppl_static_call pos reason =
2826 let error_msg = "Cannot call a static method on a <<__PPL>> class "^reason in
2827 add (Typing.err_code Typing.InvalidPPLStaticCall) pos error_msg
2829 let ppl_meth_pointer pos func =
2830 let error_msg = func^" cannot be used with a <<__PPL>> class" in
2831 add (Typing.err_code Typing.PPLMethPointer) pos error_msg
2833 let coroutine_outside_experimental pos =
2834 add (Typing.err_code Typing.CoroutineOutsideExperimental) pos
2835 Coroutine_errors.error_message
2837 let return_disposable_mismatch pos1_return_disposable pos1 pos2 =
2838 let m1 = "This is marked <<__ReturnDisposable>>." in
2839 let m2 = "This is not marked <<__ReturnDisposable>>." in
2840 add_list
2841 (Typing.err_code Typing.ReturnDisposableMismatch)
2843 pos1, if pos1_return_disposable then m1 else m2;
2844 pos2, if pos1_return_disposable then m2 else m1;
2847 let return_void_to_rx_mismatch ~pos1_has_attribute pos1 pos2 =
2848 let m1 = "This is marked <<__ReturnsVoidToRx>>." in
2849 let m2 = "This is not marked <<__ReturnsVoidToRx>>." in
2850 add_list
2851 (Typing.err_code Typing.ReturnVoidToRxMismatch)
2853 pos1, if pos1_has_attribute then m1 else m2;
2854 pos2, if pos1_has_attribute then m2 else m1;
2857 let this_as_lexical_variable pos =
2858 add (Naming.err_code Naming.ThisAsLexicalVariable) pos "Cannot use $this as lexical variable"
2860 let dollardollar_lvalue pos =
2861 add (Typing.err_code Typing.DollardollarLvalue) pos
2862 "Cannot assign a value to the special pipe variable ($$)"
2864 let assigning_to_const pos =
2865 add (Typing.err_code Typing.AssigningToConst) pos
2866 "Cannot assign to a __Const property"
2868 let self_const_parent_not pos =
2869 add (Typing.err_code Typing.SelfConstParentNot) pos
2870 "A __Const class may only extend other __Const classes"
2872 let parent_const_self_not pos =
2873 add (Typing.err_code Typing.ParentConstSelfNot) pos
2874 "Only __Const classes may extend a __Const class"
2876 let overriding_prop_const_mismatch parent_pos parent_const child_pos child_const =
2877 let m1 = "This property is __Const" in
2878 let m2 = "This property is not __Const" in
2879 add_list (Typing.err_code Typing.OverridingPropConstMismatch)
2881 parent_pos, if parent_const then m1 else m2;
2882 child_pos, if child_const then m1 else m2;
2885 let mutable_return_result_mismatch pos1_has_mutable_return pos1 pos2 =
2886 let m1 = "This is marked <<__MutableReturn>>." in
2887 let m2 = "This is not marked <<__MutableReturn>>." in
2888 add_list
2889 (Typing.err_code Typing.MutableReturnResultMismatch)
2891 pos1, if pos1_has_mutable_return then m1 else m2;
2892 pos2, if pos1_has_mutable_return then m2 else m1;
2895 (*****************************************************************************)
2896 (* Typing decl errors *)
2897 (*****************************************************************************)
2899 let wrong_extend_kind child_pos child parent_pos parent =
2900 let msg1 = child_pos, child^" cannot extend "^parent in
2901 let msg2 = parent_pos, "This is "^parent in
2902 add_list (Typing.err_code Typing.WrongExtendKind) [msg1; msg2]
2904 let unsatisfied_req parent_pos req_name req_pos =
2905 let s1 = "Failure to satisfy requirement: "^(Utils.strip_ns req_name) in
2906 let s2 = "Required here" in
2907 if req_pos = parent_pos
2908 then add (Typing.err_code Typing.UnsatisfiedReq) parent_pos s1
2909 else add_list (Typing.err_code Typing.UnsatisfiedReq) [parent_pos, s1; req_pos, s2]
2911 let cyclic_class_def stack pos =
2912 let stack =
2913 SSet.fold ~f:(fun x y -> (Utils.strip_ns x)^" "^y) stack ~init:"" in
2914 add (Typing.err_code Typing.CyclicClassDef) pos ("Cyclic class definition : "^stack)
2916 let trait_reuse p_pos p_name class_name trait =
2917 let c_pos, c_name = class_name in
2918 let c_name = Utils.strip_ns c_name in
2919 let trait = Utils.strip_ns trait in
2920 let err = "Class "^c_name^" reuses trait "^trait^" in its hierarchy" in
2921 let err' = "It is already used through "^(Utils.strip_ns p_name) in
2922 add_list (Typing.err_code Typing.TraitReuse) [c_pos, err; p_pos, err']
2924 let invalid_is_as_expression_hint op hint_pos ty_pos ty_str =
2925 add_list (Typing.err_code Typing.InvalidIsAsExpressionHint) [
2926 hint_pos, ("Invalid \"" ^ op ^ "\" expression hint");
2927 ty_pos, ("The \"" ^ op ^ "\" operator cannot be used with " ^ ty_str);
2930 let invalid_enforceable_type kind_str (tp_pos, tp_name) targ_pos ty_pos ty_str =
2931 add_list (Typing.err_code Typing.InvalidEnforceableTypeArgument) [
2932 targ_pos, "Invalid type";
2933 tp_pos, "Type " ^ kind_str ^ " " ^ tp_name ^ " was declared __Enforceable here";
2934 ty_pos, "This type is not enforceable because it has " ^ ty_str
2937 let invalid_newable_type_argument (tp_pos, tp_name) ta_pos =
2938 add_list (Typing.err_code Typing.InvalidNewableTypeArgument) [
2939 ta_pos, "A newable type argument must be a concrete class or a newable type parameter.";
2940 tp_pos, "Type parameter " ^ tp_name ^ " was declared __Newable here";
2943 let invalid_newable_type_param_constraints (tparam_pos, tparam_name) constraint_list =
2944 let partial =
2945 if List.is_empty constraint_list
2946 then "No constraints"
2947 else "The constraints " ^ (String.concat ~sep:", " (List.map ~f:Utils.strip_ns constraint_list)) in
2948 let msg = "The type parameter " ^ tparam_name ^ " has the <<__Newable>> attribute. \
2949 Newable type parameters must be constrained with `as`, and exactly one of those constraints must be \
2950 a valid newable class. The class must either be final, or it must have the <<__ConsistentConstruct>> \
2951 attribute or extend a class that has it. " ^ partial ^ " are valid newable classes" in
2952 add (Typing.err_code Typing.InvalidNewableTypeParamConstraints) tparam_pos msg
2954 let override_final ~parent ~child =
2955 add_list (Typing.err_code Typing.OverrideFinal) [child, "You cannot override this method";
2956 parent, "It was declared as final"]
2958 let override_memoizelsb ~parent ~child =
2959 add_list (Typing.err_code Typing.OverrideMemoizeLSB) [
2960 child, "__MemoizeLSB method may not be an override (temporary due to HHVM bug)";
2961 parent, "This method is being overridden"]
2963 let override_lsb ~member_name ~parent ~child =
2964 add_list (Typing.err_code Typing.OverrideLSB) [
2965 child, "Member " ^ member_name ^ " may not override __LSB member of parent";
2966 parent, "This is being overridden"]
2968 let should_be_override pos class_id id =
2969 add (Typing.err_code Typing.ShouldBeOverride) pos
2970 ((Utils.strip_ns class_id)^"::"^id^"() is marked as override; \
2971 no non-private parent definition found \
2972 or overridden parent is defined in non-<?hh code")
2974 let override_per_trait class_name id m_pos =
2975 let c_pos, c_name = class_name in
2976 let err_msg =
2977 ("Method "^(Utils.strip_ns c_name)^"::"^id^" should be an override \
2978 per the declaring trait; no non-private parent definition found \
2979 or overridden parent is defined in non-<?hh code")
2980 in add_list (Typing.err_code Typing.OverridePerTrait) [
2981 c_pos, err_msg;
2982 m_pos, "Declaration of "^id^"() is here"
2985 let missing_assign pos =
2986 add (Typing.err_code Typing.MissingAssign) pos "Please assign a value"
2988 let private_override pos class_id id =
2989 add (Typing.err_code Typing.PrivateOverride) pos ((Utils.strip_ns class_id)^"::"^id
2990 ^": combining private and override is nonsensical")
2992 let invalid_memoized_param pos ty_reason_msg =
2993 add_list (Typing.err_code Typing.InvalidMemoizedParam) (
2994 (pos,
2995 "Parameters to memoized function must be null, bool, int, float, string, \
2996 an object deriving IMemoizeParam, or a Container thereof. See also \
2997 http://docs.hhvm.com/hack/attributes/special#__memoize") :: ty_reason_msg)
2999 let invalid_disposable_hint pos class_name =
3000 add (Typing.err_code Typing.InvalidDisposableHint) pos
3001 ("Parameter with type '" ^ class_name ^ "' must not \
3002 implement IDisposable or IAsyncDisposable. Please use <<__AcceptDisposable>> attribute or \
3003 create disposable object with 'using' statement instead.")
3005 let invalid_disposable_return_hint pos class_name =
3006 add (Typing.err_code Typing.InvalidDisposableReturnHint) pos
3007 ("Return type '" ^ class_name ^ "' must not \
3008 implement IDisposable or IAsyncDisposable. Please add <<__ReturnDisposable>> attribute.")
3010 let xhp_required pos why_xhp ty_reason_msg =
3011 let msg = "An XHP instance was expected" in
3012 add_list (Typing.err_code Typing.XhpRequired) ((pos, msg)::(pos, why_xhp)::ty_reason_msg)
3014 let illegal_xhp_child pos ty_reason_msg =
3015 let msg = "XHP children must be compatible with XHPChild" in
3016 add_list (Typing.err_code Typing.IllegalXhpChild) ((pos, msg)::ty_reason_msg)
3018 let missing_xhp_required_attr pos attr ty_reason_msg =
3019 let msg = "Required attribute " ^ attr ^ " is missing." in
3020 add_list (Typing.err_code Typing.MissingXhpRequiredAttr) ((pos, msg)::ty_reason_msg)
3021 let nullsafe_not_needed p nonnull_witness =
3022 add_list (Typing.err_code Typing.NullsafeNotNeeded) (
3025 "You are using the ?-> operator but this object cannot be null. "
3026 ] @ nonnull_witness)
3028 let generic_at_runtime p prefix =
3029 add (Typing.err_code Typing.ErasedGenericAtRuntime) p
3030 (prefix ^ " generics can only be used in type hints because \
3031 they do not exist at runtime.")
3033 let generics_not_allowed p =
3034 add (Typing.err_code Typing.GenericsNotAllowed) p
3035 "Generics are not allowed in this position."
3037 let trivial_strict_eq p b left right left_trail right_trail =
3038 let msg = "This expression is always "^b in
3039 let left_trail = List.map left_trail typedef_trail_entry in
3040 let right_trail = List.map right_trail typedef_trail_entry in
3041 add_list (Typing.err_code Typing.TrivialStrictEq)
3042 ((p, msg) :: left @ left_trail @ right @ right_trail)
3044 let trivial_strict_not_nullable_compare_null p result type_reason =
3045 let msg = "This expression is always "^result in
3046 add_list (Typing.err_code Typing.NotNullableCompareNullTrivial)
3047 ((p, msg) :: type_reason)
3049 let eq_incompatible_types p left right =
3050 let msg = "This equality test has incompatible types" in
3051 add_list (Typing.err_code Typing.EqIncompatibleTypes)
3052 ((p, msg) :: left @ right)
3054 let comparison_invalid_types p left right =
3055 let msg = "This comparison has invalid types. Only comparisons in which \
3056 both arguments are strings, nums, DateTime, or DateTimeImmutable \
3057 are allowed" in
3058 add_list (Typing.err_code Typing.ComparisonInvalidTypes) ((p, msg) :: left @ right)
3060 let void_usage p void_witness =
3061 let msg = "You are using the return value of a void function" in
3062 add_list (Typing.err_code Typing.VoidUsage) ((p, msg) :: void_witness)
3064 let noreturn_usage p noreturn_witness =
3065 let msg = "You are using the return value of a noreturn function" in
3066 add_list (Typing.err_code Typing.NoreturnUsage) ((p, msg) :: noreturn_witness)
3068 let attribute_too_few_arguments pos x n =
3069 let n = string_of_int n in
3070 add (Typing.err_code Typing.AttributeTooFewArguments) pos (
3071 "The attribute "^x^" expects at least "^n^" arguments"
3074 let attribute_too_many_arguments pos x n =
3075 let n = string_of_int n in
3076 add (Typing.err_code Typing.AttributeTooManyArguments) pos (
3077 "The attribute "^x^" expects at most "^n^" arguments"
3080 let attribute_param_type pos x =
3081 add (Typing.err_code Typing.AttributeParamType) pos (
3082 "This attribute parameter should be "^x
3085 let deprecated_use pos pos_def msg =
3086 add_list (Typing.err_code Typing.DeprecatedUse) [
3087 pos, msg;
3088 pos_def, "Definition is here";
3091 let cannot_declare_constant kind pos (class_pos, class_name) =
3092 let kind_str =
3093 match kind with
3094 | `enum -> "an enum"
3095 | `trait -> "a trait"
3096 | `record -> "a record"
3098 add_list (Typing.err_code Typing.CannotDeclareConstant) [
3099 pos, "Cannot declare a constant in "^kind_str;
3100 class_pos, (strip_ns class_name)^" was defined as "^kind_str^" here";
3103 let ambiguous_inheritance pos class_ origin (error: error) =
3104 let origin = strip_ns origin in
3105 let class_ = strip_ns class_ in
3106 let message = "This declaration was inherited from an object of type "^origin^
3107 ". Redeclare this member in "^class_^" with a compatible signature." in
3108 let code, msgl = (get_code error), (to_list error) in
3109 add_list code (msgl @ [pos, message])
3111 let multiple_concrete_defs child_pos parent_pos child_origin parent_origin name class_ =
3112 let child_origin = strip_ns child_origin in
3113 let parent_origin = strip_ns parent_origin in
3114 let class_ = strip_ns class_ in
3115 add_list (Typing.err_code Typing.MultipleConcreteDefs) [
3116 child_pos, child_origin ^ " and " ^ parent_origin ^
3117 " both declare ambiguous implementations of " ^ name ^ ".";
3118 child_pos, child_origin ^ "'s definition is here.";
3119 parent_pos, parent_origin ^ "'s definition is here.";
3120 child_pos, "Redeclare " ^ name ^ " in " ^ class_ ^ " with a compatible signature.";
3123 let local_variable_modified_and_used pos_modified pos_used_l =
3124 let used_msg p = p, "And accessed here" in
3125 add_list (Typing.err_code Typing.LocalVariableModifedAndUsed)
3126 ((pos_modified, "Unsequenced modification and access to local \
3127 variable. Modified here") ::
3128 List.map pos_used_l used_msg)
3130 let local_variable_modified_twice pos_modified pos_modified_l =
3131 let modified_msg p = p, "And also modified here" in
3132 add_list (Typing.err_code Typing.LocalVariableModifedTwice)
3133 ((pos_modified, "Unsequenced modifications to local variable. \
3134 Modified here") ::
3135 List.map pos_modified_l modified_msg)
3137 let assign_during_case p =
3138 add (Typing.err_code Typing.AssignDuringCase) p
3139 "Don't assign to variables inside of case labels"
3141 let cyclic_enum_constraint pos =
3142 add (Typing.err_code Typing.CyclicEnumConstraint) pos "Cyclic enum constraint"
3144 let invalid_classname p =
3145 add (Typing.err_code Typing.InvalidClassname) p "Not a valid class name"
3147 let illegal_type_structure pos errmsg =
3148 let msg =
3149 "The two arguments to type_structure() must be:"
3150 ^"\n - first: ValidClassname::class or an object of that class"
3151 ^"\n - second: a single-quoted string literal containing the name"
3152 ^" of a type constant of that class"
3153 ^"\n"^errmsg in
3154 add (Typing.err_code Typing.IllegalTypeStructure) pos msg
3156 let illegal_typeconst_direct_access pos =
3157 let msg =
3158 "Type constants cannot be directly accessed. "
3159 ^"Use type_structure(ValidClassname::class, 'TypeConstName') instead" in
3160 add (Typing.err_code Typing.IllegalTypeStructure) pos msg
3162 let override_no_default_typeconst pos_child pos_parent =
3163 add_list (Typing.err_code Typing.OverrideNoDefaultTypeconst) [
3164 pos_child, "This abstract type constant does not have a default type";
3165 pos_parent, "It cannot override an abstract type constant that has a default type"
3168 let reference_expr pos =
3169 let msg = "References are only allowed as function call arguments" in
3170 add (Typing.err_code Typing.ReferenceExprNotFunctionArg) pos msg
3172 let pass_by_ref_annotation_missing pos1 pos2 =
3173 let msg1 = pos1, "This argument should be annotated with &" in
3174 let msg2 = pos2, "Because this parameter is passed by reference" in
3175 add_list (Typing.err_code Typing.PassByRefAnnotationMissing) [msg1; msg2]
3177 let pass_by_ref_annotation_unexpected pos1 pos2 pos2_is_variadic =
3178 let msg1 = pos1, "This argument should not be annotated with &" in
3179 let param_str = if pos2_is_variadic
3180 then "variadic parameters are"
3181 else "this parameter is" in
3182 let msg2 = pos2, "Because " ^ param_str ^ " passed by value" in
3183 add_list (Typing.err_code Typing.PassByRefAnnotationUnexpected) [msg1; msg2]
3185 let reffiness_invariant pos1 pos2 mode2 =
3186 let msg1 = pos1, "This parameter is passed by reference" in
3187 let mode_str = match mode2 with
3188 | `normal -> "a normal parameter"
3189 | `inout -> "an inout parameter" in
3190 let msg2 = pos2, "It is incompatible with " ^ mode_str in
3191 add_list (Typing.err_code Typing.ReffinessInvariant) [msg1; msg2]
3193 let inout_annotation_missing pos1 pos2 =
3194 let msg1 = pos1, "This argument should be annotated with 'inout'" in
3195 let msg2 = pos2, "Because this is an inout parameter" in
3196 add_list (Typing.err_code Typing.InoutAnnotationMissing) [msg1; msg2]
3198 let inout_annotation_unexpected pos1 pos2 pos2_is_variadic =
3199 let msg1 = pos1, "Unexpected inout annotation for argument" in
3200 let msg2 = pos2, if pos2_is_variadic
3201 then "A variadic parameter can never be inout"
3202 else "This is a normal parameter (does not have 'inout')" in
3203 add_list (Typing.err_code Typing.InoutAnnotationUnexpected) [msg1; msg2]
3205 let inoutness_mismatch pos1 pos2 =
3206 let msg1 = pos1, "This is an inout parameter" in
3207 let msg2 = pos2, "It is incompatible with a normal parameter" in
3208 add_list (Typing.err_code Typing.InoutnessMismatch) [msg1; msg2]
3210 let invalid_new_disposable pos =
3211 let msg =
3212 "Disposable objects may only be created in a 'using' statement or 'return' from function marked <<__ReturnDisposable>>" in
3213 add (Typing.err_code Typing.InvalidNewDisposable) pos msg
3215 let invalid_return_disposable pos =
3216 let msg =
3217 "Return expression must be new disposable in function marked <<__ReturnDisposable>>" in
3218 add (Typing.err_code Typing.InvalidReturnDisposable) pos msg
3220 let nonreactive_function_call pos decl_pos callee_reactivity cause_pos_opt =
3221 add_list (Typing.err_code Typing.NonreactiveFunctionCall) ([
3222 pos, "Reactive functions can only call other reactive functions.";
3223 decl_pos, "This function is " ^ callee_reactivity ^ "."
3224 ] @ Option.value_map cause_pos_opt ~default:[] ~f:(fun cause_pos ->
3225 [cause_pos, "This argument caused function to be " ^ callee_reactivity ^ "."]
3228 let nonreactive_call_from_shallow pos decl_pos callee_reactivity cause_pos_opt=
3229 add_list (Typing.err_code Typing.NonreactiveCallFromShallow) ([
3230 pos, "Shallow reactive functions cannot call non-reactive functions.";
3231 decl_pos, "This function is " ^ callee_reactivity ^ "."
3232 ] @ Option.value_map cause_pos_opt ~default:[] ~f:(fun cause_pos ->
3233 [cause_pos, "This argument caused function to be " ^ callee_reactivity ^ "."]
3235 let rx_enabled_in_non_rx_context pos =
3236 add (Typing.err_code Typing.RxEnabledInNonRxContext) pos (
3237 "\\HH\\Rx\\IS_ENABLED can only be used in reactive functions."
3240 let rx_parameter_condition_mismatch cond pos def_pos =
3241 add_list (Typing.err_code Typing.RxParameterConditionMismatch) [
3242 pos, "This parameter does not satisfy "^ cond ^ " condition defined on \
3243 matching parameter in function super type.";
3244 def_pos, "This is parameter declaration from the function super type."
3246 let nonreactive_indexing is_append pos =
3247 let msg =
3248 if is_append
3249 then "Cannot append to a Hack Collection object in a reactive context. \
3250 Instead, use the 'add' method."
3251 else "Cannot assign to element of Hack Collection object via [] in a reactive context. \
3252 Instead, use the 'set' method." in
3253 add (Typing.err_code Typing.NonreactiveIndexing) pos msg
3255 let obj_set_reactive pos =
3256 let msg = ("This object's property is being mutated(used as an lvalue)" ^
3257 "\nYou cannot set non-mutable object properties in reactive functions") in
3258 add (Typing.err_code Typing.ObjSetReactive) pos msg
3260 let invalid_unset_target_rx pos =
3261 add (Typing.err_code Typing.InvalidUnsetTargetInRx) pos (
3262 "Non-mutable argument for 'unset' is not allowed in reactive functions."
3265 let inout_argument_bad_type pos msgl =
3266 let msg =
3267 "Expected argument marked inout to be contained in a local or " ^
3268 "a value-typed container (e.g. vec, dict, keyset, array). " ^
3269 "To use inout here, assign to/from a temporary local variable." in
3270 add_list (Typing.err_code Typing.InoutArgumentBadType) ((pos, msg) :: msgl)
3272 let ambiguous_lambda pos uses =
3273 let msg1 =
3274 "Lambda has parameter types that could not be determined at definition site." in
3275 let msg2 =
3276 Printf.sprintf
3277 "%d distinct use types were determined: please add type hints to lambda parameters."
3278 (List.length uses) in
3279 add_list (Typing.err_code Typing.AmbiguousLambda) ([(pos, msg1); (pos, msg2)] @
3280 List.map uses (fun (pos, ty) -> (pos, "This use has type " ^ ty)))
3282 let wrong_expression_kind_attribute expr_kind pos attr attr_class_pos attr_class_name intf_name =
3283 let msg1 =
3284 Printf.sprintf "The %s attribute cannot be used on %s." (Utils.strip_ns attr) expr_kind in
3285 let msg2 =
3286 Printf.sprintf "The attribute's class is defined here. To be available for use on \
3287 %s, the %s class must implement %s." expr_kind
3288 (String_utils.string_after attr_class_name 1)
3289 (String_utils.string_after intf_name 1) in
3290 add_list (Typing.err_code Typing.WrongExpressionKindAttribute) [
3291 pos, msg1;
3292 attr_class_pos, msg2
3295 let cannot_return_borrowed_value_as_immutable fun_pos value_pos =
3296 add_list (Typing.err_code Typing.CannotReturnBorrowedValueAsImmutable) [
3297 fun_pos, "Values returned from reactive function by default are treated \
3298 as immutable.";
3299 value_pos, "This value is mutably borrowed and cannot be returned as immutable"
3302 let decl_override_missing_hint pos =
3303 add (Typing.err_code Typing.DeclOverrideMissingHint) pos
3304 "When redeclaring class members, both declarations must have a typehint"
3306 let let_var_immutability_violation pos id =
3307 add (Typing.err_code Typing.LetVarImmutabilityViolation) pos
3308 ("Let variables are immutable. Using let variable " ^ id ^ " in write context is not allowed.")
3310 let invalid_type_for_atmost_rx_as_rxfunc_parameter pos type_str =
3311 add (Typing.err_code Typing.InvalidTypeForOnlyrxIfRxfuncParameter) pos (
3312 "Parameter annotated with <<__AtMostRxAsFunc>> attribute must be function, \
3313 now '" ^ type_str ^ "'."
3316 let missing_annotation_for_atmost_rx_as_rxfunc_parameter pos =
3317 add (Typing.err_code Typing.MissingAnnotationForOnlyrxIfRxfuncParameter) pos (
3318 "Missing function type annotation on parameter marked with <<__AtMostRxAsFunc>> attribute."
3321 let binding_ref_in_array pos =
3322 let msg = "Arrays cannot contain references." in
3323 add (Typing.err_code Typing.BindingRefInArray) pos msg
3325 let binding_ref_to_array pos =
3326 let msg = "Cannot take references to array elements." in
3327 add (Typing.err_code Typing.BindingRefInArray) pos msg
3329 let passing_array_cell_by_ref pos =
3330 let msg = "Passing array elements by reference is no longer supported; " ^
3331 "use 'inout' instead" in
3332 add (Typing.err_code Typing.PassingArrayCellByRef) pos msg
3334 let superglobal_in_reactive_context pos name =
3335 add (Typing.err_code Typing.SuperglobalInReactiveContext) pos (
3336 "Superglobal "^ name ^ " cannot be used in a reactive context."
3339 let static_property_in_reactive_context pos =
3340 add (Typing.err_code Typing.StaticPropertyInReactiveContext) pos (
3341 "Static property cannot be used in a reactive context."
3344 let returns_void_to_rx_function_as_non_expression_statement pos fpos =
3345 add_list (Typing.err_code Typing.ReturnsVoidToRxAsNonExpressionStatement) [
3346 pos, "Cannot use result of function annotated with <<__ReturnsVoidToRx>> \
3347 in reactive context";
3348 fpos, "This is function declaration."
3351 let non_awaited_awaitable_in_rx pos =
3352 add (Typing.err_code Typing.NonawaitedAwaitableInReactiveContext) pos (
3353 "This value has Awaitable type. Awaitable typed values in reactive code \
3354 must be either immediately await'ed or passed as arguments to 'genva' function."
3357 let shapes_key_exists_always_true pos1 name pos2 =
3358 add_list (Typing.err_code Typing.ShapesKeyExistsAlwaysTrue) [
3359 pos1, "This Shapes::keyExists() check is always true";
3360 pos2, "The field '" ^ name ^ "' exists because of this definition"
3363 let shape_field_non_existence_reason name = function
3364 | `Undefined ->
3365 "The field '" ^ name ^ "' is not defined in this shape"
3366 | `Unset ->
3367 "The field '" ^ name ^ "' was unset here"
3369 let shapes_key_exists_always_false pos1 name pos2 reason =
3370 add_list (Typing.err_code Typing.ShapesKeyExistsAlwaysFalse) [
3371 pos1, "This Shapes::keyExists() check is always false";
3372 pos2, shape_field_non_existence_reason name reason
3375 let shapes_method_access_with_non_existent_field pos1 name pos2 method_name reason =
3376 add_list (Typing.err_code Typing.ShapesMethodAccessWithNonExistentField) [
3377 pos1, "You are calling Shapes::" ^ method_name ^ "() on a field known to not exist";
3378 pos2, shape_field_non_existence_reason name reason
3381 let ambiguous_object_access pos name self_pos vis subclass_pos class_self class_subclass =
3382 let class_self = Utils.strip_ns class_self in
3383 let class_subclass = Utils.strip_ns class_subclass in
3384 add_list (Typing.err_code Typing.AmbiguousObjectAccess) [
3385 pos, "This object access to " ^ name ^ " is ambiguous";
3386 self_pos, "You will access the private instance declared in " ^ class_self;
3387 subclass_pos, "Instead of the " ^ vis ^ " instance declared in " ^ class_subclass;
3390 let invalid_traversable_in_rx pos =
3391 add (Typing.err_code Typing.InvalidTraversableInRx) pos (
3392 "Cannot traverse over non-reactive traversable in reactive code."
3395 let lateinit_with_default pos =
3396 add (Typing.err_code Typing.LateInitWithDefault) pos
3397 "A late-initialized property cannot have a default value"
3399 let bad_lateinit_override parent_is_lateinit parent_pos child_pos =
3400 let verb = if parent_is_lateinit then "is" else "is not" in
3401 add_list (Typing.err_code Typing.BadLateInitOverride) [
3402 child_pos, "Redeclared properties must be consistently declared as late-initialized";
3403 parent_pos, "The property "^verb^" late-initialized here";
3406 let bad_xhp_attr_required_override parent_tag child_tag parent_pos child_pos =
3407 add_list (Typing.err_code Typing.BadXhpAttrRequiredOverride) [
3408 child_pos, "Redeclared attribute must not be less strict";
3409 parent_pos, "The attribute is " ^ parent_tag ^ ", which is stricter than " ^ child_tag;
3412 let invalid_truthiness_test pos ty =
3413 add (Typing.err_code Typing.InvalidTruthinessTest) pos @@
3414 Printf.sprintf
3415 "Invalid condition: a value of type %s will always be truthy" ty
3417 let invalid_truthiness_test_falsy pos ty =
3418 add (Typing.err_code Typing.InvalidTruthinessTest) pos @@
3419 Printf.sprintf
3420 "Invalid condition: a value of type %s will always be falsy" ty
3422 let sketchy_truthiness_test pos ty truthiness =
3423 add (Typing.err_code Typing.SketchyTruthinessTest) pos @@
3424 match truthiness with
3425 | `String ->
3426 Printf.sprintf
3427 "Sketchy condition: testing the truthiness of %s may not behave as expected.\n\
3428 The values '' and '0' are both considered falsy. \
3429 To check for emptiness, use Str\\is_empty."
3431 | `Arraykey ->
3432 Printf.sprintf
3433 "Sketchy condition: testing the truthiness of %s may not behave as expected.\n\
3434 The values 0, '', and '0' are all considered falsy. \
3435 Test for them explicitly."
3437 | `Stringish ->
3438 Printf.sprintf
3439 "Sketchy condition: testing the truthiness of a %s may not behave as expected.\n\
3440 The values '' and '0' are both considered falsy, \
3441 but objects will be truthy even if their __toString returns '' or '0'.\n\
3442 To check for emptiness, convert to a string and use Str\\is_empty."
3444 | `XHPChild ->
3445 Printf.sprintf
3446 "Sketchy condition: testing the truthiness of an %s may not behave as expected.\n\
3447 The values '' and '0' are both considered falsy, \
3448 but objects (including XHP elements) will be truthy \
3449 even if their __toString returns '' or '0'."
3451 | `Traversable ->
3452 (* We have a truthiness test on a value with an interface type which is a
3453 subtype of Traversable, but not a subtype of Container.
3454 Since the runtime value may be a falsy-when-empty Container or an
3455 always-truthy Iterable/Generator, we forbid the test. *)
3456 Printf.sprintf
3457 "Sketchy condition: a value of type %s may be truthy even when empty.\n\
3458 Hack collections and arrays are falsy when empty, but user-defined \
3459 Traversables will always be truthy, even when empty.\n\
3460 If you would like to only allow containers which are falsy \
3461 when empty, use the Container or KeyedContainer interfaces."
3464 let invalid_switch_case_value_type case_value_p case_value_ty scrutinee_ty =
3465 add (Typing.err_code Typing.InvalidSwitchCaseValueType) case_value_p @@
3466 Printf.sprintf
3467 "This case value has type %s, which is incompatible with type %s."
3468 case_value_ty
3469 scrutinee_ty
3471 let unserializable_type pos message =
3472 add (Typing.err_code Typing.UnserializableType) pos
3473 ("Unserializable type (could not be converted to JSON and back again): "
3474 ^ message)
3476 let redundant_rx_condition pos =
3477 add (Typing.err_code Typing.RedundantRxCondition) pos
3478 "Reactivity condition for this method is always true, consider removing it."
3480 let invalid_arraykey pos (cpos, ctype) (kpos, ktype) =
3481 add_list (Typing.err_code Typing.InvalidArrayKey) [
3482 pos, "This value is not a valid key type for this container";
3483 cpos, "This container is " ^ ctype;
3484 kpos, (String.capitalize ktype) ^ " cannot be used as a key for " ^ ctype;
3487 let invalid_sub_string pos ty =
3488 add (Typing.err_code Typing.InvalidSubString) pos @@
3489 "Expected an object convertible to string but got " ^ ty
3491 let typechecker_timeout (pos, fun_name) seconds =
3492 add (Typing.err_code Typing.TypecheckerTimeout) pos
3493 (Printf.sprintf "Type checker timed out after %d seconds whilst checking function %s" seconds fun_name)
3495 let unresolved_type_variable pos =
3496 add (Typing.err_code Typing.UnresolvedTypeVariable) pos
3497 ("The type of this expression contains an unresolved type variable")
3499 let invalid_arraykey_constraint pos t =
3500 add (Typing.err_code Typing.InvalidArrayKeyConstraint) pos
3501 ("This type is " ^ t ^ ", which cannot be used as an arraykey (string | int)")
3503 (*****************************************************************************)
3504 (* Printing *)
3505 (*****************************************************************************)
3507 let to_json (error : Pos.absolute error_) =
3508 let error_code, msgl = (get_code error), (to_list error) in
3509 let elts = List.map msgl begin fun (p, w) ->
3510 let line, scol, ecol = Pos.info_pos p in
3511 Hh_json.JSON_Object [
3512 "descr", Hh_json.JSON_String w;
3513 "path", Hh_json.JSON_String (Pos.filename p);
3514 "line", Hh_json.int_ line;
3515 "start", Hh_json.int_ scol;
3516 "end", Hh_json.int_ ecol;
3517 "code", Hh_json.int_ error_code
3519 end in
3520 Hh_json.JSON_Object [ "message", Hh_json.JSON_Array elts ]
3522 (*****************************************************************************)
3523 (* Try if errors. *)
3524 (*****************************************************************************)
3526 let try_ f1 f2 = try_with_result f1 (fun _ l -> f2 l)
3528 let try_with_error f1 f2 = try_ f1 (fun err -> add_error err; f2 ())
3530 let try_add_err pos err f1 f2 =
3531 try_ f1 begin fun error ->
3532 let error_code, l = (get_code error), (to_list error) in
3533 add_list error_code ((pos, err) :: l);
3534 f2()
3537 let has_no_errors f =
3538 try_ (fun () -> let _ = f () in true) (fun _ -> false)
3540 (*****************************************************************************)
3541 (* Do. *)
3542 (*****************************************************************************)
3544 let ignore_ f =
3545 let allow_errors_in_default_path_copy = !allow_errors_in_default_path in
3546 set_allow_errors_in_default_path true;
3547 let _, result = (do_ f) in
3548 set_allow_errors_in_default_path allow_errors_in_default_path_copy;
3549 result
3551 let try_when f ~when_ ~do_ =
3552 try_with_result f begin fun result (error: error) ->
3553 if when_()
3554 then do_ error
3555 else add_error error;
3556 result