Moving from class wrapper to class-less wrapper
[hiphop-php.git] / hphp / hack / src / errors / errors.ml
blob809ed9efef2c6fda86a5ac03a0d2aa8fb8fb844d
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_prelude
11 open Reordered_argument_collections
12 open String_utils
14 type error_code = int [@@deriving eq]
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 [@@deriving eq]
20 let get_message_pos (msg : 'a message) = fst msg
22 let get_message_str (msg : 'a message) = snd msg
24 type phase =
25 | Init
26 | Parsing
27 | Naming
28 | Decl
29 | Typing
30 [@@deriving eq]
32 type severity =
33 | Warning
34 | Error
36 type format =
37 | Context
38 | Raw
39 | Highlighted
41 type typing_error_callback =
42 ?code:int -> Pos.t * string -> (Pos.t * string) list -> unit
44 type name_context =
45 | FunctionNamespace
46 | ConstantNamespace
47 | TypeNamespace (** Classes, interfaces, traits, records and type aliases.*)
48 (* The following are all subsets of TypeNamespace, used when we can
49 give a more specific naming error. E.g. `use Foo;` only allows
50 traits. *)
51 | TraitContext
52 | ClassContext
53 | RecordContext
55 (* The file and phase of analysis being currently performed *)
56 let current_context : (Relative_path.t * phase) ref =
57 ref (Relative_path.default, Typing)
59 let current_span : Pos.t ref = ref Pos.none
61 let allow_errors_in_default_path = ref true
63 module PhaseMap = Reordered_argument_map (WrappedMap.Make (struct
64 type t = phase
66 let rank = function
67 | Init -> 0
68 | Parsing -> 1
69 | Naming -> 2
70 | Decl -> 3
71 | Typing -> 4
73 let compare x y = rank x - rank y
74 end))
76 (** Results of single file analysis. *)
77 type 'a file_t = 'a list PhaseMap.t [@@deriving eq]
79 (** Results of multi-file analysis. *)
80 type 'a files_t = 'a file_t Relative_path.Map.t [@@deriving eq]
82 let files_t_fold v ~f ~init =
83 Relative_path.Map.fold v ~init ~f:(fun path v acc ->
84 PhaseMap.fold v ~init:acc ~f:(fun phase v acc -> f path phase v acc))
86 let files_t_map v ~f = Relative_path.Map.map v ~f:(fun v -> PhaseMap.map v ~f)
88 let files_t_merge ~f x y =
89 (* Using fold instead of merge to make the runtime proportional to the size
90 * of first argument (like List.rev_append ) *)
91 Relative_path.Map.fold x ~init:y ~f:(fun k x acc ->
92 let y =
93 Option.value (Relative_path.Map.find_opt y k) ~default:PhaseMap.empty
95 Relative_path.Map.add
96 acc
98 (PhaseMap.merge x y ~f:(fun phase x y -> f phase k x y)))
100 let files_t_to_list x =
101 files_t_fold x ~f:(fun _ _ x acc -> List.rev_append x acc) ~init:[]
102 |> List.rev
104 let list_to_files_t = function
105 | [] -> Relative_path.Map.empty
106 | x ->
107 (* Values constructed here should not be used with incremental mode.
108 * See assert in incremental_update. *)
109 Relative_path.Map.singleton
110 Relative_path.default
111 (PhaseMap.singleton Typing x)
113 let get_code_severity code =
115 code
116 = Error_codes.Init.err_code Error_codes.Init.ForwardCompatibilityNotCurrent
117 then
118 Warning
119 else
120 Error
122 (* Get most recently-ish added error. *)
123 let get_last error_map =
124 (* If this map has more than one element, we pick an arbitrary file. Because
125 * of that, we might not end up with the most recent error and generate a
126 * less-specific error message. This should be rare. *)
127 match Relative_path.Map.max_binding_opt error_map with
128 | None -> None
129 | Some (_, phase_map) ->
130 let error_list =
131 PhaseMap.max_binding_opt phase_map |> Option.value_map ~f:snd ~default:[]
133 (match List.rev error_list with
134 | [] -> None
135 | e :: _ -> Some e)
137 type 'a error_ = {
138 code: error_code;
139 claim: 'a message;
140 reasons: 'a message list;
142 [@@deriving eq]
144 type error = Pos.t error_ [@@deriving eq]
146 type applied_fixme = Pos.t * int [@@deriving eq]
148 let applied_fixmes : applied_fixme files_t ref = ref Relative_path.Map.empty
150 let (error_map : error files_t ref) = ref Relative_path.Map.empty
152 let accumulate_errors = ref false
154 (* Some filename when declaring *)
155 let in_lazy_decl = ref None
157 let (is_hh_fixme : (Pos.t -> error_code -> bool) ref) = ref (fun _ _ -> false)
159 let badpos_message =
160 Printf.sprintf
161 "There is an error somewhere in this file. However the type checker reports that the error is in another file. %s"
162 Error_message_sentinel.please_file_a_bug_message
164 let badpos_message_2 =
165 Printf.sprintf
166 "There is an error somewhere in this definition. However the type checker reports that the error is elsewhere. %s"
167 Error_message_sentinel.please_file_a_bug_message
169 let try_with_result f1 f2 =
170 let error_map_copy = !error_map in
171 let accumulate_errors_copy = !accumulate_errors in
172 let is_hh_fixme_copy = !is_hh_fixme in
173 (is_hh_fixme := (fun _ _ -> false));
174 error_map := Relative_path.Map.empty;
175 accumulate_errors := true;
176 let (result, errors) =
177 Utils.try_finally
179 begin
180 fun () ->
181 let result = f1 () in
182 (result, !error_map)
184 ~finally:
185 begin
186 fun () ->
187 error_map := error_map_copy;
188 accumulate_errors := accumulate_errors_copy;
189 is_hh_fixme := is_hh_fixme_copy
192 match get_last errors with
193 | None -> result
194 | Some { code; claim; reasons } ->
195 (* Remove bad position sentinel if present: we might be about to add a new primary
196 * error position*)
197 let l =
198 let (_, msg) = claim in
199 if String.equal msg badpos_message || String.equal msg badpos_message_2
200 then
201 if List.is_empty reasons then
202 failwith "in try_with_result"
203 else
204 reasons
205 else
206 claim :: reasons
208 f2 result { code; claim = List.hd_exn l; reasons = List.tl_exn l }
210 (* Reset errors before running [f] so that we can return the errors
211 * caused by f. These errors are not added in the global list of errors. *)
212 let do_ f =
213 let error_map_copy = !error_map in
214 let applied_fixmes_copy = !applied_fixmes in
215 let accumulate_errors_copy = !accumulate_errors in
216 error_map := Relative_path.Map.empty;
217 applied_fixmes := Relative_path.Map.empty;
218 accumulate_errors := true;
219 let (result, out_errors, out_applied_fixmes) =
220 Utils.try_finally
222 begin
223 fun () ->
224 let result = f () in
225 (result, !error_map, !applied_fixmes)
227 ~finally:
228 begin
229 fun () ->
230 error_map := error_map_copy;
231 applied_fixmes := applied_fixmes_copy;
232 accumulate_errors := accumulate_errors_copy
235 let out_errors = files_t_map ~f:List.rev out_errors in
236 ((out_errors, out_applied_fixmes), result)
238 let run_in_context path phase f =
239 let context_copy = !current_context in
240 current_context := (path, phase);
241 Utils.try_finally ~f ~finally:(fun () -> current_context := context_copy)
243 let run_with_span span f =
244 let old_span = !current_span in
245 current_span := span;
246 Utils.try_finally ~f ~finally:(fun () -> current_span := old_span)
248 (* Log important data if lazy_decl triggers a crash *)
249 let lazy_decl_error_logging error error_map to_absolute to_string =
250 let error_list = files_t_to_list !error_map in
251 (* Print the current error list, which should be empty *)
252 Printf.eprintf "%s" "Error list(should be empty):\n";
253 List.iter error_list ~f:(fun err ->
254 let msg = err |> to_absolute |> to_string in
255 Printf.eprintf "%s\n" msg);
256 Printf.eprintf "%s" "Offending error:\n";
257 Printf.eprintf "%s" error;
259 (* Print out a larger stack trace *)
260 Printf.eprintf "%s" "Callstack:\n";
261 Printf.eprintf
262 "%s"
263 (Caml.Printexc.raw_backtrace_to_string (Caml.Printexc.get_callstack 500));
265 (* Exit with special error code so we can see the log after *)
266 Exit.exit Exit_status.Lazy_decl_bug
268 (*****************************************************************************)
269 (* Error code printing. *)
270 (*****************************************************************************)
272 let error_kind error_code =
273 match error_code / 1000 with
274 | 1 -> "Parsing"
275 | 2 -> "Naming"
276 | 3 -> "NastCheck"
277 | 4 -> "Typing"
278 | 5 -> "Lint"
279 | 8 -> "Init"
280 | _ -> "Other"
282 let error_code_to_string error_code =
283 let error_kind = error_kind error_code in
284 let error_number = Printf.sprintf "%04d" error_code in
285 error_kind ^ "[" ^ error_number ^ "]"
287 let phase_to_string (phase : phase) : string =
288 match phase with
289 | Init -> "Init"
290 | Parsing -> "Parsing"
291 | Naming -> "Naming"
292 | Decl -> "Decl"
293 | Typing -> "Typing"
295 let phase_of_string (value : string) : phase option =
296 match Caml.String.lowercase_ascii value with
297 | "init" -> Some Init
298 | "parsing" -> Some Parsing
299 | "naming" -> Some Naming
300 | "decl" -> Some Decl
301 | "typing" -> Some Typing
302 | _ -> None
304 let (name_context_to_string : name_context -> string) = function
305 | FunctionNamespace -> "function"
306 | ConstantNamespace -> "constant"
307 | TypeNamespace -> "type"
308 | TraitContext -> "trait"
309 | ClassContext -> "class"
310 | RecordContext -> "record"
312 let get_pos { claim; _ } = fst claim
314 let sort err =
315 let rec compare (x_code, x_messages) (y_code, y_messages) =
316 match (x_messages, y_messages) with
317 | ([], []) -> 0
318 | (_x_messages, []) -> -1
319 | ([], _y_messages) -> 1
320 | (x_message :: x_messages, y_message :: y_messages) ->
321 (* The primary sort order is by file *)
322 let comparison =
323 Relative_path.compare
324 (fst x_message |> Pos.filename)
325 (fst y_message |> Pos.filename)
327 (* Then within each file, sort by phase *)
328 let comparison =
329 if comparison = 0 then
330 Int.compare (x_code / 1000) (y_code / 1000)
331 else
332 comparison
334 (* If the error codes are the same, sort by position *)
335 let comparison =
336 if comparison = 0 then
337 Pos.compare (fst x_message) (fst y_message)
338 else
339 comparison
341 (* If the error codes are also the same, sort by message text *)
342 let comparison =
343 if comparison = 0 then
344 String.compare (snd x_message) (snd y_message)
345 else
346 comparison
348 (* Finally, if the message text is also the same, then continue comparing
349 the reason messages (which indicate the reason why Hack believes
350 there is an error reported in the claim message) *)
351 if comparison = 0 then
352 compare (x_code, x_messages) (y_code, y_messages)
353 else
354 comparison
356 let equal x y = compare x y = 0 in
357 let coalesce { code; claim; reasons } = (code, claim :: reasons) in
358 List.sort ~compare:(fun x y -> compare (coalesce x) (coalesce y)) err
359 |> List.remove_consecutive_duplicates ~equal:(fun x y ->
360 equal (coalesce x) (coalesce y))
362 let get_sorted_error_list (err, _) = sort (files_t_to_list err)
364 (* Getters and setter for passed-in map, based on current context *)
365 let get_current_file_t file_t_map =
366 let current_file = fst !current_context in
367 Relative_path.Map.find_opt file_t_map current_file
368 |> Option.value ~default:PhaseMap.empty
370 let get_current_list file_t_map =
371 let current_phase = snd !current_context in
372 get_current_file_t file_t_map |> fun x ->
373 PhaseMap.find_opt x current_phase |> Option.value ~default:[]
375 let set_current_list file_t_map new_list =
376 let (current_file, current_phase) = !current_context in
377 file_t_map :=
378 Relative_path.Map.add
379 !file_t_map
380 current_file
381 (PhaseMap.add (get_current_file_t !file_t_map) current_phase new_list)
383 let do_with_context path phase f = run_in_context path phase (fun () -> do_ f)
385 (** Turn on lazy decl mode for the duration of the closure.
386 This runs without returning the original state,
387 since we collect it later in do_with_lazy_decls_ *)
388 let run_in_decl_mode filename f =
389 let old_in_lazy_decl = !in_lazy_decl in
390 in_lazy_decl := Some filename;
391 Utils.try_finally ~f ~finally:(fun () -> in_lazy_decl := old_in_lazy_decl)
393 and make_error code claim reasons : error = { code; claim; reasons }
395 (*****************************************************************************)
396 (* Accessors. *)
397 (*****************************************************************************)
398 and get_code ({ code; _ } : 'a error_) = (code : error_code)
400 let get_severity (error : 'a error_) = get_code_severity (get_code error)
402 let to_list ({ claim; reasons; _ } : 'a error_) = claim :: reasons
404 let to_absolute { code; claim; reasons } =
405 let claim = (fst claim |> Pos.to_absolute, snd claim) in
406 let reasons = List.map reasons (fun (p, s) -> (Pos.to_absolute p, s)) in
407 { code; claim; reasons }
409 let make_absolute_error code (x : (Pos.absolute * string) list) :
410 Pos.absolute error_ =
411 match x with
412 | [] -> failwith "an error must have at least one message"
413 | claim :: reasons -> { code; claim; reasons }
415 let get_messages ({ claim; reasons; _ } : 'a error_) = claim :: reasons
417 let read_lines path =
418 try In_channel.read_lines path
419 with Sys_error _ ->
420 (try Multifile.read_file_from_multifile path with Sys_error _ -> [])
422 let num_digits x = int_of_float (Float.log10 (float_of_int x)) + 1
424 (* Sort [xs] such that all the values that return the same
425 value for (f x) are consecutive. For any two elements
426 x1 and x2 in xs where (f x1) = (f x2), if x1 occurs before x2 in
427 xs, then x1 also occurs before x2 in the returned list. *)
428 let combining_sort (xs : 'a list) ~(f : 'a -> string) : 'a list =
429 let rec build_map xs grouped keys =
430 match xs with
431 | x :: xs ->
432 let key = f x in
433 (match String.Map.find grouped key with
434 | Some members ->
435 let grouped = String.Map.set grouped ~key ~data:(members @ [x]) in
436 build_map xs grouped keys
437 | None ->
438 let grouped = String.Map.set grouped ~key ~data:[x] in
439 build_map xs grouped (key :: keys))
440 | [] -> (grouped, keys)
442 let (grouped, keys) = build_map xs String.Map.empty [] in
443 List.concat_map (List.rev keys) ~f:(fun fn -> String.Map.find_exn grouped fn)
445 (* E.g. "10 errors found." *)
446 let format_summary format errors dropped_count max_errors : string option =
447 match format with
448 | Context
449 | Highlighted ->
450 let total = List.length errors + dropped_count in
451 let formatted_total =
452 Printf.sprintf
453 "%d error%s found"
454 total
455 ( if total = 1 then
457 else
458 "s" )
460 let truncated =
461 match max_errors with
462 | Some max_errors when dropped_count > 0 ->
463 Printf.sprintf
464 " (only showing first %d, dropped %d).\n"
465 max_errors
466 dropped_count
467 | _ -> ".\n"
469 Some (formatted_total ^ truncated)
470 | Raw -> None
472 let to_absolute_for_test { code; claim; reasons } =
473 let f (p, s) =
474 let path = Pos.filename p in
475 let path_without_prefix = Relative_path.suffix path in
476 let p =
477 Pos.set_file
478 (Relative_path.create Relative_path.Dummy path_without_prefix)
481 (Pos.to_absolute p, s)
483 let claim = f claim in
484 let reasons = List.map ~f reasons in
485 { code; claim; reasons }
487 let report_pos_from_reason = ref false
489 let to_string ({ code; claim; reasons } : Pos.absolute error_) : string =
490 let buf = Buffer.create 50 in
491 let (pos1, msg1) = claim in
492 Buffer.add_string
494 begin
495 let error_code = error_code_to_string code in
496 let reason_msg =
497 if !report_pos_from_reason && Pos.get_from_reason pos1 then
498 " [FROM REASON INFO]"
499 else
502 Printf.sprintf
503 "%s\n%s (%s)%s\n"
504 (Pos.string pos1)
505 msg1
506 error_code
507 reason_msg
508 end;
509 List.iter reasons (fun (p, w) ->
510 let msg = Printf.sprintf " %s\n %s\n" (Pos.string p) w in
511 Buffer.add_string buf msg);
512 Buffer.contents buf
514 let add_error_impl error =
515 if !accumulate_errors then
516 let () =
517 match !current_context with
518 | (path, _)
519 when Relative_path.equal path Relative_path.default
520 && not !allow_errors_in_default_path ->
521 Hh_logger.log
522 "WARNING: adding an error in default path\n%s\n"
523 (Caml.Printexc.raw_backtrace_to_string
524 (Caml.Printexc.get_callstack 100))
525 | _ -> ()
527 (* Cheap test to avoid duplicating most recent error *)
528 let error_list = get_current_list !error_map in
529 match error_list with
530 | old_error :: _ when equal_error error old_error -> ()
531 | _ -> set_current_list error_map (error :: error_list)
532 else
533 (* We have an error, but haven't handled it in any way *)
534 let msg = error |> to_absolute |> to_string in
535 match !in_lazy_decl with
536 | Some _ -> lazy_decl_error_logging msg error_map to_absolute to_string
537 | None -> Utils.assert_false_log_backtrace (Some msg)
539 (* Whether we've found at least one error *)
540 let currently_has_errors () = not (List.is_empty (get_current_list !error_map))
542 module Parsing = Error_codes.Parsing
543 module Naming = Error_codes.Naming
544 module NastCheck = Error_codes.NastCheck
545 module Typing = Error_codes.Typing
547 (*****************************************************************************)
548 (* Types *)
549 (*****************************************************************************)
551 type t = error files_t * applied_fixme files_t [@@deriving eq]
553 module type Error_category = sig
554 type t
556 val min : int
558 val max : int
560 val of_enum : int -> t option
562 val show : t -> string
564 val err_code : t -> int
567 (*****************************************************************************)
568 (* HH_FIXMEs hook *)
569 (*****************************************************************************)
571 let error_codes_treated_strictly = ref (ISet.of_list [])
573 let is_strict_code code = ISet.mem code !error_codes_treated_strictly
575 (* The 'phps FixmeAllHackErrors' tool must be kept in sync with this list *)
576 let hard_banned_codes =
577 ISet.of_list
579 Typing.err_code Typing.InvalidIsAsExpressionHint;
580 Typing.err_code Typing.InvalidEnforceableTypeArgument;
581 Typing.err_code Typing.RequireArgsReify;
582 Typing.err_code Typing.InvalidReifiedArgument;
583 Typing.err_code Typing.GenericsNotAllowed;
584 Typing.err_code Typing.InvalidNewableTypeArgument;
585 Typing.err_code Typing.InvalidNewableTypeParamConstraints;
586 Typing.err_code Typing.NewWithoutNewable;
587 Typing.err_code Typing.NewClassReified;
588 Typing.err_code Typing.MemoizeReified;
589 Typing.err_code Typing.ClassGetReified;
592 let allowed_fixme_codes_strict = ref ISet.empty
594 let allowed_fixme_codes_partial = ref ISet.empty
596 let codes_not_raised_partial = ref ISet.empty
598 let set_allow_errors_in_default_path x = allow_errors_in_default_path := x
600 let is_allowed_code_strict code = ISet.mem code !allowed_fixme_codes_strict
602 let is_allowed_code_partial code = ISet.mem code !allowed_fixme_codes_partial
604 let is_not_raised_partial code = ISet.mem code !codes_not_raised_partial
606 let (get_hh_fixme_pos : (Pos.t -> error_code -> Pos.t option) ref) =
607 ref (fun _ _ -> None)
609 let (is_hh_fixme_disallowed : (Pos.t -> error_code -> bool) ref) =
610 ref (fun _ _ -> false)
612 (*****************************************************************************)
613 (* Errors accumulator. *)
614 (*****************************************************************************)
616 (* If primary position in error list isn't in current file, wrap with a sentinel error *)
617 let check_pos_msg (claim, pos_msg_l) =
618 let pos = fst claim in
619 let current_file = fst !current_context in
620 let current_span = !current_span in
621 (* If error is reported inside the current span, or no span has been set but the error
622 * is reported in the current file, then accept the error *)
624 Pos.contains current_span pos
625 || Pos.equal current_span Pos.none
626 && Relative_path.equal (Pos.filename pos) current_file
627 || Relative_path.equal current_file Relative_path.default
628 then
629 (claim, pos_msg_l)
630 else
631 let pos_msg_l = claim :: pos_msg_l in
632 let message =
633 pos_msg_l
634 |> List.map ~f:(fun (pos, msg) ->
635 Pos.print_verbose_relative pos ^ ": " ^ msg)
637 let stack =
638 Exception.get_current_callstack_string 99 |> Exception.clean_stack
640 HackEventLogger.type_check_primary_position_bug
641 ~current_file
642 ~message
643 ~stack;
644 let err =
645 if Pos.equal current_span Pos.none then
646 (Pos.make_from current_file, badpos_message)
647 else
648 (current_span, badpos_message_2)
650 (err, pos_msg_l)
652 let add_error_with_fixme_error error explanation =
653 let { code; claim; reasons = _ } = error in
654 let (pos, _) = claim in
655 let pos = Option.value (!get_hh_fixme_pos pos code) ~default:pos in
656 add_error_impl error;
657 add_error_impl { code; claim = (pos, explanation); reasons = [] }
659 let rec add_applied_fixme code pos =
660 if ServerLoadFlag.get_no_load () then
661 let applied_fixmes_list = get_current_list !applied_fixmes in
662 set_current_list applied_fixmes ((pos, code) :: applied_fixmes_list)
663 else
666 and add code pos msg = add_list code (pos, msg) []
668 and fixme_present pos code =
669 !is_hh_fixme pos code || !is_hh_fixme_disallowed pos code
671 and add_list code (claim : _ message) reasons =
672 add_error { code; claim; reasons }
674 and add_error error =
675 let { code; claim; reasons } = error in
676 let (claim, reasons) = check_pos_msg (claim, reasons) in
677 let error = { code; claim; reasons } in
679 let pos = fst claim in
681 if ISet.mem code hard_banned_codes then
682 if fixme_present pos code then
683 let explanation =
684 Printf.sprintf
685 "You cannot use `HH_FIXME` or `HH_IGNORE_ERROR` comments to suppress error %d, and this cannot be enabled by configuration"
686 code
688 add_error_with_fixme_error error explanation
689 else
690 add_error_impl error
691 else if
692 is_not_raised_partial code && Relative_path.is_partial (Pos.filename pos)
693 then
695 else if not (fixme_present pos code) then
696 (* Fixmes and banned decl fixmes are separated by the parser because Errors can't recover
697 * the position information after the fact. This is the default case, where an HH_FIXME
698 * comment is not present. Therefore, the remaining cases are variations on behavior when
699 * a fixme is present *)
700 add_error_impl error
701 else if Relative_path.(is_hhi (prefix (Pos.filename pos))) then
702 add_applied_fixme code pos
703 else if !report_pos_from_reason && Pos.get_from_reason pos then
704 let explanation =
705 "You cannot use `HH_FIXME` or `HH_IGNORE_ERROR` comments to suppress an error whose position was derived from reason information"
707 add_error_with_fixme_error error explanation
708 else if !is_hh_fixme_disallowed pos code then
709 let explanation =
710 Printf.sprintf
711 "You cannot use `HH_FIXME` or `HH_IGNORE_ERROR` comments to suppress error %d in declarations"
712 code
714 add_error_with_fixme_error error explanation
715 else
716 let whitelist =
718 (not (ISet.is_empty !allowed_fixme_codes_partial))
719 && Relative_path.is_partial (Pos.filename pos)
720 then
721 is_allowed_code_partial
722 else
723 is_allowed_code_strict
725 if whitelist code then
726 add_applied_fixme code pos
727 else
728 let explanation =
729 Printf.sprintf
730 "You cannot use `HH_FIXME` or `HH_IGNORE_ERROR` comments to suppress error %d"
731 code
733 add_error_with_fixme_error error explanation
735 and merge (err', fixmes') (err, fixmes) =
736 let append _ _ x y =
737 let x = Option.value x ~default:[] in
738 let y = Option.value y ~default:[] in
739 Some (List.rev_append x y)
741 (files_t_merge ~f:append err' err, files_t_merge ~f:append fixmes' fixmes)
743 and merge_into_current errors =
744 let merged = merge errors (!error_map, !applied_fixmes) in
745 error_map := fst merged;
746 applied_fixmes := snd merged
748 and incremental_update :
749 type (* Need to write out the entire ugly type to convince OCaml it's polymorphic
750 * and can update both error_map as well as applied_fixmes map *)
752 a files_t ->
753 a files_t ->
754 ((* function folding over paths of rechecked files *)
755 a files_t ->
756 (Relative_path.t -> a files_t -> a files_t) ->
757 a files_t) ->
758 phase ->
759 a files_t =
760 fun old new_ fold phase ->
761 (* Helper to remove acc[path][phase]. If acc[path] becomes empty afterwards,
762 * remove it too (i.e do not store empty maps or lists ever). *)
763 let remove path phase acc =
764 let new_phase_map =
765 match Relative_path.Map.find_opt acc path with
766 | None -> None
767 | Some phase_map ->
768 let new_phase_map = PhaseMap.remove phase_map phase in
769 if PhaseMap.is_empty new_phase_map then
770 None
771 else
772 Some new_phase_map
774 match new_phase_map with
775 | None -> Relative_path.Map.remove acc path
776 | Some x -> Relative_path.Map.add acc path x
778 (* Replace old errors with new *)
779 let res =
780 files_t_merge new_ old ~f:(fun phase path new_ old ->
781 ( if Relative_path.equal path Relative_path.default then
782 let phase =
783 match phase with
784 | Init -> "Init"
785 | Parsing -> "Parsing"
786 | Naming -> "Naming"
787 | Decl -> "Decl"
788 | Typing -> "Typing"
790 Utils.assert_false_log_backtrace
791 (Some
792 ( "Default (untracked) error sources should not get into incremental "
793 ^ "mode. There might be a missing call to `Errors.do_with_context`/"
794 ^ "`run_in_context` somwhere or incorrectly used `Errors.from_error_list`."
795 ^ "Phase: "
796 ^ phase )) );
797 match new_ with
798 | Some new_ -> Some (List.rev new_)
799 | None -> old)
801 (* For files that were rechecked, but had no errors - remove them from maps *)
802 fold res (fun path acc ->
803 let has_errors =
804 match Relative_path.Map.find_opt new_ path with
805 | None -> false
806 | Some phase_map -> PhaseMap.mem phase_map phase
808 if has_errors then
810 else
811 remove path phase acc)
813 and incremental_update_set ~old ~new_ ~rechecked phase =
814 let fold init g =
815 Relative_path.Set.fold
817 begin
818 fun path acc ->
819 g path acc
821 ~init
822 rechecked
824 ( incremental_update (fst old) (fst new_) fold phase,
825 incremental_update (snd old) (snd new_) fold phase )
827 and incremental_update_map ~old ~new_ ~rechecked phase =
828 let fold init g =
829 Relative_path.Map.fold
831 begin
832 fun path _ acc ->
833 g path acc
835 ~init
836 rechecked
838 ( incremental_update (fst old) (fst new_) fold phase,
839 incremental_update (snd old) (snd new_) fold phase )
841 and empty = (Relative_path.Map.empty, Relative_path.Map.empty)
843 and is_empty (err, _fixmes) = Relative_path.Map.is_empty err
845 and count (err, _fixmes) =
846 files_t_fold err ~f:(fun _ _ x acc -> acc + List.length x) ~init:0
848 and get_error_list (err, _fixmes) = files_t_to_list err
850 and get_applied_fixmes (_err, fixmes) = files_t_to_list fixmes
852 and from_error_list err = (list_to_files_t err, Relative_path.Map.empty)
854 (*****************************************************************************)
855 (* Accessors. (All methods delegated to the parameterized module.) *)
856 (*****************************************************************************)
858 let iter_error_list f err = List.iter ~f (get_sorted_error_list err)
860 let fold_errors ?phase err ~init ~f =
861 match phase with
862 | None ->
863 files_t_fold (fst err) ~init ~f:(fun source _ errors acc ->
864 List.fold_right errors ~init:acc ~f:(f source))
865 | Some phase ->
866 Relative_path.Map.fold (fst err) ~init ~f:(fun source phases acc ->
867 match PhaseMap.find_opt phases phase with
868 | None -> acc
869 | Some errors -> List.fold_right errors ~init:acc ~f:(f source))
871 let fold_errors_in ?phase err ~source ~init ~f =
872 Relative_path.Map.find_opt (fst err) source
873 |> Option.value ~default:PhaseMap.empty
874 |> PhaseMap.fold ~init ~f:(fun p errors acc ->
875 match phase with
876 | Some x when not (equal_phase x p) -> acc
877 | _ -> List.fold_right errors ~init:acc ~f)
879 let get_failed_files err phase =
880 files_t_fold (fst err) ~init:Relative_path.Set.empty ~f:(fun source p _ acc ->
881 if not (equal_phase phase p) then
883 else
884 Relative_path.Set.add acc source)
886 (*****************************************************************************)
887 (* Error code printing. *)
888 (*****************************************************************************)
890 let internal_error pos msg = add 0 pos ("Internal error: " ^ msg)
892 let unimplemented_feature pos msg = add 0 pos ("Feature not implemented: " ^ msg)
894 let experimental_feature pos msg =
895 add 0 pos ("Cannot use experimental feature: " ^ msg)
897 let strip_ns id = id |> Utils.strip_ns |> Hh_autoimport.reverse_type
899 let on_error_or_add (on_error : typing_error_callback option) code claim reasons
901 match on_error with
902 | None -> add_error { code; claim; reasons }
903 | Some f -> f ~code claim reasons
905 (*****************************************************************************)
906 (* Parsing errors. *)
907 (*****************************************************************************)
909 let fixme_format pos =
911 (Parsing.err_code Parsing.FixmeFormat)
913 "`HH_FIXME` wrong format, expected `/* HH_FIXME[ERROR_NUMBER] */`"
915 let parsing_error (p, msg) = add (Parsing.err_code Parsing.ParsingError) p msg
917 let xhp_parsing_error (p, msg) =
918 add (Parsing.err_code Parsing.XhpParsingError) p msg
920 (*****************************************************************************)
921 (* Legacy AST / AAST errors *)
922 (*****************************************************************************)
924 let mk_unsupported_trait_use_as pos =
926 code = Naming.err_code Naming.UnsupportedTraitUseAs;
927 claim =
928 ( pos,
929 "Aliasing with `as` within a trait `use` is a PHP feature that is unsupported in Hack"
931 reasons = [];
934 let unsupported_trait_use_as pos = add_error (mk_unsupported_trait_use_as pos)
936 let mk_unsupported_instead_of pos =
938 code = Naming.err_code Naming.UnsupportedInsteadOf;
939 claim = (pos, "`insteadof` is a PHP feature that is unsupported in Hack");
940 reasons = [];
943 let unsupported_instead_of pos = add_error (mk_unsupported_instead_of pos)
945 let mk_invalid_trait_use_as_visibility pos =
947 code = Naming.err_code Naming.InvalidTraitUseAsVisibility;
948 claim = (pos, "Cannot redeclare trait method's visibility in this manner");
949 reasons = [];
952 let invalid_trait_use_as_visibility pos =
953 add_error (mk_invalid_trait_use_as_visibility pos)
955 (*****************************************************************************)
956 (* Naming errors *)
957 (*****************************************************************************)
959 let unexpected_arrow pos cname =
961 (Naming.err_code Naming.UnexpectedArrow)
963 ( "Keys may not be specified for "
964 ^ Markdown_lite.md_codify cname
965 ^ " initialization" )
967 let missing_arrow pos cname =
969 (Naming.err_code Naming.MissingArrow)
971 ( "Keys must be specified for "
972 ^ Markdown_lite.md_codify cname
973 ^ " initialization" )
975 let disallowed_xhp_type pos name =
977 (Naming.err_code Naming.DisallowedXhpType)
979 ( Markdown_lite.md_codify name
980 ^ " is not a valid type. Use `:xhp` or `XHPChild`." )
982 let name_is_reserved name pos =
983 let name = Utils.strip_all_ns name in
985 (Naming.err_code Naming.NameIsReserved)
987 (Markdown_lite.md_codify name ^ " cannot be used as it is reserved.")
989 let dollardollar_unused pos =
991 (Naming.err_code Naming.DollardollarUnused)
993 ( "This expression does not contain a "
994 ^ "usage of the special pipe variable. Did you forget to use the `$$` "
995 ^ "variable?" )
997 let method_name_already_bound pos name =
999 (Naming.err_code Naming.MethodNameAlreadyBound)
1001 ("Method name already bound: " ^ Markdown_lite.md_codify name)
1003 (* Given two equal-length strings, highlights the characters in
1004 the second that differ from the first *)
1005 let highlight_differences base to_highlight =
1006 match List.zip (String.to_list base) (String.to_list to_highlight) with
1007 | List.Or_unequal_lengths.Ok l ->
1008 List.group l ~break:(fun (o1, s1) (o2, s2) ->
1009 not (Bool.equal (Char.equal o1 s1) (Char.equal o2 s2)))
1010 |> List.map ~f:(fun cs ->
1011 let s = List.map cs ~f:snd |> String.of_char_list in
1012 let (c1, c2) = List.hd_exn cs in
1013 if Char.equal c1 c2 then
1015 else
1016 Markdown_lite.md_highlight s)
1017 |> String.concat
1018 | List.Or_unequal_lengths.Unequal_lengths -> to_highlight
1020 let error_name_already_bound name name_prev p p_prev =
1021 let name = strip_ns name in
1022 let name_prev = strip_ns name_prev in
1023 let (claim, reasons) =
1024 ( (p, "Name already bound: " ^ Markdown_lite.md_codify name),
1026 ( p_prev,
1027 if String.equal name name_prev then
1028 "Previous definition is here"
1029 else
1030 "Previous definition "
1031 ^ (highlight_differences name name_prev |> Markdown_lite.md_codify)
1032 ^ " differs only by case " );
1035 let hhi_msg =
1036 "This appears to be defined in an hhi file included in your project "
1037 ^ "root. The hhi files for the standard library are now a part of the "
1038 ^ "typechecker and must be removed from your project. Typically, you can "
1039 ^ "do this by deleting the \"hhi\" directory you copied into your "
1040 ^ "project when first starting with Hack."
1042 let reasons =
1043 if Relative_path.(is_hhi (prefix (Pos.filename p))) then
1044 reasons @ [(p_prev, hhi_msg)]
1045 else if Relative_path.(is_hhi (prefix (Pos.filename p_prev))) then
1046 reasons @ [(p, hhi_msg)]
1047 else
1048 reasons
1050 add_list (Naming.err_code Naming.ErrorNameAlreadyBound) claim reasons
1052 let error_class_attribute_already_bound name name_prev p p_prev =
1053 let name = strip_ns name in
1054 let name_prev = strip_ns name_prev in
1055 let (claim, reasons) =
1056 ( ( p,
1057 "A class and an attribute class cannot share the same name. Conflicting class: "
1058 ^ Markdown_lite.md_codify name ),
1059 [(p_prev, "Previous definition: " ^ Markdown_lite.md_codify name_prev)] )
1061 add_list (Naming.err_code Naming.AttributeClassNameConflict) claim reasons
1063 let unbound_name pos name kind =
1064 let kind_str =
1065 match kind with
1066 | ConstantNamespace -> " (a global constant)"
1067 | FunctionNamespace -> " (a global function)"
1068 | TypeNamespace -> ""
1069 | ClassContext -> " (an object type)"
1070 | TraitContext -> " (a trait)"
1071 | RecordContext -> " (a record type)"
1074 (Naming.err_code Naming.UnboundName)
1076 ("Unbound name: " ^ Markdown_lite.md_codify (strip_ns name) ^ kind_str)
1078 let invalid_fun_pointer pos name =
1080 (Naming.err_code Naming.InvalidFunPointer)
1082 ( "Unbound global function: "
1083 ^ Markdown_lite.md_codify (strip_ns name)
1084 ^ " is not a valid name for fun()" )
1086 let rx_move_invalid_location pos =
1088 (Naming.err_code Naming.RxMoveInvalidLocation)
1090 "`Rx\\move` is only allowed in argument position or as right hand side of the assignment."
1092 let hint_message ?(modifier = "") orig hint hint_pos =
1093 let s =
1095 (not (String.equal orig hint))
1096 && String.equal (String.lowercase orig) (String.lowercase hint)
1097 then
1098 Printf.sprintf
1099 "Did you mean %s%s instead (which only differs by case)?"
1100 modifier
1101 (highlight_differences orig hint |> Markdown_lite.md_codify)
1102 else
1103 Printf.sprintf
1104 "Did you mean %s%s instead?"
1105 modifier
1106 (Markdown_lite.md_codify hint)
1108 (hint_pos, s)
1110 let undefined ~in_rx_scope pos var_name did_you_mean =
1111 let msg =
1112 if in_rx_scope then
1113 Printf.sprintf
1114 "Variable %s is undefined, not always defined, or unset afterwards."
1115 (Markdown_lite.md_codify var_name)
1116 else
1117 Printf.sprintf
1118 "Variable %s is undefined, or not always defined."
1119 (Markdown_lite.md_codify var_name)
1121 let suggestion =
1122 match did_you_mean with
1123 | Some (did_you_mean, pos) -> [hint_message var_name did_you_mean pos]
1124 | None -> []
1126 add_list (Naming.err_code Naming.Undefined) (pos, msg) suggestion
1128 let this_reserved pos =
1130 (Naming.err_code Naming.ThisReserved)
1132 "The type parameter `this` is reserved"
1134 let start_with_T pos =
1136 (Naming.err_code Naming.StartWith_T)
1138 "Please make your type parameter start with the letter `T` (capital)"
1140 let already_bound pos name =
1142 (Naming.err_code Naming.NameAlreadyBound)
1144 ("Argument already bound: " ^ Markdown_lite.md_codify name)
1146 let unexpected_typedef pos def_pos expected_kind =
1147 let expected_type = name_context_to_string expected_kind in
1148 add_list
1149 (Naming.err_code Naming.UnexpectedTypedef)
1150 ( pos,
1151 Printf.sprintf
1152 "Expected a %s but got a type alias."
1153 (Markdown_lite.md_codify expected_type) )
1154 [(def_pos, "Alias definition is here.")]
1156 let mk_fd_name_already_bound pos =
1158 code = Naming.err_code Naming.FdNameAlreadyBound;
1159 claim = (pos, "Field name already bound");
1160 reasons = [];
1163 let fd_name_already_bound pos = add_error (mk_fd_name_already_bound pos)
1165 let repeated_record_field name pos prev_pos =
1166 let msg =
1167 Printf.sprintf "Duplicate record field %s" (Markdown_lite.md_codify name)
1169 add_list
1170 (NastCheck.err_code NastCheck.RepeatedRecordFieldName)
1171 (pos, msg)
1172 [(prev_pos, "Previous field is here")]
1174 let unexpected_record_field_name ~field_name ~field_pos ~record_name ~decl_pos =
1175 let msg =
1176 Printf.sprintf
1177 "Record %s has no field %s"
1178 (strip_ns record_name |> Markdown_lite.md_codify)
1179 (Markdown_lite.md_codify field_name)
1181 add_list
1182 (Typing.err_code Typing.RecordUnknownField)
1183 (field_pos, msg)
1184 [(decl_pos, "Definition is here")]
1186 let missing_record_field_name ~field_name ~new_pos ~record_name ~field_decl_pos
1188 let msg =
1189 Printf.sprintf
1190 "Mising required field %s in %s"
1191 (Markdown_lite.md_codify field_name)
1192 (strip_ns record_name |> Markdown_lite.md_codify)
1194 add_list
1195 (Typing.err_code Typing.RecordMissingRequiredField)
1196 (new_pos, msg)
1197 [(field_decl_pos, "Field definition is here")]
1199 let type_not_record id pos =
1201 (Typing.err_code Typing.NotARecord)
1203 (Printf.sprintf
1204 "Expected a record type, but got %s."
1205 (strip_ns id |> Markdown_lite.md_codify))
1207 let primitive_toplevel pos =
1209 (Naming.err_code Naming.PrimitiveToplevel)
1211 "Primitive type annotations are always available and may no longer be referred to in the toplevel namespace."
1213 let primitive_invalid_alias pos used valid =
1215 (Naming.err_code Naming.PrimitiveInvalidAlias)
1217 ( "Invalid Hack type. Using "
1218 ^ Markdown_lite.md_codify used
1219 ^ " in Hack is considered an error. Use "
1220 ^ Markdown_lite.md_codify valid
1221 ^ " instead, to keep the codebase consistent." )
1223 let dynamic_new_in_strict_mode pos =
1225 (Naming.err_code Naming.DynamicNewInStrictMode)
1227 "Cannot use dynamic `new`."
1229 let invalid_type_access_root (pos, id) =
1231 (Naming.err_code Naming.InvalidTypeAccessRoot)
1233 ( Markdown_lite.md_codify id
1234 ^ " must be an identifier for a class, `self`, or `this`" )
1236 let duplicate_user_attribute (pos, name) existing_attr_pos =
1237 add_list
1238 (Naming.err_code Naming.DuplicateUserAttribute)
1239 (pos, "You cannot reuse the attribute " ^ Markdown_lite.md_codify name)
1241 ( existing_attr_pos,
1242 Markdown_lite.md_codify name ^ " was already used here" );
1245 let unbound_attribute_name pos name =
1246 let reason =
1247 if string_starts_with name "__" then
1248 "starts with __ but is not a standard attribute"
1249 else
1250 "does not have a class. Please declare a class for the attribute."
1253 (Naming.err_code Naming.UnboundName)
1255 ( "Unrecognized user attribute: "
1256 ^ (strip_ns name |> Markdown_lite.md_codify)
1257 ^ " "
1258 ^ reason )
1260 let this_no_argument pos =
1261 add (Naming.err_code Naming.ThisNoArgument) pos "`this` expects no arguments"
1263 let object_cast pos =
1265 (Naming.err_code Naming.ObjectCast)
1267 "Casts are only supported for `bool`, `int`, `float` and `string`."
1269 let this_hint_outside_class pos =
1271 (Naming.err_code Naming.ThisHintOutsideClass)
1273 "Cannot use `this` outside of a class"
1275 let this_type_forbidden pos =
1277 (Naming.err_code Naming.ThisMustBeReturn)
1279 "The type `this` cannot be used as a constraint on a class generic, or as the type of a static member variable"
1281 let nonstatic_property_with_lsb pos =
1283 (Naming.err_code Naming.NonstaticPropertyWithLSB)
1285 "`__LSB` attribute may only be used on static properties"
1287 let lowercase_this pos type_ =
1289 (Naming.err_code Naming.LowercaseThis)
1291 ( "Invalid Hack type "
1292 ^ Markdown_lite.md_codify type_
1293 ^ ". Use `this` instead" )
1295 let classname_param pos =
1297 (Naming.err_code Naming.ClassnameParam)
1299 ( "Missing type parameter to `classname`; `classname` is entirely"
1300 ^ " meaningless without one" )
1302 (** Used if higher-kinded types are disabled *)
1303 let typaram_applied_to_type pos x =
1305 (Naming.err_code Naming.HigherKindedTypesUnsupportedFeature)
1307 (Printf.sprintf
1308 "`%s` is a type parameter. Type parameters cannot take type arguments (e.g. `%s<int>` isn't allowed)"
1312 (** Used if higher-kinded types are disabled *)
1313 let tparam_with_tparam pos x =
1314 let param_desc =
1315 match x with
1316 | "_" -> ""
1317 | _ -> Markdown_lite.md_codify x ^ " is a type parameter. "
1320 (Naming.err_code Naming.HigherKindedTypesUnsupportedFeature)
1322 (Printf.sprintf
1323 "%sType parameters cannot themselves have type parameters"
1324 param_desc)
1326 let shadowed_type_param p pos name =
1327 add_list
1328 (Naming.err_code Naming.ShadowedTypeParam)
1329 ( p,
1330 Printf.sprintf
1331 "You cannot re-bind the type parameter %s"
1332 (Markdown_lite.md_codify name) )
1334 ( pos,
1335 Printf.sprintf "%s is already bound here" (Markdown_lite.md_codify name)
1339 let missing_typehint pos =
1340 add (Naming.err_code Naming.MissingTypehint) pos "Please add a type hint"
1342 let expected_variable pos =
1344 (Naming.err_code Naming.ExpectedVariable)
1346 "Was expecting a variable name"
1348 let clone_too_many_arguments pos =
1350 (Naming.err_code Naming.NamingTooManyArguments)
1352 "`__clone` method cannot take arguments"
1354 let naming_too_few_arguments pos =
1355 add (Naming.err_code Naming.NamingTooFewArguments) pos "Too few arguments"
1357 let naming_too_many_arguments pos =
1358 add (Naming.err_code Naming.NamingTooManyArguments) pos "Too many arguments"
1360 let expected_collection pos cn =
1362 (Naming.err_code Naming.ExpectedCollection)
1364 ("Unexpected collection type " ^ (strip_ns cn |> Markdown_lite.md_codify))
1366 let illegal_CLASS pos =
1368 (Naming.err_code Naming.IllegalClass)
1370 "Using `__CLASS__` outside a class or trait"
1372 let illegal_TRAIT pos =
1374 (Naming.err_code Naming.IllegalTrait)
1376 "Using `__TRAIT__` outside a trait"
1378 let lvar_in_obj_get pos =
1380 (Naming.err_code Naming.LvarInObjGet)
1382 "Dynamic method or attribute access is not allowed on a non-dynamic value."
1384 let nullsafe_property_write_context pos =
1386 (Typing.err_code Typing.NullsafePropertyWriteContext)
1388 "`?->` syntax not supported here, this function effectively does a write"
1390 let illegal_fun pos =
1391 let msg =
1392 "The argument to `fun()` must be a single-quoted, constant "
1393 ^ "literal string representing a valid function name."
1395 add (Naming.err_code Naming.IllegalFun) pos msg
1397 let illegal_member_variable_class pos =
1398 let msg =
1399 "Cannot declare a constant named `class`. The name `class` is reserved for the class constant that represents the name of the class"
1401 add (Naming.err_code Naming.IllegalMemberVariableClass) pos msg
1403 let illegal_meth_fun pos =
1404 let msg =
1405 "String argument to `fun()` contains `:`;"
1406 ^ " for static class methods, use"
1407 ^ " `class_meth(Cls::class, 'method_name')`, not `fun('Cls::method_name')`"
1409 add (Naming.err_code Naming.IllegalMethFun) pos msg
1411 let illegal_inst_meth pos =
1412 let msg =
1413 "The argument to `inst_meth()` must be an expression and a "
1414 ^ "constant literal string representing a valid method name."
1416 add (Naming.err_code Naming.IllegalInstMeth) pos msg
1418 let illegal_meth_caller pos =
1419 let msg =
1420 "The two arguments to `meth_caller()` must be:"
1421 ^ "\n - first: `ClassOrInterface::class`"
1422 ^ "\n - second: a single-quoted string literal containing the name"
1423 ^ " of a non-static method of that class"
1425 add (Naming.err_code Naming.IllegalMethCaller) pos msg
1427 let illegal_class_meth pos =
1428 let msg =
1429 "The two arguments to `class_meth()` must be:"
1430 ^ "\n - first: `ValidClassname::class`"
1431 ^ "\n - second: a single-quoted string literal containing the name"
1432 ^ " of a static method of that class"
1434 add (Naming.err_code Naming.IllegalClassMeth) pos msg
1436 let class_meth_non_final_self pos class_name =
1437 let msg =
1438 "`class_meth` with `self::class` does not preserve class calling context.\n"
1439 ^ "Use `static::class`, or `"
1440 ^ strip_ns class_name
1441 ^ "::class` explicitly"
1443 add (Naming.err_code Naming.ClassMethNonFinalSelf) pos msg
1445 let class_meth_non_final_CLASS pos is_trait class_name =
1446 let suggestion =
1447 if not is_trait then
1448 "Use `" ^ strip_ns class_name ^ "::class` explicitly"
1449 else
1452 let msg =
1453 "`class_meth` with `__CLASS__` in non-final classes is not allowed.\n"
1454 ^ suggestion
1456 add (Naming.err_code Naming.ClassMethNonFinalCLASS) pos msg
1458 let assert_banned pos =
1460 (Naming.err_code Naming.CallingAssert)
1462 "assert() is banned in Hack. Did you mean `invariant()`?"
1464 let unexpected_ty_in_tast pos ~actual_ty ~expected_ty =
1466 (Typing.err_code Typing.UnexpectedTy)
1468 ( "Unexpected type in TAST: expected "
1469 ^ Markdown_lite.md_codify expected_ty
1470 ^ ", got "
1471 ^ Markdown_lite.md_codify actual_ty )
1473 let uninstantiable_class usage_pos decl_pos name reason_msgl =
1474 let name = strip_ns name in
1475 let (claim, reasons) =
1476 ( (usage_pos, Markdown_lite.md_codify name ^ " is uninstantiable"),
1477 [(decl_pos, "Declaration is here")] )
1479 let (claim, reasons) =
1480 match reason_msgl with
1481 | (reason_pos, reason_str) :: tail ->
1482 let reasons = tail @ (claim :: reasons) in
1483 let claim = (reason_pos, reason_str ^ " which must be instantiable") in
1484 (claim, reasons)
1485 | [] -> (claim, reasons)
1487 add_list (Typing.err_code Typing.UninstantiableClass) claim reasons
1489 let new_abstract_record (pos, name) =
1490 let name = strip_ns name in
1492 (Typing.err_code Typing.NewAbstractRecord)
1494 (Printf.sprintf
1495 "Cannot create instance of abstract record %s"
1496 (Markdown_lite.md_codify name))
1498 let abstract_const_usage usage_pos decl_pos name =
1499 let name = strip_ns name in
1500 add_list
1501 (Typing.err_code Typing.AbstractConstUsage)
1502 ( usage_pos,
1503 "Cannot reference abstract constant "
1504 ^ Markdown_lite.md_codify name
1505 ^ " directly" )
1506 [(decl_pos, "Declaration is here")]
1508 let concrete_const_interface_override
1509 child_pos parent_pos parent_origin name (on_error : typing_error_callback) =
1510 let parent_origin = strip_ns parent_origin in
1511 on_error
1512 ~code:(Typing.err_code Typing.ConcreteConstInterfaceOverride)
1513 ( child_pos,
1514 "Non-abstract constants defined in an interface cannot be overridden when implementing or extending that interface."
1517 ( parent_pos,
1518 "You could make "
1519 ^ Markdown_lite.md_codify name
1520 ^ " abstract in "
1521 ^ Markdown_lite.md_codify parent_origin
1522 ^ "." );
1525 let const_without_typehint sid =
1526 let (pos, name) = sid in
1527 let msg =
1528 Printf.sprintf
1529 "Please add a type hint `const SomeType %s`"
1530 (Utils.strip_all_ns name)
1532 add (Naming.err_code Naming.AddATypehint) pos msg
1534 let prop_without_typehint visibility sid =
1535 let (pos, name) = sid in
1536 let msg =
1537 Printf.sprintf "Please add a type hint `%s SomeType %s`" visibility name
1539 add (Naming.err_code Naming.AddATypehint) pos msg
1541 let illegal_constant pos =
1542 add (Naming.err_code Naming.IllegalConstant) pos "Illegal constant value"
1544 let invalid_req_implements pos =
1546 (Naming.err_code Naming.InvalidReqImplements)
1548 "Only traits may use `require implements`"
1550 let invalid_req_extends pos =
1552 (Naming.err_code Naming.InvalidReqExtends)
1554 "Only traits and interfaces may use `require extends`"
1556 let did_you_mean_naming pos name suggest_pos suggest_name =
1557 let name = strip_ns name in
1558 let suggest_name = strip_ns suggest_name in
1559 add_list
1560 (Naming.err_code Naming.DidYouMeanNaming)
1561 (pos, "Could not find " ^ Markdown_lite.md_codify name ^ ".")
1562 [hint_message name suggest_name suggest_pos]
1564 let using_internal_class pos name =
1566 (Naming.err_code Naming.UsingInternalClass)
1568 ( Markdown_lite.md_codify name
1569 ^ " is an implementation internal class that cannot be used directly" )
1571 let too_few_type_arguments p =
1573 (Naming.err_code Naming.TooFewTypeArguments)
1575 "Too few type arguments for this type"
1577 let mk_method_needs_visibility pos =
1579 code = Naming.err_code Naming.MethodNeedsVisibility;
1580 claim =
1581 (pos, "Methods need to be marked `public`, `private`, or `protected`.");
1582 reasons = [];
1585 let method_needs_visibility pos = add_error (mk_method_needs_visibility pos)
1587 let dynamic_class_name_in_strict_mode pos =
1589 (Naming.err_code Naming.DynamicClassNameInStrictMode)
1591 "Cannot use dynamic class name in strict mode"
1593 let xhp_optional_required_attr pos id =
1595 (Naming.err_code Naming.XhpOptionalRequiredAttr)
1597 ( "XHP attribute "
1598 ^ Markdown_lite.md_codify id
1599 ^ " cannot be marked as nullable and `@required`" )
1601 let xhp_required_with_default pos id =
1603 (Naming.err_code Naming.XhpRequiredWithDefault)
1605 ( "XHP attribute "
1606 ^ Markdown_lite.md_codify id
1607 ^ " cannot be marked `@required` and provide a default" )
1609 let array_typehints_disallowed pos =
1611 (Naming.err_code Naming.ArrayTypehintsDisallowed)
1613 "Array typehints are no longer legal; use `varray` or `darray` instead"
1615 let wildcard_hint_disallowed pos =
1617 (Naming.err_code Naming.WildcardHintDisallowed)
1619 "Wildcard typehints are not allowed in this position"
1621 let wildcard_param_disallowed pos =
1623 (Naming.err_code Naming.WildcardTypeParamDisallowed)
1625 "Cannot use anonymous type parameter in this position."
1627 let misplaced_mutability_hint pos =
1629 (Naming.err_code Naming.MisplacedMutabilityHint)
1631 "Setting mutability via type hints is only allowed for parameters of reactive function types. For other cases consider using attributes."
1633 let mutability_hint_in_non_rx_function pos =
1635 (Naming.err_code Naming.MutabilityHintInNonRx)
1637 "Parameter with mutability hint cannot appear in non-reactive function type."
1639 let invalid_mutability_in_return_type_hint pos =
1641 (Naming.err_code Naming.InvalidReturnMutableHint)
1643 "`OwnedMutable` is the only mutability related hint allowed in return type annotation for reactive function types."
1645 let illegal_use_of_dynamically_callable attr_pos meth_pos visibility =
1646 add_list
1647 (Naming.err_code Naming.IllegalUseOfDynamicallyCallable)
1648 (attr_pos, "`__DynamicallyCallable` can only be used on public methods")
1650 ( meth_pos,
1651 sprintf "But this method is %s" (Markdown_lite.md_codify visibility) );
1654 let dynamically_callable_reified attr_pos =
1656 (NastCheck.err_code NastCheck.DynamicallyCallableReified)
1657 attr_pos
1658 "`__DynamicallyCallable` cannot be used on reified functions or methods"
1660 let parent_in_function_pointer pos parento meth_name =
1661 let suggestion =
1662 match parento with
1663 | None -> "Consider using the name of the parent class explicitly."
1664 | Some id ->
1665 let name = Markdown_lite.md_codify (strip_ns id ^ "::" ^ meth_name) in
1666 "Consider using " ^ name ^ " instead"
1669 (Naming.err_code Naming.ParentInFunctionPointer)
1671 ( "Cannot use `parent::` in a function pointer due to class context ambiguity. "
1672 ^ suggestion )
1674 let self_in_non_final_function_pointer pos cido meth_name =
1675 let suggestion =
1676 match cido with
1677 | None -> ""
1678 | Some id ->
1679 let name = Markdown_lite.md_codify (strip_ns id ^ "::" ^ meth_name) in
1680 "Consider using " ^ name ^ " instead"
1683 (Naming.err_code Naming.SelfInNonFinalFunctionPointer)
1685 ( "Cannot use `self::` in a function pointer in a non-final class due to class context ambiguity. "
1686 ^ suggestion )
1688 (*****************************************************************************)
1689 (* Init check errors *)
1690 (*****************************************************************************)
1692 let no_construct_parent pos =
1694 (NastCheck.err_code NastCheck.NoConstructParent)
1696 (Utils.sl
1698 "You are extending a class that needs to be initialized\n";
1699 "Make sure you call `parent::__construct`.\n";
1702 let nonstatic_method_in_abstract_final_class pos =
1704 (NastCheck.err_code NastCheck.NonstaticMethodInAbstractFinalClass)
1706 "Abstract final classes cannot have nonstatic methods or constructors."
1708 let constructor_required (pos, name) prop_names =
1709 let name = strip_ns name in
1710 let props_str =
1711 List.map ~f:Markdown_lite.md_codify prop_names |> String.concat ~sep:" "
1714 (NastCheck.err_code NastCheck.ConstructorRequired)
1716 ( "Lacking `__construct`, class "
1717 ^ Markdown_lite.md_codify name
1718 ^ " does not initialize its private member(s): "
1719 ^ props_str )
1721 let not_initialized (pos, cname) props =
1722 let cname = strip_ns cname in
1723 let prop_msgs =
1724 List.map props ~f:(fun (pos, prop) ->
1725 ( pos,
1726 Markdown_lite.md_codify ("$this->" ^ prop) ^ " is not initialized." ))
1728 add_list
1729 (NastCheck.err_code NastCheck.NotInitialized)
1730 ( pos,
1731 "Class "
1732 ^ Markdown_lite.md_codify cname
1733 ^ " has properties that cannot be null and aren't always set in `__construct`."
1735 prop_msgs
1737 let call_before_init pos cv =
1739 (NastCheck.err_code NastCheck.CallBeforeInit)
1741 (Utils.sl
1743 "Until the initialization of `$this` is over,";
1744 " you can only call private methods\n";
1745 "The initialization is not over because ";
1748 if String.equal cv "parent::__construct" then
1749 ["you forgot to call `parent::__construct`"]
1750 else
1752 Markdown_lite.md_codify ("$this->" ^ cv);
1753 " can still potentially be null";
1754 ] ))
1756 (*****************************************************************************)
1757 (* Nast errors check *)
1758 (*****************************************************************************)
1760 let type_arity use_pos def_pos ~expected ~actual =
1761 add_list
1762 (Typing.err_code Typing.TypeArityMismatch)
1763 ( use_pos,
1764 Printf.sprintf
1765 "Wrong number of type arguments (expected %d, got %d)"
1766 expected
1767 actual )
1768 [(def_pos, "Definition is here")]
1770 let abstract_with_body (p, _) =
1772 (NastCheck.err_code NastCheck.AbstractWithBody)
1774 "This method is declared as abstract, but has a body"
1776 let not_abstract_without_body (p, _) =
1778 (NastCheck.err_code NastCheck.NotAbstractWithoutBody)
1780 "This method is not declared as abstract, it must have a body"
1782 let mk_not_abstract_without_typeconst (p, _) =
1784 code = NastCheck.err_code NastCheck.NotAbstractWithoutTypeconst;
1785 claim =
1786 ( p,
1787 "This type constant is not declared as abstract, it must have"
1788 ^ " an assigned type" );
1789 reasons = [];
1792 let not_abstract_without_typeconst node =
1793 add_error (mk_not_abstract_without_typeconst node)
1795 let typeconst_depends_on_external_tparam pos ext_pos ext_name =
1796 add_list
1797 (NastCheck.err_code NastCheck.TypeconstDependsOnExternalTparam)
1798 ( pos,
1799 "A type constant can only use type parameters declared in its own"
1800 ^ " type parameter list" )
1802 ( ext_pos,
1803 Markdown_lite.md_codify ext_name
1804 ^ " was declared as a type parameter here" );
1807 let interface_with_partial_typeconst tconst_pos =
1809 (NastCheck.err_code NastCheck.InterfaceWithPartialTypeconst)
1810 tconst_pos
1811 "An interface cannot contain a partially abstract type constant"
1813 let mk_multiple_xhp_category pos =
1815 code = NastCheck.err_code NastCheck.MultipleXhpCategory;
1816 claim = (pos, "XHP classes can only contain one category declaration");
1817 reasons = [];
1820 let multiple_xhp_category pos = add_error (mk_multiple_xhp_category pos)
1822 let return_in_gen p =
1824 (NastCheck.err_code NastCheck.ReturnInGen)
1826 ( "You cannot return a value in a generator (a generator"
1827 ^ " is a function that uses `yield`)" )
1829 let return_in_finally p =
1831 (NastCheck.err_code NastCheck.ReturnInFinally)
1833 ( "Don't use `return` in a `finally` block;"
1834 ^ " there's nothing to receive the return value" )
1836 let toplevel_break p =
1838 (NastCheck.err_code NastCheck.ToplevelBreak)
1840 "`break` can only be used inside loops or `switch` statements"
1842 let toplevel_continue p =
1844 (NastCheck.err_code NastCheck.ToplevelContinue)
1846 "`continue` can only be used inside loops"
1848 let continue_in_switch p =
1850 (NastCheck.err_code NastCheck.ContinueInSwitch)
1852 ( "In PHP, `continue;` inside a switch statement is equivalent to `break;`."
1853 ^ " Hack does not support this; use `break` if that is what you meant." )
1855 let await_in_sync_function p =
1857 (NastCheck.err_code NastCheck.AwaitInSyncFunction)
1859 "`await` can only be used inside `async` functions"
1861 let interface_use_trait p =
1863 (NastCheck.err_code NastCheck.InterfaceUsesTrait)
1865 "Interfaces cannot use traits"
1867 let static_memoized_function p =
1869 (NastCheck.err_code NastCheck.StaticMemoizedFunction)
1871 "`memoize` is not allowed on static methods in classes that aren't final "
1873 let magic (p, s) =
1875 (NastCheck.err_code NastCheck.Magic)
1877 ( Markdown_lite.md_codify s
1878 ^ " is a magic method and cannot be called directly" )
1880 let non_interface (p : Pos.t) (c2 : string) (verb : string) : 'a =
1882 (NastCheck.err_code NastCheck.NonInterface)
1884 ( "Cannot "
1885 ^ verb
1886 ^ " "
1887 ^ (strip_ns c2 |> Markdown_lite.md_codify)
1888 ^ " - it is not an interface" )
1890 let toString_returns_string pos =
1892 (NastCheck.err_code NastCheck.ToStringReturnsString)
1894 "`__toString` should return a string"
1896 let toString_visibility pos =
1898 (NastCheck.err_code NastCheck.ToStringVisibility)
1900 "`__toString` must have public visibility and cannot be static"
1902 let uses_non_trait (p : Pos.t) (n : string) (t : string) =
1904 (NastCheck.err_code NastCheck.UsesNonTrait)
1906 ( (strip_ns n |> Markdown_lite.md_codify)
1907 ^ " is not a trait. It is "
1909 ^ "." )
1911 let requires_non_class (p : Pos.t) (n : string) (t : string) =
1913 (NastCheck.err_code NastCheck.RequiresNonClass)
1915 ( (strip_ns n |> Markdown_lite.md_codify)
1916 ^ " is not a class. It is "
1918 ^ "." )
1920 let requires_final_class (p : Pos.t) (n : string) =
1922 (NastCheck.err_code NastCheck.RequiresFinalClass)
1924 ((strip_ns n |> Markdown_lite.md_codify) ^ " is not an extendable class.")
1926 let abstract_body pos =
1928 (NastCheck.err_code NastCheck.AbstractBody)
1930 "This method shouldn't have a body"
1932 let interface_with_member_variable pos =
1934 (NastCheck.err_code NastCheck.InterfaceWithMemberVariable)
1936 "Interfaces cannot have member variables"
1938 let interface_with_static_member_variable pos =
1940 (NastCheck.err_code NastCheck.InterfaceWithStaticMemberVariable)
1942 "Interfaces cannot have static variables"
1944 let illegal_function_name pos mname =
1946 (NastCheck.err_code NastCheck.IllegalFunctionName)
1948 ("Illegal function name: " ^ (strip_ns mname |> Markdown_lite.md_codify))
1950 let conflicting_mutable_and_maybe_mutable_attributes pos =
1952 (NastCheck.err_code NastCheck.ConflictingMutableAndMaybeMutableAttributes)
1954 "Declaration cannot have both `<<__Mutable>>` and `<<__MaybeMutable>>` attributes."
1956 let mutable_methods_must_be_reactive pos name =
1958 (NastCheck.err_code NastCheck.MutableMethodsMustBeReactive)
1960 ( "The method "
1961 ^ (strip_ns name |> Markdown_lite.md_codify)
1962 ^ " has a mutable parameter"
1963 ^ " (or mutable `this`), so it must be marked reactive with `<<__Rx>>`." )
1965 let mutable_return_annotated_decls_must_be_reactive kind pos name =
1967 (NastCheck.err_code NastCheck.MutableReturnAnnotatedDeclsMustBeReactive)
1969 ( "The "
1970 ^ kind
1971 ^ " "
1972 ^ (strip_ns name |> Markdown_lite.md_codify)
1973 ^ " is annotated with `<<__MutableReturn>>`, "
1974 ^ " so it must be marked reactive with `<<__Rx>>`." )
1976 let maybe_mutable_methods_must_be_reactive pos name =
1978 (NastCheck.err_code NastCheck.MaybeMutableMethodsMustBeReactive)
1980 ( "The method "
1981 ^ (strip_ns name |> Markdown_lite.md_codify)
1982 ^ " is annotated with `<<__MaybeMutable>>` attribute, or has this attribute on one of its parameters so it must be marked reactive."
1985 let entrypoint_arguments pos =
1987 (NastCheck.err_code NastCheck.EntryPointArguments)
1989 "`__EntryPoint` functions cannot take arguments."
1991 let variadic_memoize pos =
1993 (NastCheck.err_code NastCheck.VariadicMemoize)
1995 "Memoized functions cannot be variadic."
1997 let abstract_method_memoize pos =
1999 (NastCheck.err_code NastCheck.AbstractMethodMemoize)
2001 "Abstract methods cannot be memoized."
2003 let instance_property_in_abstract_final_class pos =
2005 (NastCheck.err_code NastCheck.InstancePropertyInAbstractFinalClass)
2007 "Abstract final classes cannot have instance properties."
2009 let inout_params_special pos =
2011 (NastCheck.err_code NastCheck.InoutParamsSpecial)
2013 "Methods with special semantics cannot have `inout` parameters."
2015 let inout_params_memoize fpos pos =
2016 let msg1 = (fpos, "Functions with `inout` parameters cannot be memoized") in
2017 let msg2 = (pos, "This is an `inout` parameter") in
2018 add_list (NastCheck.err_code NastCheck.InoutParamsMemoize) msg1 [msg2]
2020 let reading_from_append pos =
2022 (NastCheck.err_code NastCheck.ReadingFromAppend)
2024 "Cannot use `[]` for reading"
2026 let inout_argument_bad_expr pos =
2028 (NastCheck.err_code NastCheck.InoutArgumentBadExpr)
2030 ( "Arguments for `inout` parameters must be local variables or simple "
2031 ^ "subscript expressions on vecs, dicts, keysets, or arrays" )
2033 let illegal_destructor pos =
2035 (NastCheck.err_code NastCheck.IllegalDestructor)
2037 ( "Destructors are not supported in Hack; use other patterns like "
2038 ^ "`IDisposable`/`using` or `try`/`catch` instead." )
2040 let multiple_conditionally_reactive_annotations pos name =
2042 (NastCheck.err_code NastCheck.MultipleConditionallyReactiveAnnotations)
2044 ( "Method '"
2045 ^ Markdown_lite.md_codify name
2046 ^ "' has multiple `<<__OnlyRxIfImpl>>` annotations." )
2048 let rx_is_enabled_invalid_location pos =
2050 (NastCheck.err_code NastCheck.RxIsEnabledInvalidLocation)
2052 ( "`HH\\Rx\\IS_ENABLED` must be the only condition in an if-statement, "
2053 ^ "and that if-statement must be the only statement in the function body."
2056 let atmost_rx_as_rxfunc_invalid_location pos =
2058 (NastCheck.err_code NastCheck.MaybeRxInvalidLocation)
2060 ( "`<<__AtMostRxAsFunc>>` attribute can only be put on parameters of conditionally reactive functions "
2061 ^ "or methods annotated with `<<__AtMostRxAsArgs>>` attribute." )
2063 let no_atmost_rx_as_rxfunc_for_rx_if_args pos =
2065 (NastCheck.err_code NastCheck.NoOnlyrxIfRxfuncForRxIfArgs)
2067 ( "Function or method annotated with `<<__AtMostRxAsArgs>>` attribute should have at least one parameter "
2068 ^ "with `<<__AtMostRxAsFunc>>` or `<<__OnlyRxIfImpl>>` annotations." )
2070 let conditionally_reactive_annotation_invalid_arguments ~is_method pos =
2071 let loc =
2072 if is_method then
2073 "Method"
2074 else
2075 "Parameter"
2078 (NastCheck.err_code
2079 NastCheck.ConditionallyReactiveAnnotationInvalidArguments)
2081 ( loc
2082 ^ " is marked with `<<__OnlyRxIfImpl>>` attribute that have "
2083 ^ "invalid arguments. This attribute must have one argument and it should be the "
2084 ^ "`::class` class constant." )
2086 let switch_non_terminal_default pos =
2088 (NastCheck.err_code NastCheck.SwitchNonTerminalDefault)
2090 "Default case in `switch` must be terminal"
2092 let switch_multiple_default pos =
2094 (NastCheck.err_code NastCheck.SwitchMultipleDefault)
2096 "There can be only one `default` case in `switch`"
2098 (*****************************************************************************)
2099 (* Nast terminality *)
2100 (*****************************************************************************)
2102 let case_fallthrough pos1 pos2 =
2103 add_list
2104 (NastCheck.err_code NastCheck.CaseFallthrough)
2105 ( pos1,
2106 "This `switch` has a `case` that implicitly falls through and is "
2107 ^ "not annotated with `// FALLTHROUGH`" )
2109 ( pos2,
2110 "This `case` implicitly falls through. Did you forget to add `break` or `return`?"
2114 let default_fallthrough pos =
2116 (NastCheck.err_code NastCheck.DefaultFallthrough)
2118 ( "This `switch` has a default case that implicitly falls "
2119 ^ "through and is not annotated with `// FALLTHROUGH`" )
2121 (*****************************************************************************)
2122 (* Typing errors *)
2123 (*****************************************************************************)
2125 let visibility_extends
2126 vis pos parent_pos parent_vis (on_error : typing_error_callback) =
2127 let msg1 =
2128 (pos, "This member visibility is: " ^ Markdown_lite.md_codify vis)
2130 let msg2 =
2131 (parent_pos, Markdown_lite.md_codify parent_vis ^ " was expected")
2133 on_error ~code:(Typing.err_code Typing.VisibilityExtends) msg1 [msg2]
2135 let member_not_implemented member_name parent_pos pos defn_pos =
2136 let msg1 =
2137 ( pos,
2138 "This type doesn't implement the method "
2139 ^ Markdown_lite.md_codify member_name )
2141 let msg2 = (parent_pos, "Which is required by this interface") in
2142 let msg3 = (defn_pos, "As defined here") in
2143 add_list (Typing.err_code Typing.MemberNotImplemented) msg1 [msg2; msg3]
2145 let bad_decl_override parent_pos parent_name pos name msgl =
2146 let msg1 =
2147 ( pos,
2148 "Class "
2149 ^ (strip_ns name |> Markdown_lite.md_codify)
2150 ^ " does not correctly implement all required members " )
2152 let msg2 =
2153 ( parent_pos,
2154 "Some members are incompatible with those declared in type "
2155 ^ (strip_ns parent_name |> Markdown_lite.md_codify) )
2157 (* This is a cascading error message *)
2158 add_list (Typing.err_code Typing.BadDeclOverride) msg1 (msg2 :: msgl)
2160 let bad_method_override pos member_name msgl (on_error : typing_error_callback)
2162 let msg =
2163 ( pos,
2164 "The method "
2165 ^ (strip_ns member_name |> Markdown_lite.md_codify)
2166 ^ " is not compatible with the overridden method" )
2168 (* This is a cascading error message *)
2169 on_error ~code:(Typing.err_code Typing.BadMethodOverride) msg msgl
2171 let bad_prop_override pos member_name msgl (on_error : typing_error_callback) =
2172 let msg =
2173 ( pos,
2174 "The property "
2175 ^ (strip_ns member_name |> Markdown_lite.md_codify)
2176 ^ " has the wrong type" )
2178 (* This is a cascading error message *)
2179 on_error ~code:(Typing.err_code Typing.BadMethodOverride) msg msgl
2181 let bad_enum_decl pos msgl =
2182 let msg = (pos, "This enum declaration is invalid.") in
2183 (* This is a cascading error message *)
2184 add_list (Typing.err_code Typing.BadEnumExtends) msg msgl
2186 let missing_constructor pos (on_error : typing_error_callback) =
2187 on_error
2188 ~code:(Typing.err_code Typing.MissingConstructor)
2189 (pos, "The constructor is not implemented")
2192 let typedef_trail_entry pos = (pos, "Typedef definition comes from here")
2194 let abstract_tconst_not_allowed pos (p, tconst_name) =
2195 add_list
2196 (Typing.err_code Typing.AbstractTconstNotAllowed)
2197 (pos, "An abstract type constant is not allowed in this position.")
2199 ( p,
2200 Printf.sprintf
2201 "%s is abstract here."
2202 (Markdown_lite.md_codify tconst_name) );
2205 let add_with_trail code claim reasons trail =
2206 add_list code claim (reasons @ List.map trail typedef_trail_entry)
2208 let enum_constant_type_bad pos ty_pos ty trail =
2209 add_with_trail
2210 (Typing.err_code Typing.EnumConstantTypeBad)
2211 (pos, "Enum constants must be an `int` or `string`")
2212 [(ty_pos, "Not " ^ Markdown_lite.md_codify ty)]
2213 trail
2215 let enum_type_bad pos ty_dependent ty trail =
2216 let ty = Markdown_lite.md_codify ty in
2217 let msg =
2218 if ty_dependent then
2219 "Invalid base type for an enum class: "
2220 else
2221 "Enums must be `int` or `string` or `arraykey`, not "
2223 add_with_trail (Typing.err_code Typing.EnumTypeBad) (pos, msg ^ ty) [] trail
2225 let enum_type_typedef_nonnull pos =
2227 (Typing.err_code Typing.EnumTypeTypedefNonnull)
2229 "Can't use `typedef` that resolves to nonnull in enum"
2231 let enum_switch_redundant const first_pos second_pos =
2232 add_list
2233 (Typing.err_code Typing.EnumSwitchRedundant)
2234 (second_pos, "Redundant `case` statement")
2235 [(first_pos, Markdown_lite.md_codify const ^ " already handled here")]
2237 let enum_switch_nonexhaustive pos missing enum_pos =
2238 add_list
2239 (Typing.err_code Typing.EnumSwitchNonexhaustive)
2240 ( pos,
2241 "`switch` statement nonexhaustive; the following cases are missing: "
2242 ^ (List.map ~f:Markdown_lite.md_codify missing |> String.concat ~sep:", ")
2244 [(enum_pos, "Enum declared here")]
2246 let enum_switch_redundant_default pos enum_pos =
2247 add_list
2248 (Typing.err_code Typing.EnumSwitchRedundantDefault)
2249 ( pos,
2250 "All cases already covered; a redundant `default` case prevents "
2251 ^ "detecting future errors. If your goal is to guard against "
2252 ^ "invalid values for this type, do an `is` check before the switch." )
2253 [(enum_pos, "Enum declared here")]
2255 let enum_switch_not_const pos =
2257 (Typing.err_code Typing.EnumSwitchNotConst)
2259 "Case in `switch` on enum is not an enum constant"
2261 let enum_switch_wrong_class pos expected got =
2263 (Typing.err_code Typing.EnumSwitchWrongClass)
2265 ( "Switching on enum "
2266 ^ Markdown_lite.md_codify expected
2267 ^ " but using constant from "
2268 ^ Markdown_lite.md_codify got )
2270 let invalid_shape_field_name p =
2272 (Typing.err_code Typing.InvalidShapeFieldName)
2274 "Was expecting a constant string, class constant, or int (for shape access)"
2276 let invalid_shape_field_name_empty p =
2278 (Typing.err_code Typing.InvalidShapeFieldNameEmpty)
2280 "A shape field name cannot be an empty string"
2282 let invalid_shape_field_type pos ty_pos ty trail =
2283 add_with_trail
2284 (Typing.err_code Typing.InvalidShapeFieldType)
2285 (pos, "A shape field name must be an `int` or `string`")
2286 [(ty_pos, "Not " ^ ty)]
2287 trail
2289 let invalid_shape_field_literal key_pos witness_pos =
2290 add_list
2291 (Typing.err_code Typing.InvalidShapeFieldLiteral)
2292 (key_pos, "Shape uses literal string as field name")
2293 [(witness_pos, "But expected a class constant")]
2295 let invalid_shape_field_const key_pos witness_pos =
2296 add_list
2297 (Typing.err_code Typing.InvalidShapeFieldConst)
2298 (key_pos, "Shape uses class constant as field name")
2299 [(witness_pos, "But expected a literal string")]
2301 let shape_field_class_mismatch key_pos witness_pos key_class witness_class =
2302 add_list
2303 (Typing.err_code Typing.ShapeFieldClassMismatch)
2304 ( key_pos,
2305 "Shape field name is class constant from "
2306 ^ Markdown_lite.md_codify key_class )
2308 ( witness_pos,
2309 "But expected constant from " ^ Markdown_lite.md_codify witness_class );
2312 let shape_field_type_mismatch key_pos witness_pos key_ty witness_ty =
2313 add_list
2314 (Typing.err_code Typing.ShapeFieldTypeMismatch)
2315 (key_pos, "Shape field name is " ^ key_ty ^ " class constant")
2316 [(witness_pos, "But expected " ^ witness_ty)]
2318 let missing_field pos1 pos2 name (on_error : typing_error_callback) =
2319 on_error
2320 ~code:(Typing.err_code Typing.MissingField)
2321 (pos1, "The field " ^ Markdown_lite.md_codify name ^ " is missing")
2322 [(pos2, "The field " ^ Markdown_lite.md_codify name ^ " is defined")]
2324 let shape_fields_unknown pos1 pos2 (on_error : typing_error_callback) =
2325 on_error
2326 ~code:(Typing.err_code Typing.ShapeFieldsUnknown)
2327 ( pos1,
2328 "This shape type allows unknown fields, and so it may contain fields other than those explicitly declared in its declaration."
2331 ( pos2,
2332 "It is incompatible with a shape that does not allow unknown fields." );
2335 let invalid_shape_remove_key p =
2337 (Typing.err_code Typing.InvalidShapeRemoveKey)
2339 "You can only unset fields of **local** variables"
2341 let unification_cycle pos ty =
2342 add_list
2343 (Typing.err_code Typing.UnificationCycle)
2344 ( pos,
2345 "Type circularity: in order to type-check this expression it "
2346 ^ "is necessary for a type [rec] to be equal to type "
2347 ^ Markdown_lite.md_codify ty )
2350 let violated_constraint
2351 p_cstr (p_tparam, tparam) left right (on_error : typing_error_callback) =
2352 on_error
2353 ~code:(Typing.err_code Typing.TypeConstraintViolation)
2354 (p_cstr, "Some type constraint(s) are violated here")
2356 ( p_tparam,
2357 Printf.sprintf
2358 "%s is a constrained type parameter"
2359 (Markdown_lite.md_codify tparam) );
2361 @ left
2362 @ right )
2364 let method_variance pos =
2366 (Typing.err_code Typing.MethodVariance)
2368 "Covariance or contravariance is not allowed in type parameter of method or function."
2370 let explain_constraint ~use_pos ~definition_pos ~param_name claim reasons =
2371 let inst_msg = "Some type constraint(s) here are violated" in
2372 (* There may be multiple constraints instantiated at one spot; avoid
2373 * duplicating the instantiation message *)
2374 let (p, msg) = claim in
2375 let msgl =
2376 if String.equal msg inst_msg && Pos.equal p use_pos then
2377 reasons
2378 else
2379 claim :: reasons
2381 let name = strip_ns param_name in
2382 add_list
2383 (Typing.err_code Typing.TypeConstraintViolation)
2384 (use_pos, inst_msg)
2385 ( ( definition_pos,
2386 Markdown_lite.md_codify name ^ " is a constrained type parameter" )
2387 :: msgl )
2389 let explain_where_constraint ~in_class ~use_pos ~definition_pos claim reasons =
2390 let callsite_ty =
2391 if in_class then
2392 "class"
2393 else
2394 "method"
2396 let definition_head =
2397 Printf.sprintf "This is the %s with `where` type constraints" callsite_ty
2399 let inst_msg = "A `where` type constraint is violated here" in
2400 add_list
2401 (Typing.err_code Typing.TypeConstraintViolation)
2402 (use_pos, inst_msg)
2403 ([(definition_pos, definition_head)] @ (claim :: reasons))
2405 let explain_tconst_where_constraint ~use_pos ~definition_pos msgl =
2406 let inst_msg = "A `where` type constraint is violated here" in
2407 add_list
2408 (Typing.err_code Typing.TypeConstraintViolation)
2409 (use_pos, inst_msg)
2411 ( definition_pos,
2412 "This method's `where` constraints contain a generic type access" );
2414 @ msgl )
2416 let format_string pos snippet s class_pos fname class_suggest =
2417 add_list
2418 (Typing.err_code Typing.FormatString)
2419 ( pos,
2420 "Invalid format string "
2421 ^ Markdown_lite.md_codify snippet
2422 ^ " in "
2423 ^ Markdown_lite.md_codify ("\"" ^ s ^ "\"") )
2425 ( class_pos,
2426 "You can add a new format specifier by adding "
2427 ^ Markdown_lite.md_codify (fname ^ "()")
2428 ^ " to "
2429 ^ Markdown_lite.md_codify class_suggest );
2432 let expected_literal_format_string pos =
2434 (Typing.err_code Typing.ExpectedLiteralFormatString)
2436 "This argument must be a literal format string"
2438 let re_prefixed_non_string pos non_strings =
2440 (Typing.err_code Typing.RePrefixedNonString)
2442 (non_strings ^ " are not allowed to be to be `re`-prefixed")
2444 let bad_regex_pattern pos s =
2446 (Typing.err_code Typing.BadRegexPattern)
2448 ("Bad regex pattern; " ^ s ^ ".")
2450 let generic_array_strict p =
2452 (Typing.err_code Typing.GenericArrayStrict)
2454 "You cannot have an array without generics in strict mode"
2456 let option_return_only_typehint p kind =
2457 let (typehint, reason) =
2458 match kind with
2459 | `void -> ("?void", "only return implicitly")
2460 | `noreturn -> ("?noreturn", "never return")
2463 (Typing.err_code Typing.OptionReturnOnlyTypehint)
2465 ( Markdown_lite.md_codify typehint
2466 ^ " is a nonsensical typehint; a function cannot both "
2467 ^ reason
2468 ^ " and return null." )
2470 let tuple_syntax p =
2472 (Typing.err_code Typing.TupleSyntax)
2474 "Did you want a *tuple*? Try `(X,Y)`, not `tuple<X,Y>`"
2476 let redeclaring_missing_method p trait_method =
2478 (Typing.err_code Typing.RedeclaringMissingMethod)
2480 ( "Attempting to redeclare a trait method "
2481 ^ Markdown_lite.md_codify trait_method
2482 ^ " which was never inherited. "
2483 ^ "You might be trying to redeclare a non-static method as `static` or vice-versa."
2486 let expecting_type_hint p =
2487 add (Typing.err_code Typing.ExpectingTypeHint) p "Was expecting a type hint"
2489 let expecting_type_hint_variadic p =
2491 (Typing.err_code Typing.ExpectingTypeHintVariadic)
2493 "Was expecting a type hint on this variadic parameter"
2495 let expecting_return_type_hint p =
2497 (Typing.err_code Typing.ExpectingReturnTypeHint)
2499 "Was expecting a return type hint"
2501 let duplicate_using_var pos =
2503 (Typing.err_code Typing.DuplicateUsingVar)
2505 "Local variable already used in `using` statement"
2507 let illegal_disposable pos verb =
2509 (Typing.err_code Typing.IllegalDisposable)
2511 ("Disposable objects must only be " ^ verb ^ " in a `using` statement")
2513 let escaping_disposable pos =
2515 (Typing.err_code Typing.EscapingDisposable)
2517 ( "Variable from `using` clause may only be used as receiver in method invocation "
2518 ^ "or passed to function with `<<__AcceptDisposable>>` parameter attribute"
2521 let escaping_disposable_parameter pos =
2523 (Typing.err_code Typing.EscapingDisposableParameter)
2525 ( "Parameter with `<<__AcceptDisposable>>` attribute may only be used as receiver in method invocation "
2526 ^ "or passed to another function with `<<__AcceptDisposable>>` parameter attribute"
2529 let escaping_this pos =
2531 (Typing.err_code Typing.EscapingThis)
2533 ( "`$this` implementing `IDisposable` or `IAsyncDisposable` may only be used as receiver in method invocation "
2534 ^ "or passed to another function with `<<__AcceptDisposable>>` parameter attribute"
2537 let escaping_mutable_object pos =
2539 (Typing.err_code Typing.EscapingMutableObject)
2541 "Neither a `Mutable` nor `MaybeMutable` object may be captured by an anonymous function."
2543 let must_extend_disposable pos =
2545 (Typing.err_code Typing.MustExtendDisposable)
2547 "A disposable type may not extend a class or use a trait that is not disposable"
2549 let accept_disposable_invariant pos1 pos2 (on_error : typing_error_callback) =
2550 let msg1 = (pos1, "This parameter is marked `<<__AcceptDisposable>>`") in
2551 let msg2 = (pos2, "This parameter is not marked `<<__AcceptDisposable>>`") in
2552 on_error ~code:(Typing.err_code Typing.AcceptDisposableInvariant) msg1 [msg2]
2554 let ifc_external_contravariant pos1 pos2 (on_error : typing_error_callback) =
2555 let msg1 =
2556 ( pos1,
2557 "Parameters with `<<__External>>` must be overridden by other parameters with <<__External>>. This parameter is marked `<<__External>>`"
2560 let msg2 = (pos2, "But this parameter is not marked `<<__External>>`") in
2561 on_error ~code:(Typing.err_code Typing.IFCExternalContravariant) msg1 [msg2]
2563 let field_kinds pos1 pos2 =
2564 add_list
2565 (Typing.err_code Typing.FieldKinds)
2566 (pos1, "You cannot use this kind of field (value)")
2567 [(pos2, "Mixed with this kind of field (key => value)")]
2569 let unbound_name_typing pos name =
2571 (Typing.err_code Typing.UnboundNameTyping)
2573 ("Unbound name (typing): " ^ Markdown_lite.md_codify (strip_ns name))
2575 let unbound_name_type_constant_access ~access_pos ~name_pos name =
2576 add_list
2577 (Typing.err_code Typing.UnboundNameTypeConstantAccess)
2578 ( access_pos,
2579 "Unbound name "
2580 ^ Markdown_lite.md_codify (strip_ns name)
2581 ^ " in type constant access" )
2582 ( []
2584 if Pos.equal name_pos access_pos then
2586 else
2587 [(name_pos, "Unbound name is here")] )
2589 let previous_default p =
2591 (Typing.err_code Typing.PreviousDefault)
2593 ( "A previous parameter has a default value.\n"
2594 ^ "Remove all the default values for the preceding parameters,\n"
2595 ^ "or add a default value to this one." )
2597 let return_only_typehint p kind =
2598 let msg =
2599 match kind with
2600 | `void -> "void"
2601 | `noreturn -> "noreturn"
2604 (Naming.err_code Naming.ReturnOnlyTypehint)
2606 ( "The "
2607 ^ Markdown_lite.md_codify msg
2608 ^ " typehint can only be used to describe a function return type" )
2610 let unexpected_type_arguments p =
2612 (Naming.err_code Naming.UnexpectedTypeArguments)
2614 "Type arguments are not expected for this type"
2616 let too_many_type_arguments p =
2618 (Naming.err_code Naming.TooManyTypeArguments)
2620 "Too many type arguments for this type"
2622 let return_in_void pos1 pos2 =
2623 add_list
2624 (Typing.err_code Typing.ReturnInVoid)
2625 (pos1, "You cannot return a value")
2626 [(pos2, "This is a `void` function")]
2628 let this_var_outside_class p =
2630 (Typing.err_code Typing.ThisVarOutsideClass)
2632 "Can't use `$this` outside of a class"
2634 let unbound_global cst_pos =
2636 (Typing.err_code Typing.UnboundGlobal)
2637 cst_pos
2638 "Unbound global constant (Typing)"
2640 let private_inst_meth ~def_pos ~use_pos =
2641 add_list
2642 (Typing.err_code Typing.PrivateInstMeth)
2643 ( use_pos,
2644 "You cannot use this method with `inst_meth` (whether you are in the same class or not)."
2646 [(def_pos, "It is declared as `private` here")]
2648 let protected_inst_meth ~def_pos ~use_pos =
2649 add_list
2650 (Typing.err_code Typing.ProtectedInstMeth)
2651 ( use_pos,
2652 "You cannot use this method with `inst_meth` (whether you are in the same class hierarchy or not)."
2654 [(def_pos, "It is declared as `protected` here")]
2656 let private_class_meth ~def_pos ~use_pos =
2657 add_list
2658 (Typing.err_code Typing.PrivateClassMeth)
2659 ( use_pos,
2660 "You cannot use this method with `class_meth` (whether you are in the same class or not)."
2662 [(def_pos, "It is declared as `private` here")]
2664 let protected_class_meth ~def_pos ~use_pos =
2665 add_list
2666 (Typing.err_code Typing.ProtectedClassMeth)
2667 ( use_pos,
2668 "You cannot use this method with `class_meth` (whether you are in the same class hierarchy or not)."
2670 [(def_pos, "It is declared as `protected` here")]
2672 let array_cast pos =
2674 (Typing.err_code Typing.ArrayCast)
2676 "(array) cast forbidden; arrays with unspecified key and value types are not allowed"
2678 let string_cast pos ty =
2679 add (Typing.err_code Typing.StringCast) pos
2680 @@ Printf.sprintf
2681 "Cannot cast a value of type %s to string. Only primitives may be used in a `(string)` cast."
2682 (Markdown_lite.md_codify ty)
2684 let nullable_cast pos ty ty_pos =
2685 add_list
2686 (Typing.err_code Typing.NullableCast)
2687 (pos, "Casting from a nullable type is forbidden")
2688 [(ty_pos, "This is " ^ Markdown_lite.md_codify ty)]
2690 let static_outside_class pos =
2692 (Typing.err_code Typing.StaticOutsideClass)
2694 "`static` is undefined outside of a class"
2696 let self_outside_class pos =
2698 (Typing.err_code Typing.SelfOutsideClass)
2700 "`self` is undefined outside of a class"
2702 let new_inconsistent_construct new_pos (cpos, cname) kind =
2703 let name = strip_ns cname in
2704 let preamble =
2705 match kind with
2706 | `static -> "Can't use `new static()` for " ^ Markdown_lite.md_codify name
2707 | `classname ->
2708 "Can't use `new` on " ^ Markdown_lite.md_codify ("classname<" ^ name ^ ">")
2710 add_list
2711 (Typing.err_code Typing.NewStaticInconsistent)
2712 ( new_pos,
2713 preamble
2714 ^ "; `__construct` arguments are not guaranteed to be consistent in child classes"
2717 ( cpos,
2718 "This declaration is neither `final` nor uses the `<<__ConsistentConstruct>>` attribute"
2722 let undefined_parent pos =
2724 (Typing.err_code Typing.UndefinedParent)
2726 "The parent class is undefined"
2728 let parent_outside_class pos =
2730 (Typing.err_code Typing.ParentOutsideClass)
2732 "`parent` is undefined outside of a class"
2734 let parent_abstract_call meth_name call_pos decl_pos =
2735 add_list
2736 (Typing.err_code Typing.AbstractCall)
2737 ( call_pos,
2738 "Cannot call "
2739 ^ Markdown_lite.md_codify ("parent::" ^ meth_name ^ "()")
2740 ^ "; it is abstract" )
2741 [(decl_pos, "Declaration is here")]
2743 let self_abstract_call meth_name call_pos decl_pos =
2744 add_list
2745 (Typing.err_code Typing.AbstractCall)
2746 ( call_pos,
2747 "Cannot call "
2748 ^ Markdown_lite.md_codify ("self::" ^ meth_name ^ "()")
2749 ^ "; it is abstract. Did you mean "
2750 ^ Markdown_lite.md_codify ("static::" ^ meth_name ^ "()")
2751 ^ "?" )
2752 [(decl_pos, "Declaration is here")]
2754 let classname_abstract_call cname meth_name call_pos decl_pos =
2755 let cname = strip_ns cname in
2756 add_list
2757 (Typing.err_code Typing.AbstractCall)
2758 ( call_pos,
2759 "Cannot call "
2760 ^ Markdown_lite.md_codify (cname ^ "::" ^ meth_name ^ "()")
2761 ^ "; it is abstract" )
2762 [(decl_pos, "Declaration is here")]
2764 let static_synthetic_method cname meth_name call_pos decl_pos =
2765 let cname = strip_ns cname in
2766 add_list
2767 (Typing.err_code Typing.StaticSyntheticMethod)
2768 ( call_pos,
2769 "Cannot call "
2770 ^ Markdown_lite.md_codify (cname ^ "::" ^ meth_name ^ "()")
2771 ^ "; "
2772 ^ Markdown_lite.md_codify meth_name
2773 ^ " is not defined in "
2774 ^ Markdown_lite.md_codify cname )
2775 [(decl_pos, "Declaration is here")]
2777 let isset_in_strict pos =
2779 (Typing.err_code Typing.IssetEmptyInStrict)
2781 ( "`isset` tends to hide errors due to variable typos and so is limited to dynamic checks in "
2782 ^ "`strict` mode" )
2784 let unset_nonidx_in_strict pos msgs =
2785 add_list
2786 (Typing.err_code Typing.UnsetNonidxInStrict)
2787 ( pos,
2788 "In `strict` mode, `unset` is banned except on dynamic, "
2789 ^ "darray, keyset, or dict indexing" )
2790 msgs
2792 let unpacking_disallowed_builtin_function pos name =
2793 let name = strip_ns name in
2795 (Typing.err_code Typing.UnpackingDisallowed)
2797 ("Arg unpacking is disallowed for " ^ Markdown_lite.md_codify name)
2799 let invalid_destructure pos1 pos2 ty (on_error : typing_error_callback) =
2800 on_error
2801 ~code:(Typing.err_code Typing.InvalidDestructure)
2802 ( pos1,
2803 "This expression cannot be destructured with a `list(...)` expression" )
2804 [(pos2, "This is " ^ Markdown_lite.md_codify ty)]
2806 let unpack_array_required_argument p fp (on_error : typing_error_callback) =
2807 on_error
2808 ~code:(Typing.err_code Typing.SplatArrayRequired)
2809 (p, "An array cannot be unpacked into the required arguments of a function")
2810 [(fp, "Definition is here")]
2812 let unpack_array_variadic_argument p fp (on_error : typing_error_callback) =
2813 on_error
2814 ~code:(Typing.err_code Typing.SplatArrayRequired)
2815 ( p,
2816 "A function that receives an unpacked array as an argument must have a variadic parameter to accept the elements of the array"
2818 [(fp, "Definition is here")]
2820 let array_get_arity pos1 name pos2 =
2821 add_list
2822 (Typing.err_code Typing.ArrayGetArity)
2823 (pos1, "You cannot use this " ^ (strip_ns name |> Markdown_lite.md_codify))
2824 [(pos2, "It is missing its type parameters")]
2826 let typing_error pos msg = add (Typing.err_code Typing.GenericUnify) pos msg
2828 let undefined_field ~use_pos ~name ~shape_type_pos =
2829 add_list
2830 (Typing.err_code Typing.UndefinedField)
2831 (use_pos, "The field " ^ Markdown_lite.md_codify name ^ " is undefined")
2832 [(shape_type_pos, "Definition is here")]
2834 let array_access code pos1 pos2 ty =
2835 add_list
2836 (Typing.err_code code)
2837 (pos1, "This is not an object of type `KeyedContainer`, this is " ^ ty)
2838 ( if not (phys_equal pos2 Pos.none) then
2839 [(pos2, "Definition is here")]
2840 else
2841 [] )
2843 let array_access_read = array_access Typing.ArrayAccessRead
2845 let array_access_write = array_access Typing.ArrayAccessWrite
2847 let keyset_set pos1 pos2 =
2848 add_list
2849 (Typing.err_code Typing.KeysetSet)
2850 (pos1, "Elements in a keyset cannot be assigned, use append instead.")
2851 ( if not (phys_equal pos2 Pos.none) then
2852 [(pos2, "Definition is here")]
2853 else
2854 [] )
2856 let array_append pos1 pos2 ty =
2857 add_list
2858 (Typing.err_code Typing.ArrayAppend)
2859 (pos1, ty ^ " does not allow array append")
2860 ( if not (phys_equal pos2 Pos.none) then
2861 [(pos2, "Definition is here")]
2862 else
2863 [] )
2865 let const_mutation pos1 pos2 ty =
2866 add_list
2867 (Typing.err_code Typing.ConstMutation)
2868 (pos1, "You cannot mutate this")
2869 ( if not (phys_equal pos2 Pos.none) then
2870 [(pos2, "This is " ^ ty)]
2871 else
2872 [] )
2874 let expected_class ?(suffix = "") pos =
2876 (Typing.err_code Typing.ExpectedClass)
2878 ("Was expecting a class" ^ suffix)
2880 let unknown_type description pos r =
2881 let msg = "Was expecting " ^ description ^ " but type is unknown" in
2882 add_list (Typing.err_code Typing.UnknownType) (pos, msg) r
2884 let not_found_hint orig hint =
2885 match hint with
2886 | `no_hint -> None
2887 | `closest (pos, v) ->
2888 Some (hint_message ~modifier:"static method " orig v pos)
2889 | `did_you_mean (pos, v) -> Some (hint_message orig v pos)
2891 let snot_found_hint orig hint =
2892 match hint with
2893 | `no_hint -> None
2894 | `closest (pos, v) ->
2895 Some (hint_message ~modifier:"instance method " orig v pos)
2896 | `did_you_mean (pos, v) -> Some (hint_message orig v pos)
2898 let string_of_class_member_kind = function
2899 | `class_constant -> "class constant"
2900 | `static_method -> "static method"
2901 | `class_variable -> "class variable"
2902 | `class_typeconst -> "type constant"
2904 let smember_not_found
2905 kind
2907 (cpos, class_name)
2908 member_name
2909 hint
2910 (on_error : typing_error_callback) =
2911 let kind = string_of_class_member_kind kind in
2912 let class_name = strip_ns class_name in
2913 let msg =
2914 Printf.sprintf
2915 "No %s %s in %s"
2916 kind
2917 (Markdown_lite.md_codify member_name)
2918 (Markdown_lite.md_codify class_name)
2920 on_error
2921 ~code:(Typing.err_code Typing.SmemberNotFound)
2922 (pos, msg)
2923 (let hint =
2924 match snot_found_hint member_name hint with
2925 | None -> []
2926 | Some hint -> [hint]
2928 hint
2930 ( cpos,
2931 "Declaration of " ^ Markdown_lite.md_codify class_name ^ " is here"
2935 let member_not_found
2936 kind
2938 (cpos, type_name)
2939 member_name
2940 hint
2941 reason
2942 (on_error : typing_error_callback) =
2943 let type_name = strip_ns type_name |> Markdown_lite.md_codify in
2944 let kind =
2945 match kind with
2946 | `method_ -> "instance method"
2947 | `property -> "property"
2949 let msg =
2950 Printf.sprintf
2951 "No %s %s in %s"
2952 kind
2953 (Markdown_lite.md_codify member_name)
2954 type_name
2956 on_error
2957 ~code:(Typing.err_code Typing.MemberNotFound)
2958 (pos, msg)
2959 (let hint =
2960 match not_found_hint member_name hint with
2961 | None -> []
2962 | Some hint -> [hint]
2964 hint @ reason @ [(cpos, "Declaration of " ^ type_name ^ " is here")])
2966 let expr_tree_unsupported_operator cls_name meth_name pos =
2967 let msg =
2968 match String.chop_prefix meth_name ~prefix:"__to" with
2969 | Some type_name ->
2970 (* Complain about usage like `if ($not_bool)` that's virtualized to
2971 `if ($not_bool->__toBool())`.
2973 Printf.sprintf
2974 "`%s` cannot be used in a %s position (it has no `%s` method)"
2975 cls_name
2976 (String.lowercase type_name)
2977 meth_name
2978 | None ->
2979 (* Complain about usage like `$not_int +` that's virtualized to
2980 `$not_int->__plus(...)`.
2982 Printf.sprintf
2983 "`%s` does not support this operator (it has no `%s` method)"
2984 cls_name
2985 meth_name
2987 add (Typing.err_code Typing.MemberNotFound) pos msg
2989 let parent_in_trait pos =
2991 (Typing.err_code Typing.ParentInTrait)
2993 "You can only use `parent::` in traits that specify `require extends SomeClass`"
2995 let parent_undefined pos =
2996 add (Typing.err_code Typing.ParentUndefined) pos "parent is undefined"
2998 let constructor_no_args pos =
3000 (Typing.err_code Typing.ConstructorNoArgs)
3002 "This constructor expects no argument"
3004 let visibility p msg1 p_vis msg2 =
3005 add_list (Typing.err_code Typing.Visibility) (p, msg1) [(p_vis, msg2)]
3007 let typing_too_many_args expected actual pos pos_def on_error =
3008 on_error_or_add
3009 on_error
3010 (Typing.err_code Typing.TypingTooManyArgs)
3011 ( pos,
3012 Printf.sprintf
3013 "Too many arguments (expected %d but got %d)"
3014 expected
3015 actual )
3016 [(pos_def, "Definition is here")]
3018 let typing_too_few_args required actual pos pos_def on_error =
3019 on_error_or_add
3020 on_error
3021 (Typing.err_code Typing.TypingTooFewArgs)
3022 ( pos,
3023 Printf.sprintf
3024 "Too few arguments (required %d but got %d)"
3025 required
3026 actual )
3027 [(pos_def, "Definition is here")]
3029 let bad_call pos ty =
3031 (Typing.err_code Typing.BadCall)
3033 ("This call is invalid, this is not a function, it is " ^ ty)
3035 let extend_final extend_pos decl_pos name =
3036 let name = strip_ns name in
3037 add_list
3038 (Typing.err_code Typing.ExtendFinal)
3039 (extend_pos, "You cannot extend final class " ^ Markdown_lite.md_codify name)
3040 [(decl_pos, "Declaration is here")]
3042 let extend_non_abstract_record name extend_pos decl_pos =
3043 let name = strip_ns name in
3044 let msg =
3045 Printf.sprintf
3046 "Cannot extend record %s because it isn't abstract"
3047 (Markdown_lite.md_codify name)
3049 add_list
3050 (Typing.err_code Typing.ExtendFinal)
3051 (extend_pos, msg)
3052 [(decl_pos, "Declaration is here")]
3054 let extend_sealed child_pos parent_pos parent_name parent_kind verb =
3055 let name = strip_ns parent_name in
3056 add_list
3057 (Typing.err_code Typing.ExtendSealed)
3058 ( child_pos,
3059 "You cannot "
3060 ^ verb
3061 ^ " sealed "
3062 ^ parent_kind
3063 ^ " "
3064 ^ Markdown_lite.md_codify name )
3065 [(parent_pos, "Declaration is here")]
3067 let trait_prop_const_class pos x =
3069 (Typing.err_code Typing.TraitPropConstClass)
3071 ( "Trait declaration of non-const property "
3072 ^ Markdown_lite.md_codify x
3073 ^ " is incompatible with a const class" )
3075 let read_before_write (pos, v) =
3077 (Typing.err_code Typing.ReadBeforeWrite)
3079 (Utils.sl
3081 "Read access to ";
3082 Markdown_lite.md_codify ("$this->" ^ v);
3083 " before initialization";
3086 let implement_abstract ~is_final pos1 pos2 kind x =
3087 let name = "abstract " ^ kind ^ " " ^ Markdown_lite.md_codify x in
3088 let msg1 =
3089 if is_final then
3090 "This class was declared as `final`. It must provide an implementation for the "
3091 ^ name
3092 else
3093 "This class must be declared `abstract`, or provide an implementation for the "
3094 ^ name
3096 add_list
3097 (Typing.err_code Typing.ImplementAbstract)
3098 (pos1, msg1)
3099 [(pos2, "Declaration is here")]
3101 let generic_static pos x =
3103 (Typing.err_code Typing.GenericStatic)
3105 ( "This static variable cannot use the type parameter "
3106 ^ Markdown_lite.md_codify x
3107 ^ "." )
3109 let fun_too_many_args
3110 required actual pos1 pos2 (on_error : typing_error_callback) =
3111 on_error
3112 ~code:(Typing.err_code Typing.FunTooManyArgs)
3113 ( pos1,
3114 Printf.sprintf
3115 "Too many mandatory arguments (expected %d but got %d)"
3116 required
3117 actual )
3118 [(pos2, "Because of this definition")]
3120 let fun_too_few_args
3121 required actual pos1 pos2 (on_error : typing_error_callback) =
3122 on_error
3123 ~code:(Typing.err_code Typing.FunTooFewArgs)
3124 ( pos1,
3125 Printf.sprintf
3126 "Too few arguments (required %d but got %d)"
3127 required
3128 actual )
3129 [(pos2, "Because of this definition")]
3131 let fun_unexpected_nonvariadic pos1 pos2 (on_error : typing_error_callback) =
3132 on_error
3133 ~code:(Typing.err_code Typing.FunUnexpectedNonvariadic)
3134 (pos1, "Should have a variadic argument")
3135 [(pos2, "Because of this definition")]
3137 let fun_variadicity_hh_vs_php56 pos1 pos2 (on_error : typing_error_callback) =
3138 on_error
3139 ~code:(Typing.err_code Typing.FunVariadicityHhVsPhp56)
3140 (pos1, "Variadic arguments: `...`-style is not a subtype of `...$args`")
3141 [(pos2, "Because of this definition")]
3143 let ellipsis_strict_mode ~require pos =
3144 let msg =
3145 match require with
3146 | `Type -> "Cannot use `...` without a **type hint** in strict mode."
3147 | `Param_name ->
3148 "Cannot use `...` without a **parameter name** in strict mode."
3149 | `Type_and_param_name ->
3150 "Cannot use `...` without a **type hint** and **parameter name** in strict mode."
3152 add (Typing.err_code Typing.EllipsisStrictMode) pos msg
3154 let untyped_lambda_strict_mode pos =
3155 let msg =
3156 "Cannot determine types of lambda parameters in strict mode. Please add type hints on parameters."
3158 add (Typing.err_code Typing.UntypedLambdaStrictMode) pos msg
3160 let expected_tparam
3161 ~use_pos ~definition_pos n (on_error : typing_error_callback option) =
3162 let claim =
3163 ( use_pos,
3164 "Expected "
3166 match n with
3167 | 0 -> "no type parameters"
3168 | 1 -> "exactly one type parameter"
3169 | n -> string_of_int n ^ " type parameters" )
3171 let reasons = [(definition_pos, "Definition is here")] in
3172 on_error_or_add on_error (Typing.err_code Typing.ExpectedTparam) claim reasons
3174 let object_string pos1 pos2 =
3175 add_list
3176 (Typing.err_code Typing.ObjectString)
3177 (pos1, "You cannot use this object as a string")
3178 [(pos2, "This object doesn't implement `__toString`")]
3180 let object_string_deprecated pos =
3182 (Typing.err_code Typing.ObjectString)
3184 "You cannot use this object as a string\nImplicit conversions of Stringish objects to string are deprecated."
3186 let cyclic_typedef def_pos use_pos =
3187 add_list
3188 (Typing.err_code Typing.CyclicTypedef)
3189 (def_pos, "Cyclic type definition")
3190 [(use_pos, "Cyclic use is here")]
3192 let type_arity_mismatch pos1 n1 pos2 n2 (on_error : typing_error_callback) =
3193 on_error
3194 ~code:(Typing.err_code Typing.TypeArityMismatch)
3195 (pos1, "This type has " ^ n1 ^ " arguments")
3196 [(pos2, "This one has " ^ n2)]
3198 let this_final id pos2 =
3199 let n = strip_ns (snd id) |> Markdown_lite.md_codify in
3200 let message1 = "Since " ^ n ^ " is not final" in
3201 let message2 = "this might not be a " ^ n in
3202 [(fst id, message1); (pos2, message2)]
3204 let exact_class_final id pos2 =
3205 let n = strip_ns (snd id) |> Markdown_lite.md_codify in
3206 let message1 = "This requires the late-bound type to be exactly " ^ n in
3207 let message2 =
3208 "Since " ^ n ^ " is not final this might be an instance of a child class"
3210 [(fst id, message1); (pos2, message2)]
3212 let fun_arity_mismatch pos1 pos2 (on_error : typing_error_callback) =
3213 on_error
3214 ~code:(Typing.err_code Typing.FunArityMismatch)
3215 (pos1, "Number of arguments doesn't match")
3216 [(pos2, "Because of this definition")]
3218 let fun_reactivity_mismatch
3219 pos1 kind1 pos2 kind2 (on_error : typing_error_callback) =
3220 let f k = "This function is " ^ k ^ "." in
3221 on_error
3222 ~code:(Typing.err_code Typing.FunReactivityMismatch)
3223 (pos1, f kind1)
3224 [(pos2, f kind2)]
3226 let inconsistent_mutability pos1 mut1 p2_opt =
3227 match p2_opt with
3228 | Some (pos2, mut2) ->
3229 add_list
3230 (Typing.err_code Typing.InconsistentMutability)
3231 (pos1, "Inconsistent mutability of local variable, here local is " ^ mut1)
3232 [(pos2, "But here it is " ^ mut2)]
3233 | None ->
3235 (Typing.err_code Typing.InconsistentMutability)
3236 pos1
3237 ("Local is " ^ mut1 ^ " in one scope and immutable in another.")
3239 let inconsistent_mutability_for_conditional p_mut p_other =
3240 add_list
3241 (Typing.err_code Typing.InconsistentMutability)
3242 ( p_mut,
3243 "Inconsistent mutability of conditional expression, this branch returns owned mutable value"
3245 [(p_other, "But this one does not.")]
3247 let invalid_mutability_flavor pos mut1 mut2 =
3249 (Typing.err_code Typing.InvalidMutabilityFlavorInAssignment)
3251 ( "Cannot assign "
3252 ^ mut2
3253 ^ " value to "
3254 ^ mut1
3255 ^ " local variable. Mutability flavor of local variable cannot be altered."
3258 let reassign_mutable_var ~in_collection pos1 =
3259 let msg =
3260 if in_collection then
3261 "This variable is mutable. You cannot create a new reference to it by putting it into the collection."
3262 else
3263 "This variable is mutable. You cannot create a new reference to it."
3265 add (Typing.err_code Typing.ReassignMutableVar) pos1 msg
3267 let reassign_mutable_this ~in_collection ~is_maybe_mutable pos1 =
3268 let kind =
3269 if is_maybe_mutable then
3270 "maybe mutable"
3271 else
3272 "mutable"
3274 let msg =
3275 if in_collection then
3276 "`$this` here is "
3277 ^ kind
3278 ^ ". You cannot create a new reference to it by putting it into the collection."
3279 else
3280 "`$this` here is " ^ kind ^ ". You cannot create a new reference to it."
3282 add (Typing.err_code Typing.ReassignMutableThis) pos1 msg
3284 let mutable_expression_as_multiple_mutable_arguments
3285 pos param_kind prev_pos prev_param_kind =
3286 add_list
3287 (Typing.err_code Typing.MutableExpressionAsMultipleMutableArguments)
3288 ( pos,
3289 "A mutable expression may not be passed as multiple arguments where at least one matching parameter is mutable. Matching parameter here is "
3290 ^ param_kind )
3292 ( prev_pos,
3293 "This is where it was used before, being passed as " ^ prev_param_kind
3297 let reassign_maybe_mutable_var ~in_collection pos1 =
3298 let msg =
3299 if in_collection then
3300 "This variable is maybe mutable. You cannot create a new reference to it by putting it into the collection."
3301 else
3302 "This variable is maybe mutable. You cannot create a new reference to it."
3304 add (Typing.err_code Typing.ReassignMaybeMutableVar) pos1 msg
3306 let mutable_call_on_immutable fpos pos1 rx_mutable_hint_pos =
3307 let l =
3308 match rx_mutable_hint_pos with
3309 | Some p ->
3311 ( p,
3312 "Consider wrapping this expression with `Rx\\mutable` to forward mutability."
3315 | None -> []
3317 let claim = (pos1, "Cannot call mutable function on immutable expression") in
3318 let reasons =
3319 ( fpos,
3320 "This function is marked `<<__Mutable>>`, so it has a mutable `$this`." )
3321 :: l
3323 add_list (Typing.err_code Typing.MutableCallOnImmutable) claim reasons
3325 let immutable_call_on_mutable fpos pos1 =
3326 add_list
3327 (Typing.err_code Typing.ImmutableCallOnMutable)
3328 (pos1, "Cannot call non-mutable function on mutable expression")
3329 [(fpos, "This function is not marked as `<<__Mutable>>`.")]
3331 let mutability_mismatch
3332 ~is_receiver pos1 mut1 pos2 mut2 (on_error : typing_error_callback) =
3333 let msg mut =
3334 let msg =
3335 if is_receiver then
3336 "Receiver of this function"
3337 else
3338 "This parameter"
3340 msg ^ " is " ^ mut
3342 on_error
3343 ~code:(Typing.err_code Typing.MutabilityMismatch)
3344 (pos1, "Incompatible mutabilities:")
3345 [(pos1, msg mut1); (pos2, msg mut2)]
3347 let invalid_call_on_maybe_mutable ~fun_is_mutable pos fpos =
3348 let msg =
3349 "Cannot call "
3350 ^ ( if fun_is_mutable then
3351 "mutable"
3352 else
3353 "non-mutable" )
3354 ^ " function on maybe mutable value."
3356 add_list
3357 (Typing.err_code Typing.InvalidCallMaybeMutable)
3358 (pos, msg)
3359 [(fpos, "This function is not marked as `<<__MaybeMutable>>`.")]
3361 let mutable_argument_mismatch param_pos arg_pos =
3362 add_list
3363 (Typing.err_code Typing.MutableArgumentMismatch)
3364 (arg_pos, "Invalid argument")
3366 (param_pos, "This parameter is marked mutable");
3367 (arg_pos, "But this expression is not");
3370 let immutable_argument_mismatch param_pos arg_pos =
3371 add_list
3372 (Typing.err_code Typing.ImmutableArgumentMismatch)
3373 (arg_pos, "Invalid argument")
3375 (param_pos, "This parameter is not marked as mutable");
3376 (arg_pos, "But this expression is mutable");
3379 let mutably_owned_argument_mismatch ~arg_is_owned_local param_pos arg_pos =
3380 let arg_msg =
3381 if arg_is_owned_local then
3382 "Owned mutable locals used as argument should be passed via `Rx\\move` function"
3383 else
3384 "But this expression is not owned mutable"
3386 add_list
3387 (Typing.err_code Typing.ImmutableArgumentMismatch)
3388 (arg_pos, "Invalid argument")
3390 (param_pos, "This parameter is marked with `<<__OwnedMutable>>`");
3391 (arg_pos, arg_msg);
3394 let maybe_mutable_argument_mismatch param_pos arg_pos =
3395 add_list
3396 (Typing.err_code Typing.MaybeMutableArgumentMismatch)
3397 (arg_pos, "Invalid argument")
3399 (param_pos, "This parameter is not marked `<<__MaybeMutable>>`");
3400 (arg_pos, "But this expression is maybe mutable");
3403 let invalid_mutable_return_result error_pos function_pos value_kind =
3404 add_list
3405 (Typing.err_code Typing.InvalidMutableReturnResult)
3406 ( error_pos,
3407 "Functions marked `<<__MutableReturn>>` must return mutably owned values: mutably owned local variables and results of calling `Rx\\mutable`."
3410 (function_pos, "This function is marked `<<__MutableReturn>>`");
3411 (error_pos, "This expression is " ^ value_kind);
3414 let freeze_in_nonreactive_context pos1 =
3416 (Typing.err_code Typing.FreezeInNonreactiveContext)
3417 pos1
3418 "`\\HH\\Rx\\freeze` can only be used in reactive functions"
3420 let mutable_in_nonreactive_context pos =
3422 (Typing.err_code Typing.MutableInNonreactiveContext)
3424 "`\\HH\\Rx\\mutable` can only be used in reactive functions"
3426 let move_in_nonreactive_context pos =
3428 (Typing.err_code Typing.MoveInNonreactiveContext)
3430 "`\\HH\\Rx\\move` can only be used in reactive functions"
3432 let invalid_argument_type_for_condition_in_rx
3433 ~is_receiver f_pos def_pos arg_pos expected_type actual_type =
3434 let arg_msg =
3435 if is_receiver then
3436 "Receiver type"
3437 else
3438 "Argument type"
3440 let arg_msg =
3441 arg_msg
3442 ^ " must be a subtype of "
3443 ^ Markdown_lite.md_codify expected_type
3444 ^ ", now "
3445 ^ Markdown_lite.md_codify actual_type
3446 ^ "."
3448 add_list
3449 (Typing.err_code Typing.InvalidConditionallyReactiveCall)
3450 ( f_pos,
3451 "Cannot invoke conditionally reactive function in reactive context, because at least one reactivity condition is not met."
3453 [(arg_pos, arg_msg); (def_pos, "This is the function declaration")]
3455 let callsite_reactivity_mismatch
3456 f_pos def_pos callee_reactivity cause_pos_opt caller_reactivity =
3457 add_list
3458 (Typing.err_code Typing.CallSiteReactivityMismatch)
3459 ( f_pos,
3460 "Reactivity mismatch: "
3461 ^ caller_reactivity
3462 ^ " function cannot call "
3463 ^ callee_reactivity
3464 ^ " function." )
3465 ( [(def_pos, "This is the declaration of the function being called.")]
3466 @ Option.value_map cause_pos_opt ~default:[] ~f:(fun cause_pos ->
3468 ( cause_pos,
3469 "Reactivity of this argument was used as reactivity of the callee."
3471 ]) )
3473 let callsite_cipp_mismatch f_pos def_pos callee_cipp caller_cipp =
3474 add_list
3475 (Typing.err_code Typing.CallsiteCIPPMismatch)
3476 ( f_pos,
3477 "CIPP mismatch: "
3478 ^ caller_cipp
3479 ^ " function cannot call "
3480 ^ callee_cipp
3481 ^ " function." )
3482 [(def_pos, "This is the declaration of the function being called.")]
3484 let invalid_argument_of_rx_mutable_function pos =
3486 (Typing.err_code Typing.InvalidArgumentOfRxMutableFunction)
3488 ( "Single argument to `\\HH\\Rx\\mutable` should be an expression that yields new mutably-owned value, "
3489 ^ "like `new A()`, Hack collection literal or `f()` where `f` is function annotated with `<<__MutableReturn>>` attribute."
3492 let invalid_freeze_use pos1 =
3494 (Typing.err_code Typing.InvalidFreezeUse)
3495 pos1
3496 "`freeze` takes a single mutably-owned local variable as an argument"
3498 let invalid_move_use pos1 =
3500 (Typing.err_code Typing.InvalidMoveUse)
3501 pos1
3502 "`move` takes a single mutably-owned local variable as an argument"
3504 let require_args_reify def_pos arg_pos =
3505 add_list
3506 (Typing.err_code Typing.RequireArgsReify)
3507 ( arg_pos,
3508 "All type arguments must be specified because a type parameter is reified"
3510 [(def_pos, "Definition is here")]
3512 let require_generic_explicit (def_pos, def_name) arg_pos =
3513 add_list
3514 (Typing.err_code Typing.RequireGenericExplicit)
3515 ( arg_pos,
3516 "Generic type parameter "
3517 ^ Markdown_lite.md_codify def_name
3518 ^ " must be specified explicitly" )
3519 [(def_pos, "Definition is here")]
3521 let invalid_reified_argument (def_pos, def_name) hint_pos arg_info =
3522 let (arg_pos, arg_kind) = List.hd_exn arg_info in
3523 add_list
3524 (Typing.err_code Typing.InvalidReifiedArgument)
3525 (hint_pos, "Invalid reified hint")
3527 ( arg_pos,
3528 "This is " ^ arg_kind ^ ", it cannot be used as a reified type argument"
3530 (def_pos, Markdown_lite.md_codify def_name ^ " is reified");
3533 let invalid_reified_argument_reifiable (def_pos, def_name) arg_pos ty_pos ty_msg
3535 add_list
3536 (Typing.err_code Typing.InvalidReifiedArgument)
3537 (arg_pos, "PHP arrays cannot be used as a reified type argument")
3539 (ty_pos, String.capitalize ty_msg);
3540 (def_pos, Markdown_lite.md_codify def_name ^ " is reified");
3543 let new_class_reified pos class_type suggested_class =
3544 let suggestion =
3545 match suggested_class with
3546 | Some s ->
3547 let s = strip_ns s in
3548 sprintf ". Try `new %s` instead." s
3549 | None -> ""
3552 (Typing.err_code Typing.NewClassReified)
3554 (sprintf
3555 "Cannot call `new %s` because the current class has reified generics%s"
3556 class_type
3557 suggestion)
3559 let class_get_reified pos =
3561 (Typing.err_code Typing.ClassGetReified)
3563 "Cannot access static properties on reified generics"
3565 let static_meth_with_class_reified_generic meth_pos generic_pos =
3566 add_list
3567 (Typing.err_code Typing.StaticMethWithClassReifiedGeneric)
3568 ( meth_pos,
3569 "Static methods cannot use generics reified at the class level. Try reifying them at the static method itself."
3571 [(generic_pos, "Class-level reified generic used here.")]
3573 let consistent_construct_reified pos =
3575 (Typing.err_code Typing.ConsistentConstructReified)
3577 "This class or one of its ancestors is annotated with `<<__ConsistentConstruct>>`. It cannot have reified generics."
3579 let bad_function_pointer_construction pos =
3581 (Typing.err_code Typing.BadFunctionPointerConstruction)
3583 "Function pointers must be explicitly named"
3585 let reified_generics_not_allowed pos =
3587 (Typing.err_code Typing.InvalidReifiedFunctionPointer)
3589 "Creating function pointers with reified generics is not currently allowed"
3591 let new_without_newable pos name =
3593 (Typing.err_code Typing.NewWithoutNewable)
3595 ( Markdown_lite.md_codify name
3596 ^ " cannot be used with `new` because it does not have the `<<__Newable>>` attribute"
3599 let invalid_freeze_target pos1 var_pos var_mutability_str =
3600 add_list
3601 (Typing.err_code Typing.InvalidFreezeTarget)
3602 (pos1, "Invalid argument - `freeze()` takes a single mutable variable")
3603 [(var_pos, "This variable is " ^ var_mutability_str)]
3605 let invalid_move_target pos1 var_pos var_mutability_str =
3606 add_list
3607 (Typing.err_code Typing.InvalidMoveTarget)
3608 (pos1, "Invalid argument - `move()` takes a single mutably-owned variable")
3609 [(var_pos, "This variable is " ^ var_mutability_str)]
3611 let discarded_awaitable pos1 pos2 =
3612 add_list
3613 (Typing.err_code Typing.DiscardedAwaitable)
3614 ( pos1,
3615 "This expression is of type `Awaitable`, but it's "
3616 ^ "either being discarded or used in a dangerous way before "
3617 ^ "being awaited" )
3618 [(pos2, "This is why I think it is `Awaitable`")]
3620 let unify_error ?code err =
3621 add_list (Option.value code ~default:(Typing.err_code Typing.UnifyError)) err
3623 let unify_error_at : Pos.t -> typing_error_callback =
3624 fun pos ?code claim reasons ->
3625 unify_error ?code (pos, "Typing error") (claim :: reasons)
3627 let maybe_unify_error specific_code ?code errl =
3628 add_list (Option.value code ~default:(Typing.err_code specific_code)) errl
3630 let index_type_mismatch = maybe_unify_error Typing.IndexTypeMismatch
3632 let expected_stringlike = maybe_unify_error Typing.ExpectedStringlike
3634 let type_constant_mismatch (on_error : typing_error_callback) ?code errl =
3635 let code =
3636 Option.value code ~default:(Typing.err_code Typing.TypeConstantMismatch)
3638 on_error ~code errl
3640 let class_constant_type_mismatch (on_error : typing_error_callback) ?code errl =
3641 let code =
3642 Option.value
3643 code
3644 ~default:(Typing.err_code Typing.ClassConstantTypeMismatch)
3646 on_error ~code errl
3648 let constant_does_not_match_enum_type =
3649 maybe_unify_error Typing.ConstantDoesNotMatchEnumType
3651 let enum_underlying_type_must_be_arraykey =
3652 maybe_unify_error Typing.EnumUnderlyingTypeMustBeArraykey
3654 let enum_constraint_must_be_arraykey =
3655 maybe_unify_error Typing.EnumConstraintMustBeArraykey
3657 let enum_subtype_must_have_compatible_constraint =
3658 maybe_unify_error Typing.EnumSubtypeMustHaveCompatibleConstraint
3660 let parameter_default_value_wrong_type =
3661 maybe_unify_error Typing.ParameterDefaultValueWrongType
3663 let newtype_alias_must_satisfy_constraint =
3664 maybe_unify_error Typing.NewtypeAliasMustSatisfyConstraint
3666 let bad_function_typevar = maybe_unify_error Typing.BadFunctionTypevar
3668 let bad_class_typevar = maybe_unify_error Typing.BadClassTypevar
3670 let bad_method_typevar = maybe_unify_error Typing.BadMethodTypevar
3672 let missing_return = maybe_unify_error Typing.MissingReturnInNonVoidFunction
3674 let inout_return_type_mismatch =
3675 maybe_unify_error Typing.InoutReturnTypeMismatch
3677 let class_constant_value_does_not_match_hint =
3678 maybe_unify_error Typing.ClassConstantValueDoesNotMatchHint
3680 let class_property_initializer_type_does_not_match_hint =
3681 maybe_unify_error Typing.ClassPropertyInitializerTypeDoesNotMatchHint
3683 let xhp_attribute_does_not_match_hint =
3684 maybe_unify_error Typing.XhpAttributeValueDoesNotMatchHint
3686 let record_init_value_does_not_match_hint =
3687 maybe_unify_error Typing.RecordInitValueDoesNotMatchHint
3689 let using_error pos has_await ?code:_ msg _list =
3690 let (note, cls) =
3691 if has_await then
3692 (" with await", Naming_special_names.Classes.cIAsyncDisposable)
3693 else
3694 ("", Naming_special_names.Classes.cIDisposable)
3696 add_list
3697 (Typing.err_code Typing.UnifyError)
3698 ( pos,
3699 Printf.sprintf
3700 "This expression is used in a `using` clause%s so it must have type `%s`"
3701 note
3702 cls )
3703 [msg]
3705 let elt_type_to_string = function
3706 | `Method -> "method"
3707 | `Property -> "property"
3709 let static_redeclared_as_dynamic
3710 dyn_position static_position member_name ~elt_type =
3711 let dollar =
3712 match elt_type with
3713 | `Property -> "$"
3714 | _ -> ""
3716 let elt_type = elt_type_to_string elt_type in
3717 let msg_dynamic =
3718 "The "
3719 ^ elt_type
3720 ^ " "
3721 ^ Markdown_lite.md_codify (dollar ^ member_name)
3722 ^ " is declared here as non-static"
3724 let msg_static =
3725 "But it conflicts with an inherited static declaration here"
3727 add_list
3728 (Typing.err_code Typing.StaticDynamic)
3729 (dyn_position, msg_dynamic)
3730 [(static_position, msg_static)]
3732 let dynamic_redeclared_as_static
3733 static_position dyn_position member_name ~elt_type =
3734 let dollar =
3735 match elt_type with
3736 | `Property -> "$"
3737 | _ -> ""
3739 let elt_type = elt_type_to_string elt_type in
3740 let msg_static =
3741 "The "
3742 ^ elt_type
3743 ^ " "
3744 ^ Markdown_lite.md_codify (dollar ^ member_name)
3745 ^ " is declared here as static"
3747 let msg_dynamic =
3748 "But it conflicts with an inherited non-static declaration here"
3750 add_list
3751 (Typing.err_code Typing.StaticDynamic)
3752 (static_position, msg_static)
3753 [(dyn_position, msg_dynamic)]
3755 let null_member code ~is_method s pos r =
3756 let msg =
3757 Printf.sprintf
3758 "You are trying to access the %s %s but this object can be null."
3759 ( if is_method then
3760 "method"
3761 else
3762 "property" )
3763 (Markdown_lite.md_codify s)
3765 add_list (Typing.err_code code) (pos, msg) r
3767 let null_member_read = null_member Typing.NullMemberRead
3769 let null_member_write = null_member Typing.NullMemberWrite
3771 (* Trying to access a member on a mixed or nonnull value. *)
3772 let top_member null_code nonnull_code ~is_method ~is_nullable s pos1 ty pos2 =
3773 let msg =
3774 Printf.sprintf
3775 "You are trying to access the %s %s but this is %s. Use a **specific** class or interface name."
3776 ( if is_method then
3777 "method"
3778 else
3779 "property" )
3780 (Markdown_lite.md_codify s)
3783 add_list
3784 (Typing.err_code
3785 ( if is_nullable then
3786 null_code
3787 else
3788 nonnull_code ))
3789 (pos1, msg)
3790 [(pos2, "Definition is here")]
3792 let top_member_read =
3793 top_member Typing.NullMemberRead Typing.NonObjectMemberRead
3795 let top_member_write =
3796 top_member Typing.NullMemberWrite Typing.NonObjectMemberWrite
3798 let non_object_member
3799 code ~is_method s pos1 ty pos2 (on_error : typing_error_callback) =
3800 let msg_start =
3801 Printf.sprintf
3802 "You are trying to access the %s %s but this is %s"
3803 ( if is_method then
3804 "method"
3805 else
3806 "property" )
3807 (Markdown_lite.md_codify s)
3810 let msg =
3811 if String.equal ty "a shape" then
3812 msg_start ^ ". Did you mean `$foo['" ^ s ^ "']` instead?"
3813 else
3814 msg_start
3816 on_error
3817 ~code:(Typing.err_code code)
3818 (pos1, msg)
3819 [(pos2, "Definition is here")]
3821 let non_object_member_read = non_object_member Typing.NonObjectMemberRead
3823 let non_object_member_write = non_object_member Typing.NonObjectMemberRead
3825 let unknown_object_member ~is_method s pos r =
3826 let msg =
3827 Printf.sprintf
3828 "You are trying to access the %s %s on a value whose class is unknown."
3829 ( if is_method then
3830 "method"
3831 else
3832 "property" )
3833 (Markdown_lite.md_codify s)
3835 add_list (Typing.err_code Typing.UnknownObjectMember) (pos, msg) r
3837 let non_class_member ~is_method s pos1 ty pos2 =
3838 let msg =
3839 Printf.sprintf
3840 "You are trying to access the static %s %s but this is %s"
3841 ( if is_method then
3842 "method"
3843 else
3844 "property" )
3845 (Markdown_lite.md_codify s)
3848 add_list
3849 (Typing.err_code Typing.NonClassMember)
3850 (pos1, msg)
3851 [(pos2, "Definition is here")]
3853 let null_container p null_witness =
3854 add_list
3855 (Typing.err_code Typing.NullContainer)
3856 ( p,
3857 "You are trying to access an element of this container"
3858 ^ " but the container could be `null`. " )
3859 null_witness
3861 let option_mixed pos =
3863 (Typing.err_code Typing.OptionMixed)
3865 "`?mixed` is a redundant typehint - just use `mixed`"
3867 let option_null pos =
3869 (Typing.err_code Typing.OptionNull)
3871 "`?null` is a redundant typehint - just use `null`"
3873 let declared_covariant pos1 pos2 emsg =
3874 add_list
3875 (Typing.err_code Typing.DeclaredCovariant)
3876 (pos2, "Illegal usage of a covariant type parameter")
3877 ( [(pos1, "This is where the parameter was declared as covariant `+`")]
3878 @ emsg )
3880 let declared_contravariant pos1 pos2 emsg =
3881 add_list
3882 (Typing.err_code Typing.DeclaredContravariant)
3883 (pos2, "Illegal usage of a contravariant type parameter")
3884 ( [(pos1, "This is where the parameter was declared as contravariant `-`")]
3885 @ emsg )
3887 let static_property_type_generic_param ~class_pos ~var_type_pos ~generic_pos =
3888 add_list
3889 (Typing.err_code Typing.ClassVarTypeGenericParam)
3890 ( generic_pos,
3891 "A generic parameter cannot be used in the type of a static property" )
3893 ( var_type_pos,
3894 "This is where the type of the static property was declared" );
3895 (class_pos, "This is the class containing the static property");
3898 let contravariant_this pos class_name tp =
3900 (Typing.err_code Typing.ContravariantThis)
3902 ( "The `this` type cannot be used in this "
3903 ^ "contravariant position because its enclosing class "
3904 ^ Markdown_lite.md_codify class_name
3905 ^ " "
3906 ^ "is final and has a variant type parameter "
3907 ^ Markdown_lite.md_codify tp )
3909 let cyclic_typeconst pos sl =
3910 let sl = List.map sl ~f:(fun s -> strip_ns s |> Markdown_lite.md_codify) in
3912 (Typing.err_code Typing.CyclicTypeconst)
3914 ("Cyclic type constant:\n " ^ String.concat ~sep:" -> " sl)
3916 let abstract_concrete_override pos parent_pos kind =
3917 let kind_str =
3918 match kind with
3919 | `method_ -> "method"
3920 | `typeconst -> "type constant"
3921 | `constant -> "constant"
3922 | `property -> "property"
3924 add_list
3925 (Typing.err_code Typing.AbstractConcreteOverride)
3926 (pos, "Cannot re-declare this " ^ kind_str ^ " as abstract")
3927 [(parent_pos, "Previously defined here")]
3929 let required_field_is_optional pos1 pos2 name (on_error : typing_error_callback)
3931 on_error
3932 ~code:(Typing.err_code Typing.RequiredFieldIsOptional)
3933 (pos1, "The field " ^ Markdown_lite.md_codify name ^ " is **optional**")
3935 ( pos2,
3936 "The field "
3937 ^ Markdown_lite.md_codify name
3938 ^ " is defined as **required**" );
3941 let array_get_with_optional_field pos1 pos2 name =
3942 add_list
3943 (Typing.err_code Typing.ArrayGetWithOptionalField)
3944 ( pos1,
3945 Printf.sprintf
3946 "The field %s may not be present in this shape. Use `Shapes::idx()` instead."
3947 (Markdown_lite.md_codify name) )
3948 [(pos2, "This is where the field was declared as optional.")]
3950 let return_disposable_mismatch
3951 pos1_return_disposable pos1 pos2 (on_error : typing_error_callback) =
3952 let m1 = "This is marked `<<__ReturnDisposable>>`." in
3953 let m2 = "This is not marked `<<__ReturnDisposable>>`." in
3954 on_error
3955 ~code:(Typing.err_code Typing.ReturnDisposableMismatch)
3956 ( pos1,
3957 if pos1_return_disposable then
3959 else
3960 m2 )
3962 ( pos2,
3963 if pos1_return_disposable then
3965 else
3966 m1 );
3969 let ifc_policy_mismatch
3970 pos_sub pos_super policy_sub policy_super (on_error : typing_error_callback)
3972 let m1 =
3973 "IFC policies must be invariant with respect to inheritance. This method is policied with "
3974 ^ policy_sub
3976 let m2 =
3977 "This is incompatible with its inherited policy, which is " ^ policy_super
3979 on_error
3980 ~code:(Typing.err_code Typing.IFCPolicyMismatch)
3981 (pos_sub, m1)
3982 [(pos_super, m2)]
3984 let return_void_to_rx_mismatch
3985 ~pos1_has_attribute pos1 pos2 (on_error : typing_error_callback) =
3986 let m1 = "This is marked `<<__ReturnsVoidToRx>>`." in
3987 let m2 = "This is not marked `<<__ReturnsVoidToRx>>`." in
3988 on_error
3989 ~code:(Typing.err_code Typing.ReturnVoidToRxMismatch)
3990 ( pos1,
3991 if pos1_has_attribute then
3993 else
3994 m2 )
3996 ( pos2,
3997 if pos1_has_attribute then
3999 else
4000 m1 );
4003 let this_as_lexical_variable pos =
4005 (Naming.err_code Naming.ThisAsLexicalVariable)
4007 "Cannot use `$this` as lexical variable"
4009 let dollardollar_lvalue pos =
4011 (Typing.err_code Typing.DollardollarLvalue)
4013 "Cannot assign a value to the special pipe variable `$$`"
4015 let mutating_const_property pos =
4017 (Typing.err_code Typing.AssigningToConst)
4019 "Cannot mutate a `__Const` property"
4021 let self_const_parent_not pos =
4023 (Typing.err_code Typing.SelfConstParentNot)
4025 "A `__Const` class may only extend other `__Const` classes"
4027 let overriding_prop_const_mismatch
4028 parent_pos
4029 parent_const
4030 child_pos
4031 child_const
4032 (on_error : typing_error_callback) =
4033 let m1 = "This property is `__Const`" in
4034 let m2 = "This property is not `__Const`" in
4035 on_error
4036 ~code:(Typing.err_code Typing.OverridingPropConstMismatch)
4037 ( child_pos,
4038 if child_const then
4040 else
4041 m2 )
4043 ( parent_pos,
4044 if parent_const then
4046 else
4047 m2 );
4050 let mutable_return_result_mismatch
4051 pos1_has_mutable_return pos1 pos2 (on_error : typing_error_callback) =
4052 let m1 = "This is marked `<<__MutableReturn>>`." in
4053 let m2 = "This is not marked `<<__MutableReturn>>`." in
4054 on_error
4055 ~code:(Typing.err_code Typing.MutableReturnResultMismatch)
4056 ( pos1,
4057 if pos1_has_mutable_return then
4059 else
4060 m2 )
4062 ( pos2,
4063 if pos1_has_mutable_return then
4065 else
4066 m1 );
4069 let php_lambda_disallowed pos =
4071 (NastCheck.err_code NastCheck.PhpLambdaDisallowed)
4073 "PHP style anonymous functions are not allowed."
4075 module CoeffectEnforcedOp = struct
4076 let output pos =
4078 (Typing.err_code Typing.OutputInWrongContext)
4080 "`echo` or `print` are not allowed in reactive functions."
4082 let static_property_access pos =
4084 (Typing.err_code Typing.StaticPropertyInWrongContext)
4086 "Static property cannot be used in a reactive context."
4088 let rx_enabled_in_non_rx_context pos =
4090 (Typing.err_code Typing.RxEnabledInNonRxContext)
4092 "`\\HH\\Rx\\IS_ENABLED` can only be used in reactive functions."
4094 let nonreactive_indexing is_append pos =
4095 let msg =
4096 if is_append then
4097 "Cannot append to a Hack Collection object in a reactive context. Instead, use the `add` method."
4098 else
4099 "Cannot assign to element of Hack Collection object via `[]` in a reactive context. Instead, use the `set` method."
4101 add (Typing.err_code Typing.NonreactiveIndexing) pos msg
4103 let obj_set_reactive pos =
4104 let msg =
4105 "This object's property is being mutated (used as an lvalue)"
4106 ^ "\nYou cannot set non-mutable object properties in reactive functions"
4108 add (Typing.err_code Typing.ObjSetReactive) pos msg
4110 let invalid_unset_target_rx pos =
4112 (Typing.err_code Typing.InvalidUnsetTargetInRx)
4114 "Non-mutable argument for `unset` is not allowed in reactive functions."
4116 let non_awaited_awaitable_in_rx pos =
4118 (Typing.err_code Typing.NonawaitedAwaitableInReactiveContext)
4120 "This value has `Awaitable` type. `Awaitable` typed values in reactive code must be immediately `await`ed."
4123 (*****************************************************************************)
4124 (* Typing decl errors *)
4125 (*****************************************************************************)
4127 let wrong_extend_kind
4128 ~parent_pos
4129 ~parent_kind
4130 ~parent_name
4131 ~parent_is_enum_class
4132 ~child_pos
4133 ~child_kind
4134 ~child_name
4135 ~child_is_enum_class =
4136 let parent_kind_str =
4137 Ast_defs.string_of_class_kind
4138 parent_kind
4139 ~is_enum_class:parent_is_enum_class
4141 let parent_name = strip_ns parent_name in
4142 let child_name = strip_ns child_name in
4143 let use_msg =
4144 Printf.sprintf
4145 " Did you mean to add `use %s;` within the body of %s?"
4146 parent_name
4147 (Markdown_lite.md_codify child_name)
4149 let child_msg =
4150 match child_kind with
4151 | Ast_defs.Cabstract
4152 | Ast_defs.Cnormal ->
4153 let extends_msg = "Classes can only extend other classes." in
4154 let suggestion =
4155 if Ast_defs.is_c_interface parent_kind then
4156 " Did you mean `implements " ^ parent_name ^ "`?"
4157 else if Ast_defs.is_c_trait parent_kind then
4158 use_msg
4159 else
4162 extends_msg ^ suggestion
4163 | Ast_defs.Cinterface ->
4164 let extends_msg = "Interfaces can only extend other interfaces." in
4165 let suggestion =
4166 if Ast_defs.is_c_trait parent_kind then
4167 use_msg
4168 else
4171 extends_msg ^ suggestion
4172 | Ast_defs.Cenum ->
4173 if child_is_enum_class then
4174 "Enum classes can only extend other enum classes."
4175 else
4176 (* This case should never happen, as the type checker will have already caught
4177 it with EnumTypeBad. But just in case, report this error here too. *)
4178 "Enums can only extend int, string, or arraykey."
4179 | Ast_defs.Ctrait ->
4180 (* This case should never happen, as the parser will have caught it before
4181 we get here. *)
4182 "A trait cannot use `extends`. This is a parser error."
4184 let msg1 = (child_pos, child_msg) in
4185 let msg2 = (parent_pos, "This is " ^ parent_kind_str ^ ".") in
4186 add_list (Typing.err_code Typing.WrongExtendKind) msg1 [msg2]
4188 let unsatisfied_req parent_pos req_name req_pos =
4189 let s1 = "Failure to satisfy requirement: " ^ strip_ns req_name in
4190 let s2 = "Required here" in
4191 if Pos.equal req_pos parent_pos then
4192 add (Typing.err_code Typing.UnsatisfiedReq) parent_pos s1
4193 else
4194 add_list
4195 (Typing.err_code Typing.UnsatisfiedReq)
4196 (parent_pos, s1)
4197 [(req_pos, s2)]
4199 let cyclic_class_def stack pos =
4200 let stack =
4201 SSet.fold
4202 ~f:(fun x y -> (strip_ns x |> Markdown_lite.md_codify) ^ " " ^ y)
4203 stack
4204 ~init:""
4207 (Typing.err_code Typing.CyclicClassDef)
4209 ("Cyclic class definition : " ^ stack)
4211 let cyclic_record_def names pos =
4212 let names =
4213 List.map ~f:(fun n -> strip_ns n |> Markdown_lite.md_codify) names
4216 (Typing.err_code Typing.CyclicRecordDef)
4218 (Printf.sprintf
4219 "Record inheritance cycle: %s"
4220 (String.concat ~sep:" " names))
4222 let trait_reuse_with_final_method use_pos trait_name parent_cls_name trace =
4223 let msg =
4224 Printf.sprintf
4225 "Traits with final methods cannot be reused, and `%s` is already used by `%s`."
4226 (strip_ns trait_name)
4227 (strip_ns parent_cls_name)
4229 add_list (Typing.err_code Typing.TraitReuse) (use_pos, msg) trace
4231 let trait_reuse p_pos p_name class_name trait =
4232 let (c_pos, c_name) = class_name in
4233 let c_name = strip_ns c_name |> Markdown_lite.md_codify in
4234 let trait = strip_ns trait |> Markdown_lite.md_codify in
4235 let err =
4236 "Class " ^ c_name ^ " reuses trait " ^ trait ^ " in its hierarchy"
4238 let err' =
4239 "It is already used through " ^ (strip_ns p_name |> Markdown_lite.md_codify)
4241 add_list (Typing.err_code Typing.TraitReuse) (c_pos, err) [(p_pos, err')]
4243 let trait_reuse_inside_class class_name trait occurrences =
4244 let (c_pos, c_name) = class_name in
4245 let c_name = strip_ns c_name |> Markdown_lite.md_codify in
4246 let trait = strip_ns trait |> Markdown_lite.md_codify in
4247 let err = "Class " ^ c_name ^ " uses trait " ^ trait ^ " multiple times" in
4248 add_list
4249 (Typing.err_code Typing.TraitReuseInsideClass)
4250 (c_pos, err)
4251 (List.map ~f:(fun p -> (p, "used here")) occurrences)
4253 let invalid_is_as_expression_hint op hint_pos reasons =
4254 add_list
4255 (Typing.err_code Typing.InvalidIsAsExpressionHint)
4256 (hint_pos, "Invalid " ^ Markdown_lite.md_codify op ^ " expression hint")
4257 (List.map reasons ~f:(fun (ty_pos, ty_str) ->
4258 ( ty_pos,
4259 "The "
4260 ^ Markdown_lite.md_codify op
4261 ^ " operator cannot be used with "
4262 ^ ty_str )))
4264 let invalid_enforceable_type kind_str (tp_pos, tp_name) targ_pos ty_info =
4265 let (ty_pos, ty_str) = List.hd_exn ty_info in
4266 add_list
4267 (Typing.err_code Typing.InvalidEnforceableTypeArgument)
4268 (targ_pos, "Invalid type")
4270 ( tp_pos,
4271 "Type "
4272 ^ kind_str
4273 ^ " "
4274 ^ Markdown_lite.md_codify tp_name
4275 ^ " was declared `__Enforceable` here" );
4276 (ty_pos, "This type is not enforceable because it has " ^ ty_str);
4279 let reifiable_attr attr_pos decl_kind decl_pos ty_info =
4280 let (ty_pos, ty_msg) = List.hd_exn ty_info in
4281 add_list
4282 (Typing.err_code Typing.DisallowPHPArraysAttr)
4283 (decl_pos, "Invalid " ^ decl_kind)
4285 (attr_pos, "This type constant has the `__Reifiable` attribute");
4286 (ty_pos, "It cannot contain " ^ ty_msg);
4289 let invalid_newable_type_argument (tp_pos, tp_name) ta_pos =
4290 add_list
4291 (Typing.err_code Typing.InvalidNewableTypeArgument)
4292 ( ta_pos,
4293 "A newable type argument must be a concrete class or a newable type parameter."
4296 ( tp_pos,
4297 "Type parameter "
4298 ^ Markdown_lite.md_codify tp_name
4299 ^ " was declared `__Newable` here" );
4302 let invalid_newable_type_param_constraints
4303 (tparam_pos, tparam_name) constraint_list =
4304 let partial =
4305 if List.is_empty constraint_list then
4306 "No constraints"
4307 else
4308 "The constraints "
4309 ^ String.concat ~sep:", " (List.map ~f:strip_ns constraint_list)
4311 let msg =
4312 "The type parameter "
4313 ^ Markdown_lite.md_codify tparam_name
4314 ^ " has the `<<__Newable>>` attribute. "
4315 ^ "Newable type parameters must be constrained with `as`, and exactly one of those constraints must be a valid newable class. "
4316 ^ "The class must either be final, or it must have the `<<__ConsistentConstruct>>` attribute or extend a class that has it. "
4317 ^ partial
4318 ^ " are valid newable classes"
4320 add (Typing.err_code Typing.InvalidNewableTypeParamConstraints) tparam_pos msg
4322 let override_final ~parent ~child ~(on_error : typing_error_callback option) =
4323 let msg1 = (child, "You cannot override this method") in
4324 let msg2 = (parent, "It was declared as final") in
4325 on_error_or_add on_error (Typing.err_code Typing.OverrideFinal) msg1 [msg2]
4327 let override_lsb ~member_name ~parent ~child (on_error : typing_error_callback)
4329 on_error
4330 ~code:(Typing.err_code Typing.OverrideLSB)
4331 ( child,
4332 "Member "
4333 ^ Markdown_lite.md_codify member_name
4334 ^ " may not override `__LSB` member of parent" )
4335 [(parent, "This is being overridden")]
4337 let should_be_override pos class_id id =
4339 (Typing.err_code Typing.ShouldBeOverride)
4341 (Printf.sprintf
4342 "%s has no parent class with a method %s to override"
4343 (strip_ns class_id |> Markdown_lite.md_codify)
4344 (Markdown_lite.md_codify id))
4346 let override_per_trait class_name meth_name trait_name m_pos =
4347 let (c_pos, c_name) = class_name in
4348 let err_msg =
4349 Printf.sprintf
4350 "`%s::%s` is marked `__Override` but `%s` does not define or inherit a `%s` method."
4351 (strip_ns trait_name)
4352 meth_name
4353 (strip_ns c_name)
4354 meth_name
4356 add_list
4357 (Typing.err_code Typing.OverridePerTrait)
4358 (c_pos, err_msg)
4360 (m_pos, "Declaration of " ^ Markdown_lite.md_codify meth_name ^ " is here");
4363 let missing_assign pos =
4364 add (Typing.err_code Typing.MissingAssign) pos "Please assign a value"
4366 let invalid_memoized_param pos ty_reason_msg =
4367 add_list
4368 (Typing.err_code Typing.InvalidMemoizedParam)
4369 ( pos,
4370 "Parameters to memoized function must be null, bool, int, float, string, an object deriving IMemoizeParam, or a Container thereof. See also http://docs.hhvm.com/hack/attributes/special#__memoize"
4372 ty_reason_msg
4374 let invalid_disposable_hint pos class_name =
4376 (Typing.err_code Typing.InvalidDisposableHint)
4378 ( "Parameter with type "
4379 ^ Markdown_lite.md_codify class_name
4380 ^ " must not implement `IDisposable` or `IAsyncDisposable`. "
4381 ^ "Please use `<<__AcceptDisposable>>` attribute or create disposable object with `using` statement instead."
4384 let invalid_disposable_return_hint pos class_name =
4386 (Typing.err_code Typing.InvalidDisposableReturnHint)
4388 ( "Return type "
4389 ^ Markdown_lite.md_codify class_name
4390 ^ " must not implement `IDisposable` or `IAsyncDisposable`. Please add `<<__ReturnDisposable>>` attribute."
4393 let xhp_required pos why_xhp ty_reason_msg =
4394 let msg = "An XHP instance was expected" in
4395 add_list
4396 (Typing.err_code Typing.XhpRequired)
4397 (pos, msg)
4398 ((pos, why_xhp) :: ty_reason_msg)
4400 let illegal_xhp_child pos ty_reason_msg =
4401 let msg = "XHP children must be compatible with XHPChild" in
4402 add_list (Typing.err_code Typing.IllegalXhpChild) (pos, msg) ty_reason_msg
4404 let missing_xhp_required_attr pos attr ty_reason_msg =
4405 let msg =
4406 "Required attribute " ^ Markdown_lite.md_codify attr ^ " is missing."
4408 add_list
4409 (Typing.err_code Typing.MissingXhpRequiredAttr)
4410 (pos, msg)
4411 ty_reason_msg
4413 let nullsafe_not_needed p nonnull_witness =
4414 add_list
4415 (Typing.err_code Typing.NullsafeNotNeeded)
4416 (p, "You are using the `?->` operator but this object cannot be null. ")
4417 nonnull_witness
4419 let generic_at_runtime p prefix =
4421 (Typing.err_code Typing.ErasedGenericAtRuntime)
4423 ( prefix
4424 ^ " generics can only be used in type hints because they do not exist at runtime."
4427 let generics_not_allowed p =
4429 (Typing.err_code Typing.GenericsNotAllowed)
4431 "Generics are not allowed in this position."
4433 let trivial_strict_eq p b left right left_trail right_trail =
4434 let msg = "This expression is always " ^ b in
4435 let left_trail = List.map left_trail typedef_trail_entry in
4436 let right_trail = List.map right_trail typedef_trail_entry in
4437 add_list
4438 (Typing.err_code Typing.TrivialStrictEq)
4439 (p, msg)
4440 (left @ left_trail @ right @ right_trail)
4442 let trivial_strict_not_nullable_compare_null p result type_reason =
4443 let msg = "This expression is always " ^ result in
4444 add_list
4445 (Typing.err_code Typing.NotNullableCompareNullTrivial)
4446 (p, msg)
4447 type_reason
4449 let eq_incompatible_types p left right =
4450 let msg = "This equality test has incompatible types" in
4451 add_list (Typing.err_code Typing.EqIncompatibleTypes) (p, msg) (left @ right)
4453 let comparison_invalid_types p left right =
4454 let msg =
4455 "This comparison has invalid types. Only comparisons in which both arguments are strings, nums, DateTime, or DateTimeImmutable are allowed"
4457 add_list
4458 (Typing.err_code Typing.ComparisonInvalidTypes)
4459 (p, msg)
4460 (left @ right)
4462 let void_usage p void_witness =
4463 let msg = "You are using the return value of a `void` function" in
4464 add_list (Typing.err_code Typing.VoidUsage) (p, msg) void_witness
4466 let noreturn_usage p noreturn_witness =
4467 let msg = "You are using the return value of a `noreturn` function" in
4468 add_list (Typing.err_code Typing.NoreturnUsage) (p, msg) noreturn_witness
4470 let attribute_too_few_arguments pos x n =
4471 let n = string_of_int n in
4473 (Typing.err_code Typing.AttributeTooFewArguments)
4475 ( "The attribute "
4476 ^ Markdown_lite.md_codify x
4477 ^ " expects at least "
4479 ^ " arguments" )
4481 let attribute_too_many_arguments pos x n =
4482 let n = string_of_int n in
4484 (Typing.err_code Typing.AttributeTooManyArguments)
4486 ( "The attribute "
4487 ^ Markdown_lite.md_codify x
4488 ^ " expects at most "
4490 ^ " arguments" )
4492 let attribute_param_type pos x =
4494 (Typing.err_code Typing.AttributeParamType)
4496 ("This attribute parameter should be " ^ x)
4498 let deprecated_use pos ?(pos_def = None) msg =
4499 let def_message =
4500 match pos_def with
4501 | Some pos_def -> [(pos_def, "Definition is here")]
4502 | None -> []
4504 add_list (Typing.err_code Typing.DeprecatedUse) (pos, msg) def_message
4506 let cannot_declare_constant kind pos (class_pos, class_name) =
4507 let kind_str =
4508 match kind with
4509 | `enum -> "an enum"
4510 | `trait -> "a trait"
4511 | `record -> "a record"
4513 add_list
4514 (Typing.err_code Typing.CannotDeclareConstant)
4515 (pos, "Cannot declare a constant in " ^ kind_str)
4517 ( class_pos,
4518 (strip_ns class_name |> Markdown_lite.md_codify)
4519 ^ " was defined as "
4520 ^ kind_str
4521 ^ " here" );
4524 let ambiguous_inheritance
4525 pos class_ origin error (on_error : typing_error_callback) =
4526 let { code; claim; reasons } = error in
4527 let origin = strip_ns origin in
4528 let class_ = strip_ns class_ in
4529 let message =
4530 "This declaration was inherited from an object of type "
4531 ^ Markdown_lite.md_codify origin
4532 ^ ". Redeclare this member in "
4533 ^ Markdown_lite.md_codify class_
4534 ^ " with a compatible signature."
4536 on_error ~code claim (reasons @ [(pos, message)])
4538 let multiple_concrete_defs
4539 child_pos
4540 parent_pos
4541 child_origin
4542 parent_origin
4543 name
4544 class_
4545 (on_error : typing_error_callback) =
4546 let child_origin = strip_ns child_origin in
4547 let parent_origin = strip_ns parent_origin in
4548 let class_ = strip_ns class_ in
4549 on_error
4550 ~code:(Typing.err_code Typing.MultipleConcreteDefs)
4551 ( child_pos,
4552 Markdown_lite.md_codify child_origin
4553 ^ " and "
4554 ^ Markdown_lite.md_codify parent_origin
4555 ^ " both declare ambiguous implementations of "
4556 ^ Markdown_lite.md_codify name
4557 ^ "." )
4559 ( child_pos,
4560 Markdown_lite.md_codify child_origin ^ "'s definition is here." );
4561 ( parent_pos,
4562 Markdown_lite.md_codify parent_origin ^ "'s definition is here." );
4563 ( child_pos,
4564 "Redeclare "
4565 ^ Markdown_lite.md_codify name
4566 ^ " in "
4567 ^ Markdown_lite.md_codify class_
4568 ^ " with a compatible signature." );
4571 let local_variable_modified_and_used pos_modified pos_used_l =
4572 let used_msg p = (p, "And accessed here") in
4573 add_list
4574 (Typing.err_code Typing.LocalVariableModifedAndUsed)
4575 ( pos_modified,
4576 "Unsequenced modification and access to local variable. Modified here" )
4577 (List.map pos_used_l used_msg)
4579 let local_variable_modified_twice pos_modified pos_modified_l =
4580 let modified_msg p = (p, "And also modified here") in
4581 add_list
4582 (Typing.err_code Typing.LocalVariableModifedTwice)
4583 (pos_modified, "Unsequenced modifications to local variable. Modified here")
4584 (List.map pos_modified_l modified_msg)
4586 let assign_during_case p =
4588 (Typing.err_code Typing.AssignDuringCase)
4590 "Don't assign to variables inside of case labels"
4592 let cyclic_enum_constraint pos =
4593 add (Typing.err_code Typing.CyclicEnumConstraint) pos "Cyclic enum constraint"
4595 let invalid_classname p =
4596 add (Typing.err_code Typing.InvalidClassname) p "Not a valid class name"
4598 let illegal_type_structure pos errmsg =
4599 let msg =
4600 "The two arguments to `type_structure()` must be:"
4601 ^ "\n - first: `ValidClassname::class` or an object of that class"
4602 ^ "\n - second: a single-quoted string literal containing the name"
4603 ^ " of a type constant of that class"
4604 ^ "\n"
4605 ^ errmsg
4607 add (Typing.err_code Typing.IllegalTypeStructure) pos msg
4609 let illegal_typeconst_direct_access pos =
4610 let msg =
4611 "Type constants cannot be directly accessed. "
4612 ^ "Use `type_structure(ValidClassname::class, 'TypeConstName')` instead"
4614 add (Typing.err_code Typing.IllegalTypeStructure) pos msg
4616 let override_no_default_typeconst pos_child pos_parent =
4617 add_list
4618 (Typing.err_code Typing.OverrideNoDefaultTypeconst)
4619 (pos_child, "This abstract type constant does not have a default type")
4621 ( pos_parent,
4622 "It cannot override an abstract type constant that has a default type"
4626 let inout_annotation_missing pos1 pos2 =
4627 let msg1 = (pos1, "This argument should be annotated with `inout`") in
4628 let msg2 = (pos2, "Because this is an `inout` parameter") in
4629 add_list (Typing.err_code Typing.InoutAnnotationMissing) msg1 [msg2]
4631 let inout_annotation_unexpected pos1 pos2 pos2_is_variadic =
4632 let msg1 = (pos1, "Unexpected `inout` annotation for argument") in
4633 let msg2 =
4634 ( pos2,
4635 if pos2_is_variadic then
4636 "A variadic parameter can never be `inout`"
4637 else
4638 "This is a normal parameter (does not have `inout`)" )
4640 add_list (Typing.err_code Typing.InoutAnnotationUnexpected) msg1 [msg2]
4642 let inoutness_mismatch pos1 pos2 (on_error : typing_error_callback) =
4643 let msg1 = (pos1, "This is an `inout` parameter") in
4644 let msg2 = (pos2, "It is incompatible with a normal parameter") in
4645 on_error ~code:(Typing.err_code Typing.InoutnessMismatch) msg1 [msg2]
4647 let invalid_new_disposable pos =
4648 let msg =
4649 "Disposable objects may only be created in a `using` statement or `return` from function marked `<<__ReturnDisposable>>`"
4651 add (Typing.err_code Typing.InvalidNewDisposable) pos msg
4653 let invalid_return_disposable pos =
4654 let msg =
4655 "Return expression must be new disposable in function marked `<<__ReturnDisposable>>`"
4657 add (Typing.err_code Typing.InvalidReturnDisposable) pos msg
4659 let nonreactive_function_call pos decl_pos callee_reactivity cause_pos_opt =
4660 add_list
4661 (Typing.err_code Typing.NonreactiveFunctionCall)
4662 (pos, "Reactive functions can only call other reactive functions.")
4663 ( [(decl_pos, "This function is " ^ callee_reactivity ^ ".")]
4664 @ Option.value_map cause_pos_opt ~default:[] ~f:(fun cause_pos ->
4666 ( cause_pos,
4667 "This argument caused function to be " ^ callee_reactivity ^ "."
4669 ]) )
4671 let nonpure_function_call pos decl_pos callee_reactivity =
4672 add_list
4673 (Typing.err_code Typing.NonpureFunctionCall)
4674 (pos, "Pure functions can only call other pure functions.")
4675 [(decl_pos, "This function is " ^ callee_reactivity ^ ".")]
4677 let nonreactive_call_from_shallow pos decl_pos callee_reactivity cause_pos_opt =
4678 add_list
4679 (Typing.err_code Typing.NonreactiveCallFromShallow)
4680 (pos, "Shallow reactive functions cannot call non-reactive functions.")
4681 ( [(decl_pos, "This function is " ^ callee_reactivity ^ ".")]
4682 @ Option.value_map cause_pos_opt ~default:[] ~f:(fun cause_pos ->
4684 ( cause_pos,
4685 "This argument caused function to be " ^ callee_reactivity ^ "."
4687 ]) )
4689 let rx_parameter_condition_mismatch
4690 cond pos def_pos (on_error : typing_error_callback) =
4691 on_error
4692 ~code:(Typing.err_code Typing.RxParameterConditionMismatch)
4693 ( pos,
4694 "This parameter does not satisfy "
4695 ^ cond
4696 ^ " condition defined on matching parameter in function super type." )
4697 [(def_pos, "This is parameter declaration from the function super type.")]
4699 let inout_argument_bad_type pos msgl =
4700 let msg =
4701 "Expected argument marked `inout` to be contained in a local or "
4702 ^ "a value-typed container (e.g. vec, dict, keyset, array). "
4703 ^ "To use `inout` here, assign to/from a temporary local variable."
4705 add_list (Typing.err_code Typing.InoutArgumentBadType) (pos, msg) msgl
4707 let ambiguous_lambda pos uses =
4708 let msg1 =
4709 "Lambda has parameter types that could not be determined at definition site."
4711 let msg2 =
4712 Printf.sprintf
4713 "%d distinct use types were determined: please add type hints to lambda parameters."
4714 (List.length uses)
4716 add_list
4717 (Typing.err_code Typing.AmbiguousLambda)
4718 (pos, msg1)
4719 ( (pos, msg2)
4720 :: List.map uses (fun (pos, ty) ->
4721 (pos, "This use has type " ^ Markdown_lite.md_codify ty)) )
4723 let wrong_expression_kind_attribute
4724 expr_kind pos attr attr_class_pos attr_class_name intf_name =
4725 let msg1 =
4726 Printf.sprintf
4727 "The %s attribute cannot be used on %s."
4728 (strip_ns attr |> Markdown_lite.md_codify)
4729 expr_kind
4731 let msg2 =
4732 Printf.sprintf
4733 "The attribute's class is defined here. To be available for use on %s, the %s class must implement %s."
4734 expr_kind
4735 (strip_ns attr_class_name |> Markdown_lite.md_codify)
4736 (strip_ns intf_name |> Markdown_lite.md_codify)
4738 add_list
4739 (Typing.err_code Typing.WrongExpressionKindAttribute)
4740 (pos, msg1)
4741 [(attr_class_pos, msg2)]
4743 let wrong_expression_kind_builtin_attribute expr_kind pos attr =
4744 let msg1 =
4745 Printf.sprintf
4746 "The %s attribute cannot be used on %s."
4747 (strip_ns attr |> Markdown_lite.md_codify)
4748 expr_kind
4750 add_list (Typing.err_code Typing.WrongExpressionKindAttribute) (pos, msg1) []
4752 let cannot_return_borrowed_value_as_immutable fun_pos value_pos =
4753 add_list
4754 (Typing.err_code Typing.CannotReturnBorrowedValueAsImmutable)
4755 ( fun_pos,
4756 "Values returned from reactive function by default are treated as immutable."
4759 ( value_pos,
4760 "This value is mutably borrowed and cannot be returned as immutable" );
4763 let decl_override_missing_hint pos (on_error : typing_error_callback) =
4764 on_error
4765 ~code:(Typing.err_code Typing.DeclOverrideMissingHint)
4766 ( pos,
4767 "When redeclaring class members, both declarations must have a typehint"
4771 let invalid_type_for_atmost_rx_as_rxfunc_parameter pos type_str =
4773 (Typing.err_code Typing.InvalidTypeForOnlyrxIfRxfuncParameter)
4775 ( "Parameter annotated with `<<__AtMostRxAsFunc>>` attribute must be function, now "
4776 ^ Markdown_lite.md_codify type_str
4777 ^ "." )
4779 let missing_annotation_for_atmost_rx_as_rxfunc_parameter pos =
4781 (Typing.err_code Typing.MissingAnnotationForOnlyrxIfRxfuncParameter)
4783 "Missing function type annotation on parameter marked with `<<__AtMostRxAsFunc>>` attribute."
4785 let superglobal_in_reactive_context pos name =
4787 (Typing.err_code Typing.SuperglobalInReactiveContext)
4789 ( "Superglobal "
4790 ^ Markdown_lite.md_codify name
4791 ^ " cannot be used in a reactive context." )
4793 let returns_void_to_rx_function_as_non_expression_statement pos fpos =
4794 add_list
4795 (Typing.err_code Typing.ReturnsVoidToRxAsNonExpressionStatement)
4796 ( pos,
4797 "Cannot use result of function annotated with `<<__ReturnsVoidToRx>>` in reactive context"
4799 [(fpos, "This is function declaration.")]
4801 let shapes_key_exists_always_true pos1 name pos2 =
4802 add_list
4803 (Typing.err_code Typing.ShapesKeyExistsAlwaysTrue)
4804 (pos1, "This `Shapes::keyExists()` check is always true")
4806 ( pos2,
4807 "The field "
4808 ^ Markdown_lite.md_codify name
4809 ^ " exists because of this definition" );
4812 let shape_field_non_existence_reason pos name = function
4813 | `Undefined ->
4815 ( pos,
4816 "The field "
4817 ^ Markdown_lite.md_codify name
4818 ^ " is not defined in this shape" );
4820 | `Nothing reason ->
4821 ( pos,
4822 "The type of the field "
4823 ^ Markdown_lite.md_codify name
4824 ^ " in this shape doesn't allow any values" )
4825 :: reason
4827 let shapes_key_exists_always_false pos1 name pos2 reason =
4828 add_list
4829 (Typing.err_code Typing.ShapesKeyExistsAlwaysFalse)
4830 (pos1, "This `Shapes::keyExists()` check is always false")
4831 @@ shape_field_non_existence_reason pos2 name reason
4833 let shapes_method_access_with_non_existent_field
4834 pos1 name pos2 method_name reason =
4835 add_list
4836 (Typing.err_code Typing.ShapesMethodAccessWithNonExistentField)
4837 ( pos1,
4838 "You are calling "
4839 ^ Markdown_lite.md_codify ("Shapes::" ^ method_name ^ "()")
4840 ^ " on a field known to not exist" )
4841 @@ shape_field_non_existence_reason pos2 name reason
4843 let shape_access_with_non_existent_field pos1 name pos2 reason =
4844 add_list
4845 (Typing.err_code Typing.ShapeAccessWithNonExistentField)
4846 (pos1, "You are accessing a field known to not exist")
4847 @@ shape_field_non_existence_reason pos2 name reason
4849 let ambiguous_object_access
4850 pos name self_pos vis subclass_pos class_self class_subclass =
4851 let class_self = strip_ns class_self in
4852 let class_subclass = strip_ns class_subclass in
4853 add_list
4854 (Typing.err_code Typing.AmbiguousObjectAccess)
4855 ( pos,
4856 "This object access to " ^ Markdown_lite.md_codify name ^ " is ambiguous"
4859 ( self_pos,
4860 "You will access the private instance declared in "
4861 ^ Markdown_lite.md_codify class_self );
4862 ( subclass_pos,
4863 "Instead of the "
4864 ^ vis
4865 ^ " instance declared in "
4866 ^ Markdown_lite.md_codify class_subclass );
4869 let invalid_traversable_in_rx pos =
4871 (Typing.err_code Typing.InvalidTraversableInRx)
4873 "Cannot traverse over non-reactive traversable in reactive code."
4875 let lateinit_with_default pos =
4877 (Typing.err_code Typing.LateInitWithDefault)
4879 "A late-initialized property cannot have a default value"
4881 let bad_lateinit_override
4882 parent_is_lateinit parent_pos child_pos (on_error : typing_error_callback) =
4883 let verb =
4884 if parent_is_lateinit then
4885 "is"
4886 else
4887 "is not"
4889 on_error
4890 ~code:(Typing.err_code Typing.BadLateInitOverride)
4891 ( child_pos,
4892 "Redeclared properties must be consistently declared `__LateInit`" )
4893 [(parent_pos, "The property " ^ verb ^ " declared `__LateInit` here")]
4895 let bad_xhp_attr_required_override
4896 parent_tag child_tag parent_pos child_pos (on_error : typing_error_callback)
4898 on_error
4899 ~code:(Typing.err_code Typing.BadXhpAttrRequiredOverride)
4900 (child_pos, "Redeclared attribute must not be less strict")
4902 ( parent_pos,
4903 "The attribute is "
4904 ^ parent_tag
4905 ^ ", which is stricter than "
4906 ^ child_tag );
4909 let invalid_switch_case_value_type case_value_p case_value_ty scrutinee_ty =
4910 add (Typing.err_code Typing.InvalidSwitchCaseValueType) case_value_p
4911 @@ Printf.sprintf
4912 "Switch statements use `==` equality, so comparing values of type %s with %s may not give the desired result."
4913 (case_value_ty |> Markdown_lite.md_codify)
4914 (scrutinee_ty |> Markdown_lite.md_codify)
4916 let unserializable_type pos message =
4918 (Typing.err_code Typing.UnserializableType)
4920 ( "Unserializable type (could not be converted to JSON and back again): "
4921 ^ message )
4923 let redundant_rx_condition pos =
4925 (Typing.err_code Typing.RedundantRxCondition)
4927 "Reactivity condition for this method is always true, consider removing it."
4929 let invalid_arraykey code pos (cpos, ctype) (kpos, ktype) =
4930 add_list
4931 (Typing.err_code code)
4932 (pos, "This value is not a valid key type for this container")
4934 (cpos, "This container is " ^ ctype);
4935 (kpos, String.capitalize ktype ^ " cannot be used as a key for " ^ ctype);
4938 let invalid_arraykey_read = invalid_arraykey Typing.InvalidArrayKeyRead
4940 let invalid_arraykey_write = invalid_arraykey Typing.InvalidArrayKeyWrite
4942 let invalid_sub_string pos ty =
4943 add (Typing.err_code Typing.InvalidSubString) pos
4944 @@ "Expected an object convertible to string but got "
4945 ^ ty
4947 let typechecker_timeout (pos, fun_name) seconds =
4949 (Typing.err_code Typing.TypecheckerTimeout)
4951 (Printf.sprintf
4952 "Type checker timed out after %d seconds whilst checking function %s"
4953 seconds
4954 fun_name)
4956 let unresolved_type_variable pos =
4958 (Typing.err_code Typing.UnresolvedTypeVariable)
4960 "The type of this expression contains an unresolved type variable"
4962 let invalid_arraykey_constraint pos t =
4964 (Typing.err_code Typing.InvalidArrayKeyConstraint)
4966 ( "This type is "
4968 ^ ", which cannot be used as an arraykey (string | int)" )
4970 let exception_occurred pos e =
4971 let pos_str = pos |> Pos.to_absolute |> Pos.string in
4972 HackEventLogger.type_check_exn_bug ~path:(Pos.filename pos) ~pos:pos_str ~e;
4973 Hh_logger.error
4974 "Exception while typechecking at position %s\n%s"
4975 pos_str
4976 (Exception.to_string e);
4978 (Typing.err_code Typing.ExceptionOccurred)
4980 (Printf.sprintf
4981 "An exception occurred while typechecking this. %s"
4982 Error_message_sentinel.please_file_a_bug_message)
4984 let redundant_covariant pos msg suggest =
4986 (Typing.err_code Typing.RedundantGeneric)
4988 ( "This generic parameter is redundant because it only appears in a covariant (output) position"
4989 ^ msg
4990 ^ ". Consider replacing uses of generic parameter with "
4991 ^ Markdown_lite.md_codify suggest
4992 ^ " or specifying `<<__Explicit>>` on the generic parameter" )
4994 let meth_caller_trait pos trait_name =
4996 (Typing.err_code Typing.MethCallerTrait)
4998 ( (strip_ns trait_name |> Markdown_lite.md_codify)
4999 ^ " is a trait which cannot be used with `meth_caller`. Use a class instead."
5002 let duplicate_interface pos name others =
5003 add_list
5004 (Typing.err_code Typing.DuplicateInterface)
5005 ( pos,
5006 Printf.sprintf
5007 "Interface %s is used more than once in this declaration."
5008 (strip_ns name |> Markdown_lite.md_codify) )
5009 (List.map others (fun pos -> (pos, "Here is another occurrence")))
5011 let hk_var_description because_nested var_name =
5012 if because_nested then
5013 Markdown_lite.md_codify var_name
5014 ^ " is a generic parameter of another (higher-kinded) generic parameter. "
5015 else
5016 Markdown_lite.md_codify var_name
5017 ^ " is a higher-kinded type parameter, standing for a type that has type parameters itself. "
5019 let unsupported_hk_feature ~because_nested pos var_name feature_description =
5020 let var_description = hk_var_description because_nested var_name in
5022 (Naming.err_code Naming.HigherKindedTypesUnsupportedFeature)
5024 ( var_description
5025 ^ "We don't support "
5026 ^ feature_description
5027 ^ " parameters like "
5028 ^ Markdown_lite.md_codify var_name
5029 ^ "." )
5031 let tparam_non_shadowing_reuse pos var_name =
5033 (Typing.err_code Typing.TypeParameterNameAlreadyUsedNonShadow)
5035 ( "The name "
5036 ^ Markdown_lite.md_codify var_name
5037 ^ " was already used for another generic parameter. Please use a different name to avoid confusion."
5040 let illegal_information_flow
5041 primary secondaries (source_poss, source) (sink_poss, sink) =
5042 let explain poss node printer reasons =
5043 let msg = printer node in
5044 List.map ~f:(fun pos -> (pos, msg)) poss @ reasons
5046 let source = Markdown_lite.md_codify source in
5047 let sink = Markdown_lite.md_codify sink in
5048 let sprintf_main = sprintf "Data with policy %s appears in context %s." in
5049 let claim = (primary, sprintf_main source sink) in
5050 let reasons =
5051 let sprintf = Printf.sprintf in
5052 let sprintf_source = sprintf "This may be the data source with policy %s" in
5053 let sprintf_sink = sprintf "This may be the data sink with policy %s" in
5054 let other_occurrences =
5055 let f p = (p, "Another program point contributing to the illegal flow") in
5056 List.map ~f secondaries
5059 |> explain source_poss source sprintf_source
5060 |> explain sink_poss sink sprintf_sink
5061 |> List.append other_occurrences
5062 |> List.rev
5064 add_list (Typing.err_code Typing.IllegalInformationFlow) claim reasons
5066 let context_implicit_policy_leakage
5067 primary secondaries (source_poss, source) (sink_poss, sink) =
5068 let program_point p =
5069 (p, "Another program point contributing to the leakage")
5071 let explain_source p = (p, "Leakage source") in
5072 let explain_sink p = (p, "Leakage sink") in
5073 let claim =
5074 ( primary,
5075 Printf.sprintf
5076 "Context-implicit policy leaks into %s via %s."
5077 (Markdown_lite.md_codify sink)
5078 (Markdown_lite.md_codify source) )
5080 let reasons =
5081 List.map ~f:program_point secondaries
5082 @ List.map ~f:explain_source source_poss
5083 @ List.map ~f:explain_sink sink_poss
5085 add_list (Typing.err_code Typing.ContextImplicitPolicyLeakage) claim reasons
5087 let unknown_information_flow pos str =
5089 (Typing.err_code Typing.UnknownInformationFlow)
5091 ("Unable to analyze information flow for " ^ str ^ ". This might be unsafe.")
5093 let reified_function_reference call_pos =
5095 (Typing.err_code Typing.ReifiedFunctionReference)
5096 call_pos
5097 "Invalid function reference. This function requires reified generics. Prefer using a lambda instead."
5099 let class_meth_abstract_call cname meth_name call_pos decl_pos =
5100 let cname = strip_ns cname in
5101 add_list
5102 (Typing.err_code Typing.ClassMethAbstractCall)
5103 ( call_pos,
5104 "Cannot create a class_meth of "
5105 ^ cname
5106 ^ "::"
5107 ^ meth_name
5108 ^ "; it is abstract." )
5109 [(decl_pos, "Declaration is here")]
5111 let higher_kinded_partial_application pos count =
5113 (Naming.err_code Naming.HigherKindedTypesUnsupportedFeature)
5115 ( "A higher-kinded type is expected here."
5116 ^ " We do not not support partial applications to yield higher-kinded types, but you are providing "
5117 ^ string_of_int count
5118 ^ " type argument(s)." )
5120 let wildcard_for_higher_kinded_type pos =
5122 (Naming.err_code Naming.HigherKindedTypesUnsupportedFeature)
5124 ( "You are supplying _ where a higher-kinded type is expected."
5125 ^ " We cannot infer higher-kinded type arguments at this time, please state the actual type."
5128 let implicit_type_argument_for_higher_kinded_type ~use_pos ~def_pos param_name =
5129 let param_desc =
5130 (* This should be Naming_special_names.Typehints.wildcard, but its not available in this
5131 module *)
5132 if String.equal param_name "_" then
5133 "the anonymous generic parameter"
5134 else
5135 "the generic parameter " ^ param_name
5137 add_list
5138 (Naming.err_code Naming.HigherKindedTypesUnsupportedFeature)
5139 ( use_pos,
5140 "You left out the type arguments here such that they may be inferred."
5141 ^ " However, a higher-kinded type is expected in place of "
5142 ^ param_desc
5143 ^ ", meaning that the type arguments cannot be inferred."
5144 ^ " Please provide the type arguments explicitly." )
5145 [(def_pos, param_desc ^ " was declared to be higher-kinded here.")]
5147 (* This is only to be used in a context where we expect something higher-kinded,
5148 meaning that expected_kind_repr should never just be * *)
5149 let kind_mismatch
5150 ~use_pos ~def_pos ~tparam_name ~expected_kind_repr ~actual_kind_repr =
5151 add_list
5152 (Typing.err_code Typing.KindMismatch)
5153 ( use_pos,
5154 "This is "
5155 ^ actual_kind_repr
5156 ^ ", but "
5157 ^ expected_kind_repr
5158 ^ " was expected here." )
5160 ( def_pos,
5161 "We are expecting "
5162 ^ expected_kind_repr
5163 ^ " due to the definition of "
5164 ^ tparam_name
5165 ^ " here." );
5168 let class_with_constraints_used_as_hk_type use_pos class_name =
5170 (Naming.err_code Naming.HigherKindedTypesUnsupportedFeature)
5171 use_pos
5172 ( "The class "
5173 ^ strip_ns class_name
5174 ^ " imposes constraints on some of its type parameters. Classes that do this cannot be used as higher-kinded types at this time."
5177 let alias_with_implicit_constraints_as_hk_type
5178 ~use_pos
5179 ~typedef_pos
5180 ~used_class_in_def_pos
5181 ~typedef_name
5182 ~typedef_tparam_name
5183 ~used_class_in_def_name
5184 ~used_class_tparam_name =
5185 add_list
5186 (Naming.err_code Naming.HigherKindedTypesUnsupportedFeature)
5187 ( use_pos,
5188 "The type "
5189 ^ strip_ns typedef_name
5190 ^ " implicitly imposes constraints on its type parameters. Therefore, it cannot be used as a higher-kinded type at this time."
5193 (typedef_pos, "The definition of " ^ strip_ns typedef_name ^ " is here.");
5194 ( used_class_in_def_pos,
5195 "The definition of "
5196 ^ strip_ns typedef_name
5197 ^ " relies on "
5198 ^ strip_ns used_class_in_def_name
5199 ^ " and the constraints that "
5200 ^ strip_ns used_class_in_def_name
5201 ^ " imposes on its type parameter "
5202 ^ strip_ns used_class_tparam_name
5203 ^ " then become implicit constraints on the type parameter "
5204 ^ typedef_tparam_name
5205 ^ " of "
5206 ^ strip_ns typedef_name
5207 ^ "." );
5210 let reinheriting_classish_const
5211 dest_classish_pos
5212 dest_classish_name
5213 src_classish_pos
5214 src_classish_name
5215 existing_const_origin
5216 const_name =
5217 add_list
5218 (Typing.err_code Typing.RedeclaringClassishConstant)
5219 ( src_classish_pos,
5220 strip_ns dest_classish_name
5221 ^ " cannot re-inherit constant "
5222 ^ const_name
5223 ^ " from "
5224 ^ src_classish_name )
5226 ( dest_classish_pos,
5227 "because it already inherited it via " ^ strip_ns existing_const_origin
5231 let redeclaring_classish_const
5232 classish_pos
5233 classish_name
5234 redeclaration_pos
5235 existing_const_origin
5236 const_name =
5237 add_list
5238 (Typing.err_code Typing.RedeclaringClassishConstant)
5239 ( redeclaration_pos,
5240 strip_ns classish_name ^ " cannot re-declare constant " ^ const_name )
5242 ( classish_pos,
5243 "because it already inherited it via " ^ strip_ns existing_const_origin
5247 let incompatible_enum_inclusion_base
5248 dest_classish_pos dest_classish_name src_classish_name =
5249 add_list
5250 (Typing.err_code Typing.IncompatibleEnumInclusion)
5251 ( dest_classish_pos,
5252 "Enum "
5253 ^ strip_ns dest_classish_name
5254 ^ " includes enum "
5255 ^ strip_ns src_classish_name
5256 ^ " but their base types are incompatible" )
5259 let incompatible_enum_inclusion_constraint
5260 dest_classish_pos dest_classish_name src_classish_name =
5261 add_list
5262 (Typing.err_code Typing.IncompatibleEnumInclusion)
5263 ( dest_classish_pos,
5264 "Enum "
5265 ^ strip_ns dest_classish_name
5266 ^ " includes enum "
5267 ^ strip_ns src_classish_name
5268 ^ " but their constraints are incompatible" )
5271 let enum_inclusion_not_enum
5272 dest_classish_pos dest_classish_name src_classish_name =
5273 add_list
5274 (Typing.err_code Typing.IncompatibleEnumInclusion)
5275 ( dest_classish_pos,
5276 "Enum "
5277 ^ strip_ns dest_classish_name
5278 ^ " includes "
5279 ^ strip_ns src_classish_name
5280 ^ " which is not an enum" )
5283 (* This is meant for subtyping functions with incompatible coeffects, i.e.
5284 * (function ()[io]: void) </: (function ()[]: void) *)
5285 let coeffect_subtyping_error
5286 pos_expected cap_expected pos_got cap_got (on_error : typing_error_callback)
5288 on_error
5289 ~code:(Typing.err_code Typing.SubtypeCoeffects)
5290 (pos_expected, "Expected a function that requires " ^ cap_expected)
5291 [(pos_got, "But got a function that requires " ^ cap_got)]
5293 let call_coeffect_error
5294 ~available_incl_unsafe ~available_pos ~required ~required_pos call_pos =
5295 add_list
5296 (Typing.err_code Typing.CallCoeffects)
5297 ( call_pos,
5298 "This call is not allowed because its coeffects are incompatible with the context"
5301 ( available_pos,
5302 "From this declaration, the context of this function body provides "
5303 ^ available_incl_unsafe );
5304 (required_pos, "But the function being called requires " ^ required);
5307 let op_coeffect_error
5308 ~locally_available ~available_pos ~err_code ~required op op_pos =
5309 add_list
5310 err_code
5311 ( op_pos,
5312 op ^ " requires " ^ required ^ ", which is not provided by the context."
5315 ( available_pos,
5316 "The local (enclosing) context provides " ^ locally_available );
5319 let abstract_function_pointer cname meth_name call_pos decl_pos =
5320 let cname = strip_ns cname in
5321 add_list
5322 (Typing.err_code Typing.AbstractFunctionPointer)
5323 ( call_pos,
5324 "Cannot create a function pointer to "
5325 ^ Markdown_lite.md_codify (cname ^ "::" ^ meth_name)
5326 ^ "; it is abstract" )
5327 [(decl_pos, "Declaration is here")]
5329 let unnecessary_attribute pos ~attr ~reason ~suggestion =
5330 let attr = strip_ns attr in
5331 let (reason_pos, reason_msg) = reason in
5332 let suggestion =
5333 match suggestion with
5334 | None -> "Try deleting this attribute"
5335 | Some s -> s
5337 add_list
5338 (Typing.err_code Typing.UnnecessaryAttribute)
5339 (pos, sprintf "The attribute `%s` is unnecessary" attr)
5340 [(reason_pos, "It is unnecessary because " ^ reason_msg); (pos, suggestion)]
5342 let inherited_class_member_with_different_case
5343 member_type name name_prev p child_class prev_class prev_class_pos =
5344 let name = strip_ns name in
5345 let name_prev = strip_ns name_prev in
5346 let child_class = strip_ns child_class in
5347 let prev_class = strip_ns prev_class in
5348 let claim =
5349 ( p,
5350 child_class
5351 ^ " inherits a "
5352 ^ member_type
5353 ^ " named "
5354 ^ Markdown_lite.md_codify name_prev
5355 ^ " which differs from this one ("
5356 ^ name
5357 ^ ") only by case." )
5359 let reasons =
5361 ( prev_class_pos,
5362 "It was inherited from "
5363 ^ prev_class
5364 ^ " as "
5365 ^ (highlight_differences name name_prev |> Markdown_lite.md_codify)
5366 ^ ". If you meant to override it, please use the same casing as the inherited "
5367 ^ member_type
5368 ^ "."
5369 ^ " Otherwise, please choose a different name for the new method." );
5372 add_list (Typing.err_code Typing.InheritedMethodCaseDiffers) claim reasons
5374 let multiple_inherited_class_member_with_different_case
5375 ~member_type ~name1 ~name2 ~class1 ~class2 ~child_class ~child_p ~p1 ~p2 =
5376 let name1 = strip_ns name1 in
5377 let name2 = strip_ns name2 in
5378 let class1 = strip_ns class1 in
5379 let class2 = strip_ns class2 in
5380 let child_class = strip_ns child_class in
5381 let claim =
5382 ( child_p,
5383 Markdown_lite.md_codify child_class
5384 ^ " inherited two versions of the "
5385 ^ member_type
5386 ^ " "
5387 ^ Markdown_lite.md_codify name1
5388 ^ " that differ only by case." )
5390 let reasons =
5392 ( p1,
5393 "It inherited "
5394 ^ Markdown_lite.md_codify name1
5395 ^ " from "
5396 ^ class1
5397 ^ " here." );
5398 ( p2,
5399 "And "
5400 ^ Markdown_lite.md_codify name2
5401 ^ " from "
5402 ^ class2
5403 ^ " here. Please rename these methods to the same casing." );
5406 add_list (Typing.err_code Typing.InheritedMethodCaseDiffers) claim reasons
5408 let atom_invalid_parameter pos =
5409 add_list
5410 (Typing.err_code Typing.AtomInvalidParameter)
5411 ( pos,
5412 "Attribute "
5413 ^ Naming_special_names.UserAttributes.uaAtom
5414 ^ " is only allowed on "
5415 ^ Naming_special_names.Classes.cMemberOf )
5418 let atom_invalid_parameter_in_enum_class pos =
5419 add_list
5420 (Typing.err_code Typing.AtomInvalidParameter)
5421 ( pos,
5422 "When using "
5423 ^ Naming_special_names.UserAttributes.uaAtom
5424 ^ ", only type parameters bounded by enum classes and "
5425 ^ "enum classes are allowed as the first parameters of "
5426 ^ Naming_special_names.Classes.cMemberOf )
5429 let atom_invalid_generic pos name =
5430 add_list
5431 (Typing.err_code Typing.AtomInvalidParameter)
5432 ( pos,
5433 "The type "
5434 ^ name
5435 ^ " must be a type constant or a reified generic "
5436 ^ "in order to be used with "
5437 ^ Naming_special_names.UserAttributes.uaAtom )
5440 let atom_unknown pos atom_name class_name =
5441 let class_name = strip_ns class_name in
5442 add_list
5443 (Typing.err_code Typing.AtomUnknown)
5444 (pos, "Unknown constant " ^ atom_name ^ " in " ^ class_name)
5447 let atom_as_expr pos =
5448 add_list
5449 (Typing.err_code Typing.AtomAsExpression)
5450 ( pos,
5451 "Atoms are not allowed in this position. They are only allowed "
5452 ^ "in function call, if the function parameter is annotated with "
5453 ^ Naming_special_names.UserAttributes.uaAtom )
5456 let atom_invalid_argument pos =
5457 add_list
5458 (Typing.err_code Typing.AtomInvalidArgument)
5459 (pos, "An atom is required here, not a class constant projection")
5462 let ifc_internal_error pos reason =
5464 (Typing.err_code Typing.IFCInternalError)
5466 ( "IFC Internal Error: "
5467 ^ reason
5468 ^ ". If you see this error and aren't expecting it, please `hh rage` and let the Hack team know."
5471 let parent_implements_dynamic
5473 (child_name, child_kind)
5474 (parent_name, parent_kind)
5475 child_implements_dynamic =
5476 let kind_to_strings = function
5477 | Ast_defs.Cabstract
5478 | Ast_defs.Cnormal ->
5479 ("class ", "implement ")
5480 | Ast_defs.Ctrait -> ("trait ", "implement ")
5481 | Ast_defs.Cinterface -> ("interface ", "extend ")
5482 | Ast_defs.Cenum -> (* cannot happen *) ("", "")
5484 let kinds_to_use child_kind parent_kind =
5485 match (child_kind, parent_kind) with
5486 | (_, Ast_defs.Cabstract)
5487 | (_, Ast_defs.Cnormal) ->
5488 "extends "
5489 | (_, Ast_defs.Ctrait) -> "uses "
5490 | (Ast_defs.Cinterface, Ast_defs.Cinterface) -> "extends "
5491 | (_, Ast_defs.Cinterface) -> "implements "
5492 | (_, _) -> ""
5494 let child_name = strip_ns child_name in
5495 let (child_kind_s, action) = kind_to_strings child_kind in
5496 let parent_name = strip_ns parent_name in
5497 let (parent_kind_s, _) = kind_to_strings parent_kind in
5499 (Typing.err_code Typing.ImplementsDynamic)
5501 ( String.capitalize child_kind_s
5502 ^ child_name
5503 ^ ( if child_implements_dynamic then
5504 " cannot "
5505 else
5506 " must " )
5507 ^ action
5508 ^ "dynamic because it "
5509 ^ kinds_to_use child_kind parent_kind
5510 ^ parent_kind_s
5511 ^ parent_name
5512 ^ " which does"
5514 if child_implements_dynamic then
5515 " not"
5516 else
5517 "" )
5519 let method_is_not_dynamically_callable pos method_name class_name =
5520 let class_name = strip_ns class_name in
5522 (Typing.err_code Typing.ImplementsDynamic)
5524 ( "Class "
5525 ^ class_name
5526 ^ " cannot implement dynamic because method "
5527 ^ method_name
5528 ^ " is not dynamically callable" )
5530 (*****************************************************************************)
5531 (* Printing *)
5532 (*****************************************************************************)
5534 let to_json (error : Pos.absolute error_) =
5535 let (error_code, msgl) = (get_code error, to_list error) in
5536 let elts =
5537 List.map msgl (fun (p, w) ->
5538 let (line, scol, ecol) = Pos.info_pos p in
5539 Hh_json.JSON_Object
5541 ("descr", Hh_json.JSON_String w);
5542 ("path", Hh_json.JSON_String (Pos.filename p));
5543 ("line", Hh_json.int_ line);
5544 ("start", Hh_json.int_ scol);
5545 ("end", Hh_json.int_ ecol);
5546 ("code", Hh_json.int_ error_code);
5549 Hh_json.JSON_Object [("message", Hh_json.JSON_Array elts)]
5551 let convert_errors_to_string ?(include_filename = false) (errors : error list) :
5552 string list =
5553 List.fold_right
5554 ~init:[]
5555 ~f:(fun err acc_out ->
5556 List.fold_right
5557 ~init:acc_out
5558 ~f:(fun (pos, msg) acc_in ->
5559 let result = Format.asprintf "%a %s" Pos.pp pos msg in
5560 if include_filename then
5561 let full_result =
5562 Printf.sprintf
5563 "%s %s"
5564 (Pos.to_absolute pos |> Pos.filename)
5565 result
5567 full_result :: acc_in
5568 else
5569 result :: acc_in)
5570 (to_list err))
5571 errors
5573 (*****************************************************************************)
5574 (* Try if errors. *)
5575 (*****************************************************************************)
5577 let try_ f1 f2 = try_with_result f1 (fun _ err -> f2 err)
5579 let try_with_error f1 f2 =
5580 try_ f1 (fun error ->
5581 add_error error;
5582 f2 ())
5584 let has_no_errors (f : unit -> 'a) : bool =
5585 try_
5586 (fun () ->
5587 let _ = f () in
5588 true)
5589 (fun _ -> false)
5591 (*****************************************************************************)
5592 (* Do. *)
5593 (*****************************************************************************)
5595 let ignore_ f =
5596 let allow_errors_in_default_path_copy = !allow_errors_in_default_path in
5597 set_allow_errors_in_default_path true;
5598 let (_, result) = do_ f in
5599 set_allow_errors_in_default_path allow_errors_in_default_path_copy;
5600 result
5602 let try_when f ~when_ ~do_ =
5603 try_with_result f (fun result error ->
5604 if when_ () then
5605 do_ error
5606 else
5607 add_error error;
5608 result)