Skip to content

Commit d6001a1

Browse files
committed
refactor: get doc kind info from merlin
1 parent ad20957 commit d6001a1

9 files changed

+84
-35
lines changed

ocaml-lsp-server/src/code_actions.ml

+1-1
Original file line numberDiff line numberDiff line change
@@ -113,7 +113,7 @@ let compute server (params : CodeActionParams.t) =
113113
let* window = (State.client_capabilities state).window in
114114
window.showDocument
115115
in
116-
Action_open_related.for_uri capabilities uri
116+
Action_open_related.for_uri capabilities doc
117117
in
118118
match Document.syntax doc with
119119
| Ocamllex | Menhir | Cram | Dune ->

ocaml-lsp-server/src/code_actions/action_open_related.ml

+8-2
Original file line numberDiff line numberDiff line change
@@ -28,11 +28,17 @@ let available (capabilities : ShowDocumentClientCapabilities.t option) =
2828
| None | Some { support = false } -> false
2929
| Some { support = true } -> true
3030

31-
let for_uri (capabilities : ShowDocumentClientCapabilities.t option) uri =
31+
let for_uri (capabilities : ShowDocumentClientCapabilities.t option) doc =
32+
let uri = Document.uri doc in
33+
let merlin_doc =
34+
match Document.kind doc with
35+
| `Merlin doc -> Some doc
36+
| `Other -> None
37+
in
3238
match available capabilities with
3339
| false -> []
3440
| true ->
35-
Document.get_impl_intf_counterparts uri
41+
Document.get_impl_intf_counterparts merlin_doc uri
3642
|> List.map ~f:(fun uri ->
3743
let path = Uri.to_path uri in
3844
let exists = Sys.file_exists path in

ocaml-lsp-server/src/code_actions/action_open_related.mli

+1-1
Original file line numberDiff line numberDiff line change
@@ -7,4 +7,4 @@ val available : ShowDocumentClientCapabilities.t option -> bool
77
val command_run : _ Server.t -> ExecuteCommandParams.t -> Json.t Fiber.t
88

99
val for_uri :
10-
ShowDocumentClientCapabilities.t option -> DocumentUri.t -> CodeAction.t list
10+
ShowDocumentClientCapabilities.t option -> Document.t -> CodeAction.t list

ocaml-lsp-server/src/custom_requests/req_switch_impl_intf.ml

+21-6
Original file line numberDiff line numberDiff line change
@@ -5,15 +5,30 @@ let capability = ("handleSwitchImplIntf", `Bool true)
55
let meth = "ocamllsp/switchImplIntf"
66

77
(** see the spec for [ocamllsp/switchImplIntf] *)
8-
let switch (param : DocumentUri.t) : Json.t =
9-
let files_to_switch_to = Document.get_impl_intf_counterparts param in
8+
let switch merlin_doc (param : DocumentUri.t) : Json.t =
9+
let files_to_switch_to =
10+
Document.get_impl_intf_counterparts merlin_doc param
11+
in
1012
Json.yojson_of_list Uri.yojson_of_t files_to_switch_to
1113

12-
let on_request ~(params : Jsonrpc.Structured.t option) =
14+
let on_request ~(params : Jsonrpc.Structured.t option) (state : State.t) =
1315
match params with
14-
| Some (`List [ file_uri ]) ->
15-
let file_uri = DocumentUri.t_of_yojson file_uri in
16-
switch file_uri
16+
| Some (`List [ json_uri ]) -> (
17+
let uri = DocumentUri.t_of_yojson json_uri in
18+
match Document_store.get_opt state.store uri with
19+
| Some doc -> (
20+
match Document.kind doc with
21+
| `Merlin merlin_doc -> switch (Some merlin_doc) uri
22+
| `Other ->
23+
Jsonrpc.Response.Error.raise
24+
(Jsonrpc.Response.Error.make
25+
~code:InvalidRequest
26+
~message:
27+
"Document with this URI is not supported by \
28+
ocamllsp/switchImplIntf"
29+
~data:(`Assoc [ ("param", (json_uri :> Json.t)) ])
30+
()))
31+
| None -> switch None uri)
1732
| Some json ->
1833
Jsonrpc.Response.Error.raise
1934
(Jsonrpc.Response.Error.make

ocaml-lsp-server/src/custom_requests/req_switch_impl_intf.mli

+1-1
Original file line numberDiff line numberDiff line change
@@ -4,4 +4,4 @@ val capability : string * Json.t
44

55
val meth : string
66

7-
val on_request : params:Jsonrpc.Structured.t option -> Json.t
7+
val on_request : params:Jsonrpc.Structured.t option -> State.t -> Json.t

ocaml-lsp-server/src/document.ml

+47-19
Original file line numberDiff line numberDiff line change
@@ -6,17 +6,20 @@ module Kind = struct
66
| Intf
77
| Impl
88

9-
let of_fname p =
9+
let of_fname_opt p =
1010
match Filename.extension p with
11-
| ".ml" | ".eliom" | ".re" -> Impl
12-
| ".mli" | ".eliomi" | ".rei" -> Intf
13-
| ext ->
14-
Jsonrpc.Response.Error.raise
15-
(Jsonrpc.Response.Error.make
16-
~code:InvalidRequest
17-
~message:"unsupported file extension"
18-
~data:(`Assoc [ ("extension", `String ext) ])
19-
())
11+
| ".ml" | ".eliom" | ".re" -> Some Impl
12+
| ".mli" | ".eliomi" | ".rei" -> Some Intf
13+
| _ -> None
14+
15+
let unsupported uri =
16+
let p = Uri.to_path uri in
17+
Jsonrpc.Response.Error.raise
18+
(Jsonrpc.Response.Error.make
19+
~code:InvalidRequest
20+
~message:"unsupported file extension"
21+
~data:(`Assoc [ ("extension", `String (Filename.extension p)) ])
22+
())
2023
end
2124

