Skip to content

Commit cb06208

Browse files
authored
Add flag to disable dune diagnostics (#1221)
* add config to control dune diagnostics
1 parent d3d8de5 commit cb06208

File tree

8 files changed

+168
-10
lines changed

8 files changed

+168
-10
lines changed

CHANGES.md

+8
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,11 @@
1+
# Unreleased
2+
3+
## Features
4+
5+
- Introduce a configuration option to control dune diagnostics. The option is
6+
called `duneDiganostics` and it may be set to `{ enable: false }` to disable
7+
diagnostics. (#1221)
8+
19
# 1.17.0
210

311
## Fixes

ocaml-lsp-server/docs/ocamllsp/config.md

+7
Original file line numberDiff line numberDiff line change
@@ -21,5 +21,12 @@ interface config {
2121
* @since 1.16
2222
*/
2323
codelens: { enable : boolean }
24+
25+
/**
26+
* Enable/Disable Dune diagnostics
27+
* @default true
28+
* @since 1.18
29+
*/
30+
duneDiagnostics: { enable : boolean }
2431
}
2532
```

ocaml-lsp-server/src/config_data.ml

+108-3
Original file line numberDiff line numberDiff line change
@@ -145,11 +145,85 @@ module ExtendedHover = struct
145145
[@@@end]
146146
end
147147

148+
module DuneDiagnostics = struct
149+
type t = { enable : bool [@default true] }
150+
[@@deriving_inline yojson] [@@yojson.allow_extra_fields]
151+
152+
let _ = fun (_ : t) -> ()
153+
154+
let t_of_yojson =
155+
(let _tp_loc = "ocaml-lsp-server/src/config_data.ml.DuneDiagnostics.t" in
156+
function
157+
| `Assoc field_yojsons as yojson -> (
158+
let enable_field = ref Ppx_yojson_conv_lib.Option.None
159+
and duplicates = ref []
160+
and extra = ref [] in
161+
let rec iter = function
162+
| (field_name, _field_yojson) :: tail ->
163+
(match field_name with
164+
| "enable" -> (
165+
match Ppx_yojson_conv_lib.( ! ) enable_field with
166+
| Ppx_yojson_conv_lib.Option.None ->
167+
let fvalue = bool_of_yojson _field_yojson in
168+
enable_field := Ppx_yojson_conv_lib.Option.Some fvalue
169+
| Ppx_yojson_conv_lib.Option.Some _ ->
170+
duplicates := field_name :: Ppx_yojson_conv_lib.( ! ) duplicates)
171+
| _ -> ());
172+
iter tail
173+
| [] -> ()
174+
in
175+
iter field_yojsons;
176+
match Ppx_yojson_conv_lib.( ! ) duplicates with
177+
| _ :: _ ->
178+
Ppx_yojson_conv_lib.Yojson_conv_error.record_duplicate_fields
179+
_tp_loc
180+
(Ppx_yojson_conv_lib.( ! ) duplicates)
181+
yojson
182+
| [] -> (
183+
match Ppx_yojson_conv_lib.( ! ) extra with
184+
| _ :: _ ->
185+
Ppx_yojson_conv_lib.Yojson_conv_error.record_extra_fields
186+
_tp_loc
187+
(Ppx_yojson_conv_lib.( ! ) extra)
188+
yojson
189+
| [] ->
190+
let enable_value = Ppx_yojson_conv_lib.( ! ) enable_field in
191+
{ enable =
192+
(match enable_value with
193+
| Ppx_yojson_conv_lib.Option.None -> true
194+
| Ppx_yojson_conv_lib.Option.Some v -> v)
195+
}))
196+
| _ as yojson ->
197+
Ppx_yojson_conv_lib.Yojson_conv_error.record_list_instead_atom
198+
_tp_loc
199+
yojson
200+
: Ppx_yojson_conv_lib.Yojson.Safe.t -> t)
201+
202+
let _ = t_of_yojson
203+
204+
let yojson_of_t =
205+
(function
206+
| { enable = v_enable } ->
207+
let bnds : (string * Ppx_yojson_conv_lib.Yojson.Safe.t) list = [] in
208+
let bnds =
209+
let arg = yojson_of_bool v_enable in
210+
("enable", arg) :: bnds
211+
in
212+
`Assoc bnds
213+
: t -> Ppx_yojson_conv_lib.Yojson.Safe.t)
214+
215+
let _ = yojson_of_t
216+
217+
[@@@end]
218+
end
219+
148220
type t =
149221
{ codelens : Lens.t Json.Nullable_option.t
150222
[@default None] [@yojson_drop_default ( = )]
151223
; extended_hover : ExtendedHover.t Json.Nullable_option.t
152224
[@key "extendedHover"] [@default None] [@yojson_drop_default ( = )]
225+
; dune_diagnostics : DuneDiagnostics.t Json.Nullable_option.t
226+
[@key "duneDiagnostics"] [@default None] [@yojson_drop_default ( = )]
153227
}
154228
[@@deriving_inline yojson] [@@yojson.allow_extra_fields]
155229

@@ -161,6 +235,7 @@ let t_of_yojson =
161235
| `Assoc field_yojsons as yojson -> (
162236
let codelens_field = ref Ppx_yojson_conv_lib.Option.None
163237
and extended_hover_field = ref Ppx_yojson_conv_lib.Option.None
238+
and dune_diagnostics_field = ref Ppx_yojson_conv_lib.Option.None
164239
and duplicates = ref []
165240
and extra = ref [] in
166241
let rec iter = function
@@ -186,6 +261,17 @@ let t_of_yojson =
186261
extended_hover_field := Ppx_yojson_conv_lib.Option.Some fvalue
187262
| Ppx_yojson_conv_lib.Option.Some _ ->
188263
duplicates := field_name :: Ppx_yojson_conv_lib.( ! ) duplicates)
264+
| "duneDiagnostics" -> (
265+
match Ppx_yojson_conv_lib.( ! ) dune_diagnostics_field with
266+
| Ppx_yojson_conv_lib.Option.None ->
267+
let fvalue =
268+
Json.Nullable_option.t_of_yojson
269+
DuneDiagnostics.t_of_yojson
270+
_field_yojson
271+
in
272+
dune_diagnostics_field := Ppx_yojson_conv_lib.Option.Some fvalue
273+
| Ppx_yojson_conv_lib.Option.Some _ ->
274+
duplicates := field_name :: Ppx_yojson_conv_lib.( ! ) duplicates)
189275
| _ -> ());
190276
iter tail
191277
| [] -> ()
@@ -205,9 +291,10 @@ let t_of_yojson =
205291
(Ppx_yojson_conv_lib.( ! ) extra)
206292
yojson
207293
| [] ->
208-
let codelens_value, extended_hover_value =
294+
let codelens_value, extended_hover_value, dune_diagnostics_value =
209295
( Ppx_yojson_conv_lib.( ! ) codelens_field
210-
, Ppx_yojson_conv_lib.( ! ) extended_hover_field )
296+
, Ppx_yojson_conv_lib.( ! ) extended_hover_field
297+
, Ppx_yojson_conv_lib.( ! ) dune_diagnostics_field )
211298
in
212299
{ codelens =
213300
(match codelens_value with
@@ -217,6 +304,10 @@ let t_of_yojson =
217304
(match extended_hover_value with
218305
| Ppx_yojson_conv_lib.Option.None -> None
219306
| Ppx_yojson_conv_lib.Option.Some v -> v)
307+
; dune_diagnostics =
308+
(match dune_diagnostics_value with
309+
| Ppx_yojson_conv_lib.Option.None -> None
310+
| Ppx_yojson_conv_lib.Option.Some v -> v)
220311
}))
221312
| _ as yojson ->
222313
Ppx_yojson_conv_lib.Yojson_conv_error.record_list_instead_atom
@@ -228,8 +319,21 @@ let _ = t_of_yojson
228319

