Skip to content

Commit 0f22b3d

Browse files
committed
Handle command in Action destruct
1 parent 1b38e8b commit 0f22b3d

File tree

4 files changed

+14
-5
lines changed

4 files changed

+14
-5
lines changed

ocaml-lsp-server/src/code_actions/action_destruct.ml

Lines changed: 11 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -14,7 +14,16 @@ let code_action_of_case_analysis doc uri (loc, newText) =
1414
WorkspaceEdit.create ~documentChanges:[ `TextDocumentEdit edit ] ()
1515
in
1616
let title = String.capitalize_ascii action_kind in
17-
let command = None in
17+
let+ command =
18+
let+ holes =
19+
doc |> Document.merlin_exn |> Typed_hole.all ~pipeline_name:"action-destruct"
20+
in
21+
holes
22+
|> Typed_hole.find ~range ~position:range.start ~direction:`Next
23+
|> Option.map ~f:(fun range ->
24+
let arguments = [ DocumentUri.yojson_of_t uri; Range.yojson_of_t range ] in
25+
Command.create ~arguments ~command:Action_jump.command_name ~title ())
26+
in
1827
CodeAction.create
1928
~title
2029
~kind:(CodeActionKind.Other action_kind)
@@ -38,7 +47,7 @@ let code_action doc (params : CodeActionParams.t) =
3847
let* res = Document.Merlin.dispatch ~name:"destruct" merlin command in
3948
(match res with
4049
| Ok (loc, newText) ->
41-
Fiber.return (Some (code_action_of_case_analysis doc uri (loc, newText)))
50+
Fiber.map ~f:Option.some (code_action_of_case_analysis doc uri (loc, newText))
4251
| Error
4352
{ exn =
4453
( Merlin_analysis.Destruct.Wrong_parent _

ocaml-lsp-server/src/custom_requests/req_jump_to_typed_hole.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -76,7 +76,7 @@ let on_request ~(params : Jsonrpc.Structured.t option) (state : State.t) =
7676
let open Fiber.O in
7777
let merlin = Document.merlin_exn doc in
7878
let+ holes = Typed_hole.all ~pipeline_name:"jump-to-typed-hole" merlin in
79-
holes |> Typed_hole.find ~position ~range ~direction |> yojson_of_t
79+
holes |> Typed_hole.find ~position ?range ~direction |> yojson_of_t
8080
| None ->
8181
Jsonrpc.Response.Error.raise
8282
@@ Jsonrpc.Response.Error.make

ocaml-lsp-server/src/typed_hole.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -34,7 +34,7 @@ let find_next ~range ~position holes =
3434
| hole -> hole
3535
;;
3636

37-
let find ~range ~position ~direction holes =
37+
let find ?range ~position ~direction holes =
3838
match direction with
3939
| `Prev -> find_prev ~range ~position holes
4040
| `Next -> find_next ~range ~position holes

ocaml-lsp-server/src/typed_hole.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
val find
2-
: range:Range.t option
2+
: ?range:Range.t
33
-> position:Position.t
44
-> direction:[< `Next | `Prev ]
55
-> Range.t list

0 commit comments

Comments
 (0)