2225
module Syntax = struct
@@ -178,6 +181,7 @@ type merlin =
178181
; timer : Lev_fiber.Timer.Wheel.task
179182
; merlin_config : Merlin_config.t
180183
; syntax : Syntax.t
184+
; kind : Kind.t option
181185
}
182186

183187
type t =
@@ -204,12 +208,24 @@ let source t = Msource.make (text t)
204208
let version t = Text_document.version (tdoc t)
205209

206210
let make_merlin wheel merlin_db pipeline tdoc syntax =
207-
let+ timer = Lev_fiber.Timer.Wheel.task wheel in
208-
let merlin_config =
209-
let uri = Text_document.documentUri tdoc in
210-
Merlin_config.DB.get merlin_db uri
211+
let* timer = Lev_fiber.Timer.Wheel.task wheel in
212+
let uri = Text_document.documentUri tdoc in
213+
let path = Uri.to_path uri in
214+
let merlin_config = Merlin_config.DB.get merlin_db uri in
215+
let* mconfig = Merlin_config.config merlin_config in
216+
let kind =
217+
let ext = Filename.extension path in
218+
List.find_map mconfig.merlin.suffixes ~f:(fun (impl, intf) ->
219+
if String.equal ext intf then Some Kind.Intf
220+
else if String.equal ext impl then Some Kind.Impl
221+
else None)
211222
in
212-
Merlin { merlin_config; tdoc; pipeline; timer; syntax }
223+
let kind =
224+
match kind with
225+
| Some _ as k -> k
226+
| None -> Kind.of_fname_opt path
227+
in
228+
Fiber.return (Merlin { merlin_config; tdoc; pipeline; timer; syntax; kind })
213229

214230
let make wheel config pipeline (doc : DidOpenTextDocumentParams.t)
215231
~position_encoding =
@@ -252,7 +268,10 @@ module Merlin = struct
252268

253269
let timer (t : t) = t.timer
254270

255-
let kind t = Kind.of_fname (Uri.to_path (uri (Merlin t)))
271+
let kind t =
272+
match t.kind with
273+
| Some k -> k
274+
| None -> Kind.unsupported (Text_document.documentUri t.tdoc)
256275

