Skip to content

Commit

Permalink
fix: stale directory target check (#8924)
Browse files Browse the repository at this point in the history
The current directory check swallows permission and other errors and
just says the directory doesn't exist.

We improve the check to emit a correct error every time.

Signed-off-by: Rudi Grinberg <me@rgrinberg.com>
  • Loading branch information
rgrinberg authored Oct 13, 2023
1 parent 81df0c8 commit 443face
Show file tree
Hide file tree
Showing 2 changed files with 49 additions and 7 deletions.
34 changes: 27 additions & 7 deletions src/dune_engine/sandbox.ml
Original file line number Diff line number Diff line change
Expand Up @@ -282,6 +282,13 @@ let apply_changes_to_source_tree t ~old_snapshot =
| Lt | Gt -> copy_file p))
;;

let hint_delete_dir =
[ Pp.text
"delete this file manually or check the permissions of the parent directory of \
this file"
]
;;

let move_targets_to_build_dir t ~loc ~should_be_skipped ~(targets : Targets.Validated.t)
: unit Targets.Produced.t Fiber.t
=
Expand All @@ -295,13 +302,26 @@ let move_targets_to_build_dir t ~loc ~should_be_skipped ~(targets : Targets.Vali
Path.Build.Set.to_list_map targets.dirs ~f:(fun target ->
let src_dir = map_path t target in
let files = collect_dir_recursively ~loc ~src_dir ~dst_dir:target in
if Path.Untracked.exists (Path.build target)
then
(* We clean up all targets (including directory targets) before running an
action, so this branch should be unreachable. *)
Code_error.raise
"Stale directory target in the build directory"
[ "dst_dir", Path.Build.to_dyn target ];
(match Path.Untracked.stat (Path.build target) with
| Error (Unix.ENOENT, _, _) -> ()
| Error e ->
User_error.raise
~hints:hint_delete_dir
[ Pp.textf "unable to stat %s" (Path.Build.to_string_maybe_quoted target)
; Pp.text "reason:"
; Pp.text (Unix_error.Detailed.to_string_hum e)
]
| Ok { Unix.st_kind; _ } ->
(* We clean up all targets (including directory targets) before
running an action, so this branch should be unreachable unless
the rule somehow escaped the sandbox *)
User_error.raise
~hints:hint_delete_dir
[ Pp.textf
"Target %s of kind %s already exists in the build directory"
(Path.Build.to_string_maybe_quoted target)
(File_kind.to_string_hum st_kind)
]);
Path.rename (Path.build src_dir) (Path.build target);
files)
|> Appendable_list.concat
Expand Down
22 changes: 22 additions & 0 deletions test/blackbox-tests/test-cases/sandboxing-stale-directory-target.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,22 @@
A faulty test escapes the sandbox by creating its target outside the sandbox

$ cat >dune-project <<EOF
> (lang dune 3.11)
> (using directory-targets 0.1)
> EOF

$ cat >dune <<EOF
> (rule
> (target (dir foo))
> (action (system "mkdir $PWD/_build/default/foo && mkdir foo")))
> EOF

$ dune build foo/ --sandbox=copy 2>&1 | sed -E 's/characters [0-9]+-[0-9]+/characters <REDACTED>/'
File "dune", line 1, characters <REDACTED>:
1 | (rule
2 | (target (dir foo))
3 | (action (system "mkdir $TESTCASE_ROOT/_build/default/foo && mkdir foo")))
Error: Target _build/default/foo of kind directory already exists in the
build directory
Hint: delete this file manually or check the permissions of the parent
directory of this file

0 comments on commit 443face

Please sign in to comment.