Skip to content

Commit

Permalink
Allow rules with directory targets to be disabled (#10367)
Browse files Browse the repository at this point in the history
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>
  • Loading branch information
gridbugs authored Apr 3, 2024
1 parent c720bf8 commit 2a4a5bf
Show file tree
Hide file tree
Showing 4 changed files with 43 additions and 39 deletions.
58 changes: 31 additions & 27 deletions src/dune_rules/dir_status.ml
Original file line number Diff line number Diff line change
Expand Up @@ -85,32 +85,36 @@ let error_no_module_consumer ~loc (qualification : Include_subdirs.qualification
]
;;

let extract_directory_targets ~dir stanzas =
let extract_directory_targets ~dir ~expander 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; _ }
->
let+ available = Expander.eval_blang expander enabled_if in
if not available
then acc
else
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 Expand Up @@ -257,15 +261,15 @@ end = struct
;;
end

let directory_targets t ~dir =
let directory_targets t ~dir ~expander =
match t with
| Lock_dir | Generated | Source_only _ | Is_component_of_a_group_but_not_the_root _ ->
Memo.return Path.Build.Map.empty
| Standalone (_, dune_file) ->
Dune_file.stanzas dune_file >>= extract_directory_targets ~dir
Dune_file.stanzas dune_file >>= extract_directory_targets ~dir ~expander
| Group_root { components; dune_file; _ } ->
let f ~dir stanzas acc =
extract_directory_targets ~dir stanzas >>| Path.Build.Map.superpose acc
extract_directory_targets ~dir ~expander stanzas >>| Path.Build.Map.superpose acc
in
let* init =
let* stanzas = Dune_file.stanzas dune_file in
Expand Down
6 changes: 5 additions & 1 deletion src/dune_rules/dir_status.mli
Original file line number Diff line number Diff line change
Expand Up @@ -42,4 +42,8 @@ module DB : sig
val get : dir:Path.Build.t -> t Memo.t
end

val directory_targets : t -> dir:Path.Build.t -> Loc.t Path.Build.Map.t Memo.t
val directory_targets
: t
-> dir:Path.Build.t
-> expander:Expander.t
-> Loc.t Path.Build.Map.t Memo.t
5 changes: 4 additions & 1 deletion src/dune_rules/gen_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -518,7 +518,10 @@ let gen_rules_regular_directory sctx ~src_dir ~components ~dir =
in
let+ rules =
let+ make_rules =
let+ directory_targets = Dir_status.directory_targets dir_status ~dir in
let* expander = sctx >>= Super_context.expander ~dir in
let+ directory_targets =
Dir_status.directory_targets dir_status ~dir ~expander
in
let allowed_subdirs =
let automatic = Automatic_subdir.subdirs components in
let toplevel =
Expand Down
13 changes: 3 additions & 10 deletions test/blackbox-tests/test-cases/gh10310.t
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
Reproduces a bug where if a rule with a directory target is excluded with
enabled_if then dune crashes.
Make sure that dune can handle rules with directory targets that are disabled
with enabled_if.

$ cat > dune-project <<EOF
> (lang dune 3.14)
Expand All @@ -13,11 +13,4 @@ enabled_if then dune crashes.
> (action (progn)))
> EOF

$ dune build 2>&1 | head -n 7
Internal error, please report upstream including the contents of _build/log.
Description:
("gen_rules returned a set of directory targets that doesn't match the set of directory targets from returned rules",
{ dir = In_build_dir "default"
; mismatched_directories =
map { "default/x" : { message = "not generated"; loc = "dune:1" } }
})
$ dune build

0 comments on commit 2a4a5bf

Please sign in to comment.