Skip to content

Commit

Permalink
feature: support --clientProcessId argument
Browse files Browse the repository at this point in the history
It does nothing for now, but it's in the standard so it's better to at
least explicitly ignore it.

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

<!-- ps-id: 35ce0575-f2a8-47b6-a0fb-97cf408d86cd -->
  • Loading branch information
rgrinberg committed Apr 30, 2023
1 parent 07ba12b commit 5589abe
Show file tree
Hide file tree
Showing 4 changed files with 22 additions and 3 deletions.
2 changes: 2 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -21,6 +21,8 @@

- Fix the type of DocumentSelector in cram document registration (#1068)

- Accept the `--clientProcessId` command line argument. (#..)

## Features
- Add "Remove type annotation" code action. (#1039)

Expand Down
18 changes: 16 additions & 2 deletions lsp/src/cli.ml
Original file line number Diff line number Diff line change
Expand Up @@ -11,25 +11,39 @@ module Arg = struct
; mutable port : int option
; mutable stdio : bool
; mutable spec : (string * Arg.spec * string) list
; mutable clientProcessId : int option
}

let create () =
let t = { pipe = None; port = None; stdio = false; spec = [] } in
let t =
{ pipe = None
; port = None
; stdio = false
; spec = []
; clientProcessId = None
}
in
let spec =
[ ("--pipe", Arg.String (fun p -> t.pipe <- Some p), "set pipe path")
; ("--socket", Arg.Int (fun p -> t.port <- Some p), "set port")
; ("--stdio", Arg.Unit (fun () -> t.stdio <- true), "set stdio")
; ( "--node-ipc"
, Arg.Unit (fun () -> raise @@ Arg.Bad "node-ipc isn't supported")
, "not supported" )
; ( "--clientProcessId"
, Arg.Int (fun pid -> t.clientProcessId <- Some pid)
, "set the pid of the lsp client" )
]
in
t.spec <- spec;
t

let spec t = t.spec

let read { pipe; port; stdio; spec = _ } : (Channel.t, string) result =
let clientProcessId t = t.clientProcessId

let read { pipe; port; stdio; spec = _; clientProcessId = _ } :
(Channel.t, string) result =
match (pipe, port, stdio) with
| None, None, _ -> Ok Stdio
| Some p, None, false -> Ok (Pipe p)
Expand Down
2 changes: 2 additions & 0 deletions lsp/src/cli.mli
Original file line number Diff line number Diff line change
Expand Up @@ -13,4 +13,6 @@ module Arg : sig
val spec : t -> (string * Arg.spec * string) list

val read : t -> (Channel.t, string) result

val clientProcessId : t -> int option
end
3 changes: 2 additions & 1 deletion ocaml-lsp-server/bin/main.ml
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,8 @@ let () =
@ Cli.Arg.spec arg
in
let usage =
"ocamllsp [ --stdio | --socket SOCKET --port PORT | --pipe PIPE ]"
"ocamllsp [ --stdio | --socket SOCKET --port PORT | --pipe PIPE ] [ \
--clientProcessId pid ]"
in
Arg.parse
spec
Expand Down

0 comments on commit 5589abe

Please sign in to comment.