257276
let with_pipeline ?name (t : t) f =
258277
Single_pipeline.use ?name t.pipeline ~doc:t.tdoc ~config:t.merlin_config ~f
@@ -346,21 +365,30 @@ let close t =
346365
(fun () -> Merlin_config.destroy t.merlin_config)
347366
(fun () -> Lev_fiber.Timer.Wheel.cancel t.timer)
348367

349-
let get_impl_intf_counterparts uri =
368+
let get_impl_intf_counterparts m uri =
350369
let fpath = Uri.to_path uri in
351370
let fname = Filename.basename fpath in
352371
let ml, mli, eliom, eliomi, re, rei, mll, mly =
353372
("ml", "mli", "eliom", "eliomi", "re", "rei", "mll", "mly")
354373
in
355374
let exts_to_switch_to =
375+
let kind =
376+
match m with
377+
| Some m -> Merlin.kind m
378+
| None -> (
379+
(* still try to guess the kind *)
380+
match Kind.of_fname_opt fpath with
381+
| Some k -> k
382+
| None -> Kind.unsupported uri)
383+
in
356384
match Syntax.of_fname fname with
357385
| Dune | Cram -> []
358386
| Ocaml -> (
359-
match Kind.of_fname fname with
387+
match kind with
360388
| Intf -> [ ml; mly; mll; eliom; re ]
361389
| Impl -> [ mli; mly; mll; eliomi; rei ])
362390
| Reason -> (
363-
match Kind.of_fname fname with
391+
match kind with
364392
| Intf -> [ re; ml ]
365393
| Impl -> [ rei; mli ])
366394
| Ocamllex -> [ mli; rei ]

ocaml-lsp-server/src/document.mli

+1-1
Original file line numberDiff line numberDiff line change
@@ -97,7 +97,7 @@ val close : t -> unit Fiber.t
9797
counterparts for the URI [uri].
9898
9999
For instance, the counterparts of the file [/file.ml] are [/file.mli]. *)
100-
val get_impl_intf_counterparts : Uri.t -> Uri.t list
100+
val get_impl_intf_counterparts : Merlin.t option -> Uri.t -> Uri.t list
101101

102102
(** [edits t edits] creates a [WorkspaceEdit.t] that applies edits [edits] to
103103
the document [t]. *)

ocaml-lsp-server/src/inference.ml

+2-2
Original file line numberDiff line numberDiff line change
@@ -69,11 +69,11 @@ let infer_intf (state : State.t) doc =
6969
Code_error.raise "the provided document is not a merlin source." []
7070
| `Merlin m when Document.Merlin.kind m = Impl ->
7171
Code_error.raise "the provided document is not an interface." []
72-
| `Merlin _ ->
72+
| `Merlin m ->
7373
Fiber.of_thunk (fun () ->
7474
let intf_uri = Document.uri doc in
7575
let impl_uri =
76-
Document.get_impl_intf_counterparts intf_uri |> List.hd
76+
Document.get_impl_intf_counterparts (Some m) intf_uri |> List.hd
7777
in
7878
let* impl =
7979
match Document_store.get_opt state.store impl_uri with

ocaml-lsp-server/src/ocaml_lsp_server.ml

+2-2
Original file line numberDiff line numberDiff line change
@@ -500,9 +500,9 @@ let on_request :
500500
| Client_request.UnknownRequest { meth; params } -> (
501501
match
502502
[ ( Req_switch_impl_intf.meth
503-
, fun ~params _ ->
503+
, fun ~params state ->
504504
Fiber.of_thunk (fun () ->
505-
Fiber.return (Req_switch_impl_intf.on_request ~params)) )
505+
Fiber.return (Req_switch_impl_intf.on_request ~params state)) )
506506
; (Req_infer_intf.meth, Req_infer_intf.on_request)
507507
; (Req_typed_holes.meth, Req_typed_holes.on_request)
508508
; (Req_wrapping_ast_node.meth, Req_wrapping_ast_node.on_request)

0 commit comments

Comments
 (0)