Skip to content

Commit

Permalink
Use merlin-protocol.argv in ocamlmerlin_server
Browse files Browse the repository at this point in the history
  • Loading branch information
xvw committed May 5, 2024
1 parent 25b1dcf commit 4500bed
Show file tree
Hide file tree
Showing 2 changed files with 7 additions and 19 deletions.
1 change: 1 addition & 0 deletions src/frontend/ocamlmerlin/dune
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,7 @@
merlin-lib.query_protocol merlin-lib.query_commands
merlin-lib.ocaml_typing merlin-lib.ocaml_utils
merlin-protocol.new_protocol merlin-protocol.old_protocol
merlin-protocol.argv
unix str))

(executable
Expand Down
25 changes: 6 additions & 19 deletions src/frontend/ocamlmerlin/ocamlmerlin_server.ml
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
open New_protocol
open Old_protocol

let merlin_timeout =
try float_of_string (Sys.getenv "MERLIN_TIMEOUT")
Expand Down Expand Up @@ -76,24 +75,12 @@ end
let main () =
(* Setup env for extensions *)
Unix.putenv "__MERLIN_MASTER_PID" (string_of_int (Unix.getpid ()));
match List.tl (Array.to_list Sys.argv) with
| "single" :: args -> exit (New_merlin.run ~new_env:None None args)
| "old-protocol" :: args -> Old_merlin.run args
| ["server"; socket_path; socket_fd] -> Server.start socket_path socket_fd
| ("-help" | "--help" | "-h" | "server") :: _ ->
Printf.eprintf
"Usage: %s <frontend> <arguments...>\n\
Select the merlin frontend to execute. Valid values are:\n\
\n- 'old-protocol' executes the merlin frontend from previous version.\n\
\ It is a top level reading and writing commands in a JSON form.\n\
\n- 'single' is a simpler frontend that reads input from stdin,\n\
\ processes a single query and outputs result on stdout.\n\
\n- 'server' works like 'single', but uses a background process to\n\
\ speedup processing.\n\
If no frontend is specified, it defaults to 'old-protocol' for\n\
compatibility with existing editors.\n"
Sys.argv.(0)
| args -> Old_merlin.run args
let argv = Sys.argv |> Array.to_list |> List.tl in
match Argv.dispatch argv with
| Argv.Void -> ()
| Argv.With_code i -> exit i
| Argv.Ask_for_server { socket_path; socket_fd } ->
Server.start socket_path socket_fd

let () =
Lib_config.Json.set_pretty_to_string Yojson.Basic.pretty_to_string;
Expand Down

0 comments on commit 4500bed

Please sign in to comment.