Skip to content

Commit

Permalink
add tests
Browse files Browse the repository at this point in the history
  • Loading branch information
jfeser committed Jul 19, 2023
1 parent 78c633d commit ea3dc23
Show file tree
Hide file tree
Showing 4 changed files with 159 additions and 84 deletions.
95 changes: 11 additions & 84 deletions ocaml-lsp-server/test/e2e-new/code_actions.ml
Original file line number Diff line number Diff line change
@@ -1,58 +1,17 @@
open Test.Import

let openDocument ~client ~uri ~source =
let textDocument =
TextDocumentItem.create ~uri ~languageId:"ocaml" ~version:0 ~text:source
in
Client.notification
client
(TextDocumentDidOpen (DidOpenTextDocumentParams.create ~textDocument))

let iter_code_actions ?(prep = fun _ -> Fiber.return ()) ?(path = "foo.ml")
~source range k =
let diagnostics = Fiber.Ivar.create () in
let handler =
Client.Handler.make
~on_notification:
(fun _ -> function
| PublishDiagnostics _ -> (
let* diag = Fiber.Ivar.peek diagnostics in
match diag with
| Some _ -> Fiber.return ()
| None -> Fiber.Ivar.fill diagnostics ())
| _ -> Fiber.return ())
()
in
Test.run ~handler @@ fun client ->
let run_client () =
let capabilities =
let window =
let showDocument =
ShowDocumentClientCapabilities.create ~support:true
in
WindowClientCapabilities.create ~showDocument ()
in
ClientCapabilities.create ~window ()
in
Client.start client (InitializeParams.create ~capabilities ())
let uri = DocumentUri.of_path path in
let context = CodeActionContext.create ~diagnostics:[] () in
let request =
let textDocument = TextDocumentIdentifier.create ~uri in
CodeActionParams.create ~textDocument ~range ~context ()
in
let run =
let* (_ : InitializeResult.t) = Client.initialized client in
let uri = DocumentUri.of_path path in
let* () = prep client in
let* () = openDocument ~client ~uri ~source in
let+ resp =
let context = CodeActionContext.create ~diagnostics:[] () in
let request =
let textDocument = TextDocumentIdentifier.create ~uri in
CodeActionParams.create ~textDocument ~range ~context ()
in
Client.request client (CodeAction request)
in
k resp
in
Fiber.fork_and_join_unit run_client (fun () ->
run >>> Fiber.Ivar.read diagnostics >>> Client.stop client)
Test.run_request
~prep:(fun client -> prep client >>> Test.openDocument ~client ~uri ~source)
(CodeAction request)
|> k
let print_code_actions ?(prep = fun _ -> Fiber.return ()) ?(path = "foo.ml")
?(filter = fun _ -> true) source range =
Expand Down Expand Up @@ -562,7 +521,7 @@ let f (x : t) = x
|ocaml}
in
let uri = DocumentUri.of_path "foo.ml" in
let prep client = openDocument ~client ~uri ~source:impl_source in
let prep client = Test.openDocument ~client ~uri ~source:impl_source in
let intf_source = "" in
let range =
let start = Position.create ~line:0 ~character:0 in
Expand Down Expand Up @@ -635,38 +594,6 @@ let parse_selection src =
in
(src', Range.create ~start ~end_)
let offset_of_position src (pos : Position.t) =
let line_offset =
String.split_lines src |> List.take pos.line
|> List.fold_left ~init:0 ~f:(fun s l -> s + String.length l)
in
line_offset + pos.line (* account for line endings *) + pos.character
let apply_edits src edits =
let rec apply src = function
| [] -> src
| (new_text, start, end_) :: edits ->
(* apply edit *)
let src' = String.take src start ^ new_text ^ String.drop src end_ in
(* calculate amount of text added (or removed) *)
let diff_len = String.length new_text - (end_ - start) in
(* offset positions of remaining edits *)
let edits' =
List.map edits ~f:(fun (new_text, start, end_) ->
(new_text, start + diff_len, end_ + diff_len))
in
apply src' edits'
in
let edits =
List.map edits ~f:(fun (e : TextEdit.t) ->
( e.newText
, offset_of_position src e.range.start
, offset_of_position src e.range.end_ ))
in
apply src edits
let apply_code_action title source range =
let open Option.O in
(* collect code action results *)
Expand All @@ -689,7 +616,7 @@ let apply_code_action title source range =
TextEdit.create ~newText:a.newText ~range:a.range
| `TextEdit e -> e)
| `CreateFile _ | `DeleteFile _ | `RenameFile _ -> [])
|> apply_edits source
|> Test.apply_edits source
let code_action_test ~title ~source =
let src, range = parse_selection source in
Expand Down
1 change: 1 addition & 0 deletions ocaml-lsp-server/test/e2e-new/dune
Original file line number Diff line number Diff line change
Expand Up @@ -44,6 +44,7 @@
document_flow
for_ppx
hover_extended
inlay_hints
metrics
semantic_hl_data
semantic_hl_helpers
Expand Down
69 changes: 69 additions & 0 deletions ocaml-lsp-server/test/e2e-new/inlay_hints.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,69 @@
open Test.Import

