Skip to content

Commit

Permalink
fix(lsp): [abs_pos] computing in [String_zipper.drop_until]
Browse files Browse the repository at this point in the history
  • Loading branch information
emilienlemaire authored and rgrinberg committed May 17, 2024
1 parent e6bd16f commit c253a1f
Show file tree
Hide file tree
Showing 3 changed files with 10 additions and 5 deletions.
5 changes: 3 additions & 2 deletions lsp/src/string_zipper.ml
Original file line number Diff line number Diff line change
Expand Up @@ -183,8 +183,9 @@ let rec prev_newline t =
})

let beginning_of_line t =
let line = t.line in
let t = prev_newline t in
if is_begin t then t else advance_char t
if is_begin t && t.line = line then t else advance_char t

let rec goto_line_backward t = function
| 0 -> beginning_of_line t
Expand Down Expand Up @@ -292,7 +293,7 @@ let drop_until from until =
| [] -> empty
| current :: left ->
let rel_pos = Substring.length current in
let abs_pos = from.rel_pos + rel_pos in
let abs_pos = from.abs_pos + rel_pos in
{ from with right; left; current; rel_pos; abs_pos })

let add_buffer_between b start stop =
Expand Down
4 changes: 2 additions & 2 deletions lsp/test/text_document_tests.ml
Original file line number Diff line number Diff line change
Expand Up @@ -248,7 +248,7 @@ let%expect_test "replace second line first line is \\n" =
let newDoc = Text_document.apply_text_document_edits doc [ edit ] in
newDoc |> Text_document.text |> String.escaped |> print_endline;
[%expect {|
\nfochange\nfoo\nbar\nbaz\n |}]
\nfochangeo\nbar\nbaz\n |}]

let%expect_test "get position after change" =
let range = tuple_range (1, 2) (1, 2) in
Expand All @@ -260,4 +260,4 @@ let%expect_test "get position after change" =
printf "pos: %d\n" pos;
[%expect {|
\nfochangeo\nbar\nbaz\n
pos: 19 |}]
pos: 22 |}]
6 changes: 5 additions & 1 deletion ocaml-lsp-server/test/e2e-new/action_mark_remove.ml
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,11 @@ let%expect_test "mark value in top level let" =
let $f$ =
let x = 1 in
0
|}
|};
[%expect {|
let _f =
let x = 1 in
0 |}]

let%expect_test "mark value in match" =
mark_test `Value {|
Expand Down

0 comments on commit c253a1f

Please sign in to comment.