Skip to content

Commit 1392cb3

Browse files
committed
Format changes
1 parent e6f223e commit 1392cb3

File tree

2 files changed

+57
-38
lines changed

2 files changed

+57
-38
lines changed

ocaml-lsp-server/src/config_data.ml

+15-14
Original file line numberDiff line numberDiff line change
@@ -441,17 +441,18 @@ let t_of_yojson =
441441
extended_hover_field := Ppx_yojson_conv_lib.Option.Some fvalue
442442
| Ppx_yojson_conv_lib.Option.Some _ ->
443443
duplicates := field_name :: Ppx_yojson_conv_lib.( ! ) duplicates)
444-
| "syntaxDocumentation" -> (
445-
match Ppx_yojson_conv_lib.( ! ) syntax_documentation_field with
446-
| Ppx_yojson_conv_lib.Option.None ->
447-
let fvalue =
448-
Json.Nullable_option.t_of_yojson
449-
SyntaxDocumentation.t_of_yojson
450-
_field_yojson
451-
in
452-
syntax_documentation_field := Ppx_yojson_conv_lib.Option.Some fvalue
453-
| Ppx_yojson_conv_lib.Option.Some _ ->
454-
duplicates := field_name :: Ppx_yojson_conv_lib.( ! ) duplicates)
444+
| "syntaxDocumentation" -> (
445+
match Ppx_yojson_conv_lib.( ! ) syntax_documentation_field with
446+
| Ppx_yojson_conv_lib.Option.None ->
447+
let fvalue =
448+
Json.Nullable_option.t_of_yojson
449+
SyntaxDocumentation.t_of_yojson
450+
_field_yojson
451+
in
452+
syntax_documentation_field :=
453+
Ppx_yojson_conv_lib.Option.Some fvalue
454+
| Ppx_yojson_conv_lib.Option.Some _ ->
455+
duplicates := field_name :: Ppx_yojson_conv_lib.( ! ) duplicates)
455456
| "inlayHints" -> (
456457
match Ppx_yojson_conv_lib.( ! ) inlay_hints_field with
457458
| Ppx_yojson_conv_lib.Option.None ->
@@ -474,7 +475,7 @@ let t_of_yojson =
474475
dune_diagnostics_field := Ppx_yojson_conv_lib.Option.Some fvalue
475476
| Ppx_yojson_conv_lib.Option.Some _ ->
476477
duplicates := field_name :: Ppx_yojson_conv_lib.( ! ) duplicates)
477-
| _ -> ());
478+
| _ -> ());
478479
iter tail
479480
| [] -> ()
480481
in
@@ -539,8 +540,8 @@ let yojson_of_t =
539540
; extended_hover = v_extended_hover
540541
; inlay_hints = v_inlay_hints
541542
; dune_diagnostics = v_dune_diagnostics
542-
; syntax_documentation =
543-
v_syntax_documentation } ->
543+
; syntax_documentation = v_syntax_documentation
544+
} ->
544545
let bnds : (string * Ppx_yojson_conv_lib.Yojson.Safe.t) list = [] in
545546
let bnds =
546547
if None = v_dune_diagnostics then bnds

ocaml-lsp-server/src/hover_req.ml

