Skip to content

Commit

Permalink
Format changes
Browse files Browse the repository at this point in the history
  • Loading branch information
voodoos committed May 14, 2024
1 parent e6f223e commit 1392cb3
Show file tree
Hide file tree
Showing 2 changed files with 57 additions and 38 deletions.
29 changes: 15 additions & 14 deletions ocaml-lsp-server/src/config_data.ml
Original file line number Diff line number Diff line change
Expand Up @@ -441,17 +441,18 @@ let t_of_yojson =
extended_hover_field := Ppx_yojson_conv_lib.Option.Some fvalue
| Ppx_yojson_conv_lib.Option.Some _ ->
duplicates := field_name :: Ppx_yojson_conv_lib.( ! ) duplicates)
| "syntaxDocumentation" -> (
match Ppx_yojson_conv_lib.( ! ) syntax_documentation_field with
| Ppx_yojson_conv_lib.Option.None ->
let fvalue =
Json.Nullable_option.t_of_yojson
SyntaxDocumentation.t_of_yojson
_field_yojson
in
syntax_documentation_field := Ppx_yojson_conv_lib.Option.Some fvalue
| Ppx_yojson_conv_lib.Option.Some _ ->
duplicates := field_name :: Ppx_yojson_conv_lib.( ! ) duplicates)
| "syntaxDocumentation" -> (
match Ppx_yojson_conv_lib.( ! ) syntax_documentation_field with
| Ppx_yojson_conv_lib.Option.None ->
let fvalue =
Json.Nullable_option.t_of_yojson
SyntaxDocumentation.t_of_yojson
_field_yojson
in
syntax_documentation_field :=
Ppx_yojson_conv_lib.Option.Some fvalue
| Ppx_yojson_conv_lib.Option.Some _ ->
duplicates := field_name :: Ppx_yojson_conv_lib.( ! ) duplicates)
| "inlayHints" -> (
match Ppx_yojson_conv_lib.( ! ) inlay_hints_field with
| Ppx_yojson_conv_lib.Option.None ->
Expand All @@ -474,7 +475,7 @@ let t_of_yojson =
dune_diagnostics_field := Ppx_yojson_conv_lib.Option.Some fvalue
| Ppx_yojson_conv_lib.Option.Some _ ->
duplicates := field_name :: Ppx_yojson_conv_lib.( ! ) duplicates)
| _ -> ());
| _ -> ());
iter tail
| [] -> ()
in
Expand Down Expand Up @@ -539,8 +540,8 @@ let yojson_of_t =
; extended_hover = v_extended_hover
; inlay_hints = v_inlay_hints
; dune_diagnostics = v_dune_diagnostics
; syntax_documentation =
v_syntax_documentation } ->
; syntax_documentation = v_syntax_documentation
} ->
let bnds : (string * Ppx_yojson_conv_lib.Yojson.Safe.t) list = [] in
let bnds =
if None = v_dune_diagnostics then bnds
Expand Down
66 changes: 42 additions & 24 deletions ocaml-lsp-server/src/hover_req.ml
Original file line number Diff line number Diff line change
Expand Up @@ -201,7 +201,7 @@ let format_as_code_block ~highlighter strings =
let format_type_enclosing ~syntax ~markdown ~typ ~doc
~(syntax_doc : Query_protocol.syntax_doc_result option) =
(* TODO for vscode, we should just use the language id. But that will not work
for all editors *)
for all editors *)
let syntax_doc =
Option.map syntax_doc ~f:(fun syntax_doc ->
sprintf
Expand All @@ -212,30 +212,32 @@ let format_type_enclosing ~syntax ~markdown ~typ ~doc
in
`MarkupContent
(if markdown then
let value =
let markdown_name = Document.Syntax.markdown_name syntax in
let type_info = Some (format_as_code_block ~highlighter:markdown_name [ typ ]) in
let doc =
Option.map doc ~f:(fun doc ->
match Doc_to_md.translate doc with
| Raw d -> d
| Markdown d -> d)
in
print_dividers (List.filter_opt [ type_info; syntax_doc; doc ])
in
{ MarkupContent.value; kind = MarkupKind.Markdown }
else
let value =
print_dividers (List.filter_opt [ Some typ; syntax_doc; doc ])
in
{ MarkupContent.value; kind = MarkupKind.PlainText })
let value =
let markdown_name = Document.Syntax.markdown_name syntax in
let type_info =
Some (format_as_code_block ~highlighter:markdown_name [ typ ])
in
let doc =
Option.map doc ~f:(fun doc ->
match Doc_to_md.translate doc with
| Raw d -> d
| Markdown d -> d)
in
print_dividers (List.filter_opt [ type_info; syntax_doc; doc ])
in
{ MarkupContent.value; kind = MarkupKind.Markdown }
else
let value =
print_dividers (List.filter_opt [ Some typ; syntax_doc; doc ])
in
{ MarkupContent.value; kind = MarkupKind.PlainText })

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

let type_enclosing_hover ~(server : State.t Server.t) ~(doc : Document.t) ~with_syntax_doc
~merlin ~mode ~uri ~position =
let type_enclosing_hover ~(server : State.t Server.t) ~(doc : Document.t)
~with_syntax_doc ~merlin ~mode ~uri ~position =
let state = Server.state server in
let verbosity =
let mode =
Expand Down Expand Up @@ -263,7 +265,11 @@ let type_enclosing_hover ~(server : State.t Server.t) ~(doc : Document.t) ~with_
v
in
let* type_enclosing =
Document.Merlin.type_enclosing merlin (Position.logical position) verbosity ~with_syntax_doc
Document.Merlin.type_enclosing
merlin
(Position.logical position)
verbosity
~with_syntax_doc
in
match type_enclosing with
| None -> Fiber.return None
Expand Down Expand Up @@ -299,7 +305,12 @@ let type_enclosing_hover ~(server : State.t Server.t) ~(doc : Document.t) ~with_
client_capabilities
~field:(fun td -> Option.map td.hover ~f:(fun h -> h.contentFormat))
in
format_type_enclosing ~syntax ~markdown ~typ ~doc:documentation ~syntax_doc
format_type_enclosing
~syntax
~markdown
~typ
~doc:documentation
~syntax_doc
in
let range = Range.of_loc loc in
let hover = Hover.create ~contents ~range () in
Expand Down Expand Up @@ -427,7 +438,14 @@ let handle server { HoverParams.textDocument = { uri }; position; _ } mode =
| Some { enable = true } -> true
| Some _ | None -> false
in
type_enclosing_hover ~server ~doc ~merlin ~mode ~uri ~position ~with_syntax_doc
type_enclosing_hover
~server
~doc
~merlin
~mode
~uri
~position
~with_syntax_doc
| Some ((`Ppx_expr _ | `Ppx_typedef_attr _) as ppx_kind) -> (
let+ ppx_parsetree =
Document.Merlin.with_pipeline_exn
Expand All @@ -439,4 +457,4 @@ let handle server { HoverParams.textDocument = { uri }; position; _ } mode =
| `Ppx_expr (expr, ppx) ->
ppx_expression_hover ~ppx_parsetree ~expr ~ppx
| `Ppx_typedef_attr (decl, attr) ->
typedef_attribute_hover ~ppx_parsetree ~decl ~attr)))
typedef_attribute_hover ~ppx_parsetree ~decl ~attr)))

0 comments on commit 1392cb3

Please sign in to comment.