@@ -174,29 +174,32 @@ let code_action server (params : CodeActionParams.t) =
174174 | Some set when not (List. mem (CodeActionKind. Other Action. destruct) ~set ) ->
175175 Fiber. return (Ok (None , state))
176176 | Some _
177- | None ->
177+ | None -> (
178178 let open Fiber.Result.O in
179179 let uri = Uri. t_of_yojson (`String params.textDocument.uri) in
180180 let * doc = Fiber. return (Document_store. get store uri) in
181- let command =
182- let start = Position. logical params.range.start in
183- let finish = Position. logical params.range.end_ in
184- Query_protocol. Case_analysis (start, finish)
185- in
186- let + result =
187- let open Fiber.O in
188- let + res = Document. dispatch doc command in
189- match res with
190- | Ok res ->
191- Ok (Some [ `CodeAction (code_action_of_case_analysis uri res) ])
192- | Error
193- ( Destruct. Wrong_parent _ | Query_commands. No_nodes
194- | Destruct. Not_allowed _ | Destruct. Useless_refine
195- | Destruct. Nothing_to_do ) ->
196- Ok (Some [] )
197- | Error exn -> raise exn
198- in
199- (result, state)
181+ match Document. kind doc with
182+ | Intf -> Fiber. return (Ok (None , state))
183+ | Impl ->
184+ let command =
185+ let start = Position. logical params.range.start in
186+ let finish = Position. logical params.range.end_ in
187+ Query_protocol. Case_analysis (start, finish)
188+ in
189+ let + result =
190+ let open Fiber.O in
191+ let + res = Document. dispatch doc command in
192+ match res with
193+ | Ok res ->
194+ Ok (Some [ `CodeAction (code_action_of_case_analysis uri res) ])
195+ | Error
196+ ( Destruct. Wrong_parent _ | Query_commands. No_nodes
197+ | Destruct. Not_allowed _ | Destruct. Useless_refine
198+ | Destruct. Nothing_to_do ) ->
199+ Ok (Some [] )
200+ | Error exn -> raise exn
201+ in
202+ (result, state) )
200203
201204module Formatter = struct
202205 let jsonrpc_error (e : Fmt.error ) =
0 commit comments