Skip to content

Commit

Permalink
refactor: remove Document.is_merlin (#888)
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <me@rgrinberg.com>

ps-id: 9f82a75d-df56-4ab8-ba05-1bbe71e783f6
  • Loading branch information
rgrinberg authored Oct 20, 2022
1 parent 38e0a1a commit 4f336ae
Show file tree
Hide file tree
Showing 4 changed files with 11 additions and 15 deletions.
4 changes: 0 additions & 4 deletions ocaml-lsp-server/src/document.ml
Original file line number Diff line number Diff line change
Expand Up @@ -106,10 +106,6 @@ let tdoc = function

let uri t = Text_document.documentUri (tdoc t)

let is_merlin = function
| Other _ -> false
| Merlin _ -> true

let kind = function
| Merlin _ as t -> `Merlin (Kind.of_fname (Uri.to_path (uri t)))
| Other _ -> `Other
Expand Down
2 changes: 0 additions & 2 deletions ocaml-lsp-server/src/document.mli
Original file line number Diff line number Diff line change
Expand Up @@ -22,8 +22,6 @@ module Kind : sig
| Impl
end

val is_merlin : t -> bool

val kind : t -> [ `Merlin of Kind.t | `Other ]

val syntax : t -> Syntax.t
Expand Down
6 changes: 3 additions & 3 deletions ocaml-lsp-server/src/dune.ml
Original file line number Diff line number Diff line change
Expand Up @@ -257,9 +257,9 @@ end = struct
| Failed | Interrupted | Success ->
let* () =
Document_store.change_all document_store ~f:(fun doc ->
match Document.is_merlin doc with
| false -> Fiber.return doc
| true ->
match Document.kind doc with
| `Other -> Fiber.return doc
| `Merlin _ ->
let doc = Document.update_text doc [] in
let+ () =
Diagnostics.merlin_diagnostics diagnostics doc
Expand Down
14 changes: 8 additions & 6 deletions ocaml-lsp-server/src/ocaml_lsp_server.ml
Original file line number Diff line number Diff line change
Expand Up @@ -269,7 +269,8 @@ module Formatter = struct

let run rpc doc =
let state : State.t = Server.state rpc in
if Document.is_merlin doc then
match Document.kind doc with
| `Merlin _ -> (
let* res =
let* res = Ocamlformat_rpc.format_doc state.ocamlformat_rpc doc in
match res with
Expand All @@ -289,8 +290,8 @@ module Formatter = struct
task_if_running state.detached ~f:(fun () ->
Server.notification rpc (ShowMessage msg))
in
Jsonrpc.Response.Error.raise error
else
Jsonrpc.Response.Error.raise error)
| `Other -> (
match Dune.for_doc (State.dune state) doc with
| [] ->
let message =
Expand All @@ -314,7 +315,7 @@ module Formatter = struct
State.log_msg rpc ~type_:MessageType.Warning ~message
in
let+ to_ = Dune.Instance.format_dune_file dune doc in
Some (Diff.edit ~from:(Document.text doc) ~to_)
Some (Diff.edit ~from:(Document.text doc) ~to_))
end

let location_of_merlin_loc uri : _ -> (_, string) result = function
Expand Down Expand Up @@ -370,13 +371,14 @@ let signature_help (state : State.t)
in
(* TODO use merlin resources efficiently and do everything in 1 thread *)
let* application_signature =
if Document.is_merlin doc then
match Document.kind doc with
| `Other -> Fiber.return None
| `Merlin _ ->
Document.with_pipeline_exn doc (fun pipeline ->
let typer = Mpipeline.typer_result pipeline in
let pos = Mpipeline.get_lexing_pos pipeline pos in
let node = Mtyper.node_at typer pos in
Signature_help.application_signature node ~prefix)
else Fiber.return None
in
match application_signature with
| None ->
Expand Down

0 comments on commit 4f336ae

Please sign in to comment.