Skip to content

Commit

Permalink
Launch process without stdin by default
Browse files Browse the repository at this point in the history
Introduce a `null` input/output for processes. This can be used for
redirecting to /dev/null or running a process without stdin.

Change the default for Process.run to not read anything from stdin.
Previously, processes would inherit stdin from dune. That seems like a
bad default.

Signed-off-by: Rudi Grinberg <[email protected]>
  • Loading branch information
rgrinberg committed Aug 5, 2020
1 parent 39c9af4 commit 7019e13
Show file tree
Hide file tree
Showing 2 changed files with 23 additions and 1 deletion.
22 changes: 21 additions & 1 deletion src/dune/process.ml
Original file line number Diff line number Diff line change
Expand Up @@ -96,6 +96,26 @@ module Io = struct
let channel = lazy (channel_of_descr (Lazy.force fd) mode) in
{ kind = File fn; mode; fd; channel; status = Close_after_exec }

let null =
let fname =
lazy
(Path.of_string
( if Sys.win32 then
"nul"
else
"/dev/null" ))
in
let empty = lazy (Temp.create File ~prefix:"empty." ~suffix:".dune") in
let f (type a) (mode : a mode) : a t =
let (lazy fname) =
match mode with
| Out -> fname
| In -> empty
in
file fname mode
in
f

let flush : type a. a t -> unit =
fun t ->
if Lazy.is_val t.channel then
Expand Down Expand Up @@ -425,7 +445,7 @@ module Exit_status = struct
end

let run_internal ?dir ?(stdout_to = Io.stdout) ?(stderr_to = Io.stderr)
?(stdin_from = Io.stdin) ~env ~purpose fail_mode prog args =
?(stdin_from = Io.null In) ~env ~purpose fail_mode prog args =
Scheduler.with_job_slot (fun () ->
let display = (Config.t ()).display in
let dir =
Expand Down
2 changes: 2 additions & 0 deletions src/dune/process.mli
Original file line number Diff line number Diff line change
Expand Up @@ -28,6 +28,8 @@ module Io : sig

val stdin : input t

val null : 'a mode -> 'a t

(** Return a buffered channel for this output. The channel is created lazily. *)
val out_channel : output t -> out_channel

Expand Down

0 comments on commit 7019e13

Please sign in to comment.