Skip to content

Commit

Permalink
add syntax doc command
Browse files Browse the repository at this point in the history
add syntax doc command

change syntax_doc output from string to record type

parse record to extract and display different fields correctly

lint code

refactor code add formatting functions and check if syn_doc is activated

check if syntax_doc is activated in ocamllsp env variables

refactor for proper types

include syntax documentation in configuation data

check if feature is activated from ocaml.server

remove redundant code

lint

add version

refactor code and lint

refactor code and lint

let merlin work only if syntax doc is activated

lint

change from italics to code pill

lint

update changelog

update documentation

remove configuration via environment variables

update docs

syntax highlighting for code block

make syntax highlighter required

add constraint for most recent version of merlin-lib

upgrade merlin-lib to latest version

add syntax doc to ppx expect

write tests for syntax doc command

linting

helper function for positions

Update README.md

Co-authored-by: Ulysse <5031221+voodoos@users.noreply.github.com>

Update README.md

Co-authored-by: Ulysse <5031221+voodoos@users.noreply.github.com>

Update ocaml-lsp-server/src/document.ml

Co-authored-by: Ulysse <5031221+voodoos@users.noreply.github.com>

Update ocaml-lsp-server/src/document.ml

Co-authored-by: Ulysse <5031221+voodoos@users.noreply.github.com>

80 char per line limit

use better descriptive function name

adjust formatting
  • Loading branch information
PizieDust committed Mar 14, 2024
1 parent ad20957 commit c5f37c9
Show file tree
Hide file tree
Showing 11 changed files with 366 additions and 24 deletions.
4 changes: 4 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,10 @@

- Support folding of `ifthenelse` expressions (#1031)

- Includes a new optional/configurable option to toggle syntax documentation. If
toggled on, allows display of sytax documentation on hover tooltips. Can be
controlled via environment variables and by GUI for VS code. (#1218)

# 1.17.0

## Fixes
Expand Down
30 changes: 30 additions & 0 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -304,6 +304,36 @@ of the value needs to be non-polymorphic to construct a meaningful value.
Tip (for VS Code OCaml Platform users): You can construct a value using a keybinding
<kbd>Alt</kbd>+<kbd>C</kbd> or on MacOS <kbd>Option</kbd>+<kbd>C</kbd>

#### Syntax Documentation

> since OCaml-LSP 1.18.0
OCaml-LSP can display documentation about the node under the cursor when
the user hovers over some OCaml code. For example, hovering over the code
snippet below will display some information about what the syntax
is:

```ocaml
type point = {x: int; y: int}
```
Hovering over the above will
display:
```
ocaml type point = { x : int; y : int }
syntax Record type:
Allows you to define variants with a fixed set of fields, and all of the
constructors for a record variant type must have the same fields. See
Manual
```
The documentation is gotten from the Merlin engine which receives
the nodes under the cursor and infers what the syntax may be about, and
displays the required information along with links to the manual for further
reading.

Syntax Documentation is an optional feature and can be activated by
using the LSP config system with the key called `syntaxDocumentation` and can
be enabled via setting it to `{ enable: true }`.

## Debugging

If you use Visual Studio Code, please see OCaml Platform extension
Expand Down
2 changes: 1 addition & 1 deletion dune-project
Original file line number Diff line number Diff line change
Expand Up @@ -67,7 +67,7 @@ possible and does not make any assumptions about IO.
(ocamlformat-rpc-lib (>= 0.21.0))
(odoc :with-doc)
(ocaml (and (>= 4.14) (< 5.2)))
(merlin-lib (and (>= 4.9) (< 5.0)))))
(merlin-lib (and (>= 4.14) (< 5.0)))))

