Skip to content

Commit

Permalink
Add flag to disable dune diagnostics
Browse files Browse the repository at this point in the history
--no-dune-diagnostics
  • Loading branch information
EduardoRFS committed Jan 3, 2024
1 parent d3d8de5 commit 585dffe
Show file tree
Hide file tree
Showing 5 changed files with 37 additions and 9 deletions.
9 changes: 8 additions & 1 deletion ocaml-lsp-server/bin/main.ml
Original file line number Diff line number Diff line change
Expand Up @@ -5,13 +5,17 @@ let () =
Printexc.record_backtrace true;
let version = ref false in
let read_dot_merlin = ref false in
let dune_diagnostics = ref true in
let arg = Lsp.Cli.Arg.create () in
let spec =
[ ("--version", Arg.Set version, "print version")
; ( "--fallback-read-dot-merlin"
, Arg.Set read_dot_merlin
, "read Merlin config from .merlin files. The `dot-merlin-reader` \
package must be installed" )
; ( "--no-dune-diagnostics"
, Arg.Clear dune_diagnostics
, "disable dune diagnostics" )
]
@ Cli.Arg.spec arg
in
Expand Down Expand Up @@ -39,7 +43,10 @@ let () =
let module Exn_with_backtrace = Stdune.Exn_with_backtrace in
match
Exn_with_backtrace.try_with
(Ocaml_lsp_server.run channel ~read_dot_merlin:!read_dot_merlin)
(Ocaml_lsp_server.run
channel
~read_dot_merlin:!read_dot_merlin
~dune_diagnostics:!dune_diagnostics)
with
| Ok () -> ()
| Error exn ->
Expand Down
24 changes: 18 additions & 6 deletions ocaml-lsp-server/src/dune.ml
Original file line number Diff line number Diff line change
Expand Up @@ -114,6 +114,8 @@ module Poll =
(Result.try_with (fun () -> Io.String_path.read_file s)))
end)

let enable_diagnostics = ref true

type config =
{ diagnostics : Diagnostics.t
; document_store : Document_store.t
Expand Down Expand Up @@ -526,14 +528,24 @@ end = struct
let progress =
progress_loop client diagnostics document_store progress
in
let diagnostics =
let dune_root =
DocumentUri.of_path (Registry.Dune.root source)
in
diagnostic_loop ~dune_root client config running diagnostics
let additional_fibers =
if !enable_diagnostics then
let diagnostics =
let dune_root =
DocumentUri.of_path (Registry.Dune.root source)
in
diagnostic_loop
~dune_root
client
config
running
diagnostics
in
[ diagnostics ]
else []
in
Fiber.all_concurrently_unit
[ progress; diagnostics; Fiber.Ivar.read finish ]))
(progress :: Fiber.Ivar.read finish :: additional_fibers)))
]
in
Progress.end_build_if_running progress
Expand Down
3 changes: 3 additions & 0 deletions ocaml-lsp-server/src/dune.mli
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,9 @@ end

type t

(** enabled by default *)
val enable_diagnostics : bool ref

val view_promotion_capability : string * Json.t

val run : t -> unit Fiber.t
Expand Down
3 changes: 2 additions & 1 deletion ocaml-lsp-server/src/ocaml_lsp_server.ml
Original file line number Diff line number Diff line change
Expand Up @@ -916,10 +916,11 @@ let run_in_directory =
let for_windows = !Merlin_utils.Std.System.run_in_directory in
fun () -> if Sys.win32 then for_windows else run_in_directory

let run channel ~read_dot_merlin () =
let run channel ~read_dot_merlin ~dune_diagnostics () =
Merlin_utils.Lib_config.set_program_name "ocamllsp";
Merlin_utils.Lib_config.System.set_run_in_directory (run_in_directory ());
Merlin_config.should_read_dot_merlin := read_dot_merlin;
Dune.enable_diagnostics := dune_diagnostics;
Unix.putenv "__MERLIN_MASTER_PID" (string_of_int (Unix.getpid ()));
Lev_fiber.run ~sigpipe:`Ignore (fun () ->
let* input, output = stream_of_channel channel in
Expand Down
7 changes: 6 additions & 1 deletion ocaml-lsp-server/src/ocaml_lsp_server.mli
Original file line number Diff line number Diff line change
@@ -1,4 +1,9 @@
val run : Lsp.Cli.Channel.t -> read_dot_merlin:bool -> unit -> unit
val run :
Lsp.Cli.Channel.t
-> read_dot_merlin:bool
-> dune_diagnostics:bool
-> unit
-> unit

module Diagnostics = Diagnostics
module Version = Version
Expand Down

0 comments on commit 585dffe

Please sign in to comment.