let apply_inlay_hints ?(path = "foo.ml") ?range ~source () =
let range =
match range with
| Some r -> r
| None ->
let end_pos =
let lines = String.split source ~on:'\n' in
let last_line = Option.value_exn (List.last lines) in
Position.create
~line:(List.length lines - 1)
~character:(String.length last_line)
in
Range.create ~start:(Position.create ~character:0 ~line:0) ~end_:end_pos
in

let uri = DocumentUri.of_path path in
let request =
let textDocument = TextDocumentIdentifier.create ~uri in
InlayHintParams.create ~textDocument ~range ()
in
let inlay_hints =
Test.run_request
~prep:(fun client -> Test.openDocument ~client ~uri ~source)
(InlayHint request)
in
match inlay_hints with
| Some hints ->
let text_edits =
List.map hints ~f:(fun (hint : InlayHint.t) ->
let paddingLeftStr =
match hint.paddingLeft with
| Some true -> "_$"
| None | Some false -> "$"
in
let paddingRightStr =
match hint.paddingRight with
| Some true -> "$_"
| None | Some false -> "$"
in

let newText =
match hint.label with
| `String s -> paddingLeftStr ^ s ^ paddingRightStr
| `List _ -> failwith "TODO: implement list hints"
in
TextEdit.create
~range:(Range.create ~start:hint.position ~end_:hint.position)
~newText)
in
Test.apply_edits source text_edits |> print_endline
| None -> print_endline "No hints found"

let%expect_test "simple" =
apply_inlay_hints ~source:"let x = 1 + 2" ();
[%expect {| let x$: int$ = 1 + 2 |}]

let%expect_test "optional argument" =
apply_inlay_hints ~source:"let f ?x () = x" ();
[%expect {| let f ?x$: 'a option$ () = x |}]

let%expect_test "optional argument with value" =
apply_inlay_hints ~source:"let f ?(x = 1) () = x" ();
[%expect {| let f ?(x$: int$ = 1) () = x |}]

let%expect_test "labeled argument" =
apply_inlay_hints ~source:"let f ~x = x + 1" ();
[%expect {| let f ~x$: int$ = x + 1 |}]
78 changes: 78 additions & 0 deletions ocaml-lsp-server/test/e2e-new/test.ml
Original file line number Diff line number Diff line change
Expand Up @@ -153,3 +153,81 @@ end = struct
end

include T

let run_request ?(prep = fun _ -> Fiber.return ()) request =
let diagnostics = Fiber.Ivar.create () in
let handler =
Client.Handler.make
~on_notification:
(fun _ -> function
| PublishDiagnostics _ -> (
let* diag = Fiber.Ivar.peek diagnostics in
match diag with
| Some _ -> Fiber.return ()
| None -> Fiber.Ivar.fill diagnostics ())
| _ -> Fiber.return ())
()
in
run ~handler @@ fun client ->
let run_client () =
let capabilities =
let window =
let showDocument =
ShowDocumentClientCapabilities.create ~support:true
in
WindowClientCapabilities.create ~showDocument ()
in
ClientCapabilities.create ~window ()
in
Client.start client (InitializeParams.create ~capabilities ())
in
let run =
let* (_ : InitializeResult.t) = Client.initialized client in
let* () = prep client in
Client.request client request
in
Fiber.fork_and_join_unit run_client (fun () ->
let* ret = run in
let* () = Fiber.Ivar.read diagnostics in
let+ () = Client.stop client in
ret)
let openDocument ~client ~uri ~source =
let textDocument =
TextDocumentItem.create ~uri ~languageId:"ocaml" ~version:0 ~text:source
in
Client.notification
client
(TextDocumentDidOpen (DidOpenTextDocumentParams.create ~textDocument))
let offset_of_position src (pos : Position.t) =
let line_offset =
String.split_lines src |> List.take pos.line
|> List.fold_left ~init:0 ~f:(fun s l -> s + String.length l)
in
line_offset + pos.line (* account for line endings *) + pos.character
let apply_edits src edits =
let rec apply src = function
| [] -> src
| (new_text, start, end_) :: edits ->
(* apply edit *)
let src' = String.take src start ^ new_text ^ String.drop src end_ in
(* calculate amount of text added (or removed) *)
let diff_len = String.length new_text - (end_ - start) in
(* offset positions of remaining edits *)
let edits' =
List.map edits ~f:(fun (new_text, start, end_) ->
(new_text, start + diff_len, end_ + diff_len))
in
apply src' edits'
in
let edits =
List.map edits ~f:(fun (e : TextEdit.t) ->
( e.newText
, offset_of_position src e.range.start
, offset_of_position src e.range.end_ ))
in
apply src edits

0 comments on commit ea3dc23

Please sign in to comment.