229320
let yojson_of_t =
230321
(function
231-
| { codelens = v_codelens; extended_hover = v_extended_hover } ->
322+
| { codelens = v_codelens
323+
; extended_hover = v_extended_hover
324+
; dune_diagnostics = v_dune_diagnostics
325+
} ->
232326
let bnds : (string * Ppx_yojson_conv_lib.Yojson.Safe.t) list = [] in
327+
let bnds =
328+
if None = v_dune_diagnostics then bnds
329+
else
330+
let arg =
331+
(Json.Nullable_option.yojson_of_t DuneDiagnostics.yojson_of_t)
332+
v_dune_diagnostics
333+
in
334+
let bnd = ("duneDiagnostics", arg) in
335+
bnd :: bnds
336+
in
233337
let bnds =
234338
if None = v_extended_hover then bnds
235339
else
@@ -259,4 +363,5 @@ let _ = yojson_of_t
259363
let default =
260364
{ codelens = Some { enable = false }
261365
; extended_hover = Some { enable = false }
366+
; dune_diagnostics = Some { enable = true }
262367
}

ocaml-lsp-server/src/configuration.ml

+5
Original file line numberDiff line numberDiff line change
@@ -47,3 +47,8 @@ let update t { DidChangeConfigurationParams.settings } =
4747
in
4848
let data = Config_data.t_of_yojson settings in
4949
Fiber.return { wheel; data }
50+
51+
let report_dune_diagnostics t =
52+
match t.data.dune_diagnostics with
53+
| Some { enable = true } | None -> true
54+
| Some { enable = false } -> false

ocaml-lsp-server/src/configuration.mli

+2
Original file line numberDiff line numberDiff line change
@@ -10,3 +10,5 @@ val default : unit -> t Fiber.t
1010
val wheel : t -> Lev_fiber.Timer.Wheel.t
1111

1212
val update : t -> DidChangeConfigurationParams.t -> t Fiber.t
13+
14+
val report_dune_diagnostics : t -> bool

ocaml-lsp-server/src/diagnostics.ml

+21-6
Original file line numberDiff line numberDiff line change
@@ -87,9 +87,11 @@ type t =
8787
; mutable dirty_uris : Uri_set.t
8888
; related_information : bool
8989
; tags : DiagnosticTag.t list
90+
; mutable report_dune_diagnostics : bool
9091
}
9192

