Skip to content

Commit b264d8f

Browse files
authored
Merge pull request #233 from ulugbekna/switch-intf-impl
implement handling 'didSwitchImplIntf' - switching between impl and intf files
2 parents 27e3d17 + 5ba6588 commit b264d8f

File tree

8 files changed

+243
-6
lines changed

8 files changed

+243
-6
lines changed
Lines changed: 34 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,34 @@
1+
#### Switch Implementation/Interface Request
2+
3+
Switch Implementation/Interface Request is sent from client to server to get
4+
URI(s) of the file(s) that the current file can switch to, e.g., if the user
5+
has "foo.ml" and "foo.mli" files, the client, who want to switch from one to
6+
the other, sends this request.
7+
8+
If there are one or more files, to which the currently open file can switch to,
9+
exist in the same folder, then URIs of all those existing files are returned.
10+
In case there is no file to switch to in that folder, the most likely candidate
11+
for creation is returned, e.g., if a user wants to switch from "foo.ml", but no
12+
files already exist in the project that could be returned, a URI for "foo.mli"
13+
is returned.
14+
15+
##### Client capability
16+
17+
nothing that should be noted
18+
19+
##### Server capability
20+
21+
property name: `handleSwitchImplIntf`
22+
property type: `boolean`
23+
24+
##### Request
25+
26+
- method: `ocamllsp/switchImplIntf`
27+
- params: `DocumentUri` (see [`DocumentUri`](https://microsoft.github.io/language-server-protocol/specifications/specification-current/#uri) in LSP specification)
28+
29+
##### Response
30+
31+
- result: DocumentUri[] (non-empty)
32+
- error: code and message set in case an exception happens during the willSaveWaitUntil request.
33+
34+

ocaml-lsp-server/src/import.ml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -38,6 +38,7 @@ module CodeLens = CodeLens
3838
module DocumentHighlight = DocumentHighlight
3939
module DocumentHighlightKind = DocumentHighlightKind
4040
module DocumentSymbol = DocumentSymbol
41+
module DocumentUri = DocumentUri
4142
module SymbolInformation = SymbolInformation
4243
module CompletionItem = CompletionItem
4344
module CompletionList = CompletionList

ocaml-lsp-server/src/ocaml_lsp_server.ml

Lines changed: 24 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -40,7 +40,12 @@ let initialize_info : InitializeResult.t =
4040
let capabilities =
4141
let experimental =
4242
`Assoc
43-
[ ("ocamllsp", `Assoc [ ("interfaceSpecificLangId", `Bool true) ]) ]
43+
[ ( "ocamllsp"
44+
, `Assoc
45+
[ ("interfaceSpecificLangId", `Bool true)
46+
; Switch_impl_intf.capability
47+
] )
48+
]
4449
in
4550
ServerCapabilities.create ~textDocumentSync ~hoverProvider:(`Bool true)
4651
~definitionProvider:(`Bool true) ~typeDefinitionProvider:(`Bool true)
@@ -508,6 +513,7 @@ let definition_query (state : State.t) uri position merlin_request =
508513
let result = location_of_merlin_loc uri result in
509514
Ok (result, state)
510515

516+
(** handles requests for OCaml (syntax) documents *)
511517
let ocaml_on_request :
512518
type resp.
513519
State.t Server.t
@@ -652,9 +658,23 @@ let on_request :
652658
let+ doc = Document_store.get_opt store uri in
653659
Document.syntax doc
654660
in
655-
match syntax with
656-
| Some (Ocamllex | Menhir) -> not_supported ()
657-
| _ -> ocaml_on_request server req
661+
match req with
662+
| Client_request.UnknownRequest { meth; params } -> (
663+
match
664+
[ (Switch_impl_intf.meth, Switch_impl_intf.on_request) ]
665+
|> List.assoc_opt meth
666+
with
667+
| None ->
668+
Fiber.return
669+
(Error
670+
(make_error ~code:InternalError ~message:"Unknown method"
671+
~data:(`Assoc [ ("method", `String meth) ])
672+
()))
673+
| Some handler -> handler ~params state )
674+
| _ -> (
675+
match syntax with
676+
| Some (Ocamllex | Menhir) -> not_supported ()
677+
| _ -> ocaml_on_request server req )
658678

659679
let on_notification server (notification : Client_notification.t) :
660680
State.t Fiber.t =
Lines changed: 61 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,61 @@
1+
open Import
2+
3+
let capability = ("handleSwitchImplIntf", `Bool true)
4+
5+
let meth = "ocamllsp/switchImplIntf"
6+
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
12+
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
17+
| Ocaml -> (
18+
match Document.kind doc with
19+
| Intf -> [ ml; mly; mll; re ]
20+
| Impl -> [ mli; mly; mll; rei ] )
21+
| Reason -> (
22+
match Document.kind doc with
23+
| Intf -> [ re; ml ]
24+
| Impl -> [ rei; mli ] )
25+
| Ocamllex -> [ mli; rei ]
26+
| Menhir -> [ mli; rei ]
27+
in
28+
let path_without_extension = Filename.remove_extension filepath ^ "." in
29+
let find_switch (exts : string list) =
30+
List.filter_map exts ~f:(fun ext ->
31+
let file_to_switch_to = path_without_extension ^ ext in
32+
Option.some_if (Sys.file_exists file_to_switch_to) file_to_switch_to)
33+
in
34+
let to_switch_to =
35+
match find_switch extensions_to_switch_to with
36+
| [] ->
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+
| to_switch_to -> to_switch_to
43+
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
48+
49+
let on_request ~(params : Json.t option) state =
50+
Fiber.return
51+
( match params with
52+
| Some (`String (file_uri : DocumentUri.t)) ->
53+
let open Result.O in
54+
let+ res = switch state file_uri in
55+
(res, state)
56+
| Some _
57+
| None ->
58+
Error
59+
(Jsonrpc.Response.Error.make ~code:InvalidRequest
60+
~message:"ocamllsp/switchImplIntf must receive param : DocumentUri.t"
61+
()) )
Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,10 @@
1+
open Import
2+
3+
val capability : string * Json.t
4+
5+
val meth : string
6+
7+
val on_request :
8+
params:Json.t option
9+
-> State.t
10+
-> (Json.t * State.t, Jsonrpc.Response.Error.t) result Fiber.t
Lines changed: 109 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,109 @@
1+
import { assert } from "console";
2+
import { promises as fs } from "fs";
3+
import * as path from "path";
4+
import { DocumentUri, TextDocumentItem } from "vscode-languageserver-types";
5+
import { URI } from "vscode-uri";
6+
import * as LanguageServer from "./../src/LanguageServer";
7+
8+
describe("ocamllsp/switchImplIntf", () => {
9+
let languageServer: LanguageServer.LanguageServer = null;
10+
11+
async function openDocument(documentUri: DocumentUri) {
12+
languageServer.sendNotification("textDocument/didOpen", {
13+
textDocument: TextDocumentItem.create(documentUri, "ocaml", 0, ""),
14+
});
15+
}
16+
17+
/* sends request "ocamllsp/switchImplIntf" */
18+
async function ocamllspSwitchImplIntf(
19+
documentUri: DocumentUri,
20+
): Promise<Array<DocumentUri>> {
21+
return languageServer.sendRequest("ocamllsp/switchImplIntf", documentUri);
22+
}
23+
24+
let testWorkspacePath = path.join(__dirname, "..", "test_files/");
25+
26+
beforeEach(async () => {
27+
languageServer = await LanguageServer.startAndInitialize();
28+
await fs.rmdir(testWorkspacePath, { recursive: true });
29+
fs.mkdir(testWorkspacePath);
30+
});
31+
32+
afterEach(async () => {
33+
await fs.rmdir(testWorkspacePath, { recursive: true });
34+
await LanguageServer.exit(languageServer);
35+
languageServer = null;
36+
});
37+
38+
let createPathForFile = (filename: string) =>
39+
path.join(testWorkspacePath, filename);
40+
41+
let createFileAtPath = async (path: string) =>
42+
fs.writeFile(path, "", { flag: "a+" });
43+
44+
let pathToDocumentUri = (path: string): DocumentUri =>
45+
URI.file(path).toString();
46+
47+
let [mli, ml, mll, mly, rei, re] = ["mli", "ml", "mll", "mly", "rei", "re"];
48+
49+
let testRequest = async (
50+
requestParam: DocumentUri,
51+
expectedResponse: DocumentUri[],
52+
) => {
53+
let response = await ocamllspSwitchImplIntf(requestParam);
54+
expect(response).toEqual(expectedResponse);
55+
};
56+
57+
/**
58+
* For testing 'ocamllsp/switchImplIntf'
59+
*
60+
* @param extsForCreation file name extension for files to be created in
61+
* (test) workspace folder. The first file created (even if only one file
62+
* is created) is treated as the file a user wants to switch from.
63+
* @param extExpected file name extensions that are expected to be returned as
64+
* a reponse to 'ocamllsp/switchImplIntf'
65+
*/
66+
let testingPipeline = async (
67+
extsForCreation: string[],
68+
extExpected: string[],
69+
) => {
70+
assert(
71+
extsForCreation.length > 0,
72+
"extensions for creation should not be empty",
73+
);
74+
assert(
75+
extExpected.length > 0,
76+
"expected response extensions should not be empty",
77+
);
78+
79+
let filePathsForCreation = extsForCreation.map((ext) => {
80+
let filename = "test.".concat(ext);
81+
return createPathForFile(filename);
82+
});
83+
84+
await Promise.all(filePathsForCreation.map(createFileAtPath));
85+
86+
let filePathToSwitchFrom = filePathsForCreation[0];
87+
let fileURIToSwitchFrom = pathToDocumentUri(filePathToSwitchFrom);
88+
await openDocument(fileURIToSwitchFrom);
89+
90+
let expectedFileURIs = extExpected.map((ext) => {
91+
let filename = "test.".concat(ext);
92+
let filePath = createPathForFile(filename);
93+
return pathToDocumentUri(filePath);
94+
});
95+
96+
testRequest(fileURIToSwitchFrom, expectedFileURIs);
97+
};
98+
99+
test.each([
100+
[[mli], [ml]],
101+
[[mli, ml], [ml]],
102+
[[ml], [mli]],
103+
[[ml, mli], [mli]],
104+
[
105+
[mli, ml, mll],
106+
[ml, mll],
107+
],
108+
])("test switches (%s => %s)", testingPipeline);
109+
});

ocaml-lsp-server/test/e2e/__tests__/textDocument-completion.test.ts

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,9 @@ import * as LanguageServer from "./../src/LanguageServer";
33

44
import * as Types from "vscode-languageserver-types";
55

6-
const describe_opt = LanguageServer.ocamlVersionGEq("4.08.0") ? describe : xdescribe;
6+
const describe_opt = LanguageServer.ocamlVersionGEq("4.08.0")
7+
? describe
8+
: xdescribe;
79

810
describe_opt("textDocument/completion", () => {
911
let languageServer = null;

ocaml-lsp-server/test/e2e/__tests__/textDocument-hover.test.ts

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@ import * as LanguageServer from "./../src/LanguageServer";
44
import * as Types from "vscode-languageserver-types";
55

66
describe("textDocument/hover", () => {
7-
let languageServer;
7+
let languageServer: LanguageServer.LanguageServer;
88

99
afterEach(async () => {
1010
await LanguageServer.exit(languageServer);

0 commit comments

Comments
 (0)