Skip to content

Commit 47d0169

Browse files
authored
Merge pull request #313 from tmattio/organize-req-actions
Reorganize code actions and custom requests into subdirs
2 parents f134467 + 749958c commit 47d0169

File tree

11 files changed

+88
-83
lines changed

11 files changed

+88
-83
lines changed
File renamed without changes.
File renamed without changes.

ocaml-lsp-server/src/inferred_intf.ml renamed to ocaml-lsp-server/src/code_actions/action_inferred_intf.ml

Lines changed: 1 addition & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -59,11 +59,7 @@ let code_action doc (state : State.t) (params : CodeActionParams.t) =
5959
| Impl -> Fiber.return (Ok None)
6060
| Intf -> (
6161
let intf_uri = Document.uri doc in
62-
let intf_path = Uri.to_path intf_uri in
63-
let impl_path =
64-
Switch_impl_intf.get_intf_impl_counterparts intf_path |> List.hd
65-
in
66-
let impl_uri = Uri.of_path impl_path in
62+
let impl_uri = Document.get_impl_intf_counterparts intf_uri |> List.hd in
6763
let* impl =
6864
match Document_store.get_opt state.store impl_uri with
6965
| None -> force_open_document state impl_uri
File renamed without changes.
Lines changed: 29 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,29 @@
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 (param : DocumentUri.t) : (Json.t, Jsonrpc.Response.Error.t) result =
9+
let files_to_switch_to =
10+
Document.get_impl_intf_counterparts (Uri.t_of_yojson (`String param))
11+
in
12+
Ok
13+
(Json.yojson_of_list
14+
(fun uri -> uri |> Uri.to_string |> fun s -> `String s)
15+
files_to_switch_to)
16+
17+
let on_request ~(params : Json.t option) state =
18+
Fiber.return
19+
( match params with
20+
| Some (`String (file_uri : DocumentUri.t)) ->
21+
let open Result.O in
22+
let+ res = switch file_uri in
23+
(res, state)
24+
| Some _
25+
| None ->
26+
Error
27+
(Jsonrpc.Response.Error.make ~code:InvalidRequest
28+
~message:"ocamllsp/switchImplIntf must receive param : DocumentUri.t"
29+
()) )

ocaml-lsp-server/src/switch_impl_intf.mli renamed to ocaml-lsp-server/src/custom_requests/req_switch_impl_intf.mli

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -4,8 +4,6 @@ val capability : string * Json.t
44

55
val meth : string
66

7-
val get_intf_impl_counterparts : string -> string list
8-
97
val on_request :
108
params:Json.t option
119
-> State.t

ocaml-lsp-server/src/document.ml

Lines changed: 42 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -145,3 +145,45 @@ let dispatch_exn (doc : t) command =
145145
Query_commands.dispatch pipeline command)
146146

147147
let close t = Scheduler.cancel_timer t.timer
148+
149+
let get_impl_intf_counterparts uri =
150+
let uri_s = Uri.to_string uri in
151+
let fpath =
152+
match String.split ~on:':' uri_s with
153+
| [ scheme; path ] ->
154+
if scheme = "file" then
155+
Uri.t_of_yojson (`String uri_s) |> Uri.to_path
156+
else
157+
path
158+
| _ -> failwith "provided file URI (param) doesn't follow URI spec"
159+
in
160+
let fname = Filename.basename fpath in
161+
let ml, mli, re, rei, mll, mly = ("ml", "mli", "re", "rei", "mll", "mly") in
162+
let exts_to_switch_to =
163+
match Syntax.of_fname fname with
164+
| Ocaml -> (
165+
match Kind.of_fname fname with
166+
| Intf -> [ ml; mly; mll; re ]
167+
| Impl -> [ mli; mly; mll; rei ] )
168+
| Reason -> (
169+
match Kind.of_fname fname with
170+
| Intf -> [ re; ml ]
171+
| Impl -> [ rei; mli ] )
172+
| Ocamllex -> [ mli; rei ]
173+
| Menhir -> [ mli; rei ]
174+
in
175+
let fpath_w_ext ext = Filename.remove_extension fpath ^ "." ^ ext in
176+
let find_switch exts =
177+
List.filter_map exts ~f:(fun ext ->
178+
let file_to_switch_to = fpath_w_ext ext in
179+
Option.some_if (Sys.file_exists file_to_switch_to) file_to_switch_to)
180+
in
181+
let files_to_switch_to =
182+
match find_switch exts_to_switch_to with
183+
| [] ->
184+
let switch_to_ext = List.hd exts_to_switch_to in
185+
let switch_to_fpath = fpath_w_ext switch_to_ext in
186+
[ switch_to_fpath ]
187+
| to_switch_to -> to_switch_to
188+
in
189+
List.map ~f:Uri.of_path files_to_switch_to

ocaml-lsp-server/src/document.mli

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -54,3 +54,9 @@ val dispatch : t -> 'a Query_protocol.t -> ('a, exn) result Fiber.t
5454
val dispatch_exn : t -> 'a Query_protocol.t -> 'a Fiber.t
5555

5656
val close : t -> unit Fiber.t
57+
58+
(** [get_impl_intf_counterparts uri] returns the implementation/interface
59+
counterparts for the URI [uri].
60+
61+
For instance, the counterparts of the file {/file.ml} are {[/file.mli]}. *)
62+
val get_impl_intf_counterparts : Uri.t -> Uri.t list

ocaml-lsp-server/src/dune

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -7,3 +7,5 @@
77
merlin.analysis merlin.kernel merlin.merlin_utils merlin.parsing
88
merlin.query_commands merlin.query_protocol merlin.specific merlin.typing
99
merlin.utils octavius omd ppx_yojson_conv_lib result stdune yojson))
10+
11+
(include_subdirs unqualified)

