Skip to content

Commit

Permalink
Merge 14edf05 into 88333f9
Browse files Browse the repository at this point in the history
  • Loading branch information
rgrinberg committed May 8, 2023
2 parents 88333f9 + 14edf05 commit 05847fc
Show file tree
Hide file tree
Showing 3 changed files with 69 additions and 4 deletions.
15 changes: 15 additions & 0 deletions lsp/src/text_document.ml
Expand Up @@ -105,6 +105,21 @@ let apply_text_document_edits t (edits : TextEdit.t list) =
let zipper = String_zipper.of_string text in
{ t with text = Some text; zipper }

let absolute_position t pos =
String_zipper.goto_position t.zipper pos t.position_encoding
|> String_zipper.offset

let absolute_range t (range : Range.t) =
let zipper =
String_zipper.goto_position t.zipper range.start t.position_encoding
in
let start = String_zipper.offset zipper in
let zipper =
String_zipper.goto_position zipper range.end_ t.position_encoding
in
let stop = String_zipper.offset zipper in
(start, stop)

module Expert = struct
let goto t pos =
let zipper = String_zipper.goto_position t.zipper pos `UTF8 in
Expand Down
20 changes: 17 additions & 3 deletions lsp/src/text_document.mli
Expand Up @@ -2,14 +2,18 @@ open Types

type t

val make :
position_encoding:[ `UTF8 | `UTF16 ] -> DidOpenTextDocumentParams.t -> t
type encoding :=
[ `UTF8
| `UTF16
]

val make : position_encoding:encoding -> DidOpenTextDocumentParams.t -> t

val languageId : t -> string

val documentUri : t -> Uri0.t

val position_encoding : t -> [ `UTF16 | `UTF8 ]
val position_encoding : t -> encoding

val version : t -> int

Expand All @@ -31,6 +35,16 @@ val set_version : t -> version:int -> t
interpreted relative to the original document. *)
val apply_text_document_edits : t -> TextEdit.t list -> t

(** [absolute_position t pos] returns the absolute position of [pos] inside
[text t]. If the position is outside the bounds of the document, the offset
returned will be the length of the document. [pos] is interpreted with
[position_encoding t] *)
val absolute_position : t -> Position.t -> int

(* [absolute_range t range] same as [(absolute_position t range.start ,
absolute_position t range.end_)] but possibly faster *)
val absolute_range : t -> Range.t -> int * int

module Expert : sig
(** These functions allow one to work with the underlying zipper. This gives
the opportunity for better performance on chained edits. *)
Expand Down
38 changes: 37 additions & 1 deletion lsp/test/text_document_tests.ml
Expand Up @@ -3,6 +3,8 @@ open Lsp.Types
module List = ListLabels
module String = StringLabels

let printf = Printf.printf

let tuple_range start end_ =
{ Range.start =
(let line, character = start in
Expand All @@ -12,6 +14,19 @@ let tuple_range start end_ =
{ Position.line; character })
}

let make_document ?(position_encoding = `UTF8) uri ~text =
let td =
let version = 1 in
let languageId = "fake language" in
let textDocument = { TextDocumentItem.uri; version; languageId; text } in
Text_document.make
~position_encoding
{ DidOpenTextDocumentParams.textDocument }
in
Text_document.apply_content_changes
td
[ TextDocumentContentChangeEvent.create ~text () ]

let test_general text changes =
let test position_encoding =
let td =
Expand All @@ -33,7 +48,6 @@ let test_general text changes =
in
let utf8 = test `UTF8 in
let utf16 = test `UTF16 in
let printf = Printf.printf in
if String.equal utf16 utf8 then printf "result: %s\n" (String.escaped utf8)
else (
print_endline "[FAILURE] utf16 and utf8 disagree";
Expand Down Expand Up @@ -204,3 +218,25 @@ let%expect_test "update when inserting a line at the end of the doc" =
[ (tuple_range (1, 9) (1, 9), "l"); (tuple_range (1, 9) (1, 10), "") ];
[%expect {|
result: 1\n2l\n3\n |}]

let%expect_test "absolute_position" =
let text = "foo|bar\nbaz.x" in
let td = make_document (Uri.of_path "foo.ml") ~text in
let test (line, character) =
let offset =
Text_document.absolute_position td (Position.create ~line ~character)
in
printf "position: %d/%d\n" offset (String.length text)
in
test (0, 0);
[%expect {| position: 0/13 |}];
test (3, 0);
[%expect {| position: 13/13 |}];
test (1, 0);
[%expect {| position: 8/13 |}];
test (1, 100);
[%expect {| position: 13/13 |}];
test (0, 100);
[%expect {| position: 7/13 |}];
test (100, 0);
[%expect {| position: 13/13 |}]

0 comments on commit 05847fc

Please sign in to comment.