Skip to content

Commit

Permalink
Add support for the alias field in rule
Browse files Browse the repository at this point in the history
A rule with [alias] set will add the action to the transitive dependency
of the alias.

Signed-off-by: Rudi Grinberg <rudi.grinberg@gmail.com>
  • Loading branch information
rgrinberg committed Oct 15, 2019
1 parent 9da6860 commit 9f0c6aa
Showing 1 changed file with 26 additions and 15 deletions.
41 changes: 26 additions & 15 deletions src/dune/simple_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -12,8 +12,18 @@ let dep_bindings ~extra_bindings deps =
| Some bindings -> Pform.Map.superpose base bindings
| None -> base

let add_alias sctx ~dir ~name ~stamp ~loc ?(locks = []) build =
let alias = Alias.make name ~dir in
SC.add_alias_action sctx alias ~dir ~loc ~locks ~stamp build

let stamp ~deps ~action ~extra_bindings =
( "user-alias"
, Bindings.map ~f:Dune_file.Dep_conf.remove_locs deps
, Option.map ~f:Action_unexpanded.remove_locs action
, Option.map extra_bindings ~f:Pform.Map.to_stamp )

let user_rule sctx ?extra_bindings ~dir ~expander (rule : Rule.t) =
if Expander.eval_blang expander rule.enabled_if then
if Expander.eval_blang expander rule.enabled_if then (
let targets : Expander.Targets.t =
match rule.targets with
| Infer -> Infer
Expand Down Expand Up @@ -58,6 +68,17 @@ let user_rule sctx ?extra_bindings ~dir ~expander (rule : Rule.t) =
in
let bindings = dep_bindings ~extra_bindings rule.deps in
let expander = Expander.add_bindings expander ~bindings in
let action =
SC.Deps.interpret_named sctx ~expander rule.deps
|> SC.Action.run sctx (snd rule.action) ~loc:(fst rule.action) ~expander
~dep_kind:Required ~targets ~targets_dir:dir
in
Option.iter rule.alias ~f:(fun name ->
let stamp =
let action = Some (snd rule.action) in
stamp ~deps:rule.deps ~extra_bindings ~action
in
add_alias sctx ~dir ~name ~stamp ~loc:(Some (fst rule.action)) action);
SC.add_rule_get_targets
sctx
(* user rules may have extra requirements, in which case they will be
Expand All @@ -66,10 +87,8 @@ let user_rule sctx ?extra_bindings ~dir ~expander (rule : Rule.t) =
~sandbox:Sandbox_config.no_special_requirements ~dir ~mode:rule.mode
~loc:rule.loc
~locks:(interpret_locks ~expander rule.locks)
( SC.Deps.interpret_named sctx ~expander rule.deps
|> SC.Action.run sctx (snd rule.action) ~loc:(fst rule.action) ~expander
~dep_kind:Required ~targets ~targets_dir:dir )
else
action
) else
Path.Build.Set.empty

let copy_files sctx ~dir ~expander ~src_dir (def : Copy_files.t) =
Expand Down Expand Up @@ -117,18 +136,10 @@ let copy_files sctx ~dir ~expander ~src_dir (def : Copy_files.t) =
~src:file_src ~dst:file_dst);
Path.build file_dst)

let add_alias sctx ~dir ~name ~stamp ~loc ?(locks = []) build =
let alias = Alias.make name ~dir in
SC.add_alias_action sctx alias ~dir ~loc ~locks ~stamp build

let alias sctx ?extra_bindings ~dir ~expander (alias_conf : Alias_conf.t) =
let stamp =
( "user-alias"
, Bindings.map ~f:Dune_file.Dep_conf.remove_locs alias_conf.deps
, Option.map
~f:(fun (_loc, a) -> Action_unexpanded.remove_locs a)
alias_conf.action
, Option.map extra_bindings ~f:Pform.Map.to_stamp )
let action = Option.map ~f:snd alias_conf.action in
stamp ~deps:alias_conf.deps ~extra_bindings ~action
in
let loc = Some alias_conf.loc in
if Expander.eval_blang expander alias_conf.enabled_if then
Expand Down

0 comments on commit 9f0c6aa

Please sign in to comment.