Skip to content

Commit

Permalink
feature: relax directory target rules
Browse files Browse the repository at this point in the history
allow non sandboxed rules to produce directory targets

Signed-off-by: Rudi Grinberg <me@rgrinberg.com>

ps-id: 49c39ffb-67c2-4ea1-9b33-ea5be360f5bb
  • Loading branch information
rgrinberg committed Aug 16, 2022
1 parent 3592108 commit aa31355
Show file tree
Hide file tree
Showing 7 changed files with 118 additions and 48 deletions.
3 changes: 3 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,9 @@

- Cinaps actions are now sandboxed by default (#6062, @rgrinberg)

- Allow rules producing directory targets to be not sandboxed (#6056,
@rgrinberg)

3.4.1 (26-07-2022)
------------------

Expand Down
17 changes: 2 additions & 15 deletions src/dune_engine/build_system.ml
Original file line number Diff line number Diff line change
Expand Up @@ -429,18 +429,7 @@ end = struct
in
let action =
match sandbox with
| None ->
(* CR-someday amokhov: It may be possible to support directory targets
without sandboxing. We just need to make sure we clean up all stale
directory targets before running the rule and then we can discover
all created files right in the build directory. *)
if not (Path.Build.Set.is_empty targets.dirs) then
User_error.raise ~loc
[ Pp.text "Rules with directory targets must be sandboxed." ]
~hints:
[ Pp.text "Add (sandbox always) to the (deps ) field of the rule."
];
action
| None -> action
| Some sandbox -> Action.sandbox action sandbox
in
let action =
Expand Down Expand Up @@ -477,9 +466,7 @@ end = struct
let produced_targets =
match sandbox with
| None ->
(* Directory targets are not allowed for non-sandboxed actions, so
the call below should not raise. *)
Targets.Produced.of_validated_files_exn targets
Targets.Produced.produced_after_rule_executed_exn ~loc targets
| Some sandbox ->
(* The stamp file for anonymous actions is always created outside
the sandbox, so we can't move it. *)
Expand Down
2 changes: 1 addition & 1 deletion src/dune_engine/rule_cache.ml
Original file line number Diff line number Diff line change
Expand Up @@ -122,7 +122,7 @@ module Workspace_local = struct
let compute_target_digests (targets : Targets.Validated.t) :
(Digest.t Targets.Produced.t, Miss_reason.t) Result.t =
match Targets.Produced.of_validated targets with
| Error unix_error ->
| Error (_, unix_error) ->
Miss (Error_while_collecting_directory_targets unix_error)
| Ok targets -> (
match
Expand Down
31 changes: 17 additions & 14 deletions src/dune_engine/targets.ml
Original file line number Diff line number Diff line change
Expand Up @@ -103,7 +103,7 @@ module Produced = struct
let of_validated =
let rec collect dir : (unit String.Map.t Path.Build.Map.t, _) result =
match Path.Untracked.readdir_unsorted_with_kinds (Path.build dir) with
| Error _ as error -> error
| Error e -> Error (`Directory dir, e)
| Ok dir_contents ->
let open Result.O in
let+ filenames, dirs =
Expand Down Expand Up @@ -138,19 +138,22 @@ module Produced = struct
in
Ok { files; dirs }

let of_validated_files_exn (validated : Validated.t) =
let dirs =
match Path.Build.Set.is_empty validated.dirs with
| true -> Path.Build.Map.empty
| false ->
Code_error.raise
"Targets.Produced.of_validated_files_exn: Unexpected directory."
[ ("validated", Validated.to_dyn validated) ]
in
let files =
Path.Build.Set.to_map validated.files ~f:(fun (_ : Path.Build.t) -> ())
in
{ files; dirs }
let produced_after_rule_executed_exn ~loc targets =
match of_validated targets with
| Ok t -> t
| Error (`Directory dir, (Unix.ENOENT, _, _)) ->
User_error.raise ~loc
[ Pp.textf "Rule failed to produce directory %S"
(Path.Build.drop_build_context_maybe_sandboxed_exn dir
|> Path.Source.to_string_maybe_quoted)
]
| Error (`Directory dir, (unix_error, _, _)) ->
User_error.raise ~loc
[ Pp.textf "Rule produced unreadable directory %S"
(Path.Build.drop_build_context_maybe_sandboxed_exn dir
|> Path.Source.to_string_maybe_quoted)
; Pp.verbatim (Unix.error_message unix_error)
]

let of_file_list_exn list =
{ files = Path.Build.Map.of_list_exn list; dirs = Path.Build.Map.empty }
Expand Down
10 changes: 6 additions & 4 deletions src/dune_engine/targets.mli
Original file line number Diff line number Diff line change
Expand Up @@ -73,11 +73,13 @@ module Produced : sig

(** Expand [targets : Validated.t] by recursively traversing directory targets
and collecting all contained files. *)
val of_validated : Validated.t -> (unit t, Unix_error.Detailed.t) result
val of_validated :
Validated.t
-> (unit t, [ `Directory of Path.Build.t ] * Unix_error.Detailed.t) result

(** Return [targets : Validated.t] with the empty map of [dirs]. Raises a code
error if [targets.dir] is not empty. *)
val of_validated_files_exn : Validated.t -> unit t
(** Like [of_validated] but assumes the targets have been just produced by a
rule. If some directory targets aren't readable, an error is raised *)
val produced_after_rule_executed_exn : loc:Loc.t -> Validated.t -> unit t

(** Populates only the [files] field, leaving [dirs] empty. Raises a code
error if the list contains duplicates. *)
Expand Down
15 changes: 1 addition & 14 deletions test/blackbox-tests/test-cases/directory-targets/main.t
Original file line number Diff line number Diff line change
Expand Up @@ -24,17 +24,6 @@ Directory targets require an extension.
> (using directory-targets 0.1)
> EOF

Directory targets are not allowed for non-sandboxed rules.

$ dune build output/x
File "dune", line 1, characters 0-56:
1 | (rule
2 | (targets (dir output))
3 | (action (bash "true")))
Error: Rules with directory targets must be sandboxed.
Hint: Add (sandbox always) to the (deps ) field of the rule.
[1]

Ensure directory targets are produced.

$ cat > dune <<EOF
Expand Down Expand Up @@ -122,9 +111,7 @@ Hints for directory targets.
Hint: did you mean output?
[1]

Print rules: currently works only with Makefiles.

# CR-someday amokhov: Add support for printing Dune rules.
Print rules:

$ dune rules -m output | tr '\t' ' '
_build/default/output: _build/default/src_x
Expand Down
88 changes: 88 additions & 0 deletions test/blackbox-tests/test-cases/directory-targets/no-sandboxing.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,88 @@
Tests for directory targets that are produced by unsandboxed rule

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

Build directory target from the command line without sandboxing

$ cat > dune <<EOF
> (rule
> (targets (dir output))
> (action (system "mkdir output; echo x > output/x; echo y > output/y")))
> EOF

$ dune build output/x
$ cat _build/default/output/x
x
$ cat _build/default/output/y
y

We ask to build a file that doesn't exist inside the directory:

$ dune build output/fake
File "dune", line 1, characters 0-102:
1 | (rule
2 | (targets (dir output))
3 | (action (system "mkdir output; echo x > output/x; echo y > output/y")))
Error: This rule defines a directory target "output" that matches the
requested path "output/fake" but the rule's action didn't produce it
[1]

When we fail to create the directory, dune complains:

$ cat > dune <<EOF
> (rule
> (targets (dir output))
> (action (system "true")))
> EOF

$ dune build output/
File "dune", line 1, characters 0-56:
1 | (rule
2 | (targets (dir output))
3 | (action (system "true")))
Error: Rule failed to produce directory "output"
[1]

Check that Dune clears stale files from directory targets.

$ cat >dune <<EOF
> (rule
> (deps src_a src_b src_c)
> (targets (dir output))
> (action (bash "\| echo running;
> "\| mkdir -p output/subdir;
> "\| cat src_a > output/new-a;
> "\| cat src_b > output/subdir/b
> )))
> (rule
> (deps output)
> (target contents)
> (action (bash "echo running; echo 'new-a:' > contents; cat output/new-a >> contents; echo 'b:' >> contents; cat output/subdir/b >> contents")))
> EOF

$ echo a > src_a
$ echo b > src_b
$ echo c > src_c
$ dune build contents
running
running
Directory target whose name conflicts with an internal directory used by Dune.

$ cat > dune <<EOF
> (rule
> (targets (dir .dune))
> (action (bash "mkdir .dune; echo hello > .dune/hello")))
> EOF

$ dune build .dune/hello
File "dune", line 1, characters 0-88:
1 | (rule
2 | (targets (dir .dune))
3 | (action (bash "mkdir .dune; echo hello > .dune/hello")))
Error: This rule defines a target ".dune" whose name conflicts with an
internal directory used by Dune. Please use a different name.
[1]

0 comments on commit aa31355

Please sign in to comment.