Skip to content

Commit

Permalink
fix bug in 'switchImplIntf':
Browse files Browse the repository at this point in the history
  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.
  • Loading branch information
ulugbekna committed Oct 2, 2020
1 parent a66d82a commit d1bdba8
Show file tree
Hide file tree
Showing 3 changed files with 33 additions and 11 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
28 changes: 17 additions & 11 deletions ocaml-lsp-server/src/switch_impl_intf.ml
Original file line number Diff line number Diff line change
Expand Up @@ -5,21 +5,27 @@ 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
let switch (param : DocumentUri.t) : (Json.t, Jsonrpc.Response.Error.t) result =
let filepath =
let file_uri = Uri.t_of_yojson (`String param) in
let possible_filepath = Uri.to_path file_uri in
if possible_filepath = Uri.to_string file_uri then
(* remove URI scheme *)
String.split ~on:':' possible_filepath |> List.tl |> List.hd
else
possible_filepath
(* Note: URI lib such as ocaml-uri would help eliminate brittle URI handling *)
in
let filename = Filename.basename filepath 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
match Document.Syntax.of_fname filename with
| Ocaml -> (
match Document.kind doc with
match Document.Kind.of_fname filename with
| Intf -> [ ml; mly; mll; re ]
| Impl -> [ mli; mly; mll; rei ] )
| Reason -> (
match Document.kind doc with
match Document.Kind.of_fname filename with
| Intf -> [ re; ml ]
| Impl -> [ rei; mli ] )
| Ocamllex -> [ mli; rei ]
Expand All @@ -44,14 +50,14 @@ let switch (state : State.t) (param : DocumentUri.t) :
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 (`List to_switch_to_json_array)

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

0 comments on commit d1bdba8

Please sign in to comment.