+42-24
Original file line numberDiff line numberDiff line change
@@ -201,7 +201,7 @@ let format_as_code_block ~highlighter strings =
201201
let format_type_enclosing ~syntax ~markdown ~typ ~doc
202202
~(syntax_doc : Query_protocol.syntax_doc_result option) =
203203
(* TODO for vscode, we should just use the language id. But that will not work
204-
for all editors *)
204+
for all editors *)
205205
let syntax_doc =
206206
Option.map syntax_doc ~f:(fun syntax_doc ->
207207
sprintf
@@ -212,30 +212,32 @@ let format_type_enclosing ~syntax ~markdown ~typ ~doc
212212
in
213213
`MarkupContent
214214
(if markdown then
215-
let value =
216-
let markdown_name = Document.Syntax.markdown_name syntax in
217-
let type_info = Some (format_as_code_block ~highlighter:markdown_name [ typ ]) in
218-
let doc =
219-
Option.map doc ~f:(fun doc ->
220-
match Doc_to_md.translate doc with
221-
| Raw d -> d
222-
| Markdown d -> d)
223-
in
224-
print_dividers (List.filter_opt [ type_info; syntax_doc; doc ])
225-
in
226-
{ MarkupContent.value; kind = MarkupKind.Markdown }
227-
else
228-
let value =
229-
print_dividers (List.filter_opt [ Some typ; syntax_doc; doc ])
230-
in
231-
{ MarkupContent.value; kind = MarkupKind.PlainText })
215+
let value =
216+
let markdown_name = Document.Syntax.markdown_name syntax in
217+
let type_info =
218+
Some (format_as_code_block ~highlighter:markdown_name [ typ ])
219+
in
220+
let doc =
221+
Option.map doc ~f:(fun doc ->
222+
match Doc_to_md.translate doc with
223+
| Raw d -> d
224+
| Markdown d -> d)
225+
in
226+
print_dividers (List.filter_opt [ type_info; syntax_doc; doc ])
227+
in
228+
{ MarkupContent.value; kind = MarkupKind.Markdown }
229+
else
230+
let value =
231+
print_dividers (List.filter_opt [ Some typ; syntax_doc; doc ])
232+
in
233+
{ MarkupContent.value; kind = MarkupKind.PlainText })
232234

233235
let format_ppx_expansion ~ppx ~expansion =
234236
let value = sprintf "(* ppx %s expansion *)\n%s" ppx expansion in
235237
`MarkedString { Lsp.Types.MarkedString.value; language = Some "ocaml" }
236238

237-
let type_enclosing_hover ~(server : State.t Server.t) ~(doc : Document.t) ~with_syntax_doc
238-
~merlin ~mode ~uri ~position =
239+
let type_enclosing_hover ~(server : State.t Server.t) ~(doc : Document.t)
240+
~with_syntax_doc ~merlin ~mode ~uri ~position =
239241
let state = Server.state server in
240242
let verbosity =
241243
let mode =
@@ -263,7 +265,11 @@ let type_enclosing_hover ~(server : State.t Server.t) ~(doc : Document.t) ~with_
263265
v
264266
in
265267
let* type_enclosing =
266-
Document.Merlin.type_enclosing merlin (Position.logical position) verbosity ~with_syntax_doc
268+
Document.Merlin.type_enclosing
269+
merlin
270+
(Position.logical position)
271+
verbosity
272+
~with_syntax_doc
267273
in
268274
match type_enclosing with
269275
| None -> Fiber.return None
@@ -299,7 +305,12 @@ let type_enclosing_hover ~(server : State.t Server.t) ~(doc : Document.t) ~with_
299305
client_capabilities
300306
~field:(fun td -> Option.map td.hover ~f:(fun h -> h.contentFormat))
301307
in
302-
format_type_enclosing ~syntax ~markdown ~typ ~doc:documentation ~syntax_doc
308+
format_type_enclosing
309+
~syntax
310+
~markdown
311+
~typ
312+
~doc:documentation
313+
~syntax_doc
303314
in
304315
let range = Range.of_loc loc in
305316
let hover = Hover.create ~contents ~range () in
@@ -427,7 +438,14 @@ let handle server { HoverParams.textDocument = { uri }; position; _ } mode =
427438
| Some { enable = true } -> true
428439
| Some _ | None -> false
429440
in
430-
type_enclosing_hover ~server ~doc ~merlin ~mode ~uri ~position ~with_syntax_doc
441+
type_enclosing_hover
442+
~server
443+
~doc
444+
~merlin
445+
~mode
446+
~uri
447+
~position
448+
~with_syntax_doc
431449
| Some ((`Ppx_expr _ | `Ppx_typedef_attr _) as ppx_kind) -> (
432450
let+ ppx_parsetree =
433451
Document.Merlin.with_pipeline_exn
@@ -439,4 +457,4 @@ let handle server { HoverParams.textDocument = { uri }; position; _ } mode =
439457
| `Ppx_expr (expr, ppx) ->
440458
ppx_expression_hover ~ppx_parsetree ~expr ~ppx
441459
| `Ppx_typedef_attr (decl, attr) ->
442-
typedef_attribute_hover ~ppx_parsetree ~decl ~attr)))
460+
typedef_attribute_hover ~ppx_parsetree ~decl ~attr)))

0 commit comments

Comments
 (0)