Skip to content

Commit 99494a6

Browse files
authored
feature: add --port as a synonym to --socket (#1076)
Signed-off-by: Rudi Grinberg <[email protected]>
1 parent 739bdf0 commit 99494a6

File tree

4 files changed

+47
-7
lines changed

4 files changed

+47
-7
lines changed

CHANGES.md

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -23,6 +23,8 @@
2323

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

26+
- Accept `--port` as a synonym for `--socket`. (#1075)
27+
2628
## Features
2729
- Add "Remove type annotation" code action. (#1039)
2830

lsp/src/cli.ml

Lines changed: 24 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,15 @@ module Arg = struct
1414
; mutable clientProcessId : int option
1515
}
1616

17+
let port t ~name ~description =
18+
( name
19+
, Arg.Int
20+
(fun p ->
21+
match t.port with
22+
| Some _ -> raise @@ Arg.Bad "port is already set once"
23+
| None -> t.port <- Some p)
24+
, description )
25+
1726
let create () =
1827
let t =
1928
{ pipe = None
@@ -25,7 +34,8 @@ module Arg = struct
2534
in
2635
let spec =
2736
[ ("--pipe", Arg.String (fun p -> t.pipe <- Some p), "set pipe path")
28-
; ("--socket", Arg.Int (fun p -> t.port <- Some p), "set port")
37+
; port t ~name:"--socket" ~description:"set the port"
38+
; port t ~name:"--port" ~description:"synonym for --socket"
2939
; ("--stdio", Arg.Unit (fun () -> t.stdio <- true), "set stdio")
3040
; ( "--node-ipc"
3141
, Arg.Unit (fun () -> raise @@ Arg.Bad "node-ipc isn't supported")
@@ -42,11 +52,23 @@ module Arg = struct
4252

4353
let clientProcessId t = t.clientProcessId
4454

45-
let read { pipe; port; stdio; spec = _; clientProcessId = _ } :
55+
let channel { pipe; port; stdio; spec = _; clientProcessId = _ } :
4656
(Channel.t, string) result =
4757
match (pipe, port, stdio) with
4858
| None, None, _ -> Ok Stdio
4959
| Some p, None, false -> Ok (Pipe p)
5060
| None, Some s, false -> Ok (Socket s)
5161
| _, _, _ -> Error "invalid arguments"
5262
end
63+
64+
let args ?channel ?clientProcessId () =
65+
let args =
66+
match clientProcessId with
67+
| None -> []
68+
| Some pid -> [ "--clientPorcessId"; string_of_int pid ]
69+
in
70+
match (channel : Channel.t option) with
71+
| None -> args
72+
| Some Stdio -> "--stdio" :: args
73+
| Some (Pipe pipe) -> "--pipe" :: pipe :: args
74+
| Some (Socket port) -> "--socket" :: string_of_int port :: args

lsp/src/cli.mli

Lines changed: 19 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,18 +1,34 @@
1+
(** Handling of standard lsp server command line arguments *)
2+
13
module Channel : sig
4+
(** The channel the server shold use to listen for connections *)
5+
26
type t =
37
| Stdio
4-
| Pipe of string
5-
| Socket of int
8+
| Pipe of string (** A path to the unix domain socket or windows pipe *)
9+
| Socket of int (** A tcp connection on localhost with the port number *)
610
end
711

812
module Arg : sig
13+
(** Parsing of the standard commnad line arguments using [Stdlib.Arg] *)
14+
915
type t
1016

17+
(** [create ()] create a new record for arguments *)
1118
val create : unit -> t
1219

20+
(** [spec t] returns the spec that should be provided to [Stdlib.Arg] to
21+
populate [t] using the interpreted cli args *)
1322
val spec : t -> (string * Arg.spec * string) list
1423

15-
val read : t -> (Channel.t, string) result
24+
(** [channel t] return the channel if correctly supplied. An error if the
25+
arguments were provided incorrectly. *)
26+
val channel : t -> (Channel.t, string) result
1627

28+
(** Return the process id of the client used to run the lsp server if it was
29+
provided *)
1730
val clientProcessId : t -> int option
1831
end
32+
33+
(** generate command line arguments that can be used to spawn an lsp client *)
34+
val args : ?channel:Channel.t -> ?clientProcessId:int -> unit -> string list

ocaml-lsp-server/bin/main.ml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -16,15 +16,15 @@ let () =
1616
@ Cli.Arg.spec arg
1717
in
1818
let usage =
19-
"ocamllsp [ --stdio | --socket SOCKET --port PORT | --pipe PIPE ] [ \
19+
"ocamllsp [ --stdio | --socket PORT | --port PORT | --pipe PIPE ] [ \
2020
--clientProcessId pid ]"
2121
in
2222
Arg.parse
2323
spec
2424
(fun _ -> raise @@ Arg.Bad "anonymous arguments aren't allowed")
2525
usage;
2626
let channel =
27-
match Cli.Arg.read arg with
27+
match Cli.Arg.channel arg with
2828
| Ok c -> c
2929
| Error s ->
3030
Format.eprintf "%s@.%!" s;

0 commit comments

Comments
 (0)