Skip to content

Commit

Permalink
Revert "fix: make ignored rules fallback (#8706)" (#8726)
Browse files Browse the repository at this point in the history
* refactor: simplify left over type signature

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

* Revert "refactor: simplify left over type signature"

This reverts commit ec929ce.

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

* Revert "fix: make ignored rules fallback (#8706)"

This reverts commit b326c30.

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

* Revert "fix: --ignore-promoted-rules should work on internal rules (#8518)"

This reverts commit 853490b.

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

* test: promote

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

---------

Signed-off-by: Rudi Grinberg <me@rgrinberg.com>
  • Loading branch information
rgrinberg authored Sep 21, 2023
1 parent b326c30 commit 2067f71
Show file tree
Hide file tree
Showing 10 changed files with 23 additions and 41 deletions.
3 changes: 0 additions & 3 deletions doc/changes/8518.md

This file was deleted.

1 change: 0 additions & 1 deletion otherlibs/dune-site/test/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -170,7 +170,6 @@ Test with an opam like installation
["dune" "install" "-p" name "--create-install-files" name]
]

$ dune build b/b.opam c/c.opam d/d.opam
$ dune build -p a --promote-install-files=false @install

$ test -e a/a.install
Expand Down
1 change: 0 additions & 1 deletion otherlibs/dune-site/test/run_2_9.t
Original file line number Diff line number Diff line change
Expand Up @@ -158,7 +158,6 @@ Test with an opam like installation
["dune" "install" "-p" name "--create-install-files" name]
]

$ dune build b/b.opam c/c.opam d/d.opam
$ dune build -p a --promote-install-files="false" @install

$ test -e a/a.install
Expand Down
21 changes: 15 additions & 6 deletions src/dune_rules/dune_file.ml
Original file line number Diff line number Diff line change
Expand Up @@ -2472,12 +2472,21 @@ type t =
; stanzas : Stanzas.t
}

let is_promoted_rule version rule =
match rule with
| Rule { mode; _ } | Menhir_stanza.T { mode; _ } ->
let until_clean = if version >= (3, 5) then `Keep else `Ignore in
Rule_mode_decoder.is_ignored mode ~until_clean
| _ -> false
let is_promoted_rule =
let is_promoted_mode version = function
| Rule.Mode.Promote { only = None; lifetime; _ } ->
if version >= (3, 5)
then (
match lifetime with
| Unlimited -> true
| Until_clean -> false)
else true
| _ -> false
in
fun version rule ->
match rule with
| Rule { mode; _ } | Menhir_stanza.T { mode; _ } -> is_promoted_mode version mode
| _ -> false
;;

let parse sexps ~dir ~file ~project =
Expand Down
12 changes: 0 additions & 12 deletions src/dune_rules/rule_mode_decoder.ml
Original file line number Diff line number Diff line change
Expand Up @@ -99,15 +99,3 @@ end

let decode = sum mode_decoders
let field = field "mode" decode ~default:Rule.Mode.Standard

let is_ignored (mode : Rule.Mode.t) ~until_clean =
!Clflags.ignore_promoted_rules
&&
match mode with
| Promote { only = None; lifetime = Unlimited; _ } -> true
| Promote { only = None; lifetime = Until_clean; _ } ->
(match until_clean with
| `Ignore -> true
| `Keep -> false)
| _ -> false
;;
8 changes: 0 additions & 8 deletions src/dune_rules/rule_mode_decoder.mli
Original file line number Diff line number Diff line change
Expand Up @@ -15,11 +15,3 @@ end

val decode : Rule.Mode.t Dune_lang.Decoder.t
val field : Rule.Mode.t Dune_lang.Decoder.fields_parser

(** [is_ignored mode ~until_clean] will return if a rule with [mode] should be
ignored whenever [--ignored-promoted-rules] is set.
[until_clean] is used to set if [(promote (until-clean))] is ignored as
considered by this function. Old versions of dune would incorrectly ignore
this, so we need to maintain the old behavior for now. *)
val is_ignored : Rule.Mode.t -> until_clean:[ `Ignore | `Keep ] -> bool
7 changes: 5 additions & 2 deletions src/dune_rules/simple_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -134,7 +134,9 @@ let user_rule sctx ?extra_bindings ~dir ~expander (rule : Rule.t) =
else action
in
(match rule_kind ~rule ~action with
| No_alias -> add_user_rule sctx ~dir ~rule ~action ~expander
| No_alias ->
let+ targets = add_user_rule sctx ~dir ~rule ~action ~expander in
Some targets
| Aliases_with_targets (aliases, alias_target) ->
let* () =
let aliases = List.map ~f:(Alias.make ~dir) aliases in
Expand All @@ -143,7 +145,8 @@ let user_rule sctx ?extra_bindings ~dir ~expander (rule : Rule.t) =
alias
(Action_builder.path (Path.build alias_target)))
in
add_user_rule sctx ~dir ~rule ~action ~expander
let+ targets = add_user_rule sctx ~dir ~rule ~action ~expander in
Some targets
| Aliases_only aliases ->
let aliases = List.map ~f:(Alias.make ~dir) aliases in
let* action = interpret_and_add_locks ~expander rule.locks action.build in
Expand Down
7 changes: 1 addition & 6 deletions src/dune_rules/super_context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -259,11 +259,6 @@ let extend_action t ~dir action =
;;

let make_rule t ?mode ?loc ~dir { Action_builder.With_targets.build; targets } =
let (mode : Rule.Mode.t option) =
match mode with
| Some mode when Rule_mode_decoder.is_ignored mode ~until_clean:`Keep -> Some Fallback
| _ -> mode
in
let build = extend_action t build ~dir in
Rule.make
?mode
Expand All @@ -281,7 +276,7 @@ let add_rule t ?mode ?loc ~dir build =
let add_rule_get_targets t ?mode ?loc ~dir build =
let rule = make_rule t ?mode ?loc ~dir build in
let+ () = Rules.Produce.rule rule in
Some rule.targets
rule.targets
;;

let add_rules t ?loc ~dir builds = Memo.parallel_iter builds ~f:(add_rule ?loc t ~dir)
Expand Down
2 changes: 1 addition & 1 deletion src/dune_rules/super_context.mli
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,7 @@ val add_rule_get_targets
-> ?loc:Loc.t
-> dir:Path.Build.t
-> Action.Full.t Action_builder.With_targets.t
-> Targets.Validated.t option Memo.t
-> Targets.Validated.t Memo.t

val add_rules
: t
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -19,4 +19,4 @@ This should not modify the file now

$ dune build --ignore-promoted-rules foo.opam
$ grep extra foo.opam
foobar_extra
[1]

0 comments on commit 2067f71

Please sign in to comment.