diff --git a/CHANGES.md b/CHANGES.md index 5bc1d3ede65..b0f8346517a 100644 --- a/CHANGES.md +++ b/CHANGES.md @@ -12,6 +12,9 @@ - Fix RPC buffer corruption issues due to multi threading. This issue was only reproducible with large RPC payloads (#7418) +- Fix printing errors from excerpts whenever character offsets span multiple + lines (#7950, fixes #7905, @rgrinberg) + 3.8.1 (2023-06-05) ------------------ diff --git a/otherlibs/stdune/src/loc.ml b/otherlibs/stdune/src/loc.ml index 81137bbd1d5..ecfa72eced1 100644 --- a/otherlibs/stdune/src/loc.ml +++ b/otherlibs/stdune/src/loc.ml @@ -57,21 +57,24 @@ let pp_file_excerpt ~context_lines ~max_lines_to_print_in_full { start; stop } : let stop_c = stop.pos_cnum - start.pos_bol in let file = start.pos_fname in let pp_file_excerpt () = - let line_num = start.pos_lnum in - let line_num_str = string_of_int line_num in - let padding_width = String.length line_num_str in let open Result.O in - let* line = - Result.try_with (fun () -> Io.String_path.file_line file line_num) - in - if stop_c <= String.length line then + match + if start.pos_lnum <> stop.pos_lnum then `Multiline else `Singleline + with + | `Singleline -> + let line_num = start.pos_lnum in + let line_num_str = string_of_int line_num in + let padding_width = String.length line_num_str in + let* line = + Result.try_with (fun () -> Io.String_path.file_line file line_num) + in let len = stop_c - start_c in let open Pp.O in Ok (pp_line padding_width (line_num_str, line) ++ pp_left_pad (stop_c + padding_width + 3) (String.make len '^') ++ Pp.newline) - else + | `Multiline -> let get_padding lines = let lnum, _ = Option.value_exn (List.last lines) in String.length lnum diff --git a/otherlibs/stdune/test/loc_tests.ml b/otherlibs/stdune/test/loc_tests.ml new file mode 100644 index 00000000000..081e12960ad --- /dev/null +++ b/otherlibs/stdune/test/loc_tests.ml @@ -0,0 +1,24 @@ +open Stdune + +let%expect_test "#7905 - inverted char offsets" = + let dir = Temp.create Dir ~prefix:"" ~suffix:"loc" in + let file = Path.relative dir "file.ml" in + Io.write_file file {| +type t = A | B + +let f () () = function + | A -> () +|}; + let pos_fname = Path.to_string file in + let start = { Lexing.pos_fname; pos_lnum = 4; pos_bol = 0; pos_cnum = 14 } in + let stop = { start with pos_lnum = 5; pos_cnum = 11 } in + let loc = { Loc.start; stop } in + Format.printf "%a@." Pp.to_fmt (Loc.pp loc); + let output = + [%expect.output] |> String.split_lines |> List.tl |> String.concat ~sep:"\n" + in + Temp.destroy Dir file; + print_endline output; + [%expect {| + 4 | let f () () = function + 5 | | A -> () |}]