Skip to content

Commit

Permalink
Merge pull request #2588 from rgrinberg/turn-off-promotion
Browse files Browse the repository at this point in the history
Add --disable-promotion option
  • Loading branch information
rgrinberg authored Aug 27, 2019
2 parents 0139485 + 7649148 commit 9355a48
Show file tree
Hide file tree
Showing 10 changed files with 79 additions and 26 deletions.
4 changes: 4 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -105,6 +105,10 @@

- Remove git integration from `$ dune upgrade` (#2565, @rgrinberg)

- Add a `--disable-promotion` to disable all modification to the source
directory. There's also a corresponding `DUNE_DISABLE_PROMOTION` environment
variable. (#2588, fix #2568, @rgrinberg)

1.11.3 (23/08/2019)
-------------------

Expand Down
30 changes: 20 additions & 10 deletions bin/common.ml
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@ type t =
; capture_outputs : bool
; x : string option
; diff_command : string option
; auto_promote : bool
; promote : Clflags.Promote.t option
; force : bool
; ignore_promoted_rules : bool
; build_dir : string
Expand Down Expand Up @@ -76,7 +76,7 @@ let set_common_other c ~targets =
Clflags.debug_backtraces := c.debug_backtraces;
Clflags.capture_outputs := c.capture_outputs;
Clflags.diff_command := c.diff_command;
Clflags.auto_promote := c.auto_promote;
Clflags.promote := c.promote;
Clflags.force := c.force;
Clflags.watch := c.watch;
Clflags.no_print_directory := c.no_print_directory;
Expand Down Expand Up @@ -405,13 +405,23 @@ let term =
& opt (some path) None
& info [ "workspace" ] ~docs ~docv:"FILE" ~doc
~env:(Arg.env_var ~doc "DUNE_WORKSPACE"))
and+ auto_promote =
Arg.(
value & flag
& info [ "auto-promote" ] ~docs
~doc:
"Automatically promote files. This is similar to running\n\
\ $(b,dune promote) after the build.")
and+ promote =
one_of
(let+ auto =
Arg.(
value & flag
& info [ "auto-promote" ] ~docs
~doc:
"Automatically promote files. This is similar to running\n\
\ $(b,dune promote) after the build.")
in
Option.some_if auto Clflags.Promote.Automatically)
(let+ disable =
let doc = "Disable all promotion rules" in
let env = Arg.env_var ~doc "DUNE_DISABLE_PROMOTION" in
Arg.(value & flag & info [ "disable-promotion" ] ~docs ~env ~doc)
in
Option.some_if disable Clflags.Promote.Never)
and+ force =
Arg.(
value & flag
Expand Down Expand Up @@ -516,7 +526,7 @@ let term =
; target_prefix =
String.concat ~sep:"" (List.map root.to_cwd ~f:(sprintf "%s/"))
; diff_command
; auto_promote
; promote
; force
; ignore_promoted_rules
; only_packages =
Expand Down
17 changes: 7 additions & 10 deletions src/dune/build_system.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1465,12 +1465,11 @@ end = struct
Fiber.return ()
in
let+ () =
match mode with
| Standard
|Fallback
|Ignore_source_files ->
match (mode, !Clflags.promote) with
| (Standard | Fallback | Ignore_source_files), _
|Promote _, Some Never ->
Fiber.return ()
| Promote { lifetime; into; only } ->
| Promote { lifetime; into; only }, (Some Automatically | None) ->
Fiber.sequential_iter targets_as_list ~f:(fun path ->
let consider_for_promotion =
match only with
Expand Down Expand Up @@ -1659,14 +1658,12 @@ let package_deps pkg files =
(* if this file isn't in the build dir, it doesnt belong to any packages
and it doesn't have dependencies that do *)
acc
| Some fn -> (
| Some fn ->
let pkgs = Fdecl.get t.packages fn in
if Package.Name.Set.is_empty pkgs then
loop_deps fn acc
else if Package.Name.Set.mem pkgs pkg then
if Package.Name.Set.is_empty pkgs || Package.Name.Set.mem pkgs pkg then
loop_deps fn acc
else
Package.Name.Set.union acc pkgs)
Package.Name.Set.union acc pkgs
and loop_deps fn acc =
match Path.Build.Table.find t.files fn with
| None -> acc
Expand Down
8 changes: 7 additions & 1 deletion src/dune/clflags.ml
Original file line number Diff line number Diff line change
@@ -1,3 +1,9 @@
module Promote = struct
type t =
| Automatically
| Never
end

let debug_findlib = ref false

let debug_dep_path = ref false
Expand All @@ -10,7 +16,7 @@ let debug_backtraces = ref false

let diff_command = ref None

let auto_promote = ref false
let promote = ref None

let force = ref false

Expand Down
10 changes: 8 additions & 2 deletions src/dune/clflags.mli
Original file line number Diff line number Diff line change
Expand Up @@ -18,8 +18,14 @@ val debug_backtraces : bool ref
(** Command to use to diff things *)
val diff_command : string option ref

(** Automatically promote files *)
val auto_promote : bool ref
module Promote : sig
type t =
| Automatically
| Never
end

(** explicit promotion mode is set *)
val promote : Promote.t option ref

(** Force re-running actions associated to aliases *)
val force : bool ref
Expand Down
7 changes: 4 additions & 3 deletions src/dune/promotion.ml
Original file line number Diff line number Diff line change
Expand Up @@ -148,9 +148,10 @@ let do_promote db files_to_promote =

let finalize () =
let db =
if !Clflags.auto_promote then
do_promote !File.db All
else
match !Clflags.promote with
| Some Automatically -> do_promote !File.db All
| Some Never
|None ->
!File.db
in
dump_db db
Expand Down
10 changes: 10 additions & 0 deletions test/blackbox-tests/dune.inc
Original file line number Diff line number Diff line change
Expand Up @@ -231,6 +231,14 @@
test-cases/dir-target-dep
(progn (run %{exe:cram.exe} -test run.t) (diff? run.t run.t.corrected)))))

(alias
(name disable-promotion)
(deps (package dune) (source_tree test-cases/disable-promotion))
(action
(chdir
test-cases/disable-promotion
(progn (run %{exe:cram.exe} -test run.t) (diff? run.t run.t.corrected)))))

(alias
(name double-echo)
(deps (package dune) (source_tree test-cases/double-echo))
Expand Down Expand Up @@ -1742,6 +1750,7 @@
(alias deps-conf-vars)
(alias dialects)
(alias dir-target-dep)
(alias disable-promotion)
(alias double-echo)
(alias dune-build-dir-exec-1101)
(alias dune-init)
Expand Down Expand Up @@ -1946,6 +1955,7 @@
(alias deps-conf-vars)
(alias dialects)
(alias dir-target-dep)
(alias disable-promotion)
(alias double-echo)
(alias dune-build-dir-exec-1101)
(alias dune-init)
Expand Down
3 changes: 3 additions & 0 deletions test/blackbox-tests/test-cases/disable-promotion/dune
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
(library
(name foo)
(public_name foo))
4 changes: 4 additions & 0 deletions test/blackbox-tests/test-cases/disable-promotion/dune-project
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
(lang dune 1.11)

(package
(name foo))
12 changes: 12 additions & 0 deletions test/blackbox-tests/test-cases/disable-promotion/run.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,12 @@
This tests shows how all promotion to the source dir may be disabled. This
includes both .install and .merlin files

$ dune build --disable-promotion @all
.merlin is absent
$ test -f .merlin && echo ".merlin exists"
[1]

now we build without the option and see that it is present:
$ dune build @all
$ test -f .merlin && echo ".merlin exists"
.merlin exists

0 comments on commit 9355a48

Please sign in to comment.