diff --git a/ocaml-lsp-server/src/custom_requests/req_typed_holes.ml b/ocaml-lsp-server/src/custom_requests/req_typed_holes.ml index 3f4ca71ae..d61fac580 100644 --- a/ocaml-lsp-server/src/custom_requests/req_typed_holes.ml +++ b/ocaml-lsp-server/src/custom_requests/req_typed_holes.ml @@ -63,7 +63,10 @@ let on_request ~(params : Jsonrpc.Structured.t option) (state : State.t) = () | Some doc -> let+ holes = - Document.Merlin.dispatch_exn ~name:"typed-holes" (Document.merlin_exn doc) Holes + Document.Merlin.dispatch_exn + ~name:"typed-holes" + (Document.merlin_exn doc) + Holes in Json.yojson_of_list (fun (loc, _type) -> loc |> Range.of_loc |> Range.yojson_of_t) diff --git a/ocaml-lsp-server/src/custom_requests/req_wrapping_ast_node.ml b/ocaml-lsp-server/src/custom_requests/req_wrapping_ast_node.ml index f9bbe373d..b98c915cb 100644 --- a/ocaml-lsp-server/src/custom_requests/req_wrapping_ast_node.ml +++ b/ocaml-lsp-server/src/custom_requests/req_wrapping_ast_node.ml @@ -44,7 +44,10 @@ let on_request ~params state = | `Merlin doc -> ( let pos = Position.logical cursor_position in let+ node = - Document.Merlin.with_pipeline_exn ~name:"wrapping-ast-node" doc (fun pipeline -> + Document.Merlin.with_pipeline_exn + ~name:"wrapping-ast-node" + doc + (fun pipeline -> let typer = Mpipeline.typer_result pipeline in let pos = Mpipeline.get_lexing_pos pipeline pos in let enclosing_nodes (* from smallest node to largest *) = diff --git a/ocaml-lsp-server/src/definition_query.ml b/ocaml-lsp-server/src/definition_query.ml index c15d8f6d5..509eae7df 100644 --- a/ocaml-lsp-server/src/definition_query.ml +++ b/ocaml-lsp-server/src/definition_query.ml @@ -37,9 +37,9 @@ let run kind (state : State.t) uri position = let command, name = let pos = Position.logical position in match kind with - | `Definition -> Query_protocol.Locate (None, `ML, pos), "definition" - | `Declaration -> Query_protocol.Locate (None, `MLI, pos), "declaration" - | `Type_definition -> Query_protocol.Locate_type pos, "type definition" + | `Definition -> (Query_protocol.Locate (None, `ML, pos), "definition") + | `Declaration -> (Query_protocol.Locate (None, `MLI, pos), "declaration") + | `Type_definition -> (Query_protocol.Locate_type pos, "type definition") in let* result = Document.Merlin.dispatch_exn ~name doc command in match location_of_merlin_loc uri result with diff --git a/ocaml-lsp-server/src/document.ml b/ocaml-lsp-server/src/document.ml index 91b7be644..0f9fae3df 100644 --- a/ocaml-lsp-server/src/document.ml +++ b/ocaml-lsp-server/src/document.ml @@ -285,7 +285,8 @@ module Merlin = struct | Error exn -> Exn_with_backtrace.reraise exn let dispatch ?name t command = - with_pipeline ?name t (fun pipeline -> Query_commands.dispatch pipeline command) + with_pipeline ?name t (fun pipeline -> + Query_commands.dispatch pipeline command) let dispatch_exn ?name t command = with_pipeline_exn ?name t (fun pipeline -> diff --git a/ocaml-lsp-server/src/document.mli b/ocaml-lsp-server/src/document.mli index 1eadf21a3..8e1e2cb5d 100644 --- a/ocaml-lsp-server/src/document.mli +++ b/ocaml-lsp-server/src/document.mli @@ -67,7 +67,8 @@ module Merlin : sig ?name:string -> t -> Msource.position - -> (* doc string *) string option Fiber.t + -> (* doc string *) + string option Fiber.t val syntax_doc : Mpipeline.t -> Msource.position -> Query_protocol.syntax_doc_result option diff --git a/ocaml-lsp-server/src/inference.ml b/ocaml-lsp-server/src/inference.ml index 52b447539..4fe51daf1 100644 --- a/ocaml-lsp-server/src/inference.ml +++ b/ocaml-lsp-server/src/inference.ml @@ -12,7 +12,10 @@ let infer_intf_for_impl doc = "expected an implementation document, got an interface instead" [] | `Merlin doc -> - Document.Merlin.with_pipeline_exn ~name:"infer-interface" doc (fun pipeline -> + Document.Merlin.with_pipeline_exn + ~name:"infer-interface" + doc + (fun pipeline -> let typer = Mpipeline.typer_result pipeline in let sig_ : Types.signature = let typedtree = Mtyper.get_typedtree typer in diff --git a/ocaml-lsp-server/src/ocaml_lsp_server.ml b/ocaml-lsp-server/src/ocaml_lsp_server.ml index e5e2a688d..674cf227d 100644 --- a/ocaml-lsp-server/src/ocaml_lsp_server.ml +++ b/ocaml-lsp-server/src/ocaml_lsp_server.ml @@ -427,7 +427,10 @@ let selection_range (state : State.t) let+ ranges = Fiber.sequential_map positions ~f:(fun x -> let+ shapes = - Document.Merlin.dispatch_exn ~name:"shape" merlin (Shape (Position.logical x)) + Document.Merlin.dispatch_exn + ~name:"shape" + merlin + (Shape (Position.logical x)) in selection_range_of_shapes x shapes) in diff --git a/ocaml-lsp-server/src/signature_help.ml b/ocaml-lsp-server/src/signature_help.ml index f9820d2f0..13367614c 100644 --- a/ocaml-lsp-server/src/signature_help.ml +++ b/ocaml-lsp-server/src/signature_help.ml @@ -203,7 +203,10 @@ let run (state : State.t) match inside_comment with | true -> Fiber.return None | false -> - Document.Merlin.with_pipeline_exn ~name:"signature-help" merlin (fun pipeline -> + Document.Merlin.with_pipeline_exn + ~name:"signature-help" + merlin + (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