Skip to content

Commit

Permalink
Adapt to new Code_action interface.
Browse files Browse the repository at this point in the history
  • Loading branch information
Jack Feser committed Oct 11, 2021
1 parent c9f2efa commit aa8b52d
Show file tree
Hide file tree
Showing 3 changed files with 29 additions and 20 deletions.
43 changes: 25 additions & 18 deletions ocaml-lsp-server/src/code_actions/action_mark_remove_unused.ml
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,8 @@ let slice doc (range : Range.t) =
and (`Offset end_) = Msource.get_offset src @@ Position.logical range.end_ in
String.sub (Msource.text src) ~pos:start ~len:(end_ - start)

(* Return contexts enclosing `pos` in order from most specific to most general. *)
(* Return contexts enclosing `pos` in order from most specific to most
general. *)
let enclosing_pos pipeline pos =
let browse =
Mpipeline.typer_result pipeline
Expand Down Expand Up @@ -121,21 +122,27 @@ let code_action_remove_value doc pos (diagnostic : Diagnostic.t) =
|> Option.map ~f:(fun range ->
code_action_remove_range doc diagnostic range))

let code_action doc (params : CodeActionParams.t) =
let find_unused_diagnostic pos (ds : Diagnostic.t list) =
List.find ds ~f:(fun d ->
let in_range =
match Position.compare_inclusion pos d.range with
| `Outside _ -> false
| `Inside -> true
in
in_range && Diagnostic_util.is_unused_var_warning d)

let code_action_mark doc (params : CodeActionParams.t) =
let pos = params.range.start in
let diag =
List.find params.context.diagnostics ~f:(fun (d : Diagnostic.t) ->
let in_range =
match Position.compare_inclusion pos d.range with
| `Outside _ -> false
| `Inside -> true
in
in_range && Diagnostic_util.is_unused_var_warning d)
in
match diag with
| None -> Fiber.return []
| Some d ->
let open Fiber.O in
let* mark_unused = code_action_mark_value_unused doc d in
let+ remove_unused = code_action_remove_value doc pos d in
List.filter_opt [ mark_unused; remove_unused ]
match find_unused_diagnostic pos params.context.diagnostics with
| None -> Fiber.return None
| Some d -> code_action_mark_value_unused doc d

let code_action_remove doc (params : CodeActionParams.t) =
let pos = params.range.start in
match find_unused_diagnostic pos params.context.diagnostics with
| None -> Fiber.return None
| Some d -> code_action_remove_value doc pos d

let mark = { Code_action.kind = QuickFix; run = code_action_mark }

let remove = { Code_action.kind = QuickFix; run = code_action_remove }
Original file line number Diff line number Diff line change
@@ -1,3 +1,3 @@
open Import
val mark : Code_action.t

val code_action : Document.t -> CodeActionParams.t -> CodeAction.t list Fiber.t
val remove : Code_action.t
2 changes: 2 additions & 0 deletions ocaml-lsp-server/src/ocaml_lsp_server.ml
Original file line number Diff line number Diff line change
Expand Up @@ -311,6 +311,8 @@ let code_action (state : State.t) (params : CodeActionParams.t) =
; Action_refactor_open.unqualify
; Action_refactor_open.qualify
; Action_add_rec.t
; Action_mark_remove_unused.mark
; Action_mark_remove_unused.remove
]
in
let code_action_results = List.filter_opt code_action_results in
Expand Down

0 comments on commit aa8b52d

Please sign in to comment.