Skip to content

Commit

Permalink
[3.8] backport #7949 and #7950 (#7975)
Browse files Browse the repository at this point in the history
* test: reproduce #7905 (#7949)

Signed-off-by: Rudi Grinberg <[email protected]>

* fix: correctly print multi-line excerpts (#7950)

The previous code would pretend that a multi-line excerpt was
single-line whenever the stop character was outside the line.

Fixes #7905

Signed-off-by: Rudi Grinberg <[email protected]>

---------

Signed-off-by: Rudi Grinberg <[email protected]>
Co-authored-by: Rudi Grinberg <[email protected]>
  • Loading branch information
emillon and rgrinberg authored Jun 16, 2023
1 parent 886ff3b commit 1405390
Show file tree
Hide file tree
Showing 3 changed files with 38 additions and 8 deletions.
3 changes: 3 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -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)
------------------

Expand Down
19 changes: 11 additions & 8 deletions otherlibs/stdune/src/loc.ml
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
24 changes: 24 additions & 0 deletions otherlibs/stdune/test/loc_tests.ml
Original file line number Diff line number Diff line change
@@ -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 -> () |}]

0 comments on commit 1405390

Please sign in to comment.