ocaml-lsp-server/src/ocaml_lsp_server.ml

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -15,8 +15,8 @@ let not_supported () =
1515
let initialize_info : InitializeResult.t =
1616
let codeActionProvider =
1717
let codeActionKinds =
18-
[ CodeActionKind.Other Destruct.action_kind
19-
; CodeActionKind.Other Inferred_intf.action_kind
18+
[ CodeActionKind.Other Action_destruct.action_kind
19+
; CodeActionKind.Other Action_inferred_intf.action_kind
2020
]
2121
in
2222
`CodeActionOptions (CodeActionOptions.create ~codeActionKinds ())
@@ -43,7 +43,7 @@ let initialize_info : InitializeResult.t =
4343
[ ( "ocamllsp"
4444
, `Assoc
4545
[ ("interfaceSpecificLangId", `Bool true)
46-
; Switch_impl_intf.capability
46+
; Req_switch_impl_intf.capability
4747
] )
4848
]
4949
in
@@ -184,10 +184,10 @@ let code_action server (params : CodeActionParams.t) =
184184
let open Fiber.O in
185185
let+ code_action_results =
186186
Fiber.parallel_map ~f:code_action
187-
[ ( CodeActionKind.Other Destruct.action_kind
188-
, fun () -> Destruct.code_action doc params )
189-
; ( CodeActionKind.Other Inferred_intf.action_kind
190-
, fun () -> Inferred_intf.code_action doc state params )
187+
[ ( CodeActionKind.Other Action_destruct.action_kind
188+
, fun () -> Action_destruct.code_action doc params )
189+
; ( CodeActionKind.Other Action_inferred_intf.action_kind
190+
, fun () -> Action_inferred_intf.code_action doc state params )
191191
]
192192
in
193193
let open Result.O in
@@ -662,7 +662,7 @@ let on_request :
662662
match req with
663663
| Client_request.UnknownRequest { meth; params } -> (
664664
match
665-
[ (Switch_impl_intf.meth, Switch_impl_intf.on_request) ]
665+
[ (Req_switch_impl_intf.meth, Req_switch_impl_intf.on_request) ]
666666
|> List.assoc_opt meth
667667
with
668668
| None ->

0 commit comments

Comments
 (0)