Skip to content

Commit

Permalink
hmm avoid passing flag to dune
Browse files Browse the repository at this point in the history
  • Loading branch information
EduardoRFS committed Jan 3, 2024
1 parent 585dffe commit 198eee1
Show file tree
Hide file tree
Showing 3 changed files with 22 additions and 9 deletions.
17 changes: 15 additions & 2 deletions lsp/src/cli.ml
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,7 @@ module Arg = struct
; mutable stdio : bool
; mutable spec : (string * Arg.spec * string) list
; mutable clientProcessId : int option
; mutable dune_diagnostics : bool
}

let port t ~name ~description =
Expand All @@ -30,6 +31,7 @@ module Arg = struct
; stdio = false
; spec = []
; clientProcessId = None
; dune_diagnostics = true
}
in
let spec =
Expand All @@ -43,6 +45,9 @@ module Arg = struct
; ( "--clientProcessId"
, Arg.Int (fun pid -> t.clientProcessId <- Some pid)
, "set the pid of the lsp client" )
; ( "--no-dune-diagnostics"
, Arg.Unit (fun () -> t.dune_diagnostics <- false)
, "disable dune diagnostics" )
]
in
t.spec <- spec;
Expand All @@ -52,7 +57,9 @@ module Arg = struct

let clientProcessId t = t.clientProcessId

let channel { pipe; port; stdio; spec = _; clientProcessId = _ } :
let dune_diagnostics t = t.dune_diagnostics

let channel { pipe; port; stdio; spec = _; clientProcessId = _; dune_diagnostics = _ } :
(Channel.t, string) result =
match (pipe, port, stdio) with
| None, None, _ -> Ok Stdio
Expand All @@ -61,12 +68,18 @@ module Arg = struct
| _, _, _ -> Error "invalid arguments"
end

let args ?channel ?clientProcessId () =
let args ?channel ?clientProcessId ?(duneDiagnostics = true) () =
let args =
match clientProcessId with
| None -> []
(* TODO: typo? *)
| Some pid -> [ "--clientPorcessId"; string_of_int pid ]
in
let args =
match duneDiagnostics with
| true -> args
| false -> "--no-dune-diagnostics" :: args
in
match (channel : Channel.t option) with
| None -> args
| Some Stdio -> "--stdio" :: args
Expand Down
6 changes: 5 additions & 1 deletion lsp/src/cli.mli
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,11 @@ module Arg : sig
(** Return the process id of the client used to run the lsp server if it was
provided *)
val clientProcessId : t -> int option


(** [dune diagnostics t] True if the dune diagnostics loop should be enabled *)
val dune_diagnostics : t -> bool
end

(** generate command line arguments that can be used to spawn an lsp client *)
val args : ?channel:Channel.t -> ?clientProcessId:int -> unit -> string list
val args : ?channel:Channel.t -> ?clientProcessId:int -> ?duneDiagnostics:bool -> unit -> string list
8 changes: 2 additions & 6 deletions ocaml-lsp-server/bin/main.ml
Original file line number Diff line number Diff line change
Expand Up @@ -5,23 +5,19 @@ 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
let usage =
"ocamllsp [ --stdio | --socket PORT | --port PORT | --pipe PIPE ] [ \
--clientProcessId pid ]"
--clientProcessId pid ] [ --no-dune-diagnostics ]"
in
Arg.parse
spec
Expand All @@ -46,7 +42,7 @@ let () =
(Ocaml_lsp_server.run
channel
~read_dot_merlin:!read_dot_merlin
~dune_diagnostics:!dune_diagnostics)
~dune_diagnostics:(Cli.Arg.dune_diagnostics arg))
with
| Ok () -> ()
| Error exn ->
Expand Down

0 comments on commit 198eee1

Please sign in to comment.