Skip to content

Commit

Permalink
feature: increase verbosity on subsequent hover
Browse files Browse the repository at this point in the history
  • Loading branch information
Khady committed Dec 3, 2021
1 parent 435d22d commit 1464507
Show file tree
Hide file tree
Showing 4 changed files with 82 additions and 3 deletions.
33 changes: 30 additions & 3 deletions ocaml-lsp-server/src/ocaml_lsp_server.ml
Original file line number Diff line number Diff line change
Expand Up @@ -509,9 +509,23 @@ let query_doc doc pos =
Some s
| _ -> None

let query_type doc pos =
let query_type ?(verbosity = 0) doc pos =
let command = Query_protocol.Type_enclosing (None, pos, None) in
let+ res = Document.dispatch_exn doc command in
let+ res =
Document.with_pipeline_exn doc (fun pipeline ->
let pipeline =
match verbosity with
| 0 -> pipeline
| verbosity ->
let source = Document.source doc in
let config = Mpipeline.final_config pipeline in
let config =
{ config with query = { config.query with verbosity } }
in
Mpipeline.make config source
in
Query_commands.dispatch pipeline command)
in
match res with
| []
| (_, `Index _, _) :: _ ->
Expand All @@ -525,8 +539,21 @@ let hover server (state : State.t)
Document_store.get store uri
in
let pos = Position.logical position in
let verbosity =
match state.hover_history with
| [] -> 0
| { uri = h_uri; position = h_pos } :: _ as hist ->
if Uri.equal uri h_uri && Ordering.is_eq (Position.compare position h_pos)
then
List.length hist
else (
state.hover_history <- [];
0
)
in
state.hover_history <- { uri; position } :: state.hover_history;
(* TODO we shouldn't acquiring the merlin thread twice per request *)
let* query_type = query_type doc pos in
let* query_type = query_type ~verbosity doc pos in
match query_type with
| None -> Fiber.return None
| Some (loc, typ) ->
Expand Down
7 changes: 7 additions & 0 deletions ocaml-lsp-server/src/state.ml
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,11 @@ type init =
; dune : Dune.t
}

type hover_history =
{ uri : Uri.t
; position : Position.t
}

type t =
{ store : Document_store.t
; merlin : Scheduler.thread
Expand All @@ -20,6 +25,7 @@ type t =
; ocamlformat_rpc : Ocamlformat_rpc.t
; diagnostics : Diagnostics.t
; symbols_thread : Scheduler.thread Lazy_fiber.t
; mutable hover_history : hover_history list
}

let create ~store ~merlin ~detached ~configuration ~ocamlformat ~ocamlformat_rpc
Expand All @@ -35,6 +41,7 @@ let create ~store ~merlin ~detached ~configuration ~ocamlformat ~ocamlformat_rpc
; ocamlformat_rpc
; diagnostics
; symbols_thread
; hover_history = []
}

let initialize_params (state : t) =
Expand Down
6 changes: 6 additions & 0 deletions ocaml-lsp-server/src/state.mli
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,11 @@ type init =
; dune : Dune.t
}

type hover_history =
{ uri : Uri.t
; position : Position.t
}

type t =
{ store : Document_store.t
; merlin : Scheduler.thread
Expand All @@ -20,6 +25,7 @@ type t =
; ocamlformat_rpc : Ocamlformat_rpc.t
; diagnostics : Diagnostics.t
; symbols_thread : Scheduler.thread Lazy_fiber.t
; mutable hover_history : hover_history list
}

val create :
Expand Down
39 changes: 39 additions & 0 deletions ocaml-lsp-server/test/e2e/__tests__/textDocument-hover.test.ts
Original file line number Diff line number Diff line change
Expand Up @@ -245,6 +245,45 @@ describe("textDocument/hover", () => {
});
});

it("returns type inferred under cursor with increased verbosity", async () => {
languageServer = await LanguageServer.startAndInitialize();
await languageServer.sendNotification("textDocument/didOpen", {
textDocument: Types.TextDocumentItem.create(
"file:///test.ml",
"ocaml",
0,
outdent`
type t = int
let x : t = 1
`
),
});

let result0 = await languageServer.sendRequest("textDocument/hover", {
textDocument: Types.TextDocumentIdentifier.create("file:///test.ml"),
position: Types.Position.create(1, 4),
});
let result1 = await languageServer.sendRequest("textDocument/hover", {
textDocument: Types.TextDocumentIdentifier.create("file:///test.ml"),
position: Types.Position.create(1, 4),
});

expect(result0).toMatchObject({
contents: { kind: "plaintext", value: "t" },
range: {
end: { character: 5, line: 1 },
start: { character: 4, line: 1 },
},
});
expect(result1).toMatchObject({
contents: { kind: "plaintext", value: "int" },
range: {
end: { character: 5, line: 1 },
start: { character: 4, line: 1 },
},
});
});

it("regression test for #343", async () => {
languageServer = await LanguageServer.startAndInitialize({
capabilities: {
Expand Down

0 comments on commit 1464507

Please sign in to comment.