Skip to content

Commit

Permalink
Merge pull request #4096 from rgrinberg/deforest-targets
Browse files Browse the repository at this point in the history
Deforest build targets
  • Loading branch information
rgrinberg authored Jan 12, 2021
2 parents 5173566 + 447d6a8 commit 31285ad
Show file tree
Hide file tree
Showing 3 changed files with 9 additions and 8 deletions.
2 changes: 2 additions & 0 deletions src/dune_engine/build.ml
Original file line number Diff line number Diff line change
Expand Up @@ -234,6 +234,8 @@ end
let with_targets build ~targets : _ With_targets.t =
{ build; targets = Path.Build.Set.of_list targets }

let with_targets_set build ~targets : _ With_targets.t = { build; targets }

let with_no_targets build : _ With_targets.t =
{ build; targets = Path.Build.Set.empty }

Expand Down
3 changes: 3 additions & 0 deletions src/dune_engine/build.mli
Original file line number Diff line number Diff line change
Expand Up @@ -58,6 +58,9 @@ val set_file_system_accessors : file_exists:(Path.t -> bool) -> unit
into [Build.With_targets.t]. *)
val with_targets : 'a t -> targets:Path.Build.t list -> 'a With_targets.t

(** [with_targets_set] is like [with_targets] but [targets] is a set *)
val with_targets_set : 'a t -> targets:Path.Build.Set.t -> 'a With_targets.t

(** Create a value of [With_targets.t] with the empty set of targets. *)
val with_no_targets : 'a t -> 'a With_targets.t

Expand Down
12 changes: 4 additions & 8 deletions src/dune_rules/action_unexpanded.ml
Original file line number Diff line number Diff line change
Expand Up @@ -663,12 +663,9 @@ end
let add_deps_if_exist deps_if_exist =
let open Build.O in
(let+ l =
Path.Set.to_list deps_if_exist
|> List.map
~f:
Build.(
fun f ->
if_file_exists f ~then_:(return (Some f)) ~else_:(return None))
Path.Set.to_list_map deps_if_exist ~f:(fun f ->
Build.if_file_exists f ~then_:(Build.return (Some f))
~else_:(Build.return None))
|> Build.all
in
List.filter_opt l)
Expand Down Expand Up @@ -705,7 +702,6 @@ let expand t ~loc ~dep_kind ~targets_dir ~targets:targets_written_by_user
; Pp.enumerate (Path.Build.Set.to_list targets) ~f:(fun target ->
Pp.text (Dpath.describe_path (Path.build target)))
]);
let targets = Path.Build.Set.to_list targets in
Build.path_set deps
>>> add_deps_if_exist deps_if_exist
>>> Build.dyn_path_set
Expand Down Expand Up @@ -734,7 +730,7 @@ let expand t ~loc ~dep_kind ~targets_dir ~targets:targets_written_by_user
((Action.Chdir (dir, action), deps), deps_if_exist))
in
(action, Path.Set.union deps deps_if_exist_which_exist))
|> Build.with_targets ~targets
|> Build.with_targets_set ~targets

(* We re-export [Action_dune_lang] in the end to avoid polluting the inferred
types in this module with all the various t's *)
Expand Down

0 comments on commit 31285ad

Please sign in to comment.