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
5 changes: 5 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
@@ -1,8 +1,13 @@
# unreleased

## Features

- Make `inlay-hint` for function parameters configurable (#1515)

## Fixes

- Support for `class`, `class type`, `method` and `property` for `DocumentSymbol` query (#1487 fixes #1449)
- Fix `inlay-hint` for function parameters (#1515)

# 1.22.0

Expand Down
33 changes: 30 additions & 3 deletions ocaml-lsp-server/src/config_data.ml
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@ module InlayHints = struct
type t =
{ hint_pattern_variables : bool [@key "hintPatternVariables"] [@default false]
; hint_let_bindings : bool [@key "hintLetBindings"] [@default false]
; hint_function_params : bool [@key "hintFunctionParams"] [@default false]
}
[@@deriving_inline yojson] [@@yojson.allow_extra_fields]

Expand All @@ -16,6 +17,7 @@ module InlayHints = struct
| `Assoc field_yojsons as yojson ->
let hint_pattern_variables_field = ref Ppx_yojson_conv_lib.Option.None
and hint_let_bindings_field = ref Ppx_yojson_conv_lib.Option.None
and hint_function_params_field = ref Ppx_yojson_conv_lib.Option.None
and duplicates = ref []
and extra = ref [] in
let rec iter = function
Expand All @@ -35,6 +37,13 @@ module InlayHints = struct
hint_let_bindings_field := Ppx_yojson_conv_lib.Option.Some fvalue
| Ppx_yojson_conv_lib.Option.Some _ ->
duplicates := field_name :: Ppx_yojson_conv_lib.( ! ) duplicates)
| "hintFunctionParams" ->
(match Ppx_yojson_conv_lib.( ! ) hint_function_params_field with
| Ppx_yojson_conv_lib.Option.None ->
let fvalue = bool_of_yojson _field_yojson in
hint_function_params_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 @@ -54,9 +63,13 @@ module InlayHints = struct
(Ppx_yojson_conv_lib.( ! ) extra)
yojson
| [] ->
let hint_pattern_variables_value, hint_let_bindings_value =
let ( hint_pattern_variables_value
, hint_let_bindings_value
, hint_function_params_value )
=
( Ppx_yojson_conv_lib.( ! ) hint_pattern_variables_field
, Ppx_yojson_conv_lib.( ! ) hint_let_bindings_field )
, Ppx_yojson_conv_lib.( ! ) hint_let_bindings_field
, Ppx_yojson_conv_lib.( ! ) hint_function_params_field )
in
{ hint_pattern_variables =
(match hint_pattern_variables_value with
Expand All @@ -66,6 +79,10 @@ module InlayHints = struct
(match hint_let_bindings_value with
| Ppx_yojson_conv_lib.Option.None -> false
| Ppx_yojson_conv_lib.Option.Some v -> v)
; hint_function_params =
(match hint_function_params_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 @@ -78,8 +95,13 @@ module InlayHints = struct
(function
| { hint_pattern_variables = v_hint_pattern_variables
; hint_let_bindings = v_hint_let_bindings
; hint_function_params = v_hint_function_params
} ->
let bnds : (string * Ppx_yojson_conv_lib.Yojson.Safe.t) list = [] in
let bnds =
let arg = yojson_of_bool v_hint_function_params in
("hintFunctionParams", arg) :: bnds
in
let bnds =
let arg = yojson_of_bool v_hint_let_bindings in
("hintLetBindings", arg) :: bnds
Expand Down Expand Up @@ -798,7 +820,12 @@ let default =
{ codelens = Some { enable = false }
; extended_hover = Some { enable = false }
; standard_hover = Some { enable = true }
; inlay_hints = Some { hint_pattern_variables = false; hint_let_bindings = false }
; inlay_hints =
Some
{ hint_pattern_variables = false
; hint_let_bindings = false
; hint_function_params = false
}
; dune_diagnostics = Some { enable = true }
; syntax_documentation = Some { enable = false }
; merlin_jump_code_actions = Some { enable = false }
Expand Down
12 changes: 11 additions & 1 deletion ocaml-lsp-server/src/inlay_hints.ml
Original file line number Diff line number Diff line change
Expand Up @@ -29,12 +29,22 @@ let compute (state : State.t) { InlayHintParams.range; textDocument = { uri }; _
c.hint_pattern_variables)
|> Option.value ~default:false
in
let hint_function_params =
Option.map state.configuration.data.inlay_hints ~f:(fun c ->
c.hint_function_params)
|> Option.value ~default:false
in
Document.Merlin.with_pipeline_exn ~name:"inlay-hints" doc (fun pipeline ->
let start = range.start |> Position.logical
and stop = range.end_ |> Position.logical in
let command =
Query_protocol.Inlay_hints
(start, stop, hint_let_bindings, hint_pattern_variables, not inside_test)
( start
, stop
, hint_let_bindings
, hint_pattern_variables
, hint_function_params
, not inside_test )
in
let hints = Query_commands.dispatch pipeline command in
List.filter_map
Expand Down
15 changes: 15 additions & 0 deletions ocaml-lsp-server/test/e2e-new/inlay_hints.ml
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@ let apply_inlay_hints
?range
?(hint_pattern_variables = false)
?(hint_let_bindings = false)
?(hint_function_params = true)
~source
()
=
Expand Down Expand Up @@ -33,6 +34,7 @@ let apply_inlay_hints
, `Assoc
[ "hintPatternVariables", `Bool hint_pattern_variables
; "hintLetBindings", `Bool hint_let_bindings
; "hintFunctionParams", `Bool hint_function_params
] )
])
(InlayHint request)
Expand Down Expand Up @@ -99,3 +101,16 @@ let%expect_test "let bindings" =
apply_inlay_hints ~hint_let_bindings:true ~source ();
[%expect {| let f () = let y$: int$ = 0 in y |}]
;;

let%expect_test "function params" =
let source = "let f a b c d = (a + b, c ^ string_of_bool d)" in
apply_inlay_hints ~source ();
[%expect
{| let f a$: int$ b$: int$ c$: string$ d$: bool$ = (a + b, c ^ string_of_bool d) |}]
;;

let%expect_test "function params (deactivated)" =
let source = "let f a b c d = (a + b, c ^ string_of_bool d)" in
apply_inlay_hints ~hint_function_params:false ~source ();
[%expect {| let f a b c d = (a + b, c ^ string_of_bool d) |}]
;;