Skip to content

Commit

Permalink
refactor: pass workspace root to restore_cwd_and_execve
Browse files Browse the repository at this point in the history
Signed-off-by: Stephen Sherratt <stephen@sherra.tt>
  • Loading branch information
gridbugs committed Oct 3, 2024
1 parent d361ee4 commit cdaa05d
Show file tree
Hide file tree
Showing 5 changed files with 11 additions and 13 deletions.
2 changes: 1 addition & 1 deletion bin/coq/coqtop.ml
Original file line number Diff line number Diff line change
Expand Up @@ -153,7 +153,7 @@ let term =
in
Fiber.return (coqtop, argv, env)
in
restore_cwd_and_execve common coqtop argv env
restore_cwd_and_execve (Common.root common) coqtop argv env
;;

let command = Cmd.v info term
6 changes: 4 additions & 2 deletions bin/exec.ml
Original file line number Diff line number Diff line change
Expand Up @@ -79,7 +79,9 @@ module Command_to_exec = struct
environment, returning the new process' pid *)
let spawn_process (common : Common.t) path ~args ~env =
let pid =
let prog = string_path_relative_to_specified_root common (Path.to_string path) in
let prog =
string_path_relative_to_specified_root (Common.root common) (Path.to_string path)
in
let env = Env.to_unix env |> Spawn.Env.of_list in
let argv = prog :: args in
let cwd = Spawn.Working_dir.Path Fpath.initial_cwd in
Expand Down Expand Up @@ -298,7 +300,7 @@ module Exec_context = struct
in
let prog = Path.to_string path in
let argv = prog :: args in
restore_cwd_and_execve common prog argv env
restore_cwd_and_execve (Common.root common) prog argv env
;;

let run_eager_watch t common config =
Expand Down
12 changes: 4 additions & 8 deletions bin/import.ml
Original file line number Diff line number Diff line change
Expand Up @@ -237,16 +237,12 @@ module Scheduler = struct
;;
end

let string_path_relative_to_specified_root (common : Common.t) path =
if Filename.is_relative path
then (
let root = Common.root common in
Filename.concat root.dir path)
else path
let string_path_relative_to_specified_root (root : Workspace_root.t) path =
if Filename.is_relative path then Filename.concat root.dir path else path
;;

let restore_cwd_and_execve common prog argv env =
let prog = string_path_relative_to_specified_root common prog in
let restore_cwd_and_execve root prog argv env =
let prog = string_path_relative_to_specified_root root prog in
Proc.restore_cwd_and_execve prog argv ~env
;;

Expand Down
2 changes: 1 addition & 1 deletion bin/ocaml/utop.ml
Original file line number Diff line number Diff line change
Expand Up @@ -56,7 +56,7 @@ let term =
~f:(fun dir env -> Env_path.cons ~var:Ocaml.Env.caml_ld_library_path env ~dir)
~init:env
in
restore_cwd_and_execve common utop_path (utop_path :: args) env
restore_cwd_and_execve (Common.root common) utop_path (utop_path :: args) env
;;

let command = Cmd.v info term
2 changes: 1 addition & 1 deletion bin/tools/ocamllsp.ml
Original file line number Diff line number Diff line change
Expand Up @@ -51,7 +51,7 @@ let term =
let open Fiber.O in
let* () = Lock_dev_tool.lock_ocamllsp () |> Memo.run in
let+ () = build_ocamllsp common in
run_ocamllsp common ~args)
run_ocamllsp (Common.root common) ~args)
;;

let info =
Expand Down

0 comments on commit cdaa05d

Please sign in to comment.