Skip to content

Commit 2d1e7c0

Browse files
authored
fix bug in 'switchImplIntf': (#254)
* fix bug in 'switchImplIntf': one couldn't switch from a new file that's not saved on disk (in vscode it's a file with URI scheme 'untitled') The previous switching logic depended on document store, which only knows files that were opened with a 'textDocument/didOpen' notification. VS Code doesn't send such notifications for unsaved files, hence the bug. Now switching handled file URIs directly without dependence on document store, which works for any 'switchImplIntf' request with a valid URI. * * refactor switchImplIntf * add a test to switch from file uri with non-file scheme
1 parent 25c4d5f commit 2d1e7c0

File tree

4 files changed

+61
-26
lines changed

4 files changed

+61
-26
lines changed

ocaml-lsp-server/src/document.ml

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -37,6 +37,18 @@ module Syntax = struct
3737
; ("ocaml.menhir", Menhir)
3838
]
3939

40+
let of_fname s =
41+
match Filename.extension s with
42+
| ".mli"
43+
| ".ml" ->
44+
Ocaml
45+
| ".rei"
46+
| ".re" ->
47+
Reason
48+
| ".mll" -> Ocamllex
49+
| ".mly" -> Menhir
50+
| ext -> failwith ("Unknown extension " ^ ext)
51+
4052
let of_language_id language_id =
4153
match List.assoc all language_id with
4254
| Some id -> id

ocaml-lsp-server/src/document.mli

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -12,12 +12,16 @@ module Syntax : sig
1212
val human_name : t -> string
1313

1414
val markdown_name : t -> string
15+
16+
val of_fname : string -> t
1517
end
1618

1719
module Kind : sig
1820
type t =
1921
| Intf
2022
| Impl
23+
24+
val of_fname : string -> t
2125
end
2226

2327
val kind : t -> Kind.t

ocaml-lsp-server/src/switch_impl_intf.ml

Lines changed: 29 additions & 26 deletions
Original file line numberDiff line numberDiff line change
@@ -4,54 +4,57 @@ let capability = ("handleSwitchImplIntf", `Bool true)
44

55
let meth = "ocamllsp/switchImplIntf"
66

7-
(** See the spec for 'ocamllsp/switchImplIntf' *)
8-
let switch (state : State.t) (param : DocumentUri.t) :
9-
(Json.t, Jsonrpc.Response.Error.t) result =
10-
let file_uri = Uri.t_of_yojson (`String param) in
11-
let filepath = Uri.to_path file_uri in
7+
(** see the spec for [ocamllsp/switchImplIntf] *)
8+
let switch (param : DocumentUri.t) : (Json.t, Jsonrpc.Response.Error.t) result =
9+
let fpath =
10+
match String.split ~on:':' param with
11+
| [ scheme; path ] ->
12+
if scheme = "file" then
13+
Uri.t_of_yojson (`String param) |> Uri.to_path
14+
else
15+
path
16+
| _ -> failwith "provided file URI (param) doesn't follow URI spec"
17+
in
18+
let fname = Filename.basename fpath in
1219
let ml, mli, re, rei, mll, mly = ("ml", "mli", "re", "rei", "mll", "mly") in
13-
let open Result.O in
14-
let+ doc = Document_store.get state.store file_uri in
15-
let extensions_to_switch_to =
16-
match Document.syntax doc with
20+
let exts_to_switch_to =
21+
match Document.Syntax.of_fname fname with
1722
| Ocaml -> (
18-
match Document.kind doc with
23+
match Document.Kind.of_fname fname with
1924
| Intf -> [ ml; mly; mll; re ]
2025
| Impl -> [ mli; mly; mll; rei ] )
2126
| Reason -> (
22-
match Document.kind doc with
27+
match Document.Kind.of_fname fname with
2328
| Intf -> [ re; ml ]
2429
| Impl -> [ rei; mli ] )
2530
| Ocamllex -> [ mli; rei ]
2631
| Menhir -> [ mli; rei ]
2732
in
28-
let path_without_extension = Filename.remove_extension filepath ^ "." in
29-
let find_switch (exts : string list) =
33+
let fpath_w_ext ext = Filename.remove_extension fpath ^ "." ^ ext in
34+
let find_switch exts =
3035
List.filter_map exts ~f:(fun ext ->
31-
let file_to_switch_to = path_without_extension ^ ext in
36+
let file_to_switch_to = fpath_w_ext ext in
3237
Option.some_if (Sys.file_exists file_to_switch_to) file_to_switch_to)
3338
in
34-
let to_switch_to =
35-
match find_switch extensions_to_switch_to with
39+
let files_to_switch_to =
40+
match find_switch exts_to_switch_to with
3641
| [] ->
37-
let main_switch_to_candidate_ext = List.hd extensions_to_switch_to in
38-
let main_switch_to_candidate_path =
39-
path_without_extension ^ main_switch_to_candidate_ext
40-
in
41-
[ main_switch_to_candidate_path ]
42+
let switch_to_ext = List.hd exts_to_switch_to in
43+
let switch_to_fpath = fpath_w_ext switch_to_ext in
44+
[ switch_to_fpath ]
4245
| to_switch_to -> to_switch_to
4346
in
44-
let to_switch_to_json_array =
45-
List.map to_switch_to ~f:(fun s -> `String (Uri.to_string @@ Uri.of_path s))
46-
in
47-
`List to_switch_to_json_array
47+
Ok
48+
(Json.yojson_of_list
49+
(fun fpath -> Uri.of_path fpath |> Uri.to_string |> fun s -> `String s)
50+
files_to_switch_to)
4851

4952
let on_request ~(params : Json.t option) state =
5053
Fiber.return
5154
( match params with
5255
| Some (`String (file_uri : DocumentUri.t)) ->
5356
let open Result.O in
54-
let+ res = switch state file_uri in
57+
let+ res = switch file_uri in
5558
(res, state)
5659
| Some _
5760
| None ->

ocaml-lsp-server/test/e2e/__tests__/ocamllsp-switchImplIntf.ts

Lines changed: 16 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -106,4 +106,20 @@ describe("ocamllsp/switchImplIntf", () => {
106106
[ml, mll],
107107
],
108108
])("test switches (%s => %s)", testingPipeline);
109+
110+
it("can switch from file URI with non-file scheme", async () => {
111+
let mlFpath = createPathForFile("test.ml");
112+
await createFileAtPath(mlFpath);
113+
let mlUri = pathToDocumentUri(mlFpath);
114+
115+
let newMliFpath = createPathForFile("test.mli");
116+
await createFileAtPath(newMliFpath);
117+
let mliUriUntitledScheme: DocumentUri = URI.file(newMliFpath)
118+
.with({
119+
scheme: "untitled",
120+
})
121+
.toString();
122+
123+
testRequest(mliUriUntitledScheme, [mlUri]);
124+
});
109125
});

0 commit comments

Comments
 (0)