92-
let create (capabilities : PublishDiagnosticsClientCapabilities.t option) send =
93+
let create (capabilities : PublishDiagnosticsClientCapabilities.t option) send
94+
~report_dune_diagnostics =
9395
let related_information, tags =
9496
match capabilities with
9597
| None -> (false, [])
@@ -105,6 +107,7 @@ let create (capabilities : PublishDiagnosticsClientCapabilities.t option) send =
105107
; send
106108
; related_information
107109
; tags
110+
; report_dune_diagnostics
108111
}
109112

110113
let send =
@@ -157,11 +160,12 @@ let send =
157160
{ d with source }
158161
else fun _pid x -> x
159162
in
160-
Table.foldi ~init:() t.dune ~f:(fun dune per_dune () ->
161-
Table.iter per_dune ~f:(fun (uri, diagnostic) ->
162-
if Uri_set.mem dirty_uris uri then
163-
let diagnostic = set_dune_source dune.pid diagnostic in
164-
add_dune_diagnostic pending uri diagnostic));
163+
if t.report_dune_diagnostics then
164+
Table.foldi ~init:() t.dune ~f:(fun dune per_dune () ->
165+
Table.iter per_dune ~f:(fun (uri, diagnostic) ->
166+
if Uri_set.mem dirty_uris uri then
167+
let diagnostic = set_dune_source dune.pid diagnostic in
168+
add_dune_diagnostic pending uri diagnostic));
165169
t.dirty_uris <-
166170
(match which with
167171
| `All -> Uri_set.empty
@@ -359,3 +363,14 @@ let merlin_diagnostics diagnostics merlin =
359363
Range.compare d1.range d2.range))
360364
in
361365
set diagnostics (`Merlin (uri, all_diagnostics))
366+
367+
let set_report_dune_diagnostics t ~report_dune_diagnostics =
368+
let open Fiber.O in
369+
let* () = Fiber.return () in
370+
if t.report_dune_diagnostics = report_dune_diagnostics then Fiber.return ()
371+
else (
372+
t.report_dune_diagnostics <- report_dune_diagnostics;
373+
Table.iter t.dune ~f:(fun per_dune ->
374+
Table.iter per_dune ~f:(fun (uri, _diagnostic) ->
375+
t.dirty_uris <- Uri_set.add t.dirty_uris uri));
376+
send t `All)

ocaml-lsp-server/src/diagnostics.mli

+4
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,7 @@ type t
99
val create :
1010
PublishDiagnosticsClientCapabilities.t option
1111
-> (PublishDiagnosticsParams.t list -> unit Fiber.t)
12+
-> report_dune_diagnostics:bool
1213
-> t
1314

1415
val send : t -> [ `All | `One of Uri.t ] -> unit Fiber.t
@@ -36,6 +37,9 @@ val tags_of_message :
3637

3738
val merlin_diagnostics : t -> Document.Merlin.t -> unit Fiber.t
3839

40+
val set_report_dune_diagnostics :
41+
t -> report_dune_diagnostics:bool -> unit Fiber.t
42+
3943
(** Exposed for testing *)
4044

4145
val equal_message : string -> string -> bool

ocaml-lsp-server/src/ocaml_lsp_server.ml

+13-1
Original file line numberDiff line numberDiff line change
@@ -209,7 +209,11 @@ let on_initialize server (ip : InitializeParams.t) =
209209
let state : State.t = Server.state server in
210210
let workspaces = Workspaces.create ip in
211211
let diagnostics =
212+
let report_dune_diagnostics =
213+
Configuration.report_dune_diagnostics state.configuration
214+
in
212215
Diagnostics.create
216+
~report_dune_diagnostics
213217
(let open Option.O in
214218
let* td = ip.capabilities.textDocument in
215219
td.publishDiagnostics)
@@ -702,7 +706,15 @@ let on_notification server (notification : Client_notification.t) :
702706
state
703707
| CancelRequest _ -> Fiber.return state
704708
| ChangeConfiguration req ->
705-
let+ configuration = Configuration.update state.configuration req in
709+
let* configuration = Configuration.update state.configuration req in
710+
let+ () =
711+
let report_dune_diagnostics =
712+
Configuration.report_dune_diagnostics configuration
713+
in
714+
Diagnostics.set_report_dune_diagnostics
715+
~report_dune_diagnostics
716+
(State.diagnostics state)
717+
in
706718
{ state with configuration }
707719
| DidSaveTextDocument { textDocument = { uri }; _ } -> (
708720
let state = Server.state server in

0 commit comments

Comments
 (0)