Skip to content

Commit

Permalink
fix: ignore insignificant_changes by default
Browse files Browse the repository at this point in the history
but introduce a --react-insignificant-changes to restore the old
behavior for anyone that needs it (to benchmark)

Signed-off-by: Rudi Grinberg <me@rgrinberg.com>
  • Loading branch information
rgrinberg committed Jul 13, 2022
1 parent 8402fa1 commit 76131b6
Show file tree
Hide file tree
Showing 4 changed files with 25 additions and 2 deletions.
4 changes: 4 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -21,6 +21,10 @@
- Fix handling of the `(deps)` field in `(test)` stanzas when there is an
`.expected` file. (#5952, #5951, fixes #5950, @emillon)

- Ignore insignificant filesystem events. This stops RPC in watch mode from
flashing errors when file system events such as changes in the `.git/`
directory occur. (#5953, @rgrinberg)

3.3.1 (19-06-2022)
------------------

Expand Down
15 changes: 15 additions & 0 deletions bin/common.ml
Original file line number Diff line number Diff line change
Expand Up @@ -49,6 +49,7 @@ type t =
; cache_debug_flags : Dune_engine.Cache_debug_flags.t
; report_errors_config : Dune_engine.Report_errors_config.t
; require_dune_project_file : bool
; insignificant_changes : [ `React | `Ignore ]
}

let capture_outputs t = t.capture_outputs
Expand All @@ -75,6 +76,8 @@ let rpc t = Lazy.force t.rpc

let stats t = t.stats

let insignificant_changes t = t.insignificant_changes

let set_print_directory t b = { t with no_print_directory = not b }

let set_promote t v = { t with promote = Some v }
Expand Down Expand Up @@ -977,6 +980,17 @@ let term ~default_root_is_cwd =
$(b,twice) - report each error twice: once as soon as the error \
is discovered and then again at the end of the build, in a \
deterministic order.")
and+ react_to_insignificant_changes =
Arg.(
value & flag
& info
[ "react-to-insignificant-changes" ]
~doc:
"react to insignificant file system changes; this is only useful \
for benchmarking dune")
in
let insignificant_changes =
if react_to_insignificant_changes then `React else `Ignore
in
let build_dir = Option.value ~default:default_build_dir build_dir in
let root =
Expand Down Expand Up @@ -1032,6 +1046,7 @@ let term ~default_root_is_cwd =
; cache_debug_flags
; report_errors_config
; require_dune_project_file
; insignificant_changes
}

let term_with_default_root_is_cwd = term ~default_root_is_cwd:true
Expand Down
2 changes: 2 additions & 0 deletions bin/common.mli
Original file line number Diff line number Diff line change
Expand Up @@ -24,6 +24,8 @@ val default_target : t -> Arg.Dep.t

val prefix_target : t -> string -> string

val insignificant_changes : t -> [ `React | `Ignore ]

(** [init] executes sequence of side-effecting actions to initialize Dune's
working environment based on the options determined in a [Common.t]
record.contents.
Expand Down
6 changes: 4 additions & 2 deletions bin/import.ml
Original file line number Diff line number Diff line change
Expand Up @@ -128,15 +128,17 @@ module Scheduler = struct
let go ~(common : Common.t) ~config:dune_config f =
let stats = Common.stats common in
let config =
Dune_config.for_scheduler dune_config stats ~insignificant_changes:`React
let insignificant_changes = Common.insignificant_changes common in
Dune_config.for_scheduler dune_config stats ~insignificant_changes
in
Scheduler.Run.go config ~on_event:(on_event dune_config) f

let go_with_rpc_server_and_console_status_reporting ~(common : Common.t)
~config:dune_config run =
let stats = Common.stats common in
let config =
Dune_config.for_scheduler dune_config stats ~insignificant_changes:`React
let insignificant_changes = Common.insignificant_changes common in
Dune_config.for_scheduler dune_config stats ~insignificant_changes
in
let file_watcher = Common.file_watcher common in
let rpc = Common.rpc common in
Expand Down

0 comments on commit 76131b6

Please sign in to comment.