Skip to content

Commit

Permalink
_
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <[email protected]>
  • Loading branch information
rgrinberg committed Oct 6, 2024
1 parent dd9e03f commit bbe624a
Showing 1 changed file with 9 additions and 11 deletions.
20 changes: 9 additions & 11 deletions bin/exec.ml
Original file line number Diff line number Diff line change
Expand Up @@ -77,11 +77,9 @@ module Command_to_exec = struct

(* Helper function to spawn a new process running a command in an
environment, returning the new process' pid *)
let spawn_process (common : Common.t) path ~args ~env =
let spawn_process ~root path ~args ~env =
let pid =
let prog =
string_path_relative_to_specified_root (Common.root common) (Path.to_string path)
in
let prog = string_path_relative_to_specified_root root (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 All @@ -93,12 +91,12 @@ module Command_to_exec = struct
(* Run the command, first (re)building the program which the command is
invoking *)
let build_and_run_in_child_process
common
~root
{ get_path_and_build_if_necessary; prog; args; env }
=
get_path_and_build_if_necessary prog
|> Fiber.map
~f:(Result.map ~f:(fun exe_path -> spawn_process common ~args ~env exe_path))
~f:(Result.map ~f:(fun exe_path -> spawn_process ~root ~args ~env exe_path))
;;
end

Expand Down Expand Up @@ -145,18 +143,18 @@ module Watch = struct

(* Kills the currently running process, then runs the given command after
(re)building the program which it will invoke *)
let run common state ~command_to_exec =
let run ~root state ~command_to_exec =
let open Fiber.O in
let* () = Fiber.return () in
let* () = kill_currently_running_process state in
let* command_to_exec = command_to_exec () in
Command_to_exec.build_and_run_in_child_process common command_to_exec
Command_to_exec.build_and_run_in_child_process ~root command_to_exec
>>| Result.map ~f:(fun pid -> state.currently_running_pid := Some pid)
;;

let loop common ~command_to_exec =
let loop ~root ~command_to_exec =
let state = init_state () in
Scheduler.Run.poll (run common state ~command_to_exec)
Scheduler.Run.poll (run ~root state ~command_to_exec)
;;
end

Expand Down Expand Up @@ -328,7 +326,7 @@ module Exec_context = struct
; env
}
in
Watch.loop common ~command_to_exec
Watch.loop ~root:(Common.root common) ~command_to_exec
;;
end

Expand Down

0 comments on commit bbe624a

Please sign in to comment.