Skip to content

Commit

Permalink
Do not connect dune's stdin to user written actions
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <[email protected]>
  • Loading branch information
rgrinberg committed Aug 7, 2020
1 parent 5a37af8 commit 44b774a
Show file tree
Hide file tree
Showing 4 changed files with 32 additions and 17 deletions.
3 changes: 3 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -62,6 +62,9 @@ next
- Add `"odoc" {with-doc}` to the dependencies in the generated `.opam` files.
(#3667, @kit-ty-kate)

- Do not allow user actions to capture dune's stdin (#3677, fixes #3672,
@rgrinberg)

2.6.1 (02/07/2020)
------------------

Expand Down
2 changes: 1 addition & 1 deletion src/dune/action_exec.ml
Original file line number Diff line number Diff line change
Expand Up @@ -476,7 +476,7 @@ let exec ~targets ~context ~env ~rule_loc ~build_deps t =
; env
; stdout_to = Process.Io.stdout
; stderr_to = Process.Io.stderr
; stdin_from = Process.Io.stdin
; stdin_from = Process.Io.null In
; prepared_dependencies = DAP.Dependency.Set.empty
; exit_codes = Predicate_lang.Element 0
}
Expand Down
38 changes: 22 additions & 16 deletions src/dune/process.ml
Original file line number Diff line number Diff line change
Expand Up @@ -146,6 +146,12 @@ type purpose =
| Internal_job
| Build_job of Path.Build.Set.t

let io_to_redirection_path (kind : Io.kind) =
match kind with
| Terminal -> None
| Null -> Some (Lazy.force Io.null_path)
| File fn -> Some (Path.to_string fn)

let command_line_enclosers ~dir ~(stdout_to : Io.output Io.t)
~(stderr_to : Io.output Io.t) ~(stdin_from : Io.input Io.t) =
let quote fn = String.quote_for_shell (Path.to_string fn) in
Expand All @@ -156,26 +162,26 @@ let command_line_enclosers ~dir ~(stdout_to : Io.output Io.t)
in
let suffix =
match stdin_from.kind with
| Null -> suffix
| Terminal -> suffix
| Null
| Terminal ->
suffix
| File fn -> suffix ^ " < " ^ quote fn
in
let suffix =
match (stdout_to.kind, stderr_to.kind) with
| File fn1, File fn2 when Path.equal fn1 fn2 -> " &> " ^ quote fn1
| _ -> (
let suffix =
match stdout_to.kind with
| Terminal -> suffix
| Null ->
suffix ^ " > " ^ String.quote_for_shell (Lazy.force Io.null_path)
| File fn -> suffix ^ " > " ^ quote fn
match
( io_to_redirection_path stdout_to.kind
, io_to_redirection_path stderr_to.kind )
with
| Some fn1, Some fn2 when String.equal fn1 fn2 ->
" &> " ^ String.quote_for_shell fn1
| path_out, path_err ->
let add_to_suffix suffix path redirect =
match path with
| None -> suffix
| Some path -> suffix ^ redirect ^ String.quote_for_shell path
in
match stderr_to.kind with
| Terminal -> suffix
| Null ->
suffix ^ " 2> " ^ String.quote_for_shell (Lazy.force Io.null_path)
| File fn -> suffix ^ " 2> " ^ quote fn )
let suffix = add_to_suffix suffix path_out " > " in
add_to_suffix suffix path_err " 2> "
in
(prefix, suffix)

Expand Down
6 changes: 6 additions & 0 deletions test/blackbox-tests/test-cases/github3672.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
$ echo "(lang dune 2.7)" > dune-project
$ cat >dune <<EOF
> (rule (with-stdout-to file.txt (run cat)))
> EOF
$ echo foo | dune build
$ cat _build/default/file.txt

0 comments on commit 44b774a

Please sign in to comment.