Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
6 changes: 6 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
@@ -1,3 +1,9 @@
# Unreleased

## Features

- Make `code-lens` for nested let bindings configurable (#1567)

# 1.24.0

## Features
Expand Down
21 changes: 15 additions & 6 deletions ocaml-lsp-server/docs/ocamllsp/config.md
Original file line number Diff line number Diff line change
Expand Up @@ -15,12 +15,21 @@ interface config {
*/
extendedHover: { enable : boolean }

/**
* Enable/Disable CodeLens
* @default false
* @since 1.16
*/
codelens: { enable : boolean }
codelens: {
/**
* Enable/Disable CodeLens
* @default false
* @since 1.16
*/
enable : boolean,

/**
* Enable CodeLens for nested let bindings
* @default false
* @since 1.25
*/
for_nested_bindings : boolean
}

/**
* Enable/Disable Dune diagnostics
Expand Down
30 changes: 26 additions & 4 deletions ocaml-lsp-server/src/config_data.ml
Original file line number Diff line number Diff line change
Expand Up @@ -192,7 +192,10 @@ module InlayHints = struct
end

module Lens = struct
type t = { enable : bool [@default true] }
type t =
{ enable : bool [@default true]
; for_nested_bindings : bool [@default false]
}
[@@deriving_inline yojson] [@@yojson.allow_extra_fields]

let _ = fun (_ : t) -> ()
Expand All @@ -202,6 +205,7 @@ module Lens = struct
function
| `Assoc field_yojsons as yojson ->
let enable_field = ref Ppx_yojson_conv_lib.Option.None
and for_nested_bindings_field = ref Ppx_yojson_conv_lib.Option.None
and duplicates = ref []
and extra = ref [] in
let rec iter = function
Expand All @@ -214,6 +218,13 @@ module Lens = struct
enable_field := Ppx_yojson_conv_lib.Option.Some fvalue
| Ppx_yojson_conv_lib.Option.Some _ ->
duplicates := field_name :: Ppx_yojson_conv_lib.( ! ) duplicates)
| "for_nested_bindings" ->
(match Ppx_yojson_conv_lib.( ! ) for_nested_bindings_field with
| Ppx_yojson_conv_lib.Option.None ->
let fvalue = bool_of_yojson _field_yojson in
for_nested_bindings_field := Ppx_yojson_conv_lib.Option.Some fvalue
| Ppx_yojson_conv_lib.Option.Some _ ->
duplicates := field_name :: Ppx_yojson_conv_lib.( ! ) duplicates)
| _ -> ());
iter tail
| [] -> ()
Expand All @@ -233,11 +244,18 @@ module Lens = struct
(Ppx_yojson_conv_lib.( ! ) extra)
yojson
| [] ->
let enable_value = Ppx_yojson_conv_lib.( ! ) enable_field in
let enable_value, for_nested_bindings_value =
( Ppx_yojson_conv_lib.( ! ) enable_field
, Ppx_yojson_conv_lib.( ! ) for_nested_bindings_field )
in
{ enable =
(match enable_value with
| Ppx_yojson_conv_lib.Option.None -> true
| Ppx_yojson_conv_lib.Option.Some v -> v)
; for_nested_bindings =
(match for_nested_bindings_value with
| Ppx_yojson_conv_lib.Option.None -> false
| Ppx_yojson_conv_lib.Option.Some v -> v)
}))
| _ as yojson ->
Ppx_yojson_conv_lib.Yojson_conv_error.record_list_instead_atom _tp_loc yojson
Expand All @@ -248,8 +266,12 @@ module Lens = struct

let yojson_of_t =
(function
| { enable = v_enable } ->
| { enable = v_enable; for_nested_bindings = v_for_nested_bindings } ->
let bnds : (string * Ppx_yojson_conv_lib.Yojson.Safe.t) list = [] in
let bnds =
let arg = yojson_of_bool v_for_nested_bindings in
("for_nested_bindings", arg) :: bnds
in
let bnds =
let arg = yojson_of_bool v_enable in
("enable", arg) :: bnds
Expand Down Expand Up @@ -921,7 +943,7 @@ let _ = yojson_of_t
[@@@end]

let default =
{ codelens = Some { enable = false }
{ codelens = Some { enable = false; for_nested_bindings = false }
; extended_hover = Some { enable = false }
; standard_hover = Some { enable = true }
; inlay_hints =
Expand Down
15 changes: 12 additions & 3 deletions ocaml-lsp-server/src/ocaml_lsp_server.ml
Original file line number Diff line number Diff line change
Expand Up @@ -363,7 +363,11 @@ module Formatter = struct
;;
end

let text_document_lens (state : State.t) { CodeLensParams.textDocument = { uri }; _ } =
let text_document_lens
(state : State.t)
{ CodeLensParams.textDocument = { uri }; _ }
~for_nested_bindings
=
let store = state.store in
let doc = Document_store.get store uri in
match Document.kind doc with
Expand All @@ -372,7 +376,11 @@ let text_document_lens (state : State.t) { CodeLensParams.textDocument = { uri }
| `Merlin doc ->
let+ outline = Document.Merlin.dispatch_exn ~name:"outline" doc Outline in
let rec symbol_info_of_outline_item (item : Query_protocol.item) =
let children = List.concat_map item.children ~f:symbol_info_of_outline_item in
let children =
if for_nested_bindings
then List.concat_map item.children ~f:symbol_info_of_outline_item
else []
in
match item.outline_type with
| None -> children
| Some typ ->
Expand Down Expand Up @@ -651,7 +659,8 @@ let on_request
| TextDocumentCodeLensResolve codeLens -> now codeLens
| TextDocumentCodeLens req ->
(match state.configuration.data.codelens with
| Some { enable = true } -> later text_document_lens req
| Some { enable = true; for_nested_bindings } ->
later (text_document_lens ~for_nested_bindings) req
| _ -> now [])
| TextDocumentHighlight req -> later highlight req
| DocumentSymbol { textDocument = { uri }; _ } -> later document_symbol uri
Expand Down
117 changes: 117 additions & 0 deletions ocaml-lsp-server/test/e2e-new/code_lens.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,117 @@
open Test.Import

let change_config client params = Client.notification client (ChangeConfiguration params)

let codelens client textDocument =
Client.request
client
(TextDocumentCodeLens
{ textDocument; workDoneToken = None; partialResultToken = None })
;;

let json_of_codelens cs = `List (List.map ~f:CodeLens.yojson_of_t cs)

let%expect_test "enable codelens for nested let bindings" =
let source =
{ocaml|
let toplevel = "Hello"

let func x = x

let f x =
let y = 10 in
let z = 3 in
x + y + z
|ocaml}
in
let req client =
let text_document = TextDocumentIdentifier.create ~uri:Helpers.uri in
let* () =
change_config
client
(DidChangeConfigurationParams.create
~settings:(`Assoc [ "codelens", `Assoc [ "for_nested_bindings", `Bool true ] ]))
in
let* resp_codelens_toplevel = codelens client text_document in
Test.print_result (json_of_codelens resp_codelens_toplevel);
Fiber.return ()
in
Helpers.test source req;
[%expect
{|
[
{
"command": { "command": "", "title": "int -> int" },
"range": {
"end": { "character": 11, "line": 8 },
"start": { "character": 0, "line": 5 }
}
},
{
"command": { "command": "", "title": "int" },
"range": {
"end": { "character": 12, "line": 6 },
"start": { "character": 2, "line": 6 }
}
},
{
"command": { "command": "", "title": "int" },
"range": {
"end": { "character": 11, "line": 7 },
"start": { "character": 2, "line": 7 }
}
},
{
"command": { "command": "", "title": "'a -> 'a" },
"range": {
"end": { "character": 14, "line": 3 },
"start": { "character": 0, "line": 3 }
}
},
{
"command": { "command": "", "title": "string" },
"range": {
"end": { "character": 22, "line": 1 },
"start": { "character": 0, "line": 1 }
}
}
]
|}]
;;

let%expect_test "enable codelens (default settings disable it for nested let binding)" =
let source =
{ocaml|
let x =
let y = 10 in
"Hello"

let () = ()
|ocaml}
in
let req client =
let text_document = TextDocumentIdentifier.create ~uri:Helpers.uri in
let* () =
change_config
client
(DidChangeConfigurationParams.create
~settings:(`Assoc [ "codelens", `Assoc [ "enable", `Bool true ] ]))
in
let* resp_codelens_toplevel = codelens client text_document in
Test.print_result (json_of_codelens resp_codelens_toplevel);
Fiber.return ()
in
Helpers.test source req;
[%expect
{|
[
{
"command": { "command": "", "title": "string" },
"range": {
"end": { "character": 9, "line": 3 },
"start": { "character": 0, "line": 1 }
}
}
]
|}]
;;
1 change: 1 addition & 0 deletions ocaml-lsp-server/test/e2e-new/dune
Original file line number Diff line number Diff line change
Expand Up @@ -44,6 +44,7 @@
action_inline
action_mark_remove
code_actions
code_lens
completion
completions
construct
Expand Down
Loading