Skip to content

Commit

Permalink
fix bug in 'switchImplIntf': (#254)
Browse files Browse the repository at this point in the history
* 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
  • Loading branch information
ulugbekna authored Oct 6, 2020
1 parent 25c4d5f commit 2d1e7c0
Show file tree
Hide file tree
Showing 4 changed files with 61 additions and 26 deletions.
12 changes: 12 additions & 0 deletions ocaml-lsp-server/src/document.ml
Original file line number Diff line number Diff line change
Expand Up @@ -37,6 +37,18 @@ module Syntax = struct
; ("ocaml.menhir", Menhir)
]

let of_fname s =
match Filename.extension s with
| ".mli"
| ".ml" ->
Ocaml
| ".rei"
| ".re" ->
Reason
| ".mll" -> Ocamllex
| ".mly" -> Menhir
| ext -> failwith ("Unknown extension " ^ ext)

let of_language_id language_id =
match List.assoc all language_id with
| Some id -> id
Expand Down
4 changes: 4 additions & 0 deletions ocaml-lsp-server/src/document.mli
Original file line number Diff line number Diff line change
Expand Up @@ -12,12 +12,16 @@ module Syntax : sig
val human_name : t -> string

val markdown_name : t -> string

val of_fname : string -> t
end

module Kind : sig
type t =
| Intf
| Impl

val of_fname : string -> t
end

val kind : t -> Kind.t
Expand Down
55 changes: 29 additions & 26 deletions ocaml-lsp-server/src/switch_impl_intf.ml
Original file line number Diff line number Diff line change
Expand Up @@ -4,54 +4,57 @@ let capability = ("handleSwitchImplIntf", `Bool true)

let meth = "ocamllsp/switchImplIntf"

(** See the spec for 'ocamllsp/switchImplIntf' *)
let switch (state : State.t) (param : DocumentUri.t) :
(Json.t, Jsonrpc.Response.Error.t) result =
let file_uri = Uri.t_of_yojson (`String param) in
let filepath = Uri.to_path file_uri in
(** see the spec for [ocamllsp/switchImplIntf] *)
let switch (param : DocumentUri.t) : (Json.t, Jsonrpc.Response.Error.t) result =
let fpath =
match String.split ~on:':' param with
| [ scheme; path ] ->
if scheme = "file" then
Uri.t_of_yojson (`String param) |> Uri.to_path
else
path
| _ -> failwith "provided file URI (param) doesn't follow URI spec"
in
let fname = Filename.basename fpath in
let ml, mli, re, rei, mll, mly = ("ml", "mli", "re", "rei", "mll", "mly") in
let open Result.O in
let+ doc = Document_store.get state.store file_uri in
let extensions_to_switch_to =
match Document.syntax doc with
let exts_to_switch_to =
match Document.Syntax.of_fname fname with
| Ocaml -> (
match Document.kind doc with
match Document.Kind.of_fname fname with
| Intf -> [ ml; mly; mll; re ]
| Impl -> [ mli; mly; mll; rei ] )
| Reason -> (
match Document.kind doc with
match Document.Kind.of_fname fname with
| Intf -> [ re; ml ]
| Impl -> [ rei; mli ] )
| Ocamllex -> [ mli; rei ]
| Menhir -> [ mli; rei ]
in
let path_without_extension = Filename.remove_extension filepath ^ "." in
let find_switch (exts : string list) =
let fpath_w_ext ext = Filename.remove_extension fpath ^ "." ^ ext in
let find_switch exts =
List.filter_map exts ~f:(fun ext ->
let file_to_switch_to = path_without_extension ^ ext in
let file_to_switch_to = fpath_w_ext ext in
Option.some_if (Sys.file_exists file_to_switch_to) file_to_switch_to)
in
let to_switch_to =
match find_switch extensions_to_switch_to with
let files_to_switch_to =
match find_switch exts_to_switch_to with
| [] ->
let main_switch_to_candidate_ext = List.hd extensions_to_switch_to in
let main_switch_to_candidate_path =
path_without_extension ^ main_switch_to_candidate_ext
in
[ main_switch_to_candidate_path ]
let switch_to_ext = List.hd exts_to_switch_to in
let switch_to_fpath = fpath_w_ext switch_to_ext in
[ switch_to_fpath ]
| to_switch_to -> to_switch_to
in
let to_switch_to_json_array =
List.map to_switch_to ~f:(fun s -> `String (Uri.to_string @@ Uri.of_path s))
in
`List to_switch_to_json_array
Ok
(Json.yojson_of_list
(fun fpath -> Uri.of_path fpath |> Uri.to_string |> fun s -> `String s)
files_to_switch_to)

let on_request ~(params : Json.t option) state =
Fiber.return
( match params with
| Some (`String (file_uri : DocumentUri.t)) ->
let open Result.O in
let+ res = switch state file_uri in
let+ res = switch file_uri in
(res, state)
| Some _
| None ->
Expand Down
16 changes: 16 additions & 0 deletions ocaml-lsp-server/test/e2e/__tests__/ocamllsp-switchImplIntf.ts
Original file line number Diff line number Diff line change
Expand Up @@ -106,4 +106,20 @@ describe("ocamllsp/switchImplIntf", () => {
[ml, mll],
],
])("test switches (%s => %s)", testingPipeline);

it("can switch from file URI with non-file scheme", async () => {
let mlFpath = createPathForFile("test.ml");
await createFileAtPath(mlFpath);
let mlUri = pathToDocumentUri(mlFpath);

let newMliFpath = createPathForFile("test.mli");
await createFileAtPath(newMliFpath);
let mliUriUntitledScheme: DocumentUri = URI.file(newMliFpath)
.with({
scheme: "untitled",
})
.toString();

testRequest(mliUriUntitledScheme, [mlUri]);
});
});

0 comments on commit 2d1e7c0

Please sign in to comment.