Skip to content

Commit

Permalink
Provide lib_config for spawning Unix processes
Browse files Browse the repository at this point in the history
  • Loading branch information
3Rafal committed Mar 30, 2023
1 parent 85ad3a6 commit a8c8e9c
Show file tree
Hide file tree
Showing 4 changed files with 20 additions and 2 deletions.
2 changes: 1 addition & 1 deletion src/ocaml/driver/pparse.ml
Original file line number Diff line number Diff line change
Expand Up @@ -46,7 +46,7 @@ let merlin_system_command =
windows_merlin_system_command
else
fun cmd ~cwd ->
Sys.command (Printf.sprintf "cd %s && %s" (Filename.quote cwd) cmd)
!Std.System_command.unix ~cmd:cmd ~cwd

let ppx_commandline cmd fn_in fn_out =
Printf.sprintf "%s %s %s%s"
Expand Down
7 changes: 6 additions & 1 deletion src/utils/lib_config.ml
Original file line number Diff line number Diff line change
Expand Up @@ -7,4 +7,9 @@ let program_name () = !program_name
module Json = struct
let set_pretty_to_string f =
Std.Json.pretty_to_string := f
end
end

module System_command = struct
let set_unix f =
Std.System_command.unix := f
end
7 changes: 7 additions & 0 deletions src/utils/lib_config.mli
Original file line number Diff line number Diff line change
Expand Up @@ -15,3 +15,10 @@ module Json : sig
is [Yojson.Basic.pretty_to_string]. *)
val set_pretty_to_string : (Std.json -> string) -> unit
end

(** Merlin spawns child processes for preprocessors (pp and ppx), which can be
customized via [System_command] *)
module System_command : sig
(** [set_unix] sets an implementation for Unix systems. *)
val set_unix : (cmd:string -> cwd:string -> int) -> unit
end
6 changes: 6 additions & 0 deletions src/utils/std.ml
Original file line number Diff line number Diff line change
Expand Up @@ -57,6 +57,12 @@ module Json = struct
A common one is `Yojson.Basic.pretty_to_string`."
end

module System_command = struct
let unix = ref @@
fun ~cmd ~cwd ->
Sys.command (Printf.sprintf "cd %s && %s" (Filename.quote cwd) cmd)
end

module Hashtbl = struct
include Hashtbl

Expand Down

0 comments on commit a8c8e9c

Please sign in to comment.