Skip to content

Commit

Permalink
[3.15] backport #10382 (#10432)
Browse files Browse the repository at this point in the history
* Add repro for gh10310 (#10330)

Signed-off-by: Stephen Sherratt <stephen@sherra.tt>

* Allow rules with directory targets to be disabled (again) (#10382)

* Allow rules with directory targets to be disabled

Previously attempting to disable a rule with a directory target would
cause dune to crash.

Fixes #10310

Signed-off-by: Stephen Sherratt <stephen@sherra.tt>

---------

Signed-off-by: Stephen Sherratt <stephen@sherra.tt>
Co-authored-by: Stephen Sherratt <stephen@sherra.tt>
  • Loading branch information
emillon and gridbugs committed Apr 17, 2024
1 parent 8118ddb commit 0c42611
Show file tree
Hide file tree
Showing 3 changed files with 52 additions and 23 deletions.
2 changes: 2 additions & 0 deletions doc/changes/10382.md
@@ -0,0 +1,2 @@
- Fix crash when a rule with a directory target is disabled with `enabled_if`
(#10382, fixes #10310, @gridbugs)
57 changes: 34 additions & 23 deletions src/dune_rules/dir_status.ml
Expand Up @@ -88,29 +88,40 @@ let error_no_module_consumer ~loc (qualification : Include_subdirs.qualification
let extract_directory_targets ~dir stanzas =
Memo.List.fold_left stanzas ~init:Path.Build.Map.empty ~f:(fun acc stanza ->
match Stanza.repr stanza with
| Rule_conf.T { targets = Static { targets = l; _ }; loc = rule_loc; _ } ->
List.fold_left l ~init:acc ~f:(fun acc (target, kind) ->
let loc = String_with_vars.loc target in
match (kind : Targets_spec.Kind.t) with
| File -> acc
| Directory ->
(match String_with_vars.text_only target with
| None ->
User_error.raise
~loc
[ Pp.text "Variables are not allowed in directory targets." ]
| Some target ->
let dir_target = Path.Build.relative ~error_loc:loc dir target in
if Path.Build.is_descendant dir_target ~of_:dir
then
(* We ignore duplicates here as duplicates are detected and
reported by [Load_rules]. *)
Path.Build.Map.set acc dir_target rule_loc
else
(* This will be checked when we interpret the stanza
completely, so just ignore this rule for now. *)
acc))
|> Memo.return
| Rule_conf.T { targets = Static { targets = l; _ }; loc = rule_loc; enabled_if; _ }
->
(match enabled_if with
| Blang.Const const -> Memo.return const
| _ ->
(* Only evaluate the expander if the enabled_if field is
non-trivial to avoid memo cycles. If the enabled_if field is absent
from the "rule" stanza then its value will be [Const true]. *)
let* expander = Expander0.get ~dir in
Expander0.eval_blang expander enabled_if)
>>| (function
| false -> acc
| true ->
List.fold_left l ~init:acc ~f:(fun acc (target, kind) ->
let loc = String_with_vars.loc target in
match (kind : Targets_spec.Kind.t) with
| File -> acc
| Directory ->
(match String_with_vars.text_only target with
| None ->
User_error.raise
~loc
[ Pp.text "Variables are not allowed in directory targets." ]
| Some target ->
let dir_target = Path.Build.relative ~error_loc:loc dir target in
if Path.Build.is_descendant dir_target ~of_:dir
then
(* We ignore duplicates here as duplicates are detected and
reported by [Load_rules]. *)
Path.Build.Map.set acc dir_target rule_loc
else
(* This will be checked when we interpret the stanza
completely, so just ignore this rule for now. *)
acc)))
| Coq_stanza.Theory.T m ->
(* It's unfortunate that we need to pull in the coq rules here. But
we don't have a generic mechanism for this yet. *)
Expand Down
16 changes: 16 additions & 0 deletions test/blackbox-tests/test-cases/gh10310.t
@@ -0,0 +1,16 @@
Make sure that dune can handle rules with directory targets that are disabled
with enabled_if.

$ cat > dune-project <<EOF
> (lang dune 3.14)
> (using directory-targets 0.1)
> EOF
$ cat > dune <<EOF
> (rule
> (enabled_if false)
> (target (dir x))
> (action (progn)))
> EOF
$ dune build

0 comments on commit 0c42611

Please sign in to comment.