Skip to content

Commit

Permalink
Remove old stuff about updated files
Browse files Browse the repository at this point in the history
This dates from the time we were using timestamps for incremental
compilation.
  • Loading branch information
Jeremie Dimino authored and jeremiedimino committed Feb 1, 2018
1 parent b9c4dd2 commit 143145b
Show file tree
Hide file tree
Showing 3 changed files with 3 additions and 22 deletions.
11 changes: 0 additions & 11 deletions src/action.ml
Original file line number Diff line number Diff line change
Expand Up @@ -543,17 +543,6 @@ let fold_one_step t ~init:acc ~f =

include Make_mapper(Ast)(Ast)

let updated_files =
let rec loop acc t =
let acc =
match t with
| Write_file (fn, _) -> Path.Set.add fn acc
| _ -> acc
in
fold_one_step t ~init:acc ~f:loop
in
fun t -> loop Path.Set.empty t

let chdirs =
let rec loop acc t =
let acc =
Expand Down
3 changes: 0 additions & 3 deletions src/action.mli
Original file line number Diff line number Diff line change
Expand Up @@ -44,9 +44,6 @@ include Action_intf.Helpers
val t : t Sexp.Of_sexp.t
val sexp_of_t : t Sexp.To_sexp.t

(** Return the list of files under an [Update_file] *)
val updated_files : t -> Path.Set.t

(** Return the list of directories the action chdirs to *)
val chdirs : t -> Path.Set.t

Expand Down
11 changes: 3 additions & 8 deletions src/build_system.ml
Original file line number Diff line number Diff line change
Expand Up @@ -672,13 +672,8 @@ let rec compile_rule t ?(copy_source=false) pre_rule =
List.exists targets_as_list ~f:Path.is_alias_stamp_file
in
if deps_or_rule_changed || targets_missing || force then (
(* Do not remove files that are just updated, otherwise this would break incremental
compilation *)
let targets_to_remove =
Pset.diff targets (Action.updated_files action)
in
Pset.iter targets_to_remove ~f:Path.unlink_no_err;
pending_targets := Pset.union targets_to_remove !pending_targets;
List.iter targets_as_list ~f:Path.unlink_no_err;
pending_targets := Pset.union targets !pending_targets;
let action =
match sandbox_dir with
| Some sandbox_dir ->
Expand All @@ -703,7 +698,7 @@ let rec compile_rule t ?(copy_source=false) pre_rule =
Action.exec ?context ~targets action) >>| fun () ->
Option.iter sandbox_dir ~f:Path.rm_rf;
(* All went well, these targets are no longer pending *)
pending_targets := Pset.diff !pending_targets targets_to_remove;
pending_targets := Pset.diff !pending_targets targets;
clear_targets_digests_after_rule_execution targets_as_list;
match mode with
| Standard | Fallback | Not_a_rule_stanza | Ignore_source_files -> ()
Expand Down

0 comments on commit 143145b

Please sign in to comment.