(package
(name jsonrpc)
Expand Down
2 changes: 1 addition & 1 deletion ocaml-lsp-server.opam
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@ depends: [
"ocamlformat-rpc-lib" {>= "0.21.0"}
"odoc" {with-doc}
"ocaml" {>= "4.14" & < "5.2"}
"merlin-lib" {>= "4.9" & < "5.0"}
"merlin-lib" {>= "4.14" & < "5.0"}
]
dev-repo: "git+https://github.com/ocaml/ocaml-lsp.git"
build: [
Expand Down
7 changes: 7 additions & 0 deletions ocaml-lsp-server/docs/ocamllsp/config.md
Original file line number Diff line number Diff line change
Expand Up @@ -28,5 +28,12 @@ interface config {
* @since 1.18
*/
duneDiagnostics: { enable : boolean }

/**
* Enable/Disable Syntax Documentation
* @default false
* @since 1.18
*/
syntaxDocumentation: { enable : boolean }
}
```
115 changes: 111 additions & 4 deletions ocaml-lsp-server/src/config_data.ml
Original file line number Diff line number Diff line change
Expand Up @@ -315,6 +315,80 @@ module DuneDiagnostics = struct
[@@@end]
end

module SyntaxDocumentation = struct
type t = { enable : bool [@default false] }
[@@deriving_inline yojson] [@@yojson.allow_extra_fields]

let _ = fun (_ : t) -> ()

let t_of_yojson =
(let _tp_loc =
"ocaml-lsp-server/src/config_data.ml.SyntaxDocumentation.t"
in
function
| `Assoc field_yojsons as yojson -> (
let enable_field = ref Ppx_yojson_conv_lib.Option.None
and duplicates = ref []
and extra = ref [] in
let rec iter = function
| (field_name, _field_yojson) :: tail ->
(match field_name with
| "enable" -> (
match Ppx_yojson_conv_lib.( ! ) enable_field with
| Ppx_yojson_conv_lib.Option.None ->
let fvalue = bool_of_yojson _field_yojson in
enable_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
iter field_yojsons;
match Ppx_yojson_conv_lib.( ! ) duplicates with
| _ :: _ ->
Ppx_yojson_conv_lib.Yojson_conv_error.record_duplicate_fields
_tp_loc
(Ppx_yojson_conv_lib.( ! ) duplicates)
yojson
| [] -> (
match Ppx_yojson_conv_lib.( ! ) extra with
| _ :: _ ->
Ppx_yojson_conv_lib.Yojson_conv_error.record_extra_fields
_tp_loc
(Ppx_yojson_conv_lib.( ! ) extra)
yojson
| [] ->
let enable_value = Ppx_yojson_conv_lib.( ! ) enable_field in
{ enable =
(match enable_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
: Ppx_yojson_conv_lib.Yojson.Safe.t -> t)

let _ = t_of_yojson

let yojson_of_t =
(function
| { enable = v_enable } ->
let bnds : (string * Ppx_yojson_conv_lib.Yojson.Safe.t) list = [] in
let bnds =
let arg = yojson_of_bool v_enable in
("enable", arg) :: bnds
in
`Assoc bnds
: t -> Ppx_yojson_conv_lib.Yojson.Safe.t)

let _ = yojson_of_t

[@@@end]
end

type t =
{ codelens : Lens.t Json.Nullable_option.t
[@default None] [@yojson_drop_default ( = )]
Expand All @@ -324,6 +398,10 @@ type t =
[@key "inlayHints"] [@default None] [@yojson_drop_default ( = )]
; dune_diagnostics : DuneDiagnostics.t Json.Nullable_option.t
[@key "duneDiagnostics"] [@default None] [@yojson_drop_default ( = )]
; syntax_documentation : SyntaxDocumentation.t Json.Nullable_option.t
[@key "syntaxDocumentation"]
[@default None]
[@yojson_drop_default ( = )]
}
[@@deriving_inline yojson] [@@yojson.allow_extra_fields]

Expand All @@ -337,6 +415,7 @@ let t_of_yojson =
and extended_hover_field = ref Ppx_yojson_conv_lib.Option.None
and inlay_hints_field = ref Ppx_yojson_conv_lib.Option.None
and dune_diagnostics_field = ref Ppx_yojson_conv_lib.Option.None
and syntax_documentation_field = ref Ppx_yojson_conv_lib.Option.None
and duplicates = ref []
and extra = ref [] in
let rec iter = function
Expand All @@ -362,6 +441,17 @@ 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)
| "inlayHints" -> (
match Ppx_yojson_conv_lib.( ! ) inlay_hints_field with
| Ppx_yojson_conv_lib.Option.None ->
Expand All @@ -384,7 +474,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 All @@ -405,10 +495,11 @@ let t_of_yojson =
| [] ->
let ( codelens_value
, extended_hover_value
, inlay_hints_value
, dune_diagnostics_value ) =
, dune_diagnostics_value
, syntax_documentation_value ) =
( Ppx_yojson_conv_lib.( ! ) codelens_field
, Ppx_yojson_conv_lib.( ! ) extended_hover_field
, Ppx_yojson_conv_lib.( ! ) syntax_documentation_field
, Ppx_yojson_conv_lib.( ! ) inlay_hints_field
, Ppx_yojson_conv_lib.( ! ) dune_diagnostics_field )
in
Expand All @@ -420,6 +511,10 @@ let t_of_yojson =
(match extended_hover_value with
| Ppx_yojson_conv_lib.Option.None -> None
| Ppx_yojson_conv_lib.Option.Some v -> v)
; syntax_documentation =
(match syntax_documentation_value with
| Ppx_yojson_conv_lib.Option.None -> None
| Ppx_yojson_conv_lib.Option.Some v -> v)
; inlay_hints =
(match inlay_hints_value with
| Ppx_yojson_conv_lib.Option.None -> None
Expand All @@ -443,7 +538,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 } ->
let bnds : (string * Ppx_yojson_conv_lib.Yojson.Safe.t) list = [] in
let bnds =
if None = v_dune_diagnostics then bnds
Expand All @@ -465,6 +561,16 @@ let yojson_of_t =
let bnd = ("inlayHints", arg) in
bnd :: bnds
in
let bnds =
if None = v_syntax_documentation then bnds
else
let arg =
(Json.Nullable_option.yojson_of_t SyntaxDocumentation.yojson_of_t)
v_syntax_documentation
in
let bnd = ("syntaxDocumentation", arg) in
bnd :: bnds
in
let bnds =
if None = v_extended_hover then bnds
else
Expand Down Expand Up @@ -497,4 +603,5 @@ let default =
; inlay_hints =
Some { hint_pattern_variables = false; hint_let_bindings = false }
; dune_diagnostics = Some { enable = true }
; syntax_documentation = Some { enable = false }
}
19 changes: 17 additions & 2 deletions ocaml-lsp-server/src/document.ml
Original file line number Diff line number Diff line change
Expand Up @@ -281,13 +281,23 @@ module Merlin = struct
| `Found s | `Builtin s -> Some s
| _ -> None

let syntax_doc pipeline pos =
let res =
let command = Query_protocol.Syntax_document pos in
Query_commands.dispatch pipeline command
in
match res with
| `Found s -> Some s
| `No_documentation -> None

type type_enclosing =
{ loc : Loc.t
; typ : string
; doc : string option
; syntax_doc : Query_protocol.syntax_doc_result option
}

let type_enclosing doc pos verbosity =
let type_enclosing doc pos verbosity ~with_syntax_doc =
with_pipeline_exn doc (fun pipeline ->
let command = Query_protocol.Type_enclosing (None, pos, Some 0) in
let pipeline =
Expand All @@ -308,7 +318,12 @@ module Merlin = struct
| [] | (_, `Index _, _) :: _ -> None
| (loc, `String typ, _) :: _ ->
let doc = doc_comment pipeline pos in
Some { loc; typ; doc })
let syntax_doc =
match with_syntax_doc with
| true -> syntax_doc pipeline pos
| false -> None
in
Some { loc; typ; doc; syntax_doc })

let doc_comment doc pos =
with_pipeline_exn doc (fun pipeline -> doc_comment pipeline pos)
Expand Down
5 changes: 5 additions & 0 deletions ocaml-lsp-server/src/document.mli
Original file line number Diff line number Diff line change
Expand Up @@ -63,16 +63,21 @@ module Merlin : sig
val doc_comment :
t -> Msource.position -> (* doc string *) string option Fiber.t

val syntax_doc :
Mpipeline.t -> Msource.position -> Query_protocol.syntax_doc_result option

type type_enclosing =
{ loc : Loc.t
; typ : string
; doc : string option
; syntax_doc : Query_protocol.syntax_doc_result option
}

val type_enclosing :
t
-> Msource.position
-> (* verbosity *) int
-> with_syntax_doc:bool
-> type_enclosing option Fiber.t

val kind : t -> Kind.t
Expand Down
Loading

0 comments on commit c5f37c9

Please sign in to comment.