__OwnedMutable
[hiphop-php.git] / hphp / hack / src / errors / errors.ml
blob8b0643e41a35403ca5b2937ad199274314b92179
1 (**
2 * Copyright (c) 2015, Facebook, Inc.
3 * All rights reserved.
5 * This source code is licensed under the MIT license found in the
6 * LICENSE file in the "hack" directory of this source tree.
8 *)
10 open Hh_core
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 error_phase = Init | Parsing | Naming | Decl | Typing
21 type error_severity = Warning | Error
23 (* For callers that don't care about tracking error origins *)
24 let default_context = (Relative_path.default, Typing)
26 (* The file and phase of analysis being currently performed *)
27 let current_context: (Relative_path.t * error_phase) ref = ref default_context
29 let allow_errors_in_default_path = ref true
31 module PhaseMap = Reordered_argument_map(MyMap.Make(struct
32 type t = error_phase
34 let rank = function
35 | Init -> 0
36 | Parsing -> 1
37 | Naming -> 2
38 | Decl -> 3
39 | Typing -> 4
41 let compare x y = (rank x) - (rank y)
42 end))
44 (* Results of single file analysis. *)
45 type 'a file_t = 'a list PhaseMap.t
46 (* Results of multi-file analysis. *)
47 type 'a files_t = ('a file_t) Relative_path.Map.t
49 let files_t_fold v ~f ~init =
50 Relative_path.Map.fold v ~init ~f:begin fun path v acc ->
51 PhaseMap.fold v ~init:acc ~f:begin fun phase v acc ->
52 f path phase v acc
53 end
54 end
56 let files_t_map v ~f =
57 Relative_path.Map.map v ~f:begin fun v ->
58 PhaseMap.map v ~f
59 end
61 let files_t_merge ~f x y =
62 (* Using fold instead of merge to make the runtime proportional to the size
63 * of first argument (like List.rev_append ) *)
64 Relative_path.Map.fold x ~init:y ~f:begin fun k x acc ->
65 let y = Option.value (Relative_path.Map.get y k) ~default:PhaseMap.empty in
66 Relative_path.Map.add acc k (
67 PhaseMap.merge x y ~f:(fun phase x y -> f phase k x y)
69 end
71 let files_t_to_list x =
72 files_t_fold x ~f:(fun _ _ x acc -> List.rev_append x acc) ~init:[] |>
73 List.rev
75 let list_to_files_t = function
76 | [] -> Relative_path.Map.empty
77 | x ->
78 (* Values constructed here should not be used with incremental mode.
79 * See assert in incremental_update. *)
80 Relative_path.Map.singleton Relative_path.default
81 (PhaseMap.singleton Typing x)
83 let get_code_severity code =
84 if code = Error_codes.Init.err_code Error_codes.Init.ForwardCompatibilityNotCurrent
85 then Warning
86 else Error
88 module Common = struct
90 (* Get most recently-ish added error. *)
91 let get_last error_map =
92 (* If this map has more than one element, we pick an arbitrary file. Because
93 * of that, we might not end up with the most recent error and generate a
94 * less-specific error message. This should be rare. *)
95 match Relative_path.Map.max_binding error_map with
96 | None -> None
97 | Some (_, phase_map) -> begin
98 let error_list = PhaseMap.max_binding phase_map
99 |> Option.value_map ~f:snd ~default:[]
101 match List.rev error_list with
102 | [] -> None
103 | e::_ -> Some e
106 let try_with_result f1 f2 error_map accumulate_errors =
107 let error_map_copy = !error_map in
108 let accumulate_errors_copy = !accumulate_errors in
109 error_map := Relative_path.Map.empty;
110 accumulate_errors := true;
111 let result, errors = Utils.try_finally
112 ~f:begin fun () ->
113 let result = f1 () in
114 result, !error_map
116 ~finally:begin fun () ->
117 error_map := error_map_copy;
118 accumulate_errors := accumulate_errors_copy;
121 match get_last errors with
122 | None -> result
123 | Some l -> f2 result l
125 let do_ f error_map accumulate_errors applied_fixmes =
126 let error_map_copy = !error_map in
127 let accumulate_errors_copy = !accumulate_errors in
128 let applied_fixmes_copy = !applied_fixmes in
129 error_map := Relative_path.Map.empty;
130 applied_fixmes := Relative_path.Map.empty;
131 accumulate_errors := true;
132 let result, out_errors, out_applied_fixmes = Utils.try_finally
133 ~f:begin fun () ->
134 let result = f () in
135 result, !error_map, !applied_fixmes
137 ~finally:begin fun () ->
138 error_map := error_map_copy;
139 applied_fixmes := applied_fixmes_copy;
140 accumulate_errors := accumulate_errors_copy;
143 let out_errors = files_t_map ~f:(List.rev) out_errors in
144 (out_errors, out_applied_fixmes), result
146 let run_in_context path phase f =
147 let context_copy = !current_context in
148 current_context := (path, phase);
149 Utils.try_finally ~f ~finally:begin fun () ->
150 current_context := context_copy;
153 (* Log important data if lazy_decl triggers a crash *)
154 let lazy_decl_error_logging error error_map to_absolute to_string =
155 let error_list = files_t_to_list !error_map in
156 (* Print the current error list, which should be empty *)
157 Printf.eprintf "%s" "Error list(should be empty):\n";
158 List.iter error_list ~f:(fun err ->
159 let msg = err |> to_absolute |> to_string in Printf.eprintf "%s\n" msg);
160 Printf.eprintf "%s" "Offending error:\n";
161 Printf.eprintf "%s" error;
163 (* Print out a larger stack trace *)
164 Printf.eprintf "%s" "Callstack:\n";
165 Printf.eprintf "%s" (Printexc.raw_backtrace_to_string
166 (Printexc.get_callstack 500));
167 (* Exit with special error code so we can see the log after *)
168 Exit_status.exit Exit_status.Lazy_decl_bug
170 (*****************************************************************************)
171 (* Error code printing. *)
172 (*****************************************************************************)
174 let error_kind error_code =
175 match error_code / 1000 with
176 | 1 -> "Parsing"
177 | 2 -> "Naming"
178 | 3 -> "NastCheck"
179 | 4 -> "Typing"
180 | 5 -> "Lint"
181 | 8 -> "Init"
182 | _ -> "Other"
184 let error_code_to_string error_code =
185 let error_kind = error_kind error_code in
186 let error_number = Printf.sprintf "%04d" error_code in
187 error_kind^"["^error_number^"]"
189 let phase_to_string (phase: error_phase) : string =
190 match phase with
191 | Init -> "Init"
192 | Parsing -> "Parsing"
193 | Naming -> "Naming"
194 | Decl -> "Decl"
195 | Typing -> "Typing"
197 let sort get_pos err =
198 List.sort ~cmp:begin fun x y ->
199 Pos.compare (get_pos x) (get_pos y)
200 end err
201 |> List.remove_consecutive_duplicates ~equal:(=)
203 let get_sorted_error_list get_pos (err,_) =
204 sort get_pos (files_t_to_list err)
206 (* Getters and setter for passed-in map, based on current context *)
207 let get_current_file_t file_t_map =
208 let current_file = fst !current_context in
209 Relative_path.Map.get file_t_map current_file |>
210 Option.value ~default:PhaseMap.empty
212 let get_current_list file_t_map =
213 let current_phase = snd !current_context in
214 get_current_file_t file_t_map |> fun x ->
215 PhaseMap.get x current_phase |>
216 Option.value ~default:[]
218 let set_current_list file_t_map new_list =
219 let current_file, current_phase = !current_context in
220 file_t_map := Relative_path.Map.add
221 !file_t_map
222 current_file
223 (PhaseMap.add
224 (get_current_file_t !file_t_map)
225 current_phase
226 new_list
230 (** The mode abstracts away the underlying errors type so errors can be
231 * stored either with backtraces (TracingErrors) or without
232 * (NonTracingErrors). *)
233 module type Errors_modes = sig
235 type 'a error_
236 type error = Pos.t error_
237 type applied_fixme = Pos.t * int
239 val applied_fixmes: applied_fixme files_t ref
240 val error_map: error files_t ref
242 val try_with_result: (unit -> 'a) -> ('a -> error -> 'a) -> 'a
243 val do_: (unit -> 'a) -> (error files_t * applied_fixme files_t) * 'a
244 val do_with_context: Relative_path.t -> error_phase ->
245 (unit -> 'a) -> (error files_t * applied_fixme files_t) * 'a
246 val run_in_context: Relative_path.t -> error_phase -> (unit -> 'a) -> 'a
247 val run_in_decl_mode: Relative_path.t -> (unit -> 'a) -> 'a
248 val add_error: error -> unit
249 val make_error: error_code -> (Pos.t message) list -> error
251 val get_code: 'a error_ -> error_code
252 val get_pos: error -> Pos.t
253 val get_severity: 'a error_ -> error_severity
254 val to_list: 'a error_ -> 'a message list
255 val to_absolute : error -> Pos.absolute error_
257 val to_string : ?indent:bool -> Pos.absolute error_ -> string
259 val get_sorted_error_list: error files_t * applied_fixme files_t -> error list
260 val sort: error list -> error list
261 val currently_has_errors : unit -> bool
265 (** Errors don't have backtraces embedded. *)
266 module NonTracingErrors: Errors_modes = struct
267 type 'a error_ = error_code * 'a message list
268 type error = Pos.t error_
269 type applied_fixme = Pos.t * int
271 let applied_fixmes: applied_fixme files_t ref = ref Relative_path.Map.empty
272 let (error_map: error files_t ref) = ref Relative_path.Map.empty
273 let accumulate_errors = ref false
274 (* Some filename when declaring *)
275 let in_lazy_decl = ref None
277 let try_with_result f1 f2 =
278 Common.try_with_result f1 f2 error_map accumulate_errors
280 let do_ f =
281 Common.do_ f error_map accumulate_errors applied_fixmes
283 let do_with_context path phase f =
284 Common.run_in_context path phase (fun () -> do_ f)
286 let run_in_context = Common.run_in_context
288 (* Turn on lazy decl mode for the duration of the closure.
289 This runs without returning the original state,
290 since we collect it later in do_with_lazy_decls_
292 let run_in_decl_mode filename f =
293 let old_in_lazy_decl = !in_lazy_decl in
294 in_lazy_decl := Some filename;
295 Utils.try_finally ~f ~finally:begin fun () ->
296 in_lazy_decl := old_in_lazy_decl;
299 and make_error code (x: (Pos.t * string) list) = ((code, x): error)
301 (*****************************************************************************)
302 (* Accessors. *)
303 (*****************************************************************************)
305 and get_code (error: 'a error_) = ((fst error): error_code)
306 let get_pos (error : error) = fst (List.hd_exn (snd error))
308 let get_severity (error: 'a error_) = get_code_severity (get_code error)
310 let to_list (error : 'a error_) = snd error
311 let to_absolute error =
312 let code, msg_l = (get_code error), (to_list error) in
313 let msg_l = List.map msg_l (fun (p, s) -> Pos.to_absolute p, s) in
314 code, msg_l
316 let to_string ?(indent=false) (error : Pos.absolute error_) : string =
317 let error_code, msgl = (get_code error), (to_list error) in
318 let buf = Buffer.create 50 in
319 (match msgl with
320 | [] -> assert false
321 | (pos1, msg1) :: rest_of_error ->
322 Buffer.add_string buf begin
323 let error_code = Common.error_code_to_string error_code in
324 Printf.sprintf "%s\n%s (%s)\n"
325 (Pos.string pos1) msg1 error_code
326 end;
327 let indentstr = if indent then " " else "" in
328 List.iter rest_of_error begin fun (p, w) ->
329 let msg = Printf.sprintf "%s%s\n%s%s\n"
330 indentstr (Pos.string p) indentstr w in
331 Buffer.add_string buf msg
334 Buffer.contents buf
336 let sort = Common.sort get_pos
337 let get_sorted_error_list = Common.get_sorted_error_list get_pos
339 let add_error error =
340 if !accumulate_errors then
341 let () = match !current_context with
342 | (path, _) when path = Relative_path.default &&
343 (not !allow_errors_in_default_path) ->
344 Hh_logger.log "WARNING: adding an error in default path\n%s\n"
345 (Printexc.raw_backtrace_to_string (Printexc.get_callstack 100))
346 | _ -> ()
348 (* Cheap test to avoid duplicating most recent error *)
349 let error_list = Common.get_current_list !error_map in
350 match error_list with
351 | old_error :: _ when error = old_error -> ()
352 | _ -> Common.set_current_list error_map (error :: error_list)
353 else
354 (* We have an error, but haven't handled it in any way *)
355 let msg = error |> to_absolute |> to_string in
356 match !in_lazy_decl with
357 | Some _ ->
358 Common.lazy_decl_error_logging msg error_map to_absolute to_string
359 | None -> assert_false_log_backtrace (Some msg)
360 let currently_has_errors () =
361 Common.get_current_list !error_map <> []
365 (** Errors with backtraces embedded. They are revealed with to_string. *)
366 module TracingErrors: Errors_modes = struct
367 type 'a error_ = (Printexc.raw_backtrace * error_code * 'a message list)
368 type error = Pos.t error_
369 type applied_fixme = Pos.t * int
371 let applied_fixmes: applied_fixme files_t ref = ref Relative_path.Map.empty
372 let (error_map: error files_t ref) = ref Relative_path.Map.empty
374 let accumulate_errors = ref false
375 let in_lazy_decl = ref None
377 let try_with_result f1 f2 =
378 Common.try_with_result f1 f2 error_map accumulate_errors
380 let do_ f =
381 Common.do_ f error_map accumulate_errors applied_fixmes
383 let run_in_context = Common.run_in_context
385 let do_with_context path phase f =
386 run_in_context path phase (fun () -> do_ f)
388 (* Turn on lazy decl mode for the duration of the closure.
389 This runs without returning the original state,
390 since we collect it later in do_with_lazy_decls_
392 let run_in_decl_mode filename f =
393 in_lazy_decl := Some filename;
394 Utils.try_finally ~f ~finally:begin fun () ->
395 in_lazy_decl := None;
398 let make_error code (x: (Pos.t * string) list) =
399 let bt = Printexc.get_callstack 25 in
400 ((bt, code, x): error)
402 let get_code ((_, c, _): 'a error_) = c
404 let get_pos ((_, _, msg_l): error) =
405 fst (List.hd_exn msg_l)
407 let get_severity (error: 'a error_) = get_code_severity (get_code error)
409 let get_bt ((bt, _, _): 'a error_) = bt
411 let to_list ((_, _, l): 'a error_) = l
413 let to_absolute (error: error) =
414 let bt, code, msg_l = (get_bt error), (get_code error), (to_list error) in
415 let msg_l = List.map msg_l (fun (p, s) -> Pos.to_absolute p, s) in
416 bt, code, msg_l
418 (** TODO: Much of this is copy-pasta. *)
419 let to_string ?(indent=false) (error : Pos.absolute error_) : string =
420 let bt, error_code, msgl = (get_bt error),
421 (get_code error), (to_list error) in
422 let buf = Buffer.create 50 in
423 (match msgl with
424 | [] -> assert false
425 | (pos1, msg1) :: rest_of_error ->
426 Buffer.add_string buf begin
427 let error_code = Common.error_code_to_string error_code in
428 Printf.sprintf "%s\n%s%s (%s)\n"
429 (Pos.string pos1) (Printexc.raw_backtrace_to_string bt)
430 msg1 error_code
431 end;
432 let indentstr = if indent then " " else "" in
433 List.iter rest_of_error begin fun (p, w) ->
434 let msg = Printf.sprintf "%s%s\n%s%s\n"
435 indentstr (Pos.string p) indentstr w in
436 Buffer.add_string buf msg
439 Buffer.contents buf
441 let add_error error =
442 if !accumulate_errors then
443 begin
444 let error_list = Common.get_current_list !error_map in
445 Common.set_current_list error_map (error :: error_list)
447 else
448 (* We have an error, but haven't handled it in any way *)
449 let msg = error |> to_absolute |> to_string in
450 match !in_lazy_decl with
451 | Some _ ->
452 Common.lazy_decl_error_logging msg error_map to_absolute to_string
453 | None -> assert_false_log_backtrace (Some msg)
455 let sort = Common.sort get_pos
456 let get_sorted_error_list = Common.get_sorted_error_list get_pos
457 let currently_has_errors () =
458 Common.get_current_list !error_map <> []
461 (** The Errors functor which produces the Errors module.
462 * Omitting gratuitous indentation. *)
463 module Errors_with_mode(M: Errors_modes) = struct
465 module Temporary = Error_codes.Temporary
466 module Parsing = Error_codes.Parsing
467 module Naming = Error_codes.Naming
468 module NastCheck = Error_codes.NastCheck
469 module Typing = Error_codes.Typing
470 module Init = Error_codes.Init
472 (*****************************************************************************)
473 (* Types *)
474 (*****************************************************************************)
476 type 'a error_ = 'a M.error_
477 type error = Pos.t error_
478 type applied_fixme = M.applied_fixme
479 type t = error files_t * applied_fixme files_t
481 type phase = error_phase = Init | Parsing | Naming | Decl | Typing
482 type severity = error_severity = Warning | Error
484 module type Error_category = sig
485 type t
486 val min : int
487 val max : int
488 val of_enum : int -> t option
489 val show : t -> string
490 val err_code : t -> int
492 (*****************************************************************************)
493 (* HH_FIXMEs hook *)
494 (*****************************************************************************)
496 let applied_fixmes = M.applied_fixmes
497 let error_map = M.error_map
499 let default_ignored_fixme_codes = ISet.of_list [
500 Typing.err_code Typing.InvalidIsAsExpressionHint;
502 let ignored_fixme_codes = ref default_ignored_fixme_codes
504 let set_allow_errors_in_default_path x = allow_errors_in_default_path := x
506 let is_ignored_code code = ISet.mem code !ignored_fixme_codes
508 let is_ignored_fixme code = is_ignored_code code
510 let (is_hh_fixme: (Pos.t -> error_code -> bool) ref) = ref (fun _ _ -> false)
511 let (get_hh_fixme_pos: (Pos.t -> error_code -> Pos.t option) ref) =
512 ref (fun _ _ -> None)
514 let add_ignored_fixme_code_error pos code =
515 if !is_hh_fixme pos code && is_ignored_code code then
516 let pos = Option.value (!get_hh_fixme_pos pos code) ~default:pos in
517 M.add_error (M.make_error code
518 [pos, Printf.sprintf "HH_FIXME cannot be used for error %d" code])
520 (*****************************************************************************)
521 (* Errors accumulator. *)
522 (*****************************************************************************)
524 let add_applied_fixme code pos =
525 if ServerLoadFlag.get_no_load () then
526 let applied_fixmes_list = Common.get_current_list !applied_fixmes in
527 Common.set_current_list applied_fixmes ((pos, code) :: applied_fixmes_list)
528 else ()
530 let rec add_error = M.add_error
532 and add code pos msg =
533 if not (is_ignored_fixme code) && !is_hh_fixme pos code
534 then add_applied_fixme code pos
535 else add_error (M.make_error code [pos, msg]);
536 add_ignored_fixme_code_error pos code
538 and add_list code pos_msg_l =
539 let pos = fst (List.hd_exn pos_msg_l) in
540 if not (is_ignored_fixme code) && !is_hh_fixme pos code
541 then add_applied_fixme code pos
542 else add_error (make_error code pos_msg_l);
543 add_ignored_fixme_code_error pos code;
545 and merge (err',fixmes') (err,fixmes) =
546 let append = fun _ _ x y ->
547 let x = Option.value x ~default: [] in
548 let y = Option.value y ~default: [] in
549 Some (List.rev_append x y)
551 files_t_merge ~f:append err' err,
552 files_t_merge ~f:append fixmes' fixmes
554 and merge_into_current errors =
555 let merged = merge errors (!error_map, !applied_fixmes) in
556 error_map := fst merged;
557 applied_fixmes := snd merged
559 and incremental_update :
560 (* Need to write out the entire ugly type to convince OCaml it's polymorphic
561 * and can update both error_map as well as applied_fixmes map *)
562 type a .
563 a files_t ->
564 a files_t ->
565 (* function folding over paths of rechecked files *)
566 (a files_t -> (Relative_path.t -> a files_t -> a files_t) -> a files_t) ->
567 phase ->
568 a files_t
569 = fun old new_ fold phase ->
570 (* Helper to remove acc[path][phase]. If acc[path] becomes empty afterwards,
571 * remove it too (i.e do not store empty maps or lists ever). *)
572 let remove path phase acc =
573 let new_phase_map = match Relative_path.Map.get acc path with
574 | None -> None
575 | Some phase_map ->
576 let new_phase_map = PhaseMap.remove phase_map phase in
577 if PhaseMap.is_empty new_phase_map then None else Some new_phase_map
579 match new_phase_map with
580 | None -> Relative_path.Map.remove acc path
581 | Some x -> Relative_path.Map.add acc path x
583 (* Replace old errors with new *)
584 let res = files_t_merge new_ old ~f:begin fun phase path new_ old ->
585 if path = Relative_path.default then begin
586 let phase = match phase with
587 | Init -> "Init"
588 | Parsing -> "Parsing"
589 | Naming -> "Naming"
590 | Decl -> "Decl"
591 | Typing -> "Typing"
593 Utils.assert_false_log_backtrace (Some(
594 "Default (untracked) error sources should not get into incremental " ^
595 "mode. There might be a missing call to Errors.do_with_context/" ^
596 "run_in_context somwhere or incorrectly used Errors.from_error_list." ^
597 "Phase: " ^ phase
599 end;
600 match new_ with
601 | Some new_ -> Some (List.rev new_)
602 | None -> old
603 end in
604 (* For files that were rechecked, but had no errors - remove them from maps *)
605 fold res begin fun path acc ->
606 let has_errors =
607 match Relative_path.Map.get new_ path with
608 | None -> false
609 | Some phase_map -> PhaseMap.mem phase_map phase
611 if has_errors then acc
612 else remove path phase acc
615 and incremental_update_set ~old ~new_ ~rechecked phase =
616 let fold = fun init g -> Relative_path.Set.fold ~f:begin fun path acc ->
617 g path acc
618 end ~init rechecked in
619 (incremental_update (fst old) (fst new_) fold phase),
620 (incremental_update (snd old) (snd new_) fold phase)
622 and incremental_update_map ~old ~new_ ~rechecked phase =
623 let fold = fun init g -> Relative_path.Map.fold ~f:begin fun path _ acc ->
624 g path acc
625 end ~init rechecked in
626 (incremental_update (fst old) (fst new_) fold phase),
627 (incremental_update (snd old) (snd new_) fold phase)
629 and empty = (Relative_path.Map.empty, Relative_path.Map.empty)
630 and is_empty (err, _fixmes) = Relative_path.Map.is_empty err
632 and count (err, _fixmes) = files_t_fold err ~f:(fun _ _ x acc -> acc + List.length x) ~init:0
633 and get_error_list (err, _fixmes) = files_t_to_list err
634 and get_applied_fixmes (_err, fixmes) = files_t_to_list fixmes
635 and from_error_list err = (list_to_files_t err, Relative_path.Map.empty)
637 (*****************************************************************************)
638 (* Accessors. (All methods delegated to the parameterized module.) *)
639 (*****************************************************************************)
641 and get_code = M.get_code
642 and get_pos = M.get_pos
643 and get_severity = M.get_severity
644 and to_list = M.to_list
646 and make_error = M.make_error
648 let sort = M.sort
649 let get_sorted_error_list = M.get_sorted_error_list
650 let iter_error_list f err = List.iter ~f:f (get_sorted_error_list err)
652 let fold_errors ?phase err ~init ~f =
653 match phase with
654 | None ->
655 files_t_fold (fst err)
656 ~init
657 ~f:begin fun source _ errors acc ->
658 List.fold_right errors ~init:acc ~f:(f source)
660 | Some phase ->
661 Relative_path.Map.fold (fst err) ~init ~f:begin fun source phases acc ->
662 match PhaseMap.get phases phase with
663 | None -> acc
664 | Some errors -> List.fold_right errors ~init:acc ~f:(f source)
667 let fold_errors_in ?phase err ~source ~init ~f =
668 Relative_path.Map.get (fst err) source |>
669 Option.value ~default:PhaseMap.empty |>
670 PhaseMap.fold ~init ~f:begin fun p errors acc ->
671 if phase <> None && phase <> Some p then acc
672 else List.fold_right errors ~init:acc ~f
675 let get_failed_files err phase =
676 files_t_fold (fst err)
677 ~init:Relative_path.Set.empty
678 ~f:begin fun source p _ acc ->
679 if phase <> p then acc else Relative_path.Set.add acc source
682 (*****************************************************************************)
683 (* Error code printing. *)
684 (*****************************************************************************)
686 let error_code_to_string = Common.error_code_to_string
688 let phase_to_string = Common.phase_to_string
690 let internal_error pos msg =
691 add 0 pos ("Internal error: "^msg)
693 let unimplemented_feature pos msg =
694 add 0 pos ("Feature not implemented: " ^ msg)
696 let experimental_feature pos msg =
697 add 0 pos ("Cannot use experimental feature: " ^ msg)
699 (*****************************************************************************)
700 (* Temporary errors. *)
701 (*****************************************************************************)
703 let darray_not_supported pos =
704 add Temporary.darray_not_supported pos "darray is not supported."
706 let varray_not_supported pos =
707 add Temporary.varray_not_supported pos "varray is not supported."
709 let varray_or_darray_not_supported pos =
711 Temporary.varray_or_darray_not_supported
713 "varray_or_darray is not supported."
715 let nonnull_not_supported pos =
716 add Temporary.nonnull_not_supported pos "nonnull is not supported."
718 (*****************************************************************************)
719 (* Parsing errors. *)
720 (*****************************************************************************)
722 let fixme_format pos =
723 add (Parsing.err_code Parsing.FixmeFormat) pos
724 "HH_FIXME wrong format, expected '/* HH_FIXME[ERROR_NUMBER] */'"
726 let unexpected_eof pos =
727 add (Parsing.err_code Parsing.UnexpectedEof) pos "Unexpected end of file"
729 let unterminated_comment pos =
730 add (Parsing.err_code Parsing.UnterminatedComment) pos "unterminated comment"
732 let unterminated_xhp_comment pos =
733 add (Parsing.err_code Parsing.UnterminatedXhpComment) pos "unterminated xhp comment"
735 let parsing_error (p, msg) =
736 add (Parsing.err_code Parsing.ParsingError) p msg
738 (*****************************************************************************)
739 (* Naming errors *)
740 (*****************************************************************************)
743 let trait_interface_constructor_promo pos =
744 add (Naming.err_code Naming.TraitInterfaceConstructorPromo) pos
745 "Constructor parameter promotion not allowed on traits or interfaces"
747 let typeparam_alok (pos, x) =
748 add (Naming.err_code Naming.TypeparamAlok) pos (
749 "You probably forgot to bind this type parameter right?\nAdd <"^x^
750 "> somewhere (after the function name definition, \
751 or after the class name)\nExamples: "^"function foo<T> or class A<T>")
753 let unexpected_arrow pos cname =
754 add (Naming.err_code Naming.UnexpectedArrow) pos (
755 "Keys may not be specified for "^cname^" initialization"
758 let missing_arrow pos cname =
759 add (Naming.err_code Naming.MissingArrow) pos (
760 "Keys must be specified for "^cname^" initialization"
763 let disallowed_xhp_type pos name =
764 add (Naming.err_code Naming.DisallowedXhpType) pos (
765 name^" is not a valid type. Use :xhp or XHPChild."
768 let name_already_bound name pos1 pos2 =
769 let name = Utils.strip_ns name in
770 add_list (Naming.err_code Naming.NameAlreadyBound) [
771 pos1, "Name already bound: "^name;
772 pos2, "Previous definition is here"
775 let name_is_reserved name pos =
776 let name = Utils.strip_all_ns name in
777 add (Naming.err_code Naming.NameIsReserved) pos (
778 name^" cannot be used as it is reserved."
781 let dollardollar_unused pos =
782 add (Naming.err_code Naming.DollardollarUnused) pos ("This expression does not contain a "^
783 "usage of the special pipe variable. Did you forget to use the ($$) "^
784 "variable?")
786 let method_name_already_bound pos name =
787 add (Naming.err_code Naming.MethodNameAlreadyBound) pos (
788 "Method name already bound: "^name
791 let reference_in_rx pos =
792 add (Naming.err_code Naming.ReferenceInRx) pos (
793 "References are not allowed in reactive code."
795 let error_name_already_bound name name_prev p p_prev =
796 let name = Utils.strip_ns name in
797 let name_prev = Utils.strip_ns name_prev in
798 let errs = [
799 p, "Name already bound: "^name;
800 p_prev, (if String.compare name name_prev == 0
801 then "Previous definition is here"
802 else "Previous definition "^name_prev^" differs only in capitalization ")
803 ] in
804 let hhi_msg =
805 "This appears to be defined in an hhi file included in your project "^
806 "root. The hhi files for the standard library are now a part of the "^
807 "typechecker and must be removed from your project. Typically, you can "^
808 "do this by deleting the \"hhi\" directory you copied into your "^
809 "project when first starting with Hack." in
810 let errs =
811 if (Relative_path.prefix (Pos.filename p)) = Relative_path.Hhi
812 then errs @ [p_prev, hhi_msg]
813 else if (Relative_path.prefix (Pos.filename p_prev)) = Relative_path.Hhi
814 then errs @ [p, hhi_msg]
815 else errs in
816 add_list (Naming.err_code Naming.ErrorNameAlreadyBound) errs
818 let error_class_attribute_already_bound name name_prev p p_prev =
819 let name = Utils.strip_ns name in
820 let name_prev = Utils.strip_ns name_prev in
821 let errs = [
822 p, "A class and an attribute class cannot share the same name. Conflicting class: "^name;
823 p_prev, "Previous definition: "^name_prev
824 ] in
825 add_list (Naming.err_code Naming.AttributeClassNameConflict) errs
827 let unbound_name pos name kind =
828 let kind_str = match kind with
829 | `cls -> "an object type"
830 | `func -> "a global function"
831 | `const -> "a global constant"
833 add (Naming.err_code Naming.UnboundName) pos
834 ("Unbound name: "^(strip_ns name)^" ("^kind_str^")")
836 let different_scope pos var_name pos' =
837 add_list (Naming.err_code Naming.DifferentScope) [
838 pos, ("The variable "^ var_name ^" is defined");
839 pos', ("But in a different scope")
842 let rx_move_invalid_location pos =
843 add (Naming.err_code Naming.RxMoveInvalidLocation) pos
844 "Rx\\move is only allowed in argument position or as right hand side of the assignment."
846 let undefined pos var_name =
847 add (Naming.err_code Naming.Undefined) pos ("Variable "^var_name^
848 " is undefined, "^
849 "or there exists at least one control flow path reaching this point which "^
850 "does not define "^var_name^".")
852 let this_reserved pos =
853 add (Naming.err_code Naming.ThisReserved) pos
854 "The type parameter \"this\" is reserved"
856 let start_with_T pos =
857 add (Naming.err_code Naming.StartWith_T) pos
858 "Please make your type parameter start with the letter T (capital)"
860 let already_bound pos name =
861 add (Naming.err_code Naming.NameAlreadyBound) pos ("Argument already bound: "^name)
863 let unexpected_typedef pos def_pos =
864 add_list (Naming.err_code Naming.UnexpectedTypedef) [
865 pos, "Unexpected typedef";
866 def_pos, "Definition is here";
869 let fd_name_already_bound pos =
870 add (Naming.err_code Naming.FdNameAlreadyBound) pos
871 "Field name already bound"
873 let primitive_toplevel pos =
874 add (Naming.err_code Naming.PrimitiveToplevel) pos (
875 "Primitive type annotations are always available and may no \
876 longer be referred to in the toplevel namespace."
879 let primitive_invalid_alias pos used valid =
880 add (Naming.err_code Naming.PrimitiveInvalidAlias) pos
881 ("Invalid Hack type. Using '"^used^"' in Hack is considered \
882 an error. Use '"^valid^"' instead, to keep the codebase \
883 consistent.")
885 let dynamic_new_in_strict_mode pos =
886 add (Naming.err_code Naming.DynamicNewInStrictMode) pos
887 "Cannot use dynamic new in strict mode"
889 let invalid_type_access_root (pos, id) =
890 add (Naming.err_code Naming.InvalidTypeAccessRoot) pos
891 (id^" must be an identifier for a class, \"self\", or \"this\"")
893 let duplicate_user_attribute (pos, name) existing_attr_pos =
894 add_list (Naming.err_code Naming.DuplicateUserAttribute) [
895 pos, "You cannot reuse the attribute "^name;
896 existing_attr_pos, name^" was already used here";
899 let misplaced_rx_of_scope pos =
900 add (Naming.err_code Naming.MisplacedRxOfScope) pos (
901 "<<__RxOfScope>> attribute is only allowed on lambdas."
903 let rx_of_scope_and_explicit_rx pos =
904 add (Naming.err_code Naming.RxOfScopeAndExplicitRx) pos (
905 "<<__RxOfScope>> attribute cannot be used with explicit reactivity annotations."
907 let unbound_attribute_name pos name =
908 let reason = if (string_starts_with name "__")
909 then "starts with __ but is not a standard attribute"
910 else "does not have a class and is not listed in .hhconfig"
911 in add (Naming.err_code Naming.UnboundName) pos
912 ("Unrecognized user attribute: "^(Utils.strip_ns name)^" "^reason)
914 let this_no_argument pos =
915 add (Naming.err_code Naming.ThisNoArgument) pos "\"this\" expects no arguments"
917 let void_cast pos =
918 add (Naming.err_code Naming.VoidCast) pos "Cannot cast to void."
920 let unset_cast pos =
921 add (Naming.err_code Naming.UnsetCast) pos "Don't use (unset), just assign null!"
923 let object_cast pos cls_opt =
924 let msg1 = "Object casts are unsupported." in
925 let msg2 =
926 match cls_opt with
927 | Some c ->
928 " Try 'if ($var instanceof "^c^")' or 'invariant($var instanceof "^c^", ...)'."
929 | None -> ""
931 add (Naming.err_code Naming.ObjectCast) pos (msg1 ^ msg2)
933 let this_hint_outside_class pos =
934 add (Naming.err_code Naming.ThisHintOutsideClass) pos
935 "Cannot use \"this\" outside of a class"
937 let this_type_forbidden pos =
938 add (Naming.err_code Naming.ThisMustBeReturn) pos
939 "The type \"this\" cannot be used as a constraint on a class' generic, \
940 or as the type of a static member variable"
942 let nonstatic_property_with_lsb pos =
943 add (Naming.err_code Naming.NonstaticPropertyWithLSB) pos
944 "__LSB attribute may only be used on static properties"
946 let lowercase_this pos type_ =
947 add (Naming.err_code Naming.LowercaseThis) pos (
948 "Invalid Hack type \""^type_^"\". Use \"this\" instead"
951 let classname_param pos =
952 add (Naming.err_code Naming.ClassnameParam) pos
953 ("Missing type parameter to classname; classname is entirely"
954 ^" meaningless without one")
956 let invalid_instanceof pos =
957 add (Naming.err_code Naming.InvalidInstanceof) pos
958 "This instanceof has an invalid right operand. Only class identifiers, \
959 local variables, accesses of objects / classes / arrays, and function / \
960 method calls are allowed."
962 let tparam_with_tparam pos x =
963 add (Naming.err_code Naming.TparamWithTparam) pos (
964 Printf.sprintf "%s is a type parameter. Type parameters cannot \
965 themselves take type parameters (e.g. %s<int> doesn't make sense)" x x
968 let shadowed_type_param p pos name =
969 add_list (Naming.err_code Naming.ShadowedTypeParam) [
970 p, Printf.sprintf "You cannot re-bind the type parameter %s" name;
971 pos, Printf.sprintf "%s is already bound here" name
974 let missing_typehint pos =
975 add (Naming.err_code Naming.MissingTypehint) pos
976 "Please add a type hint"
978 let expected_variable pos =
979 add (Naming.err_code Naming.ExpectedVariable) pos
980 "Was expecting a variable name"
982 let clone_too_many_arguments pos =
983 add (Naming.err_code Naming.NamingTooManyArguments) pos
984 "__clone method cannot take arguments"
986 let naming_too_few_arguments pos =
987 add (Naming.err_code Naming.NamingTooFewArguments) pos
988 "Too few arguments"
990 let naming_too_many_arguments pos =
991 add (Naming.err_code Naming.NamingTooManyArguments) pos
992 "Too many arguments"
994 let expected_collection pos cn =
995 add (Naming.err_code Naming.ExpectedCollection) pos (
996 "Unexpected collection type " ^ (Utils.strip_ns cn)
999 let illegal_CLASS pos =
1000 add (Naming.err_code Naming.IllegalClass) pos
1001 "Using __CLASS__ outside a class or trait"
1003 let illegal_TRAIT pos =
1004 add (Naming.err_code Naming.IllegalTrait) pos
1005 "Using __TRAIT__ outside a trait"
1007 let dynamic_method_call pos =
1008 add (Naming.err_code Naming.DynamicMethodCall) pos
1009 "Dynamic method call"
1011 let nullsafe_property_write_context pos =
1012 add (Typing.err_code Typing.NullsafePropertyWriteContext) pos
1013 "?-> syntax not supported here, this function effectively does a write"
1015 let illegal_fun pos =
1016 let msg = "The argument to fun() must be a single-quoted, constant "^
1017 "literal string representing a valid function name." in
1018 add (Naming.err_code Naming.IllegalFun) pos msg
1020 let illegal_member_variable_class pos =
1021 let msg = "Cannot declare a constant named 'class'. \
1022 The name 'class' is reserved for the class \
1023 constant that represents the name of the class" in
1024 add (Naming.err_code Naming.IllegalMemberVariableClass) pos msg
1026 let illegal_meth_fun pos =
1027 let msg = "String argument to fun() contains ':';"^
1028 " for static class methods, use"^
1029 " class_meth(Cls::class, 'method_name'), not fun('Cls::method_name')" in
1030 add (Naming.err_code Naming.IllegalMethFun) pos msg
1032 let illegal_inst_meth pos =
1033 let msg = "The argument to inst_meth() must be an expression and a "^
1034 "constant literal string representing a valid method name." in
1035 add (Naming.err_code Naming.IllegalInstMeth) pos msg
1037 let illegal_meth_caller pos =
1038 let msg =
1039 "The two arguments to meth_caller() must be:"
1040 ^"\n - first: ClassOrInterface::class"
1041 ^"\n - second: a single-quoted string literal containing the name"
1042 ^" of a non-static method of that class" in
1043 add (Naming.err_code Naming.IllegalMethCaller) pos msg
1045 let illegal_class_meth pos =
1046 let msg =
1047 "The two arguments to class_meth() must be:"
1048 ^"\n - first: ValidClassname::class"
1049 ^"\n - second: a single-quoted string literal containing the name"
1050 ^" of a static method of that class" in
1051 add (Naming.err_code Naming.IllegalClassMeth) pos msg
1053 let assert_arity pos =
1054 add (Naming.err_code Naming.AssertArity) pos
1055 "assert expects exactly one argument"
1057 let gena_arity pos =
1058 add (Naming.err_code Naming.GenaArity) pos
1059 "gena() expects exactly 1 argument"
1061 let genva_arity pos =
1062 add (Naming.err_code Naming.GenvaArity) pos
1063 "genva() expects at least 1 argument"
1065 let gen_array_rec_arity pos =
1066 add (Naming.err_code Naming.GenArrayRecArity) pos
1067 "gen_array_rec() expects exactly 1 argument"
1069 let uninstantiable_class usage_pos decl_pos name reason_msgl =
1070 let name = strip_ns name in
1071 let msgl = [
1072 usage_pos, (name^" is uninstantiable");
1073 decl_pos, "Declaration is here"
1074 ] in
1075 let msgl = match reason_msgl with
1076 | (reason_pos, reason_str) :: tail ->
1077 (reason_pos, reason_str^" which must be instantiable") :: tail @ msgl
1078 | _ -> msgl in
1079 add_list (Typing.err_code Typing.UninstantiableClass) msgl
1081 let abstract_const_usage usage_pos decl_pos name =
1082 let name = strip_ns name in
1083 add_list (Typing.err_code Typing.AbstractConstUsage) [
1084 usage_pos, ("Cannot reference abstract constant "^name^" directly");
1085 decl_pos, "Declaration is here"
1088 let add_a_typehint pos =
1089 add (Naming.err_code Naming.AddATypehint) pos
1090 "Please add a type hint"
1092 let local_const var_pos =
1093 add (Naming.err_code Naming.LocalConst) var_pos
1094 "You cannot use a local variable in a constant definition"
1096 let illegal_constant pos =
1097 add (Naming.err_code Naming.IllegalConstant) pos
1098 "Illegal constant value"
1100 let invalid_req_implements pos =
1101 add (Naming.err_code Naming.InvalidReqImplements) pos
1102 "Only traits may use 'require implements'"
1104 let invalid_req_extends pos =
1105 add (Naming.err_code Naming.InvalidReqExtends) pos
1106 "Only traits and interfaces may use 'require extends'"
1108 let did_you_mean_naming pos name suggest_pos suggest_name =
1109 add_list (Naming.err_code Naming.DidYouMeanNaming) [
1110 pos, "Could not find "^(strip_ns name);
1111 suggest_pos, "Did you mean "^(strip_ns suggest_name)^"?"
1114 let using_internal_class pos name =
1115 add (Naming.err_code Naming.UsingInternalClass) pos (
1116 name^" is an implementation internal class that cannot be used directly"
1119 let too_few_type_arguments p =
1120 add (Naming.err_code Naming.TooFewTypeArguments) p
1121 ("Too few type arguments for this type")
1123 let goto_label_already_defined
1124 label_name
1125 redeclaration_pos
1126 original_delcaration_pos =
1127 add_list
1128 (Naming.err_code Naming.GotoLabelAlreadyDefined)
1130 redeclaration_pos, "Cannot redeclare the goto label '" ^ label_name ^ "'";
1131 original_delcaration_pos, "Declaration is here";
1134 let goto_label_undefined pos label_name =
1135 add (Naming.err_code Naming.GotoLabelUndefined) pos ("Undefined goto label: " ^ label_name)
1137 let goto_label_defined_in_finally pos =
1138 add (Naming.err_code Naming.GotoLabelDefinedInFinally)
1140 "It is illegal to define a goto label within a finally block."
1142 let unsupported_feature pos name =
1143 add (Naming.err_code Naming.UnsupportedFeature) pos (name ^ " is not supported in Hack.")
1145 let goto_invoked_in_finally pos =
1146 add (Naming.err_code Naming.GotoInvokedInFinally)
1148 "It is illegal to invoke goto within a finally block."
1150 let method_needs_visibility pos =
1151 add (Naming.err_code Naming.MethodNeedsVisibility)
1152 pos ("Methods need to be marked public, private, or protected.")
1154 let dynamic_class_property_name_in_strict_mode pos =
1155 add (Naming.err_code Naming.DynamicClassPropertyNameInStrictMode)
1157 "Cannot use dynamic class property name in strict mode"
1159 let dynamic_class_name_in_strict_mode pos =
1160 add (Naming.err_code Naming.DynamicClassNameInStrictMode)
1162 "Cannot use dynamic class name in strict mode"
1164 let xhp_optional_required_attr pos id =
1165 add (Naming.err_code Naming.XhpOptionalRequiredAttr)
1167 ("XHP attribute " ^ id ^ " cannot be marked as nullable and required")
1169 let xhp_required_with_default pos id =
1170 add (Naming.err_code Naming.XhpRequiredWithDefault)
1172 ("XHP attribute " ^ id ^ " cannot be marked as required and provide a default")
1174 let variable_variables_disallowed pos =
1175 add (Naming.err_code Naming.VariableVariablesDisallowed) pos
1176 "Variable variables are not legal; all variable identifiers must be static strings."
1178 let array_typehints_disallowed pos =
1179 add (Naming.err_code Naming.ArrayTypehintsDisallowed) pos
1180 "Array typehints are no longer legal; use varray or darray instead"
1182 let array_literals_disallowed pos =
1183 add (Naming.err_code Naming.ArrayLiteralsDisallowed) pos
1184 "Array literals are no longer legal; use varray or darray instead"
1186 let wildcard_disallowed pos =
1187 add (Naming.err_code Naming.WildcardDisallowed) pos
1188 "Wildcard typehints are not allowed in this position"
1190 let reference_in_strict_mode pos =
1191 add (Naming.err_code Naming.ReferenceInStrictMode) pos
1192 "Don't use references!"
1194 let anon_use_capture_by_ref pos =
1195 add (Naming.err_code Naming.ReferenceInAnonUseClause) pos (
1196 "Capturing variables by PHP reference is no longer supported on anonymous "^
1197 "functions. If the variable is a value type, store it on an object "^
1198 "instead or refactor your code to avoid using a closure.")
1200 (*****************************************************************************)
1201 (* Init check errors *)
1202 (*****************************************************************************)
1204 let no_construct_parent pos =
1205 add (NastCheck.err_code NastCheck.NoConstructParent) pos (
1206 sl["You are extending a class that needs to be initialized\n";
1207 "Make sure you call parent::__construct.\n"
1211 let mutable_on_static pos =
1212 add (NastCheck.err_code NastCheck.MutableOnStatic) pos (
1213 "<<__Mutable>> attribute is not allowed on static methods."
1216 let nonstatic_method_in_abstract_final_class pos =
1217 add (NastCheck.err_code NastCheck.NonstaticMethodInAbstractFinalClass) pos (
1218 "Abstract final classes cannot have nonstatic methods or constructors."
1221 let constructor_required (pos, name) prop_names =
1222 let name = Utils.strip_ns name in
1223 let props_str = SSet.fold ~f:(fun x acc -> x^" "^acc) prop_names ~init:"" in
1224 add (NastCheck.err_code NastCheck.ConstructorRequired) pos
1225 ("Lacking __construct, class "^name^" does not initialize its private member(s): "^props_str)
1227 let not_initialized (pos, cname) prop_names =
1228 let cname = Utils.strip_ns cname in
1229 let props_str = List.fold_right prop_names
1230 ~f:(fun x acc -> x^" "^acc) ~init:"" in
1231 let members, verb =
1232 if 1 == List.length prop_names
1233 then "member", "is"
1234 else "members", "are" in
1235 let setters_str = List.fold_right prop_names
1236 ~f:(fun x acc -> "$this->"^x^" "^acc) ~init:"" in
1237 add (NastCheck.err_code NastCheck.NotInitialized) pos (
1239 "Class "; cname ; " does not initialize all of its members; ";
1240 props_str; verb; " not always initialized.";
1241 "\nMake sure you systematically set "; setters_str;
1242 "when the method __construct is called.";
1243 "\nAlternatively, you can define the "; members ;" as optional (?...)\n"
1246 let call_before_init pos cv =
1247 add (NastCheck.err_code NastCheck.CallBeforeInit) pos (
1248 sl([
1249 "Until the initialization of $this is over,";
1250 " you can only call private methods\n";
1251 "The initialization is not over because ";
1253 if cv = "parent::__construct"
1254 then ["you forgot to call parent::__construct"]
1255 else ["$this->"; cv; " can still potentially be null"])
1258 (*****************************************************************************)
1259 (* Nast errors check *)
1260 (*****************************************************************************)
1262 let type_arity pos name nargs =
1263 add (Typing.err_code Typing.TypeArityMismatch) pos (
1264 sl["The type ";(Utils.strip_ns name);
1265 " expects ";nargs;" type parameter(s)"]
1268 let abstract_with_body (p, _) =
1269 add (NastCheck.err_code NastCheck.AbstractWithBody) p
1270 "This method is declared as abstract, but has a body"
1272 let not_abstract_without_body (p, _) =
1273 add (NastCheck.err_code NastCheck.NotAbstractWithoutBody) p
1274 "This method is not declared as abstract, it must have a body"
1276 let not_abstract_without_typeconst (p, _) =
1277 add (NastCheck.err_code NastCheck.NotAbstractWithoutTypeconst) p
1278 ("This type constant is not declared as abstract, it must have"^
1279 " an assigned type")
1281 let abstract_with_typeconst (p, _) =
1282 add (NastCheck.err_code NastCheck.AbstractWithTypeconst) p
1283 ("This type constant is declared as abstract, it cannot be assigned a type")
1285 let typeconst_depends_on_external_tparam pos ext_pos ext_name =
1286 add_list (NastCheck.err_code NastCheck.TypeconstDependsOnExternalTparam) [
1287 pos, ("A type constant can only use type parameters declared in its own"^
1288 " type parameter list");
1289 ext_pos, (ext_name ^ " was declared as a type parameter here");
1292 let typeconst_assigned_tparam pos tp_name =
1293 add (NastCheck.err_code NastCheck.TypeconstAssignedTparam) pos
1294 (tp_name ^" is a type parameter. It cannot be assigned to a type constant")
1296 let interface_with_partial_typeconst tconst_pos =
1297 add (NastCheck.err_code NastCheck.InterfaceWithPartialTypeconst) tconst_pos
1298 "An interface cannot contain a partially abstract type constant"
1300 let multiple_xhp_category pos =
1301 add (NastCheck.err_code NastCheck.MultipleXhpCategory) pos
1302 "XHP classes can only contain one category declaration"
1304 let return_in_gen p =
1305 add (NastCheck.err_code NastCheck.ReturnInGen) p
1306 ("You cannot return a value in a generator (a generator"^
1307 " is a function that uses yield)")
1309 let return_in_finally p =
1310 add (NastCheck.err_code NastCheck.ReturnInFinally) p
1311 ("Don't use return in a finally block;"^
1312 " there's nothing to receive the return value")
1314 let toplevel_break p =
1315 add (NastCheck.err_code NastCheck.ToplevelBreak) p
1316 "break can only be used inside loops or switch statements"
1318 let toplevel_continue p =
1319 add (NastCheck.err_code NastCheck.ToplevelContinue) p
1320 "continue can only be used inside loops"
1322 let continue_in_switch p =
1323 add (NastCheck.err_code NastCheck.ContinueInSwitch) p
1324 ("In PHP, 'continue;' inside a switch \
1325 statement is equivalent to 'break;'."^
1326 " Hack does not support this; use 'break' if that is what you meant.")
1328 let await_in_sync_function p =
1329 add (NastCheck.err_code NastCheck.AwaitInSyncFunction) p
1330 "await can only be used inside async functions"
1332 let interface_use_trait p =
1333 add (NastCheck.err_code NastCheck.InterfaceUsesTrait) p
1334 "Interfaces cannot use traits"
1336 let await_not_allowed p =
1337 add (NastCheck.err_code NastCheck.AwaitNotAllowed) p
1338 "await is only permitted as a statement, expression in a return statement \
1339 or as a right hand side in top level assignment."
1341 let async_in_interface p =
1342 add (NastCheck.err_code NastCheck.AsyncInInterface) p
1343 "async is only meaningful when it modifies a method body"
1345 let await_in_coroutine p =
1346 add (NastCheck.err_code NastCheck.AwaitInCoroutine) p
1347 "await is not allowed in coroutines."
1349 let yield_in_coroutine p =
1350 add (NastCheck.err_code NastCheck.YieldInCoroutine) p
1351 "yield is not allowed in coroutines."
1353 let suspend_outside_of_coroutine p =
1354 add (NastCheck.err_code NastCheck.SuspendOutsideOfCoroutine) p
1355 "suspend is only allowed in coroutines."
1357 let suspend_in_finally p =
1358 add (NastCheck.err_code NastCheck.SuspendInFinally) p
1359 "suspend is not allowed inside finally blocks."
1361 let break_continue_n_not_supported p =
1362 add (NastCheck.err_code NastCheck.BreakContinueNNotSupported) p
1363 "Break/continue N operators are not supported."
1365 let static_memoized_function p =
1366 add (NastCheck.err_code NastCheck.StaticMemoizedFunction) p
1367 "memoize is not allowed on static methods in classes that aren't final "
1369 let magic (p, s) =
1370 add (NastCheck.err_code NastCheck.Magic) p
1371 ("Don't call "^s^" it's one of these magic things we want to avoid")
1373 let non_interface (p : Pos.t) (c2: string) (verb: string): 'a =
1374 add (NastCheck.err_code NastCheck.NonInterface) p
1375 ("Cannot " ^ verb ^ " " ^ (strip_ns c2) ^ " - it is not an interface")
1377 let toString_returns_string pos =
1378 add (NastCheck.err_code NastCheck.ToStringReturnsString) pos "__toString should return a string"
1380 let toString_visibility pos =
1381 add (NastCheck.err_code NastCheck.ToStringVisibility) pos
1382 "__toString must have public visibility and cannot be static"
1384 let uses_non_trait (p: Pos.t) (n: string) (t: string) =
1385 add (NastCheck.err_code NastCheck.UsesNonTrait) p
1386 ((Utils.strip_ns n) ^ " is not a trait. It is " ^ t ^ ".")
1388 let requires_non_class (p: Pos.t) (n: string) (t: string) =
1389 add (NastCheck.err_code NastCheck.RequiresNonClass) p
1390 ((Utils.strip_ns n) ^ " is not a class. It is " ^ t ^ ".")
1392 let requires_final_class (p: Pos.t) (n: string) =
1393 add (NastCheck.err_code NastCheck.RequiresFinalClass) p
1394 ((Utils.strip_ns n) ^ " is not an extendable class.")
1396 let abstract_body pos =
1397 add (NastCheck.err_code NastCheck.AbstractBody) pos "This method shouldn't have a body"
1399 let not_public_or_protected_interface pos =
1400 add (NastCheck.err_code NastCheck.NotPublicInterface) pos
1401 "Access type for interface method must be public or protected."
1403 let interface_with_member_variable pos =
1404 add (NastCheck.err_code NastCheck.InterfaceWithMemberVariable) pos
1405 "Interfaces cannot have member variables"
1407 let interface_with_static_member_variable pos =
1408 add (NastCheck.err_code NastCheck.InterfaceWithStaticMemberVariable) pos
1409 "Interfaces cannot have static variables"
1411 let illegal_function_name pos mname =
1412 add (NastCheck.err_code NastCheck.IllegalFunctionName) pos
1413 ("Illegal function name: " ^ strip_ns mname)
1415 let dangerous_method_name pos =
1416 add (NastCheck.err_code NastCheck.DangerousMethodName) pos (
1417 "This is a dangerous method name, "^
1418 "if you want to define a constructor, use "^
1419 "__construct"
1422 let inout_params_outside_of_sync pos =
1423 add (NastCheck.err_code NastCheck.InoutParamsOutsideOfSync) pos (
1424 "Inout parameters cannot be defined on async functions, "^
1425 "generators or coroutines."
1428 let mutable_params_outside_of_sync pos fpos name fname =
1429 add_list (NastCheck.err_code NastCheck.MutableParamsOutsideOfSync) [
1430 pos, "Mutable parameters are not allowed on async functions";
1431 pos, "This parameter "^ (strip_ns name) ^" is marked mutable.";
1432 fpos, "The function "^ (strip_ns fname) ^" is marked async.";
1435 let mutable_async_method pos =
1436 add (NastCheck.err_code NastCheck.MutableAsyncMethod) pos (
1437 "Mutable methods must be synchronous. Try removing the async tag from the function."
1440 let mutable_attribute_on_function pos =
1441 add (NastCheck.err_code NastCheck.MutableAttributeOnFunction) pos (
1442 "<<__Mutable>> only makes sense on methods, or parameters on functions or methods."
1445 let maybe_mutable_attribute_on_function pos =
1446 add (NastCheck.err_code NastCheck.MaybeMutableAttributeOnFunction) pos (
1447 "<<__MaybeMutable>> only makes sense on methods, or parameters on functions or methods."
1450 let conflicting_mutable_and_maybe_mutable_attributes pos =
1451 add (NastCheck.err_code NastCheck.ConflictingMutableAndMaybeMutableAttributes) pos (
1452 "Declaration cannot have both <<__Mutable>> and <<__MaybeMutable>> attributtes."
1455 let mutable_methods_must_be_reactive pos name =
1456 add (NastCheck.err_code NastCheck.MutableMethodsMustBeReactive) pos (
1457 "The method " ^ (strip_ns name) ^ " has a mutable parameter" ^
1458 " (or mutable this), so it must be marked reactive with <<__Rx>>."
1461 let mutable_return_annotated_decls_must_be_reactive kind pos name =
1462 add (NastCheck.err_code NastCheck.MutableReturnAnnotatedDeclsMustBeReactive) pos (
1463 "The " ^ kind ^ " " ^ (strip_ns name) ^ " is annotated with <<__MutableReturn>>, " ^
1464 " so it must be marked reactive with <<__Rx>>."
1467 let maybe_mutable_methods_must_be_reactive pos name =
1468 add (NastCheck.err_code NastCheck.MaybeMutableMethodsMustBeReactive) pos (
1469 "The method " ^ (strip_ns name) ^ " is annotated with <<__MaybeMutable> attribute, \
1470 or has this attribute on one of parameters so it must be marked reactive."
1474 let inout_params_special pos =
1475 add (NastCheck.err_code NastCheck.InoutParamsSpecial) pos
1476 "Methods with special semantics cannot have inout parameters."
1478 let inout_params_mix_byref pos1 pos2 =
1479 if pos1 <> pos2 then begin
1480 let msg1 = pos1, "Cannot mix inout and byRef parameters" in
1481 let msg2 = pos2, "This parameter is passed by reference" in
1482 add_list (NastCheck.err_code NastCheck.InoutParamsMixByref) [msg1; msg2]
1485 let inout_params_memoize fpos pos =
1486 let msg1 = fpos, "Functions with inout parameters cannot be memoized" in
1487 let msg2 = pos, "This is an inout parameter" in
1488 add_list (NastCheck.err_code NastCheck.InoutParamsMemoize) [msg1; msg2]
1490 let inout_params_ret_by_ref fpos pos =
1491 let msg1 = fpos,
1492 "Functions with inout parameters cannot return by reference (&)" in
1493 let msg2 = pos, "This is an inout parameter" in
1494 add_list (NastCheck.err_code NastCheck.InoutParamsRetByRef) [msg1; msg2]
1496 let reading_from_append pos =
1497 add (NastCheck.err_code NastCheck.ReadingFromAppend) pos "Cannot use [] for reading"
1499 let const_attribute_prohibited pos kind =
1500 add (NastCheck.err_code NastCheck.ConstAttributeProhibited) pos
1501 ("Cannot apply __Const attribute to " ^ kind)
1503 let inout_argument_bad_expr pos =
1504 add (NastCheck.err_code NastCheck.InoutArgumentBadExpr) pos (
1505 "Arguments for inout parameters must be local variables or simple " ^
1506 "subscript expressions on vecs, dicts, keysets, or arrays"
1509 let illegal_destructor pos =
1510 add (NastCheck.err_code NastCheck.IllegalDestructor) pos (
1511 "Destructors are not supported in Hack; use other patterns like " ^
1512 "IDisposable/using or try/catch instead."
1515 let multiple_conditionally_reactive_annotations pos name =
1516 add (NastCheck.err_code NastCheck.MultipleConditionallyReactiveAnnotations) pos (
1517 "Method '" ^ name ^ "' has multiple <<__OnlyRxIfImpl>> annotations."
1520 let rx_is_enabled_invalid_location pos =
1521 add (NastCheck.err_code NastCheck.RxIsEnabledInvalidLocation) pos (
1522 "HH\\Rx\\IS_ENABLED must be the only condition in an if-statement, " ^
1523 "and that if-statement must be the only statement in the function body."
1526 let atmost_rx_as_rxfunc_invalid_location pos =
1527 add (NastCheck.err_code NastCheck.MaybeRxInvalidLocation) pos (
1528 "<<__AtMostRxAsFunc>> attribute can only be put on parameters of \
1529 conditionally reactive function or method annotated with \
1530 <<__AtMostRxAsArgs>> attribute."
1533 let no_atmost_rx_as_rxfunc_for_rx_if_args pos =
1534 add (NastCheck.err_code NastCheck.NoOnlyrxIfRxfuncForRxIfArgs) pos (
1535 "Function or method annotated with <<__AtMostRxAsArgs>> attribute \
1536 should have at least one parameter with <<__AtMostRxAsFunc>> or \
1537 <<__OnlyRxIfImpl>> annotations."
1540 let conditionally_reactive_annotation_invalid_arguments ~is_method pos =
1541 let loc = if is_method then "Method" else "Parameter" in
1542 add (NastCheck.err_code NastCheck.ConditionallyReactiveAnnotationInvalidArguments) pos (
1543 loc ^ " is marked with <<__OnlyRxIfImpl>> attribute that have " ^
1544 "invalid arguments. This attribute must have one argument and it should be " ^
1545 "'::class' class constant."
1548 let coroutine_in_constructor pos =
1549 add (NastCheck.err_code NastCheck.CoroutineInConstructor) pos
1550 "A class constructor may not be a coroutine"
1552 let illegal_return_by_ref pos =
1553 add (NastCheck.err_code NastCheck.IllegalReturnByRef) pos
1554 "Returning by reference from a function is no longer supported in Hack."
1556 let illegal_by_ref_expr pos str =
1557 add (NastCheck.err_code NastCheck.IllegalByRefExpr) pos
1558 (str ^ " cannot be passed by reference")
1560 let variadic_byref_param pos =
1561 add (NastCheck.err_code NastCheck.VariadicByRefParam) pos
1562 "Variadic parameters should not be taken by reference"
1564 let classname_const_instanceof class_name pos =
1565 add (NastCheck.err_code NastCheck.ClassnameConstInstanceOf) pos
1566 (class_name^"::class is redundant in an instanceof, just write '"^class_name^"'.")
1568 (*****************************************************************************)
1569 (* Nast terminality *)
1570 (*****************************************************************************)
1572 let case_fallthrough pos1 pos2 =
1573 add_list (NastCheck.err_code NastCheck.CaseFallthrough) [
1574 pos1, ("This switch has a case that implicitly falls through and is "^
1575 "not annotated with // FALLTHROUGH");
1576 pos2, "This case implicitly falls through"
1579 let default_fallthrough pos =
1580 add (NastCheck.err_code NastCheck.DefaultFallthrough) pos
1581 ("This switch has a default case that implicitly falls "^
1582 "through and is not annotated with // FALLTHROUGH")
1584 (*****************************************************************************)
1585 (* Typing errors *)
1586 (*****************************************************************************)
1588 let visibility_extends vis pos parent_pos parent_vis =
1589 let msg1 = pos, "This member visibility is: " ^ vis in
1590 let msg2 = parent_pos, parent_vis ^ " was expected" in
1591 add_list (Typing.err_code Typing.VisibilityExtends) [msg1; msg2]
1593 let member_not_implemented member_name parent_pos pos defn_pos =
1594 let msg1 = pos, "This type doesn't implement the method "^member_name in
1595 let msg2 = parent_pos, "Which is required by this interface" in
1596 let msg3 = defn_pos, "As defined here" in
1597 add_list (Typing.err_code Typing.MemberNotImplemented) [msg1; msg2; msg3]
1599 let bad_decl_override parent_pos parent_name pos name (error: error) =
1600 let msg1 = pos, ("Class " ^ (strip_ns name)
1601 ^ " does not correctly implement all required members ") in
1602 let msg2 = parent_pos,
1603 ("Some members are incompatible with those declared in type "
1604 ^ (strip_ns parent_name) ^
1605 "\nRead the following to see why:"
1606 ) in
1607 (* This is a cascading error message *)
1608 let code, msgl = (get_code error), (to_list error) in
1609 add_list code (msg1 :: msg2 :: msgl)
1611 let bad_method_override pos member_name (error: error) =
1612 let msg = pos, ("Member " ^ (strip_ns member_name)
1613 ^ " has the wrong type") in
1614 (* This is a cascading error message *)
1615 let code, msgl = (get_code error), (to_list error) in
1616 add_list code (msg :: msgl)
1618 let bad_enum_decl pos (error: error) =
1619 let msg = pos,
1620 "This enum declaration is invalid.\n\
1621 Read the following to see why:"
1623 (* This is a cascading error message *)
1624 let code, msgl = (get_code error), (to_list error) in
1625 add_list code (msg :: msgl)
1627 let missing_constructor pos =
1628 add (Typing.err_code Typing.MissingConstructor) pos
1629 "The constructor is not implemented"
1631 let typedef_trail_entry pos =
1632 pos, "Typedef definition comes from here"
1634 let add_with_trail code errs trail =
1635 add_list code (errs @ List.map trail typedef_trail_entry)
1637 let enum_constant_type_bad pos ty_pos ty trail =
1638 add_with_trail (Typing.err_code Typing.EnumConstantTypeBad)
1639 [pos, "Enum constants must be an int or string";
1640 ty_pos, "Not " ^ ty]
1641 trail
1643 let enum_type_bad pos ty trail =
1644 add_with_trail (Typing.err_code Typing.EnumTypeBad)
1645 [pos, "Enums must be int or string, not " ^ ty]
1646 trail
1648 let enum_type_typedef_mixed pos =
1649 add (Typing.err_code Typing.EnumTypeTypedefMixed) pos
1650 "Can't use typedef that resolves to mixed in enum"
1652 let enum_type_typedef_nonnull pos =
1653 add (Typing.err_code Typing.EnumTypeTypedefNonnull) pos
1654 "Can't use typedef that resolves to nonnull in enum"
1656 let enum_switch_redundant const first_pos second_pos =
1657 add_list (Typing.err_code Typing.EnumSwitchRedundant) [
1658 second_pos, "Redundant case statement";
1659 first_pos, const ^ " already handled here"
1662 let enum_switch_nonexhaustive pos missing enum_pos =
1663 add_list (Typing.err_code Typing.EnumSwitchNonexhaustive) [
1664 pos, "Switch statement nonexhaustive; the following cases are missing: " ^
1665 String.concat ", " missing;
1666 enum_pos, "Enum declared here"
1669 let enum_switch_redundant_default pos enum_pos =
1670 add_list (Typing.err_code Typing.EnumSwitchRedundantDefault) [
1671 pos, "All cases already covered; a redundant default case prevents "^
1672 "detecting future errors";
1673 enum_pos, "Enum declared here"
1676 let enum_switch_not_const pos =
1677 add (Typing.err_code Typing.EnumSwitchNotConst) pos
1678 "Case in switch on enum is not an enum constant"
1680 let enum_switch_wrong_class pos expected got =
1681 add (Typing.err_code Typing.EnumSwitchWrongClass) pos
1682 ("Switching on enum " ^ expected ^ " but using constant from " ^ got)
1684 let invalid_shape_field_name p =
1685 add (Typing.err_code Typing.InvalidShapeFieldName) p
1686 "Was expecting a constant string, class constant, or int (for shape access)"
1688 let invalid_shape_field_name_empty p =
1689 add (Typing.err_code Typing.InvalidShapeFieldNameEmpty) p
1690 "A shape field name cannot be an empty string"
1692 let invalid_shape_field_name_number p =
1693 add (Typing.err_code Typing.InvalidShapeFieldNameNumber) p
1694 "A shape field name cannot start with numbers"
1696 let invalid_shape_field_type pos ty_pos ty trail =
1697 add_with_trail (Typing.err_code Typing.InvalidShapeFieldType)
1698 [pos, "A shape field name must be an int or string";
1699 ty_pos, "Not " ^ ty]
1700 trail
1702 let invalid_shape_field_literal key_pos witness_pos =
1703 add_list (Typing.err_code Typing.InvalidShapeFieldLiteral)
1704 [key_pos, "Shape uses literal string as field name";
1705 witness_pos, "But expected a class constant"]
1707 let invalid_shape_field_const key_pos witness_pos =
1708 add_list (Typing.err_code Typing.InvalidShapeFieldConst)
1709 [key_pos, "Shape uses class constant as field name";
1710 witness_pos, "But expected a literal string"]
1712 let shape_field_class_mismatch key_pos witness_pos key_class witness_class =
1713 add_list (Typing.err_code Typing.ShapeFieldClassMismatch)
1714 [key_pos, "Shape field name is class constant from " ^ key_class;
1715 witness_pos, "But expected constant from " ^ witness_class]
1717 let shape_field_type_mismatch key_pos witness_pos key_ty witness_ty =
1718 add_list (Typing.err_code Typing.ShapeFieldTypeMismatch)
1719 [key_pos, "Shape field name is " ^ key_ty ^ " class constant";
1720 witness_pos, "But expected " ^ witness_ty]
1722 let missing_field pos1 pos2 name =
1723 add_list (Typing.err_code Typing.MissingField) (
1724 (pos1, "The field '"^name^"' is missing")::
1725 [pos2, "The field '"^name^"' is defined"])
1727 let unknown_field_disallowed_in_shape pos1 pos2 name =
1728 add_list
1729 (Typing.err_code Typing.UnknownFieldDisallowedInShape)
1731 pos1,
1732 "The field '" ^ name ^ "' is not defined in this shape type, and \
1733 this shape type does not allow unknown fields.";
1734 pos2,
1735 "The field '" ^ name ^ "' is set in the shape.";
1738 let shape_fields_unknown pos1 pos2 =
1739 add_list (Typing.err_code Typing.ShapeFieldsUnknown)
1741 pos1,
1742 "This shape type allows unknown fields, and so it may contain fields \
1743 other than those explicitly declared in its declaration.";
1744 pos2,
1745 "It is incompatible with a shape that does not allow unknown fields.";
1748 let shape_field_unset pos1 pos2 name =
1749 add_list (Typing.err_code Typing.ShapeFieldUnset) (
1750 [(pos1, "The field '"^name^"' was unset here");
1751 (pos2, "The field '"^name^"' might be present in this shape because of " ^
1752 "structural subtyping")]
1755 let invalid_shape_remove_key p =
1756 add (Typing.err_code Typing.InvalidShapeRemoveKey) p
1757 "You can only unset fields of local variables"
1759 let unification_cycle pos ty =
1760 add_list (Typing.err_code Typing.UnificationCycle)
1761 [pos, "Type circularity: in order to type-check this expression it " ^
1762 "is necessary for a type [rec] to be equal to type " ^ ty]
1765 let explain_constraint ~use_pos ~definition_pos ~param_name (error : error) =
1766 let inst_msg = "Some type constraint(s) here are violated" in
1767 let code, msgl = (get_code error), (to_list error) in
1768 (* There may be multiple constraints instantiated at one spot; avoid
1769 * duplicating the instantiation message *)
1770 let msgl = match msgl with
1771 | (p, x) :: rest when x = inst_msg && p = use_pos -> rest
1772 | _ -> msgl in
1773 let name = Utils.strip_ns param_name in
1774 add_list code begin
1775 [use_pos, inst_msg;
1776 definition_pos, "'" ^ name ^ "' is a constrained type parameter"] @ msgl
1779 let explain_where_constraint ~use_pos ~definition_pos (error : error) =
1780 let inst_msg = "A 'where' type constraint is violated here" in
1781 let code, msgl = (get_code error), (to_list error) in
1782 add_list code begin
1783 [use_pos, inst_msg;
1784 definition_pos, "This is the method with 'where' type constraints"] @ msgl
1787 let explain_tconst_where_constraint ~use_pos ~definition_pos (error: error) =
1788 let inst_msg = "A 'where' type constraint is violated here" in
1789 let code, msgl = (get_code error), (to_list error) in
1790 add_list code begin
1791 [use_pos, inst_msg;
1792 definition_pos,
1793 "This method's where constraints contain a generic type access"] @ msgl
1796 let explain_type_constant reason_msgl (error: error) =
1797 let code, msgl = (get_code error), (to_list error) in
1798 add_list code (msgl @ reason_msgl)
1800 let overflow p =
1801 add (Typing.err_code Typing.Overflow) p "Value is too large"
1803 let format_string pos snippet s class_pos fname class_suggest =
1804 add_list (Typing.err_code Typing.FormatString) [
1805 (pos, "I don't understand the format string " ^ snippet ^ " in " ^ s);
1806 (class_pos,
1807 "You can add a new format specifier by adding "
1808 ^fname^"() to "^class_suggest)]
1810 let expected_literal_format_string pos =
1811 add (Typing.err_code Typing.ExpectedLiteralFormatString) pos
1812 "This argument must be a literal format string"
1814 let re_prefixed_non_string pos non_strings =
1815 add (Typing.err_code Typing.RePrefixedNonString) pos
1816 (non_strings^" are not allowed to be to be `re`-prefixed")
1818 let bad_regex_pattern pos s =
1819 add (Typing.err_code Typing.BadRegexPattern) pos
1820 ("Bad regex pattern; "^s^".")
1822 let generic_array_strict p =
1823 add (Typing.err_code Typing.GenericArrayStrict) p
1824 "You cannot have an array without generics in strict mode"
1826 let strict_members_not_known p name =
1827 let name = Utils.strip_ns name in
1828 add (Typing.err_code Typing.StrictMembersNotKnown) p
1829 (name^" has a non-<?hh grandparent; this is not allowed in strict mode"
1830 ^" because that parent may define methods of unknowable name and type")
1832 let option_return_only_typehint p kind =
1833 let (typehint, reason) = match kind with
1834 | `void -> ("?void", "only return implicitly")
1835 | `noreturn -> ("?noreturn", "never return")
1837 add (Typing.err_code Typing.OptionReturnOnlyTypehint) p
1838 (typehint^" is a nonsensical typehint; a function cannot both "^reason
1839 ^" and return null.")
1841 let tuple_syntax p =
1842 add (Typing.err_code Typing.TupleSyntax) p
1843 ("Did you want a tuple? Try (X,Y), not tuple<X,Y>")
1845 let class_arity usage_pos class_pos class_name arity =
1846 add_list (Typing.err_code Typing.ClassArity)
1847 [usage_pos, ("The class "^(Utils.strip_ns class_name)^" expects "^
1848 soi arity^" arguments");
1849 class_pos, "Definition is here"]
1851 let expecting_type_hint p =
1852 add (Typing.err_code Typing.ExpectingTypeHint) p "Was expecting a type hint"
1854 let expecting_type_hint_suggest p ty =
1855 add (Typing.err_code Typing.ExpectingTypeHintSuggest) p
1856 ("Was expecting a type hint (what about: "^ty^")")
1858 let expecting_return_type_hint p =
1859 add (Typing.err_code Typing.ExpectingReturnTypeHint) p
1860 "Was expecting a return type hint"
1862 let expecting_return_type_hint_suggest p ty =
1863 add (Typing.err_code Typing.ExpectingReturnTypeHintSuggest) p
1864 ("Was expecting a return type hint (what about: ': "^ty^"')")
1866 let expecting_awaitable_return_type_hint p =
1867 add (Typing.err_code Typing.ExpectingAwaitableReturnTypeHint) p
1868 "Was expecting an Awaitable return type hint"
1870 let duplicate_using_var pos =
1871 add (Typing.err_code Typing.DuplicateUsingVar) pos
1872 "Local variable already used in 'using' statement"
1874 let illegal_disposable pos verb =
1875 add (Typing.err_code Typing.IllegalDisposable) pos
1876 ("Disposable objects must only be " ^ verb ^ " in a 'using' statement")
1878 let escaping_disposable pos =
1879 add (Typing.err_code Typing.EscapingDisposable) pos
1880 "Variable from 'using' clause may only be used as receiver in method invocation or \
1881 passed to function with <<__AcceptDisposable>> parameter attribute"
1883 let escaping_disposable_parameter pos =
1884 add (Typing.err_code Typing.EscapingDisposableParameter) pos
1885 "Parameter with <<__AcceptDisposable>> attribute may only be used as receiver in method \
1886 invocation or passed to another function with <<__AcceptDisposable>> parameter attribute"
1888 let escaping_this pos =
1889 add (Typing.err_code Typing.EscapingThis) pos
1890 "$this implementing IDisposable or IAsyncDisposable may only be used as receiver in method \
1891 invocation or passed to another function with <<__AcceptDisposable>> parameter attribute"
1893 let escaping_mutable_object pos =
1894 add (Typing.err_code Typing.EscapingMutableObject) pos
1895 "Neither a Mutable nor MaybeMutable object may be captured by an \
1896 anonymous function."
1898 let must_extend_disposable pos =
1899 add (Typing.err_code Typing.MustExtendDisposable) pos
1900 "A disposable type may not extend a class or use a trait that is not disposable"
1902 let accept_disposable_invariant pos1 pos2 =
1903 let msg1 = pos1, "This parameter is marked <<__AcceptDisposable>>" in
1904 let msg2 = pos2, "This parameter is not marked <<__AcceptDisposable>>" in
1905 add_list (Typing.err_code Typing.AcceptDisposableInvariant) [msg1; msg2]
1907 let field_kinds pos1 pos2 =
1908 add_list (Typing.err_code Typing.FieldKinds)
1909 [pos1, "You cannot use this kind of field (value)";
1910 pos2, "Mixed with this kind of field (key => value)"]
1912 let unbound_name_typing pos name =
1913 add (Typing.err_code Typing.UnboundNameTyping) pos
1914 ("Unbound name (typing): "^(strip_ns name))
1916 let previous_default p =
1917 add (Typing.err_code Typing.PreviousDefault) p
1918 ("A previous parameter has a default value.\n"^
1919 "Remove all the default values for the preceding parameters,\n"^
1920 "or add a default value to this one.")
1922 let return_only_typehint p kind =
1923 let msg = match kind with
1924 | `void -> "void"
1925 | `noreturn -> "noreturn" in
1926 add (Naming.err_code Naming.ReturnOnlyTypehint) p
1927 ("The "^msg^" typehint can only be used to describe a function return type")
1929 let unexpected_type_arguments p =
1930 add (Naming.err_code Naming.UnexpectedTypeArguments) p
1931 ("Type arguments are not expected for this type")
1933 let too_many_type_arguments p =
1934 add (Naming.err_code Naming.TooManyTypeArguments) p
1935 ("Too many type arguments for this type")
1937 let declare_statement_in_hack p =
1938 add (Naming.err_code Naming.DeclareStatement) p
1939 ("Declare statements are disallowed in Hack code.")
1940 let return_in_void pos1 pos2 =
1941 add_list (Typing.err_code Typing.ReturnInVoid) [
1942 pos1,
1943 "You cannot return a value";
1944 pos2,
1945 "This is a void function"
1948 let this_in_static p =
1949 add (Typing.err_code Typing.ThisInStatic) p
1950 "Don't use $this in a static method, use static:: instead"
1952 let this_var_outside_class p =
1953 add (Typing.err_code Typing.ThisVarOutsideClass) p "Can't use $this outside of a class"
1955 let unbound_global cst_pos =
1956 add (Typing.err_code Typing.UnboundGlobal) cst_pos "Unbound global constant (Typing)"
1958 let private_inst_meth method_pos p =
1959 add_list (Typing.err_code Typing.PrivateInstMeth) [
1960 method_pos, "This is a private method";
1961 p, "you cannot use it with inst_meth \
1962 (whether you are in the same class or not)."
1965 let protected_inst_meth method_pos p =
1966 add_list (Typing.err_code Typing.ProtectedInstMeth) [
1967 method_pos, "This is a protected method";
1968 p, "you cannot use it with inst_meth \
1969 (whether you are in the same class hierarchy or not)."
1972 let private_class_meth pos1 pos2 =
1973 add_list (Typing.err_code Typing.PrivateClassMeth) [
1974 pos1, "This is a private method";
1975 pos2, "you cannot use it with class_meth \
1976 (whether you are in the same class or not)."
1979 let protected_class_meth pos1 pos2 =
1980 add_list (Typing.err_code Typing.ProtectedClassMeth) [
1981 pos1, "This is a protected method";
1982 pos2, "you cannot use it with class_meth \
1983 (whether you are in the same class hierarchy or not)."
1986 let array_cast pos =
1987 add (Typing.err_code Typing.ArrayCast) pos
1988 "(array) cast forbidden; arrays with unspecified \
1989 key and value types are not allowed"
1991 let string_cast pos ty =
1992 add (Typing.err_code Typing.StringCast) pos @@
1993 Printf.sprintf
1994 "Cannot cast a value of type %s to string.\n\
1995 Only primitives may be used in a (string) cast."
1998 let nullable_cast pos ty ty_pos =
1999 add_list (Typing.err_code Typing.NullableCast) [
2000 pos, "Casting from a nullable type is forbidden";
2001 ty_pos, "This is "^ty;
2004 let anonymous_recursive pos =
2005 add (Typing.err_code Typing.AnonymousRecursive) pos
2006 "Anonymous functions cannot be recursive"
2008 let static_outside_class pos =
2009 add (Typing.err_code Typing.StaticOutsideClass) pos
2010 "'static' is undefined outside of a class"
2012 let self_outside_class pos =
2013 add (Typing.err_code Typing.SelfOutsideClass) pos
2014 "'self' is undefined outside of a class"
2016 let new_inconsistent_construct new_pos (cpos, cname) kind =
2017 let name = Utils.strip_ns cname in
2018 let preamble = match kind with
2019 | `static -> "Can't use new static() for "^name
2020 | `classname -> "Can't use new on classname<"^name^">"
2022 add_list (Typing.err_code Typing.NewStaticInconsistent) [
2023 new_pos, preamble^"; __construct arguments are not \
2024 guaranteed to be consistent in child classes";
2025 cpos, ("This declaration neither defines an abstract/final __construct"
2026 ^" nor uses <<__ConsistentConstruct>> attribute")]
2028 let pair_arity pos =
2029 add (Typing.err_code Typing.PairArity) pos "A pair has exactly 2 elements"
2031 let tuple_arity pos2 size2 pos1 size1 =
2032 add_list (Typing.err_code Typing.TupleArity) [
2033 pos2, "This tuple has "^ string_of_int size2^" elements";
2034 pos1, string_of_int size1 ^ " were expected"]
2036 let undefined_parent pos =
2037 add (Typing.err_code Typing.UndefinedParent) pos
2038 "The parent class is undefined"
2040 let parent_outside_class pos =
2041 add (Typing.err_code Typing.ParentOutsideClass) pos
2042 "'parent' is undefined outside of a class"
2044 let parent_abstract_call meth_name call_pos decl_pos =
2045 add_list (Typing.err_code Typing.AbstractCall) [
2046 call_pos, ("Cannot call parent::"^meth_name^"(); it is abstract");
2047 decl_pos, "Declaration is here"
2050 let self_abstract_call meth_name call_pos decl_pos =
2051 add_list (Typing.err_code Typing.AbstractCall) [
2052 call_pos, ("Cannot call self::"^meth_name^"(); it is abstract. Did you mean static::"^meth_name^"()?");
2053 decl_pos, "Declaration is here"
2056 let classname_abstract_call cname meth_name call_pos decl_pos =
2057 let cname = Utils.strip_ns cname in
2058 add_list (Typing.err_code Typing.AbstractCall) [
2059 call_pos, ("Cannot call "^cname^"::"^meth_name^"(); it is abstract");
2060 decl_pos, "Declaration is here"
2063 let static_synthetic_method cname meth_name call_pos decl_pos =
2064 let cname = Utils.strip_ns cname in
2065 add_list (Typing.err_code Typing.StaticSyntheticMethod) [
2066 call_pos, ("Cannot call "^cname^"::"^meth_name^"(); "^meth_name^" is not defined in "^cname);
2067 decl_pos, "Declaration is here"
2070 let empty_in_strict pos =
2071 add (Typing.err_code Typing.IssetEmptyInStrict) pos
2072 ("empty cannot be used in a completely type safe way and so is banned in "
2073 ^"strict mode")
2075 let isset_in_strict pos =
2076 add (Typing.err_code Typing.IssetEmptyInStrict) pos
2077 ("isset cannot be used in a completely type safe way and so is banned in "
2078 ^"strict mode; try using array_key_exists instead")
2080 let unset_nonidx_in_strict pos msgs =
2081 add_list (Typing.err_code Typing.UnsetNonidxInStrict)
2082 ([pos, "In strict mode, unset is banned except on array, keyset, "^
2083 "or dict indexing"] @
2084 msgs)
2086 let unset_nonidx_in_strict_no_varray pos msgs =
2087 add_list (Typing.err_code Typing.UnsetNonidxInStrict)
2088 ([pos, "In strict mode, unset is banned except on dict-like array, "^
2089 "darray, keyset, or dict indexing"] @
2090 msgs)
2092 let unpacking_disallowed_builtin_function pos name =
2093 let name = Utils.strip_ns name in
2094 add (Typing.err_code Typing.UnpackingDisallowed) pos
2095 ("Arg unpacking is disallowed for "^name)
2097 let array_get_arity pos1 name pos2 =
2098 add_list (Typing.err_code Typing.ArrayGetArity) [
2099 pos1, "You cannot use this "^(Utils.strip_ns name);
2100 pos2, "It is missing its type parameters"
2103 let typing_error pos msg =
2104 add (Typing.err_code Typing.GenericUnify) pos msg
2106 let typing_error_l err =
2107 add_error err
2109 let undefined_field ~use_pos ~name ~shape_type_pos =
2110 add_list (Typing.err_code Typing.UndefinedField) [
2111 use_pos, "The field "^name^" is undefined";
2112 shape_type_pos, "You might want to check this out"
2115 let array_access pos1 pos2 ty =
2116 add_list (Typing.err_code Typing.ArrayAccess)
2117 ((pos1, "This is not an object of type KeyedContainer, this is "^ty) ::
2118 if pos2 != Pos.none
2119 then [pos2, "You might want to check this out"]
2120 else [])
2122 let keyset_set pos1 pos2 =
2123 add_list (Typing.err_code Typing.KeysetSet)
2124 ((pos1, "Keysets entries cannot be set, use append instead.") ::
2125 if pos2 != Pos.none
2126 then [pos2, "You might want to check this out"]
2127 else [])
2129 let array_append pos1 pos2 ty =
2130 add_list (Typing.err_code Typing.ArrayAppend)
2131 ((pos1, ty^" does not allow array append") ::
2132 if pos2 != Pos.none
2133 then [pos2, "You might want to check this out"]
2134 else [])
2136 let const_mutation pos1 pos2 ty =
2137 add_list (Typing.err_code Typing.ConstMutation)
2138 ((pos1, "You cannot mutate this") ::
2139 if pos2 != Pos.none
2140 then [(pos2, "This is " ^ ty)]
2141 else [])
2143 let expected_class ?(suffix="") pos =
2144 add (Typing.err_code Typing.ExpectedClass) pos ("Was expecting a class"^suffix)
2146 let snot_found_hint = function
2147 | `no_hint ->
2149 | `closest (pos, v) ->
2150 [pos, "The closest thing is "^v^" but it's not a static method"]
2151 | `did_you_mean (pos, v) ->
2152 [pos, "Did you mean: "^v]
2154 let string_of_class_member_kind = function
2155 | `class_constant -> "class constant"
2156 | `static_method -> "static method"
2157 | `class_variable -> "class variable"
2158 | `class_typeconst -> "type constant"
2160 let smember_not_found kind pos (cpos, class_name) member_name hint =
2161 let kind = string_of_class_member_kind kind in
2162 let class_name = strip_ns class_name in
2163 let msg = "Could not find "^kind^" "^member_name^" in type "^class_name in
2164 add_list (Typing.err_code Typing.SmemberNotFound)
2165 ((pos, msg) :: (snot_found_hint hint
2166 @ [(cpos, "Declaration of "^class_name^" is here")]))
2168 let not_found_hint = function
2169 | `no_hint ->
2171 | `closest (pos, v) ->
2172 [pos, "The closest thing is "^v^" but it's a static method"]
2173 | `did_you_mean (pos, v) ->
2174 [pos, "Did you mean: "^v]
2176 let member_not_found kind pos (cpos, type_name) member_name hint reason =
2177 let type_name = strip_ns type_name in
2178 let kind =
2179 match kind with
2180 | `method_ -> "method"
2181 | `member -> "member"
2183 let msg = "Could not find "^kind^" "^member_name^" in an object of type "^
2184 type_name in
2185 add_list (Typing.err_code Typing.MemberNotFound)
2186 ((pos, msg) :: (not_found_hint hint @ reason
2187 @ [(cpos, "Declaration of "^type_name^" is here")]))
2189 let parent_in_trait pos =
2190 add (Typing.err_code Typing.ParentInTrait) pos
2191 ("parent:: inside a trait is undefined"
2192 ^" without 'require extends' of a class defined in <?hh")
2194 let parent_undefined pos =
2195 add (Typing.err_code Typing.ParentUndefined) pos
2196 "parent is undefined"
2198 let constructor_no_args pos =
2199 add (Typing.err_code Typing.ConstructorNoArgs) pos
2200 "This constructor expects no argument"
2202 let visibility p msg1 p_vis msg2 =
2203 add_list (Typing.err_code Typing.Visibility) [p, msg1; p_vis, msg2]
2205 let typing_too_many_args pos pos_def =
2206 add_list (Typing.err_code Typing.TypingTooManyArgs)
2207 [pos, "Too many arguments"; pos_def, "Definition is here"]
2209 let typing_too_few_args pos pos_def =
2210 add_list (Typing.err_code Typing.TypingTooFewArgs)
2211 [pos, "Too few arguments"; pos_def, "Definition is here"]
2213 let anonymous_recursive_call pos =
2214 add (Typing.err_code Typing.AnonymousRecursiveCall) pos
2215 "recursive call to anonymous function"
2217 let bad_call pos ty =
2218 add (Typing.err_code Typing.BadCall) pos
2219 ("This call is invalid, this is not a function, it is "^ty)
2221 let sketchy_null_check pos name kind =
2222 let name = Option.value name ~default:"$x" in
2223 add (Typing.err_code Typing.SketchyNullCheck) pos @@
2224 "You are using a sketchy null check ...\n"^
2225 match kind with
2226 | `Coalesce ->
2227 Printf.sprintf "Use %s ?? $default instead of %s ?: $default" name name
2228 | `Eq ->
2229 Printf.sprintf "Use %s === null instead" name
2230 | `Neq ->
2231 Printf.sprintf "Use %s !== null instead" name
2233 let sketchy_null_check_primitive pos name kind =
2234 let name = Option.value name ~default:"$x" in
2235 add (Typing.err_code Typing.SketchyNullCheckPrimitive) pos @@
2236 "You are using a sketchy null check on a primitive type ...\n"^
2237 match kind with
2238 | `Coalesce ->
2239 Printf.sprintf "Use %s ?? $default instead of %s ?: $default" name name
2240 | `Eq ->
2241 Printf.sprintf "Use %s === null instead" name
2242 | `Neq ->
2243 Printf.sprintf "Use %s !== null instead" name
2245 let extend_final extend_pos decl_pos name =
2246 let name = (strip_ns name) in
2247 add_list (Typing.err_code Typing.ExtendFinal) [
2248 extend_pos, ("You cannot extend final class "^name);
2249 decl_pos, "Declaration is here"
2252 let extend_sealed child_pos parent_pos parent_name parent_kind verb =
2253 let name = (strip_ns parent_name) in
2254 add_list (Typing.err_code Typing.ExtendSealed) [
2255 child_pos, ("You cannot "^verb^" sealed "^parent_kind^" "^name);
2256 parent_pos, "Declaration is here"
2259 let trait_implement_sealed child_pos parent_pos parent_name =
2260 let name = (strip_ns parent_name) in
2261 add_list (Typing.err_code Typing.ExtendSealed) [
2262 child_pos, (
2263 "A trait cannot implement sealed interface "^name^
2264 ". Use `require implements` instead");
2265 parent_pos, "Declaration is here"
2268 let extend_ppl
2269 child_pos child_class_type child_is_ppl parent_pos parent_class_type parent_name verb =
2270 let name = (strip_ns parent_name) in
2271 let warning =
2272 if child_is_ppl
2273 then child_class_type^" annotated with <<__PPL>> cannot "^verb^
2274 " non <<__PPL>> "^parent_class_type^": "^name
2275 else child_class_type^" must be annotated with <<__PPL>> to "^verb^
2276 " <<__PPL>> "^parent_class_type^": "^name in
2277 add_list (Typing.err_code Typing.ExtendPPL) [
2278 child_pos, warning;
2279 parent_pos, "Declaration is here";
2282 let sealed_final pos name =
2283 let name = (strip_ns name) in
2284 add (Typing.err_code Typing.SealedFinal) pos ("Sealed class "^name^" cannot be marked final")
2286 let unsealable pos kind =
2287 add (Typing.err_code Typing.Unsealable) pos (kind^" cannot be sealed")
2289 let read_before_write (pos, v) =
2290 add (Typing.err_code Typing.ReadBeforeWrite) pos (
2292 "Read access to $this->"; v; " before initialization"
2295 let interface_final pos =
2296 add (Typing.err_code Typing.InterfaceFinal) pos
2297 "Interfaces cannot be final"
2299 let trait_final pos =
2300 add (Typing.err_code Typing.TraitFinal) pos
2301 "Traits cannot be final"
2303 let final_property pos =
2304 add (Typing.err_code Typing.FinalProperty) pos "Properties cannot be declared final"
2306 let implement_abstract ~is_final pos1 pos2 kind x =
2307 let name = "abstract "^kind^" '"^x^"'" in
2308 let msg1 =
2309 if is_final then
2310 "This class was declared as final. It must provide an implementation \
2311 for the "^name
2312 else
2313 "This class must be declared abstract, or provide an implementation \
2314 for the "^name in
2315 add_list (Typing.err_code Typing.ImplementAbstract) [
2316 pos1, msg1;
2317 pos2, "Declaration is here";
2320 let generic_static pos x =
2321 add (Typing.err_code Typing.GenericStatic) pos (
2322 "This static variable cannot use the type parameter "^x^"."
2325 let fun_too_many_args pos1 pos2 =
2326 add_list (Typing.err_code Typing.FunTooManyArgs) [
2327 pos1, "Too many mandatory arguments";
2328 pos2, "Because of this definition";
2331 let fun_too_few_args pos1 pos2 =
2332 add_list (Typing.err_code Typing.FunTooFewArgs) [
2333 pos1, "Too few arguments";
2334 pos2, "Because of this definition";
2337 let fun_unexpected_nonvariadic pos1 pos2 =
2338 add_list (Typing.err_code Typing.FunUnexpectedNonvariadic) [
2339 pos1, "Should have a variadic argument";
2340 pos2, "Because of this definition";
2343 let fun_variadicity_hh_vs_php56 pos1 pos2 =
2344 add_list (Typing.err_code Typing.FunVariadicityHhVsPhp56) [
2345 pos1, "Variadic arguments: ...-style is not a subtype of ...$args";
2346 pos2, "Because of this definition";
2349 let ellipsis_strict_mode ~require pos =
2350 let msg = match require with
2351 | `Type -> "Cannot use ... without a type hint in strict mode. Please add a type hint."
2352 | `Param_name ->
2353 "Cannot use ... without a parameter name in strict mode. Please add a parameter name."
2354 | `Type_and_param_name ->
2355 "Cannot use ... without a type hint and parameter name in strict mode. \
2356 Please add a type hint and parameter name."
2358 add (Typing.err_code Typing.EllipsisStrictMode) pos msg
2360 let untyped_lambda_strict_mode pos =
2361 let msg =
2362 "Cannot determine types of lambda parameters in strict mode. \
2363 Please add type hints on parameters."
2365 add (Typing.err_code Typing.UntypedLambdaStrictMode) pos msg
2367 let echo_in_reactive_context pos =
2368 add (Typing.err_code Typing.EchoInReactiveContext) pos (
2369 "'echo' or 'print' are not allowed in reactive or shallow-reactive functions."
2372 let expected_tparam ~use_pos ~definition_pos n =
2373 add_list (Typing.err_code Typing.ExpectedTparam)
2375 use_pos, "Expected " ^
2376 (match n with
2377 | 0 -> "no type parameter"
2378 | 1 -> "a type parameter"
2379 | n -> string_of_int n ^ " type parameters"
2381 definition_pos, "Definition is here"
2384 let object_string pos1 pos2 =
2385 add_list (Typing.err_code Typing.ObjectString) [
2386 pos1, "You cannot use this object as a string";
2387 pos2, "This object doesn't implement __toString";
2390 let object_string_deprecated pos =
2391 add (Typing.err_code Typing.ObjectString) pos
2392 "You cannot use this object as a string\n\
2393 Implicit conversions of Stringish objects to string are deprecated."
2395 let type_param_arity pos x n =
2396 add (Typing.err_code Typing.TypeParamArity) pos (
2397 "The type "^x^" expects "^n^" parameters"
2400 let cyclic_typedef p =
2401 add (Typing.err_code Typing.CyclicTypedef) p
2402 "Cyclic typedef"
2404 let type_arity_mismatch pos1 n1 pos2 n2 =
2405 add_list (Typing.err_code Typing.TypeArityMismatch) [
2406 pos1, "This type has "^n1^" arguments";
2407 pos2, "This one has "^n2;
2410 let this_final id pos2 (error: error) =
2411 let n = Utils.strip_ns (snd id) in
2412 let message1 = "Since "^n^" is not final" in
2413 let message2 = "this might not be a "^n in
2414 let code, msgl = (get_code error), (to_list error) in
2415 add_list code (msgl @ [(fst id, message1); (pos2, message2)])
2417 let exact_class_final id pos2 (error: error) =
2418 let n = Utils.strip_ns (snd id) in
2419 let message1 = "This requires the late-bound type to be exactly "^n in
2420 let message2 =
2421 "Since " ^n^" is not final this might be an instance of a child class" in
2422 let code, msgl = (get_code error), (to_list error) in
2423 add_list code (msgl @ [(fst id, message1); (pos2, message2)])
2425 let tuple_arity_mismatch pos1 n1 pos2 n2 =
2426 add_list (Typing.err_code Typing.TupleArityMismatch) [
2427 pos1, "This tuple has "^n1^" elements";
2428 pos2, "This one has "^n2^" elements"
2431 let fun_arity_mismatch pos1 pos2 =
2432 add_list (Typing.err_code Typing.FunArityMismatch) [
2433 pos1, "Number of arguments doesn't match";
2434 pos2, "Because of this definition";
2437 let fun_reactivity_mismatch pos1 kind1 pos2 kind2 =
2438 let f k = "This function is " ^ k ^ "." in
2439 add_list
2440 (Typing.err_code Typing.FunReactivityMismatch)
2442 pos1, f kind1;
2443 pos2, f kind2
2446 let frozen_in_incorrect_scope pos1 =
2447 add (Typing.err_code Typing.FrozenInIncorrectScope) pos1
2448 ("This variable is frozen in one scope but not the other")
2451 let reassign_mutable_var pos1 =
2452 add (Typing.err_code Typing.ReassignMutableVar) pos1
2453 ("This variable is mutable. You cannot create a new reference to it.")
2455 let reassign_mutable_this pos1 =
2456 add (Typing.err_code Typing.ReassignMutableThis) pos1
2457 ("$this here is mutable. You cannot create a new reference to it.")
2459 let mutable_expression_as_multiple_mutable_arguments pos param_kind prev_pos prev_param_kind =
2460 add_list (Typing.err_code Typing.MutableExpressionAsMultipleMutableArguments) [
2461 pos, "A mutable expression may not be passed as multiple arguments where \
2462 at least one matching parameter is mutable. Matching parameter here is " ^ param_kind;
2463 prev_pos, "This is where it was used before, being passed as " ^ prev_param_kind
2466 let reassign_maybe_mutable_var pos1 =
2467 add (Typing.err_code Typing.ReassignMaybeMutableVar) pos1
2468 ("This variable is maybe mutable. You cannot create a new reference to it.")
2471 let mutable_call_on_immutable fpos pos1 =
2472 add_list (Typing.err_code Typing.MutableCallOnImmutable)
2474 pos1, "Cannot call mutable function on immutable expression";
2475 fpos, "This function is marked <<__Mutable>>, so it has a mutable $this.";
2478 let immutable_call_on_mutable fpos pos1 =
2479 add_list (Typing.err_code Typing.ImmutableCallOnMutable)
2481 pos1, "Cannot call non-mutable function on mutable expression";
2482 fpos, "This function is not marked as <<__Mutable>>.";
2485 let mutability_mismatch ~is_receiver pos1 mut1 pos2 mut2 =
2486 let msg mut =
2487 let msg = if is_receiver then "Receiver of this function" else "This parameter" in
2488 msg ^ " is " ^ mut in
2489 add_list (Typing.err_code Typing.MutabilityMismatch)
2491 pos1, "Incompatible mutabilities:";
2492 pos1, msg mut1;
2493 pos2, msg mut2;
2496 let invalid_call_on_maybe_mutable ~fun_is_mutable pos fpos =
2497 let msg =
2498 "Cannot call " ^ (if fun_is_mutable then "mutable" else "non-mutable") ^ " \
2499 function on maybe mutable value." in
2500 add_list (Typing.err_code Typing.InvalidCallMaybeMutable)
2502 pos, msg;
2503 fpos, "This function is not marked as <<__MaybeMutable>>."
2506 let mutable_argument_mismatch param_pos arg_pos =
2507 add_list (Typing.err_code Typing.MutableArgumentMismatch)
2509 arg_pos, "Invalid argument";
2510 param_pos, "This parameter is marked mutable";
2511 arg_pos, "But this expression is not";
2514 let immutable_argument_mismatch param_pos arg_pos =
2515 add_list (Typing.err_code Typing.ImmutableArgumentMismatch)
2517 arg_pos, "Invalid argument";
2518 param_pos, "This parameter is not marked as mutable";
2519 arg_pos, "But this expression is mutable";
2522 let mutably_owned_argument_mismatch ~arg_is_owned_local param_pos arg_pos =
2523 let arg_msg =
2524 if arg_is_owned_local
2525 then "Owned mutable locals used as argument should be passed via \
2526 Rx\\move function"
2527 else "But this expression is not owned mutable" in
2528 add_list (Typing.err_code Typing.ImmutableArgumentMismatch)
2530 arg_pos, "Invalid argument";
2531 param_pos, "This parameter is marked with <<__OwnedMutable>>";
2532 arg_pos, arg_msg;
2535 let maybe_mutable_argument_mismatch param_pos arg_pos =
2536 add_list (Typing.err_code Typing.MaybeMutableArgumentMismatch)
2538 arg_pos, "Invalid argument";
2539 param_pos, "This parameter is not marked <<__MaybeMutable>>";
2540 arg_pos, "But this expression is maybe mutable"
2543 let invalid_mutable_return_result error_pos function_pos value_kind =
2544 add_list (Typing.err_code Typing.InvalidMutableReturnResult)
2546 error_pos, "Functions marked <<__MutableReturn>> must return mutably owned values: \
2547 mutably owned local variables and results of calling Rx\\mutable.";
2548 function_pos, "This function is marked <<__MutableReturn>>";
2549 error_pos, "This expression is " ^ value_kind
2552 let freeze_in_nonreactive_context pos1 =
2553 add (Typing.err_code Typing.FreezeInNonreactiveContext) pos1
2554 ("\\HH\\Rx\\freeze can only be used in reactive functions")
2556 let mutable_in_nonreactive_context pos =
2557 add (Typing.err_code Typing.MutableInNonreactiveContext) pos
2558 ("\\HH\\Rx\\mutable can only be used in reactive functions")
2560 let move_in_nonreactive_context pos =
2561 add (Typing.err_code Typing.MoveInNonreactiveContext) pos
2562 ("\\HH\\Rx\\move can only be used in reactive functions")
2565 let invalid_argument_type_for_condition_in_rx
2566 ~is_receiver f_pos def_pos arg_pos expected_type actual_type =
2567 let arg_msg =
2568 if is_receiver then "Receiver type" else "Argument type" in
2569 let arg_msg =
2570 arg_msg ^ " must be a subtype of " ^ expected_type ^
2571 ", now " ^ actual_type ^ "." in
2572 add_list (Typing.err_code Typing.InvalidConditionallyReactiveCall) [
2573 f_pos, "Cannot invoke conditionally reactive function in reactive context, \
2574 because at least one reactivity condition is not met.";
2575 arg_pos, arg_msg;
2576 def_pos, "This is the function declaration";
2579 let callsite_reactivity_mismatch f_pos def_pos callee_reactivity cause_pos_opt caller_reactivity =
2580 add_list (Typing.err_code Typing.CallSiteReactivityMismatch) ([
2581 f_pos, "Reactivity mismatch: " ^ caller_reactivity ^ " function cannot call " ^
2582 callee_reactivity ^ " function.";
2583 def_pos, "This is declaration of the function being called."
2584 ] @ Option.value_map cause_pos_opt ~default:[] ~f:(fun cause_pos ->
2585 [cause_pos, "Reactivity of this argument was used as reactivity of the callee."]
2587 let invalid_function_type_for_condition_in_rx
2588 f_pos def_pos arg_pos actual_reactivity expected_reactivity =
2589 let arg_msg =
2590 "Argument type is must be " ^ expected_reactivity ^ " function, " ^
2591 actual_reactivity ^ " given." in
2592 add_list (Typing.err_code Typing.InvalidConditionallyReactiveCall) [
2593 f_pos, "Cannot invoke conditionally reactive function in reactive context, \
2594 because at least one reactivity condition is not met.";
2595 arg_pos, arg_msg;
2596 def_pos, "This is the function declaration";
2600 let invalid_argument_of_rx_mutable_function pos =
2601 add (Typing.err_code Typing.InvalidArgumentOfRxMutableFunction) pos (
2602 "Single argument to \\HH\\Rx\\mutable should be an expression that yields new \
2603 mutably-owned value, like 'new A()', Hack collection literal or 'f()' where f is function \
2604 annotated with <<__MutableReturn>> attribute."
2607 let invalid_freeze_use pos1 =
2608 add (Typing.err_code Typing.InvalidFreezeUse) pos1
2609 ("freeze takes a single mutably-owned local variable as an argument")
2611 let invalid_move_use pos1 =
2612 add (Typing.err_code Typing.InvalidMoveUse) pos1
2613 ("move takes a single mutably-owned local variable as an argument")
2615 let ignored_result_of_freeze pos =
2616 add (Typing.err_code Typing.IgnoredResultOfFreeze) pos
2617 ("Result of freeze operation is unused. Note that freeze unsets local variable \
2618 that was passed as an argument so it won't be accessible after calling freeze.")
2620 let ignored_result_of_move pos =
2621 add (Typing.err_code Typing.IgnoredResultOfMove) pos
2622 ("Result of move operation is unused. Note that move unsets local variable \
2623 that was passed as an argument so it won't be accessible after calling move.")
2626 let invalid_freeze_target pos1 var_pos var_mutability_str =
2627 add_list (Typing.err_code Typing.InvalidFreezeTarget)
2629 pos1, "Invalid argument - freeze() takes a single mutable variable";
2630 var_pos, "This variable is "^var_mutability_str;
2633 let invalid_move_target pos1 var_pos var_mutability_str =
2634 add_list (Typing.err_code Typing.InvalidMoveTarget)
2636 pos1, "Invalid argument - move() takes a single mutably-owned variable";
2637 var_pos, "This variable is "^var_mutability_str;
2640 let discarded_awaitable pos1 pos2 =
2641 add_list (Typing.err_code Typing.DiscardedAwaitable) [
2642 pos1, "This expression is of type Awaitable, but it's "^
2643 "either being discarded or used in a dangerous way before "^
2644 "being awaited";
2645 pos2, "This is why I think it is Awaitable"
2648 let gena_expects_array pos1 pos2 ty_str =
2649 add_list (Typing.err_code Typing.GenaExpectsArray) [
2650 pos1, "gena expects an array";
2651 pos2, "It is incompatible with " ^ ty_str;
2654 let unify_error left right =
2655 add_list (Typing.err_code Typing.UnifyError) (left @ right)
2657 let static_dynamic static_position dyn_position method_name ~elt_type =
2658 let msg_static = "The "^elt_type^" "^method_name^" is static" in
2659 let msg_dynamic = "It is defined as non-static here" in
2660 add_list (Typing.err_code Typing.StaticDynamic) [
2661 static_position, msg_static;
2662 dyn_position, msg_dynamic
2665 let null_member s pos r =
2666 add_list (Typing.err_code Typing.NullMember) ([
2667 pos,
2668 "You are trying to access the member "^s^
2669 " but this object can be null. "
2670 ] @ r
2673 let non_object_member s pos1 ty pos2 =
2674 let msg_start = ("You are trying to access the member "^s^
2675 " but this is not an object, it is "^ty) in
2676 let msg =
2677 if ty = "a shape" then
2678 msg_start ^ ". Did you mean $foo['" ^ s ^ "'] instead?"
2679 else
2680 msg_start in
2681 add_list (Typing.err_code Typing.NonObjectMember) [
2682 pos1, msg;
2683 pos2, "Check this out"
2686 let non_class_member s pos1 ty pos2 =
2687 add_list (Typing.err_code Typing.NonClassMember) [
2688 pos1,
2689 ("You are trying to access the member "^s^
2690 " but this is not a class, it is "^
2691 ty);
2692 pos2,
2693 "Check this out"
2696 let ambiguous_member s pos1 ty pos2 =
2697 add_list (Typing.err_code Typing.AmbiguousMember) [
2698 pos1,
2699 ("You are trying to access the member "^s^
2700 " but there is more than one implementation on "^
2701 ty);
2702 pos2,
2703 "Check this out"
2706 let null_container p null_witness =
2707 add_list (Typing.err_code Typing.NullContainer) (
2710 "You are trying to access an element of this container"^
2711 " but the container could be null. "
2712 ] @ null_witness)
2714 let option_mixed pos =
2715 add (Typing.err_code Typing.OptionMixed) pos
2716 "?mixed is a redundant typehint - just use mixed"
2718 let option_void pos =
2719 add (Typing.err_code Typing.OptionVoid) pos
2720 "?void is a redundant typehint - just use void"
2722 let declared_covariant pos1 pos2 emsg =
2723 add_list (Typing.err_code Typing.DeclaredCovariant) (
2724 [pos2, "Illegal usage of a covariant type parameter";
2725 pos1, "This is where the parameter was declared as covariant (+)"
2726 ] @ emsg
2729 let declared_contravariant pos1 pos2 emsg =
2730 add_list (Typing.err_code Typing.DeclaredContravariant) (
2731 [pos2, "Illegal usage of a contravariant type parameter";
2732 pos1, "This is where the parameter was declared as contravariant (-)"
2733 ] @ emsg
2736 let static_property_type_generic_param ~class_pos ~var_type_pos ~generic_pos =
2737 add_list (Typing.err_code Typing.ClassVarTypeGenericParam)
2738 [generic_pos, "A generic parameter cannot be used in the type of a static property";
2739 var_type_pos, "This is where the type of the static property was declared";
2740 class_pos, "This is the class containing the static property"]
2742 let contravariant_this pos class_name tp =
2743 add (Typing.err_code Typing.ContravariantThis) pos (
2744 "The \"this\" type cannot be used in this " ^
2745 "contravariant position because its enclosing class \"" ^ class_name ^
2746 "\" " ^ "is final and has a variant type parameter \"" ^ tp ^ "\"")
2748 let cyclic_typeconst pos sl =
2749 let sl = List.map sl strip_ns in
2750 add (Typing.err_code Typing.CyclicTypeconst) pos
2751 ("Cyclic type constant:\n "^String.concat " -> " sl)
2753 let this_lvalue pos =
2754 add (Typing.err_code Typing.ThisLvalue) pos "Cannot assign a value to $this"
2756 let abstract_concrete_override pos parent_pos kind =
2757 let kind_str = match kind with
2758 | `method_ -> "method"
2759 | `typeconst -> "type constant"
2760 | `constant -> "constant" in
2761 add_list (Typing.err_code Typing.AbstractConcreteOverride) ([
2762 pos, "Cannot re-declare this " ^ kind_str ^ " as abstract";
2763 parent_pos, "Previously defined here"
2766 let instanceof_generic_classname pos name =
2767 add (Typing.err_code Typing.InstanceofGenericClassname) pos
2768 ("'instanceof' cannot be used on 'classname<" ^ name ^ ">' because '" ^
2769 name ^ "' may be instantiated with a type such as \
2770 'C<int>' that cannot be checked at runtime")
2772 let required_field_is_optional pos1 pos2 name =
2773 add_list (Typing.err_code Typing.RequiredFieldIsOptional)
2775 pos1, "The field '"^name^"' is optional";
2776 pos2, "The field '"^name^"' is defined as required"
2779 let array_get_with_optional_field pos1 pos2 name =
2780 add_list
2781 (Typing.err_code Typing.ArrayGetWithOptionalField)
2783 pos1,
2784 "Invalid index operation: '" ^ name ^ "' is marked as an optional shape \
2785 field. It may not be present in the shape. Use the `??` operator \
2786 instead.";
2787 pos2,
2788 "This is where the field was declared as optional."
2791 let non_call_argument_in_suspend pos msgs =
2792 add_list
2793 (Typing.err_code Typing.NonCallArgumentInSuspend) (
2795 pos,
2796 "'suspend' operator expects call to a coroutine as an argument."
2797 ] @ msgs
2799 let non_coroutine_call_in_suspend pos msgs =
2800 add_list
2801 (Typing.err_code Typing.NonCoroutineCallInSuspend) (
2803 pos,
2804 "Only coroutine functions are allowed to be called in \
2805 'suspend' operator."
2806 ] @ msgs
2809 let coroutine_call_outside_of_suspend pos =
2810 add_list
2811 (Typing.err_code Typing.CoroutineCallOutsideOfSuspend)
2813 pos,
2814 "Coroutine calls are only allowed when they are arguments to \
2815 'suspend' operator"
2818 let function_is_not_coroutine pos name =
2819 add_list
2820 (Typing.err_code Typing.FunctionIsNotCoroutine)
2822 pos,
2823 "Function '" ^ name ^ "' is not a coroutine and cannot be \
2824 used in as an argument of 'suspend' operator."
2827 let coroutinness_mismatch pos1_is_coroutine pos1 pos2 =
2828 let m1 = "This is a coroutine." in
2829 let m2 = "This is not a coroutine." in
2830 add_list
2831 (Typing.err_code Typing.CoroutinnessMismatch)
2833 pos1, if pos1_is_coroutine then m1 else m2;
2834 pos2, if pos1_is_coroutine then m2 else m1;
2837 let invalid_ppl_call pos context =
2838 let error_msg = "Cannot call a method on an object of a <<__PPL>> class "^context in
2839 add (Typing.err_code Typing.InvalidPPLCall) pos error_msg
2841 let invalid_ppl_static_call pos reason =
2842 let error_msg = "Cannot call a static method on a <<__PPL>> class "^reason in
2843 add (Typing.err_code Typing.InvalidPPLStaticCall) pos error_msg
2845 let ppl_meth_pointer pos func =
2846 let error_msg = func^" cannot be used with a <<__PPL>> class" in
2847 add (Typing.err_code Typing.PPLMethPointer) pos error_msg
2849 let coroutine_outside_experimental pos =
2850 add (Typing.err_code Typing.CoroutineOutsideExperimental) pos
2851 Coroutine_errors.error_message
2853 let return_disposable_mismatch pos1_return_disposable pos1 pos2 =
2854 let m1 = "This is marked <<__ReturnDisposable>>." in
2855 let m2 = "This is not marked <<__ReturnDisposable>>." in
2856 add_list
2857 (Typing.err_code Typing.ReturnDisposableMismatch)
2859 pos1, if pos1_return_disposable then m1 else m2;
2860 pos2, if pos1_return_disposable then m2 else m1;
2863 let return_void_to_rx_mismatch ~pos1_has_attribute pos1 pos2 =
2864 let m1 = "This is marked <<__ReturnsVoidToRx>>." in
2865 let m2 = "This is not marked <<__ReturnsVoidToRx>>." in
2866 add_list
2867 (Typing.err_code Typing.ReturnVoidToRxMismatch)
2869 pos1, if pos1_has_attribute then m1 else m2;
2870 pos2, if pos1_has_attribute then m2 else m1;
2873 let this_as_lexical_variable pos =
2874 add (Naming.err_code Naming.ThisAsLexicalVariable) pos "Cannot use $this as lexical variable"
2876 let dollardollar_lvalue pos =
2877 add (Typing.err_code Typing.DollardollarLvalue) pos
2878 "Cannot assign a value to the special pipe variable ($$)"
2880 let assigning_to_const pos =
2881 add (Typing.err_code Typing.AssigningToConst) pos
2882 "Cannot assign to a __Const property"
2884 let self_const_parent_not pos =
2885 add (Typing.err_code Typing.SelfConstParentNot) pos
2886 "A __Const class may only extend other __Const classes"
2888 let parent_const_self_not pos =
2889 add (Typing.err_code Typing.ParentConstSelfNot) pos
2890 "Only __Const classes may extend a __Const class"
2892 let overriding_prop_const_mismatch parent_pos parent_const child_pos child_const =
2893 let m1 = "This property is __Const" in
2894 let m2 = "This property is not __Const" in
2895 add_list (Typing.err_code Typing.OverridingPropConstMismatch)
2897 parent_pos, if parent_const then m1 else m2;
2898 child_pos, if child_const then m1 else m2;
2901 let mutable_return_result_mismatch pos1_has_mutable_return pos1 pos2 =
2902 let m1 = "This is marked <<__MutableReturn>>." in
2903 let m2 = "This is not marked <<__MutableReturn>>." in
2904 add_list
2905 (Typing.err_code Typing.MutableReturnResultMismatch)
2907 pos1, if pos1_has_mutable_return then m1 else m2;
2908 pos2, if pos1_has_mutable_return then m2 else m1;
2911 (*****************************************************************************)
2912 (* Typing decl errors *)
2913 (*****************************************************************************)
2915 let wrong_extend_kind child_pos child parent_pos parent =
2916 let msg1 = child_pos, child^" cannot extend "^parent in
2917 let msg2 = parent_pos, "This is "^parent in
2918 add_list (Typing.err_code Typing.WrongExtendKind) [msg1; msg2]
2920 let unsatisfied_req parent_pos req_name req_pos =
2921 let s1 = "Failure to satisfy requirement: "^(Utils.strip_ns req_name) in
2922 let s2 = "Required here" in
2923 if req_pos = parent_pos
2924 then add (Typing.err_code Typing.UnsatisfiedReq) parent_pos s1
2925 else add_list (Typing.err_code Typing.UnsatisfiedReq) [parent_pos, s1; req_pos, s2]
2927 let cyclic_class_def stack pos =
2928 let stack =
2929 SSet.fold ~f:(fun x y -> (Utils.strip_ns x)^" "^y) stack ~init:"" in
2930 add (Typing.err_code Typing.CyclicClassDef) pos ("Cyclic class definition : "^stack)
2932 let trait_reuse p_pos p_name class_name trait =
2933 let c_pos, c_name = class_name in
2934 let c_name = Utils.strip_ns c_name in
2935 let trait = Utils.strip_ns trait in
2936 let err = "Class "^c_name^" reuses trait "^trait^" in its hierarchy" in
2937 let err' = "It is already used through "^(Utils.strip_ns p_name) in
2938 add_list (Typing.err_code Typing.TraitReuse) [c_pos, err; p_pos, err']
2941 * This error should be unfixmeable, because the `is` expression does not
2942 * support it at all.
2944 let invalid_is_as_expression_hint op hint_pos ty_pos ty_str =
2945 add_list (Typing.err_code Typing.InvalidIsAsExpressionHint) [
2946 hint_pos, ("Invalid \"" ^ op ^ "\" expression hint");
2947 ty_pos, ("The \"" ^ op ^ "\" operator cannot be used with " ^ ty_str);
2951 * This error is fixmeable, because the typechecker will still refine the type
2952 * despite the hint not being completely valid.
2954 let partially_valid_is_as_expression_hint op hint_pos ty_pos ty_str =
2955 add_list (Typing.err_code Typing.PartiallyValidIsAsExpressionHint) [
2956 hint_pos, ("Invalid \"" ^ op ^ "\" expression hint");
2957 ty_pos, ("The \"" ^ op ^ "\" operator should not be used with " ^ ty_str);
2960 let override_final ~parent ~child =
2961 add_list (Typing.err_code Typing.OverrideFinal) [child, "You cannot override this method";
2962 parent, "It was declared as final"]
2964 let override_memoizelsb ~parent ~child =
2965 add_list (Typing.err_code Typing.OverrideMemoizeLSB) [
2966 child, "__MemoizeLSB method may not be an override (temporary due to HHVM bug)";
2967 parent, "This method is being overridden"]
2969 let override_lsb ~member_name ~parent ~child =
2970 add_list (Typing.err_code Typing.OverrideLSB) [
2971 child, "Member " ^ member_name ^ " may not override __LSB member of parent";
2972 parent, "This is being overridden"]
2974 let should_be_override pos class_id id =
2975 add (Typing.err_code Typing.ShouldBeOverride) pos
2976 ((Utils.strip_ns class_id)^"::"^id^"() is marked as override; \
2977 no non-private parent definition found \
2978 or overridden parent is defined in non-<?hh code")
2980 let override_per_trait class_name id m_pos =
2981 let c_pos, c_name = class_name in
2982 let err_msg =
2983 ("Method "^(Utils.strip_ns c_name)^"::"^id^" should be an override \
2984 per the declaring trait; no non-private parent definition found \
2985 or overridden parent is defined in non-<?hh code")
2986 in add_list (Typing.err_code Typing.OverridePerTrait) [
2987 c_pos, err_msg;
2988 m_pos, "Declaration of "^id^"() is here"
2991 let missing_assign pos =
2992 add (Typing.err_code Typing.MissingAssign) pos "Please assign a value"
2994 let private_override pos class_id id =
2995 add (Typing.err_code Typing.PrivateOverride) pos ((Utils.strip_ns class_id)^"::"^id
2996 ^": combining private and override is nonsensical")
2998 let invalid_memoized_param pos ty_reason_msg =
2999 add_list (Typing.err_code Typing.InvalidMemoizedParam) (
3000 ty_reason_msg @ [pos,
3001 "Parameters to memoized function must be null, bool, int, float, string, \
3002 an object deriving IMemoizeParam, or a Container thereof. See also \
3003 http://docs.hhvm.com/hack/attributes/special#__memoize"])
3005 let invalid_disposable_hint pos class_name =
3006 add (Typing.err_code Typing.InvalidDisposableHint) pos
3007 ("Parameter with type '" ^ class_name ^ "' must not \
3008 implement IDisposable or IAsyncDisposable. Please use <<__AcceptDisposable>> attribute or \
3009 create disposable object with 'using' statement instead.")
3011 let invalid_disposable_return_hint pos class_name =
3012 add (Typing.err_code Typing.InvalidDisposableReturnHint) pos
3013 ("Return type '" ^ class_name ^ "' must not \
3014 implement IDisposable or IAsyncDisposable. Please add <<__ReturnDisposable>> attribute.")
3016 let xhp_required pos why_xhp ty_reason_msg =
3017 let msg = "An XHP instance was expected" in
3018 add_list (Typing.err_code Typing.XhpRequired) ((pos, msg)::(pos, why_xhp)::ty_reason_msg)
3020 let illegal_xhp_child pos ty_reason_msg =
3021 let msg = "XHP children must be compatible with XHPChild" in
3022 add_list (Typing.err_code Typing.IllegalXhpChild) ((pos, msg)::ty_reason_msg)
3024 let nullsafe_not_needed p nonnull_witness =
3025 add_list (Typing.err_code Typing.NullsafeNotNeeded) (
3028 "You are using the ?-> operator but this object cannot be null. "
3029 ] @ nonnull_witness)
3031 let generic_at_runtime p =
3032 add (Typing.err_code Typing.GenericAtRuntime) p
3033 "Generics can only be used in type hints since they are erased at runtime."
3035 let trivial_strict_eq p b left right left_trail right_trail =
3036 let msg = "This expression is always "^b in
3037 let left_trail = List.map left_trail typedef_trail_entry in
3038 let right_trail = List.map right_trail typedef_trail_entry in
3039 add_list (Typing.err_code Typing.TrivialStrictEq)
3040 ((p, msg) :: left @ left_trail @ right @ right_trail)
3042 let trivial_strict_not_nullable_compare_null p result type_reason =
3043 let msg = "This expression is always "^result in
3044 add_list (Typing.err_code Typing.NotNullableCompareNullTrivial)
3045 ((p, msg) :: type_reason)
3047 let eq_incompatible_types p left right =
3048 let msg = "This equality test has incompatible types" in
3049 add_list (Typing.err_code Typing.EqIncompatibleTypes)
3050 ((p, msg) :: left @ right)
3052 let comparison_invalid_types p left right =
3053 let msg = "This comparison has invalid types. Only comparisons in which \
3054 both arguments are strings, nums, DateTime, or DateTimeImmutable \
3055 are allowed" in
3056 add_list (Typing.err_code Typing.ComparisonInvalidTypes) ((p, msg) :: left @ right)
3058 let void_usage p void_witness =
3059 let msg = "You are using the return value of a void function" in
3060 add_list (Typing.err_code Typing.VoidUsage) ((p, msg) :: void_witness)
3062 let noreturn_usage p noreturn_witness =
3063 let msg = "You are using the return value of a noreturn function" in
3064 add_list (Typing.err_code Typing.NoreturnUsage) ((p, msg) :: noreturn_witness)
3066 let attribute_too_few_arguments pos x n =
3067 let n = string_of_int n in
3068 add (Typing.err_code Typing.AttributeTooFewArguments) pos (
3069 "The attribute "^x^" expects at least "^n^" arguments"
3072 let attribute_too_many_arguments pos x n =
3073 let n = string_of_int n in
3074 add (Typing.err_code Typing.AttributeTooManyArguments) pos (
3075 "The attribute "^x^" expects at most "^n^" arguments"
3078 let attribute_param_type pos x =
3079 add (Typing.err_code Typing.AttributeParamType) pos (
3080 "This attribute parameter should be "^x
3083 let deprecated_use pos pos_def msg =
3084 add_list (Typing.err_code Typing.DeprecatedUse) [
3085 pos, msg;
3086 pos_def, "Definition is here";
3089 let cannot_declare_constant kind pos (class_pos, class_name) =
3090 let kind_str =
3091 match kind with
3092 | `enum -> "an enum"
3093 | `trait -> "a trait"
3095 add_list (Typing.err_code Typing.CannotDeclareConstant) [
3096 pos, "Cannot declare a constant in "^kind_str;
3097 class_pos, (strip_ns class_name)^" was defined as "^kind_str^" here";
3100 let ambiguous_inheritance pos class_ origin (error: error) =
3101 let origin = strip_ns origin in
3102 let class_ = strip_ns class_ in
3103 let message = "This declaration was inherited from an object of type "^origin^
3104 ". Redeclare this member in "^class_^" with a compatible signature." in
3105 let code, msgl = (get_code error), (to_list error) in
3106 add_list code (msgl @ [pos, message])
3108 let multiple_concrete_defs child_pos parent_pos child_origin parent_origin name class_ =
3109 let child_origin = strip_ns child_origin in
3110 let parent_origin = strip_ns parent_origin in
3111 let class_ = strip_ns class_ in
3112 add_list (Typing.err_code Typing.MultipleConcreteDefs) [
3113 child_pos, child_origin ^ " and " ^ parent_origin ^
3114 " both declare ambiguous implementations of " ^ name ^ ".";
3115 child_pos, child_origin ^ "'s definition is here.";
3116 parent_pos, parent_origin ^ "'s definition is here.";
3117 child_pos, "Redeclare " ^ name ^ " in " ^ class_ ^ " with a compatible signature.";
3120 let explain_contravariance pos c_name error =
3121 let message = "Considering that this type argument is contravariant "^
3122 "with respect to " ^ strip_ns c_name in
3123 let code, msgl = (get_code error), (to_list error) in
3124 add_list code (msgl @ [pos, message])
3126 let explain_invariance pos c_name suggestion error =
3127 let message = "Considering that this type argument is invariant "^
3128 "with respect to " ^ strip_ns c_name ^ suggestion in
3129 let code, msgl = (get_code error), (to_list error) in
3130 add_list code (msgl @ [pos, message])
3132 let local_variable_modified_and_used pos_modified pos_used_l =
3133 let used_msg p = p, "And accessed here" in
3134 add_list (Typing.err_code Typing.LocalVariableModifedAndUsed)
3135 ((pos_modified, "Unsequenced modification and access to local \
3136 variable. Modified here") ::
3137 List.map pos_used_l used_msg)
3139 let local_variable_modified_twice pos_modified pos_modified_l =
3140 let modified_msg p = p, "And also modified here" in
3141 add_list (Typing.err_code Typing.LocalVariableModifedTwice)
3142 ((pos_modified, "Unsequenced modifications to local variable. \
3143 Modified here") ::
3144 List.map pos_modified_l modified_msg)
3146 let assign_during_case p =
3147 add (Typing.err_code Typing.AssignDuringCase) p
3148 "Don't assign to variables inside of case labels"
3150 let cyclic_enum_constraint pos =
3151 add (Typing.err_code Typing.CyclicEnumConstraint) pos "Cyclic enum constraint"
3153 let invalid_classname p =
3154 add (Typing.err_code Typing.InvalidClassname) p "Not a valid class name"
3156 let illegal_type_structure pos errmsg =
3157 let msg =
3158 "The two arguments to type_structure() must be:"
3159 ^"\n - first: ValidClassname::class or an object of that class"
3160 ^"\n - second: a single-quoted string literal containing the name"
3161 ^" of a type constant of that class"
3162 ^"\n"^errmsg in
3163 add (Typing.err_code Typing.IllegalTypeStructure) pos msg
3165 let illegal_typeconst_direct_access pos =
3166 let msg =
3167 "Type constants cannot be directly accessed. "
3168 ^"Use type_structure(ValidClassname::class, 'TypeConstName') instead" in
3169 add (Typing.err_code Typing.IllegalTypeStructure) pos msg
3171 let class_property_only_static_literal pos =
3172 let msg =
3173 "Initialization of class property must be a static literal expression." in
3174 add (Typing.err_code Typing.ClassPropertyOnlyStaticLiteral) pos msg
3176 let reference_expr pos =
3177 let msg = "Cannot take a value by reference in strict mode." in
3178 add (Typing.err_code Typing.ReferenceExpr) pos msg
3180 let pass_by_ref_annotation_missing pos1 pos2 =
3181 let msg1 = pos1, "This argument should be annotated with &" in
3182 let msg2 = pos2, "Because this parameter is passed by reference" in
3183 add_list (Typing.err_code Typing.PassByRefAnnotationMissing) [msg1; msg2]
3185 let pass_by_ref_annotation_unexpected pos1 pos2 pos2_is_variadic =
3186 let msg1 = pos1, "This argument should not be annotated with &" in
3187 let param_str = if pos2_is_variadic
3188 then "variadic parameters are"
3189 else "this parameter is" in
3190 let msg2 = pos2, "Because " ^ param_str ^ " passed by value" in
3191 add_list (Typing.err_code Typing.PassByRefAnnotationUnexpected) [msg1; msg2]
3193 let reffiness_invariant pos1 pos2 mode2 =
3194 let msg1 = pos1, "This parameter is passed by reference" in
3195 let mode_str = match mode2 with
3196 | `normal -> "a normal parameter"
3197 | `inout -> "an inout parameter" in
3198 let msg2 = pos2, "It is incompatible with " ^ mode_str in
3199 add_list (Typing.err_code Typing.ReffinessInvariant) [msg1; msg2]
3201 let inout_annotation_missing pos1 pos2 =
3202 let msg1 = pos1, "This argument should be annotated with 'inout'" in
3203 let msg2 = pos2, "Because this is an inout parameter" in
3204 add_list (Typing.err_code Typing.InoutAnnotationMissing) [msg1; msg2]
3206 let inout_annotation_unexpected pos1 pos2 pos2_is_variadic =
3207 let msg1 = pos1, "Unexpected inout annotation for argument" in
3208 let msg2 = pos2, if pos2_is_variadic
3209 then "A variadic parameter can never be inout"
3210 else "This is a normal parameter (does not have 'inout')" in
3211 add_list (Typing.err_code Typing.InoutAnnotationUnexpected) [msg1; msg2]
3213 let inoutness_mismatch pos1 pos2 =
3214 let msg1 = pos1, "This is an inout parameter" in
3215 let msg2 = pos2, "It is incompatible with a normal parameter" in
3216 add_list (Typing.err_code Typing.InoutnessMismatch) [msg1; msg2]
3218 let invalid_new_disposable pos =
3219 let msg =
3220 "Disposable objects may only be created in a 'using' statement or 'return' from function marked <<__ReturnDisposable>>" in
3221 add (Typing.err_code Typing.InvalidNewDisposable) pos msg
3223 let invalid_return_disposable pos =
3224 let msg =
3225 "Return expression must be new disposable in function marked <<__ReturnDisposable>>" in
3226 add (Typing.err_code Typing.InvalidReturnDisposable) pos msg
3228 let nonreactive_function_call pos decl_pos callee_reactivity cause_pos_opt =
3229 add_list (Typing.err_code Typing.NonreactiveFunctionCall) ([
3230 pos, "Reactive functions can only call other 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 ^ "."]
3236 let nonreactive_call_from_shallow pos decl_pos callee_reactivity cause_pos_opt=
3237 add_list (Typing.err_code Typing.NonreactiveCallFromShallow) ([
3238 pos, "Shallow reactive functions cannot call non-reactive functions.";
3239 decl_pos, "This function is " ^ callee_reactivity ^ "."
3240 ] @ Option.value_map cause_pos_opt ~default:[] ~f:(fun cause_pos ->
3241 [cause_pos, "This argument caused function to be " ^ callee_reactivity ^ "."]
3243 let rx_enabled_in_non_rx_context pos =
3244 add (Typing.err_code Typing.RxEnabledInNonRxContext) pos (
3245 "\\HH\\Rx\\IS_ENABLED can only be used in reactive functions."
3248 let rx_enabled_in_lambdas pos =
3249 add (Typing.err_code Typing.RxEnabledInLambdas) pos (
3250 "\\HH\\Rx\\IS_ENABLED cannot be used inside lambdas."
3253 let rx_parameter_condition_mismatch cond pos def_pos =
3254 add_list (Typing.err_code Typing.RxParameterConditionMismatch) [
3255 pos, "This parameter does not satisfy "^ cond ^ " condition defined on \
3256 matching parameter in function super type.";
3257 def_pos, "This is parameter declaration from the function super type."
3259 let nonreactive_append pos =
3260 let msg = "Cannot append to a Hack Collection object in a reactive context" in
3261 add (Typing.err_code Typing.NonreactiveAppend) pos msg
3263 let obj_set_reactive pos =
3264 let msg = ("This object's property is being mutated(used as an lvalue)" ^
3265 "\nYou cannot set non-mutable object properties in reactive functions") in
3266 add (Typing.err_code Typing.ObjSetReactive) pos msg
3268 let invalid_unset_target_rx pos =
3269 add (Typing.err_code Typing.InvalidUnsetTargetInRx) pos (
3270 "Non-mutable argument for 'unset' is not allowed in reactive functions."
3273 let inout_argument_bad_type pos msgl =
3274 let msg =
3275 "Expected argument marked inout to be contained in a local or " ^
3276 "a value-typed container (e.g. vec, dict, keyset, array). " ^
3277 "To use inout here, assign to/from a temporary local variable." in
3278 add_list (Typing.err_code Typing.InoutArgumentBadType) ((pos, msg) :: msgl)
3280 let ambiguous_lambda pos uses =
3281 let msg1 =
3282 "Lambda has parameter types that could not be determined at definition site." in
3283 let msg2 =
3284 Printf.sprintf
3285 "%d distinct use types were determined: please add type hints to lambda parameters."
3286 (List.length uses) in
3287 add_list (Typing.err_code Typing.AmbiguousLambda) ([(pos, msg1); (pos, msg2)] @
3288 List.map uses (fun (pos, ty) -> (pos, "This use has type " ^ ty)))
3290 let wrong_expression_kind_attribute expr_kind pos attr attr_class_pos attr_class_name intf_name =
3291 let msg1 =
3292 Printf.sprintf "The %s attribute cannot be used on %s." (Utils.strip_ns attr) expr_kind in
3293 let msg2 =
3294 Printf.sprintf "The attribute's class is defined here. To be available for use on \
3295 %s, the %s class must implement %s." expr_kind
3296 (String_utils.string_after attr_class_name 1)
3297 (String_utils.string_after intf_name 1) in
3298 add_list (Typing.err_code Typing.WrongExpressionKindAttribute) [
3299 pos, msg1;
3300 attr_class_pos, msg2
3303 let attribute_class_no_constructor_args pos def_pos =
3304 let msg =
3305 "The class associated with this attribute has no constructor. " ^
3306 "Please add a constructor to use arguments with this attribute." in
3307 add_list (Typing.err_code Typing.AttributeClassNoConstructorArgs) [
3308 pos, msg;
3309 def_pos, "The attribute's class is defined here."
3312 let cannot_return_borrowed_value_as_immutable fun_pos value_pos =
3313 add_list (Typing.err_code Typing.CannotReturnBorrowedValueAsImmutable) [
3314 fun_pos, "Values returned from reactive function by default are treated \
3315 as immutable.";
3316 value_pos, "This value is mutably borrowed and cannot be returned as immutable"
3319 let decl_override_missing_hint pos =
3320 add (Typing.err_code Typing.DeclOverrideMissingHint) pos
3321 "When redeclaring class members, both declarations must have a typehint"
3323 let let_var_immutability_violation pos id =
3324 add (Typing.err_code Typing.LetVarImmutabilityViolation) pos
3325 ("Let variables are immutable. Using let variable " ^ id ^ " in write context is not allowed.")
3327 let invalid_type_for_atmost_rx_as_rxfunc_parameter pos type_str =
3328 add (Typing.err_code Typing.InvalidTypeForOnlyrxIfRxfuncParameter) pos (
3329 "Parameter annotated with <<__AtMostRxAsFunc>> attribute must be function, \
3330 now '" ^ type_str ^ "'."
3333 let missing_annotation_for_atmost_rx_as_rxfunc_parameter pos =
3334 add (Typing.err_code Typing.MissingAnnotationForOnlyrxIfRxfuncParameter) pos (
3335 "Missing function type annotation on parameter marked with <<__AtMostRxAsFunc>> attribute."
3338 let binding_ref_in_array pos =
3339 let msg = "Binding a reference in an array is no longer supported in Hack." in
3340 add (Typing.err_code Typing.BindingRefInArray) pos msg
3342 let return_ref_in_array pos =
3343 let msg = "Returning a reference to an element in an array is no longer " ^
3344 "supported in Hack." in
3345 add (Typing.err_code Typing.BindingRefInArray) pos msg
3347 let passing_array_cell_by_ref pos =
3348 let msg = "Passing array cells by reference is no longer supported; " ^
3349 "use 'inout' instead" in
3350 add (Typing.err_code Typing.PassingArrayCellByRef) pos msg
3352 let superglobal_in_reactive_context pos name =
3353 add (Typing.err_code Typing.SuperglobalInReactiveContext) pos (
3354 "Superglobal "^ name ^ " cannot be used in a reactive context."
3357 let global_in_reactive_context pos name =
3358 add (Typing.err_code Typing.GlobalInReactiveContext) pos (
3359 "Global " ^ name ^ " cannot be used in a reactive context."
3362 let static_property_in_reactive_context pos =
3363 add (Typing.err_code Typing.StaticPropertyInReactiveContext) pos (
3364 "Static property cannot be used in a reactive context."
3367 let static_in_reactive_context pos name =
3368 add (Typing.err_code Typing.StaticInReactiveContext) pos (
3369 "Static " ^ name ^ " cannot be used in a reactive context."
3372 let returns_void_to_rx_function_as_non_expression_statement pos fpos =
3373 add_list (Typing.err_code Typing.ReturnsVoidToRxAsNonExpressionStatement) [
3374 pos, "Cannot use result of function annotated with <<__ReturnsVoidToRx>> \
3375 in reactive context";
3376 fpos, "This is function declaration."
3379 let non_awaited_awaitable_in_rx pos =
3380 add (Typing.err_code Typing.NonawaitedAwaitableInReactiveContext) pos (
3381 "This value has Awaitable type. Awaitable typed values in reactive code \
3382 must be either immediately await'ed or passed as arguments to 'genva' function."
3385 let shapes_key_exists_always_true pos1 name pos2 =
3386 add_list (Typing.err_code Typing.ShapesKeyExistsAlwaysTrue) [
3387 pos1, "This Shapes::keyExists() check is always true";
3388 pos2, "The field '" ^ name ^ "' exists because of this definition"
3391 let shape_field_non_existence_reason name = function
3392 | `Undefined ->
3393 "The field '" ^ name ^ "' is not defined in this shape"
3394 | `Unset ->
3395 "The field '" ^ name ^ "' was unset here"
3397 let shapes_key_exists_always_false pos1 name pos2 reason =
3398 add_list (Typing.err_code Typing.ShapesKeyExistsAlwaysFalse) [
3399 pos1, "This Shapes::keyExists() check is always false";
3400 pos2, shape_field_non_existence_reason name reason
3403 let shapes_idx_with_non_existent_field pos1 name pos2 reason =
3404 add_list (Typing.err_code Typing.ShapesIdxWithNonExistentField) [
3405 pos1, "You are calling Shapes::idx() on a field known to not exist";
3406 pos2, shape_field_non_existence_reason name reason
3409 let ambiguous_object_access pos name self_pos vis subclass_pos class_self class_subclass =
3410 let class_self = Utils.strip_ns class_self in
3411 let class_subclass = Utils.strip_ns class_subclass in
3412 add_list (Typing.err_code Typing.AmbiguousObjectAccess) [
3413 pos, "This object access to " ^ name ^ " is ambiguous";
3414 self_pos, "You will access the private instance declared in " ^ class_self;
3415 subclass_pos, "Instead of the " ^ vis ^ " instance declared in " ^ class_subclass;
3418 let invalid_traversable_in_rx pos =
3419 add (Typing.err_code Typing.InvalidTraversableInRx) pos (
3420 "Cannot traverse over non-reactive traversable in reactive code."
3423 let lateinit_with_default pos =
3424 add (Typing.err_code Typing.LateInitWithDefault) pos
3425 "A late-initialized property cannot have a default value"
3427 let bad_lateinit_override parent_is_lateinit parent_pos child_pos =
3428 let verb = if parent_is_lateinit then "is" else "is not" in
3429 add_list (Typing.err_code Typing.BadLateInitOverride) [
3430 child_pos, "Redeclared properties must be consistently declared __LateInit";
3431 parent_pos, "The property "^verb^" declared __LateInit here";
3434 let invalid_truthiness_test pos ty =
3435 add (Typing.err_code Typing.InvalidTruthinessTest) pos @@
3436 Printf.sprintf
3437 "Invalid condition: a value of type %s will always be truthy" ty
3439 let forward_compatibility_not_current pos value =
3440 let current = ForwardCompatibilityLevel.current in
3441 add (Init.err_code Init.ForwardCompatibilityNotCurrent)
3443 (Printf.sprintf
3444 "forward_compatibility_level is set to '%s' (%d), which is stale; current is '%s' (%d). Errors may be missing."
3445 (ForwardCompatibilityLevel.as_string value)
3446 (ForwardCompatibilityLevel.as_int value)
3447 (ForwardCompatibilityLevel.as_string current)
3448 (ForwardCompatibilityLevel.as_int current)
3451 let forward_compatibility_below_minimum pos value =
3452 let minimum = ForwardCompatibilityLevel.minimum in
3453 let current = ForwardCompatibilityLevel.current in
3454 add (Init.err_code Init.ForwardCompatibilityBelowMinimum)
3456 (Printf.sprintf
3457 "forward_compatibility_level is set to '%s' (%d), which is below the minimum of '%s' (%d); current is '%s' (%d)"
3458 (ForwardCompatibilityLevel.as_string value)
3459 (ForwardCompatibilityLevel.as_int value)
3460 (ForwardCompatibilityLevel.as_string minimum)
3461 (ForwardCompatibilityLevel.as_int minimum)
3462 (ForwardCompatibilityLevel.as_string current)
3463 (ForwardCompatibilityLevel.as_int current)
3466 let invalid_switch_case_value_type case_value_p case_value_ty scrutinee_ty =
3467 add (Typing.err_code Typing.InvalidSwitchCaseValueType) case_value_p @@
3468 Printf.sprintf
3469 "This case value has type %s, which is incompatible with type %s."
3470 case_value_ty
3471 scrutinee_ty
3473 (*****************************************************************************)
3474 (* Convert relative paths to absolute. *)
3475 (*****************************************************************************)
3477 let to_absolute = M.to_absolute
3479 (*****************************************************************************)
3480 (* Printing *)
3481 (*****************************************************************************)
3483 let to_json (error : Pos.absolute error_) =
3484 let error_code, msgl = (get_code error), (to_list error) in
3485 let elts = List.map msgl begin fun (p, w) ->
3486 let line, scol, ecol = Pos.info_pos p in
3487 Hh_json.JSON_Object [
3488 "descr", Hh_json.JSON_String w;
3489 "path", Hh_json.JSON_String (Pos.filename p);
3490 "line", Hh_json.int_ line;
3491 "start", Hh_json.int_ scol;
3492 "end", Hh_json.int_ ecol;
3493 "code", Hh_json.int_ error_code
3495 end in
3496 Hh_json.JSON_Object [ "message", Hh_json.JSON_Array elts ]
3498 let to_string = M.to_string
3500 (*****************************************************************************)
3501 (* Try if errors. *)
3502 (*****************************************************************************)
3504 let try_ f1 f2 =
3505 M.try_with_result f1 (fun _ l -> f2 l)
3507 let try_with_error f1 f2 =
3508 try_ f1 (fun err -> add_error err; f2())
3510 let try_add_err pos err f1 f2 =
3511 try_ f1 begin fun error ->
3512 let error_code, l = (get_code error), (to_list error) in
3513 add_list error_code ((pos, err) :: l);
3514 f2()
3517 let has_no_errors f =
3518 try_ (fun () -> f(); true) (fun _ -> false)
3520 (*****************************************************************************)
3521 (* Do. *)
3522 (*****************************************************************************)
3524 let do_ = M.do_
3525 let do_with_context = M.do_with_context
3527 let run_in_context = M.run_in_context
3528 let run_in_decl_mode = M.run_in_decl_mode
3530 let ignore_ f =
3531 let allow_errors_in_default_path_copy = !allow_errors_in_default_path in
3532 set_allow_errors_in_default_path true;
3533 let _, result = (do_ f) in
3534 set_allow_errors_in_default_path allow_errors_in_default_path_copy;
3535 result
3537 let try_when f ~when_ ~do_ =
3538 M.try_with_result f begin fun result (error: error) ->
3539 if when_()
3540 then do_ error
3541 else add_error error;
3542 result
3545 (* Whether we've found at least one error *)
3546 let currently_has_errors = M.currently_has_errors
3548 (* Runs the first function that is expected to produce an error. If it doesn't
3549 * then we run the second function we are given
3551 let must_error f error_fun =
3552 let had_no_errors = try_with_error (fun () -> f(); true) (fun _ -> false) in
3553 if had_no_errors then error_fun();
3557 let errors_without_tracing =
3558 (module Errors_with_mode(NonTracingErrors) : Errors_sig.S)
3559 let errors_with_tracing =
3560 (module Errors_with_mode(TracingErrors) : Errors_sig.S)
3562 include (val (if Injector_config.use_error_tracing
3563 then errors_with_tracing
3564 else errors_without_tracing))