Skip to content

Commit

Permalink
feature(dune): annotate dune diagnostics with pid
Browse files Browse the repository at this point in the history
when we are connected to more than one dune instance, we annotate them
with a pid so it's clear to the user

Signed-off-by: Rudi Grinberg <[email protected]>

ps-id: 4b487e5f-cd4d-42f2-ae20-b02059f4b5c4
  • Loading branch information
rgrinberg committed Jul 24, 2022
1 parent 6f4c5f6 commit 032e3ff
Show file tree
Hide file tree
Showing 5 changed files with 44 additions and 9 deletions.
2 changes: 1 addition & 1 deletion dune-project
Original file line number Diff line number Diff line change
Expand Up @@ -49,7 +49,7 @@ possible and does not make any assumptions about IO.
yojson
(re (>= 1.5.0))
(ppx_yojson_conv_lib (>= "v0.14"))
dune-rpc
(dune-rpc (>= 3.4.0))
(chrome-trace (>= 3.3.0))
dyn
stdune
Expand Down
2 changes: 1 addition & 1 deletion ocaml-lsp-server.opam
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@ depends: [
"yojson"
"re" {>= "1.5.0"}
"ppx_yojson_conv_lib" {>= "v0.14"}
"dune-rpc"
"dune-rpc" {>= "3.4.0"}
"chrome-trace" {>= "3.3.0"}
"dyn"
"stdune"
Expand Down
36 changes: 34 additions & 2 deletions ocaml-lsp-server/src/diagnostics.ml
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,8 @@ open Import

let ocamllsp_source = "ocamllsp"

let dune_source = "dune"

module Uri = struct
include Uri

Expand All @@ -19,7 +21,29 @@ module Id = struct
let to_dyn = Dyn.opaque
end

module Dune = Stdune.Id.Make ()
module Dune = struct
module Id = Stdune.Id.Make ()

module T = struct
type t =
{ pid : Pid.t
; id : Id.t
}

let compare = Poly.compare

let equal x y = Ordering.is_eq (compare x y)

let hash = Poly.hash

let to_dyn = Dyn.opaque
end

include T
module C = Comparable.Make (T)

let gen pid = { pid; id = Id.gen () }
end

let equal_message =
(* because the compiler and merlin wrap messages differently *)
Expand Down Expand Up @@ -115,9 +139,17 @@ let send =
let diagnostics = Table.Multi.find t.merlin uri in
Table.set pending uri
(range_map_of_unduplicated_diagnostics diagnostics));
Table.iter t.dune ~f:(fun per_dune ->
let set_dune_source =
let annotate_dune_pid = Table.length t.dune > 1 in
if annotate_dune_pid then fun pid (d : Diagnostic.t) ->
let source = Some (sprintf "dune (pid=%d)" (Pid.to_int pid)) in
{ d with source }
else fun _pid x -> x
in
Table.foldi ~init:() t.dune ~f:(fun dune per_dune () ->
Table.iter per_dune ~f:(fun (uri, diagnostic) ->
if Uri_set.mem dirty_uris uri then
let diagnostic = set_dune_source dune.pid diagnostic in
add_dune_diagnostic pending uri diagnostic));
t.dirty_uris <-
(match which with
Expand Down
4 changes: 3 additions & 1 deletion ocaml-lsp-server/src/diagnostics.mli
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,8 @@ open Import

val ocamllsp_source : string

val dune_source : string

type t

val create :
Expand All @@ -16,7 +18,7 @@ val workspace_root : t -> Uri.t
module Dune : sig
type t

val gen : unit -> t
val gen : Pid.t -> t
end

val set :
Expand Down
9 changes: 5 additions & 4 deletions ocaml-lsp-server/src/dune.ml
Original file line number Diff line number Diff line change
Expand Up @@ -224,8 +224,8 @@ end = struct
let promotions = List.map promotions ~f:For_diff.Diff.of_promotion in
Some (`Assoc [ For_diff.diagnostic_data promotions ]))
in
Diagnostic.create ?relatedInformation ~range ?severity ~source:"dune"
~message ?data ()
Diagnostic.create ?relatedInformation ~range ?severity
~source:Diagnostics.dune_source ~message ?data ()

let progress_loop client progress =
match Progress.should_report_build_progress progress with
Expand Down Expand Up @@ -407,7 +407,7 @@ end = struct
t.state <- Connected (session, where);
Fiber.return (Ok ())

let run ({ config; _ } as t) =
let run ({ config; source; _ } as t) =
let* () = Fiber.return () in
let session, where =
match t.state with
Expand All @@ -421,7 +421,8 @@ end = struct
; finish
; promotions = String.Map.empty
; client = None
; diagnostics_id = Diagnostics.Dune.gen ()
; diagnostics_id =
Diagnostics.Dune.gen (Pid.of_int (Registry.Dune.pid source))
; id = Id.gen ()
}
in
Expand Down

0 comments on commit 032e3ff

Please sign in to comment.