Skip to content

Commit

Permalink
feature: multiple alias support in rules
Browse files Browse the repository at this point in the history
Signed-off-by: Ali Caglayan <[email protected]>

ps-id: 7f58c532-3611-4290-b07c-9ad973f2a995
Signed-off-by: Ali Caglayan <[email protected]>
  • Loading branch information
Alizter committed Oct 8, 2022
1 parent b423d7c commit 91357bb
Show file tree
Hide file tree
Showing 7 changed files with 160 additions and 28 deletions.
3 changes: 3 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -76,6 +76,9 @@
- on macOS, sign executables produced by artifact substitution (#6137, fixes
#5650, @emillon)

- Added an (aliases ...) field to the (rules ...) stanza which allows the
specification of multiple aliases per rule (#6194, @Alizter)

3.4.1 (26-07-2022)
------------------

Expand Down
2 changes: 2 additions & 0 deletions doc/dune-files.rst
Original file line number Diff line number Diff line change
Expand Up @@ -1055,6 +1055,8 @@ See the :ref:`user-actions` section for more details.
- ``(alias <alias-name>)`` specifies this rule's alias. Building this
alias means building the targets of this rule.

- ``(aliases <alias-name list>)`` specifies many aliases for this rule.

- ``(package <package>)`` specifies this rule's package. This rule
will be unavailable when installing other packages in release mode.

Expand Down
28 changes: 23 additions & 5 deletions src/dune_rules/dune_file.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1476,7 +1476,7 @@ module Rule = struct
; locks : Locks.t
; loc : Loc.t
; enabled_if : Blang.t
; alias : Alias.Name.t option
; aliases : Alias.Name.t list
; package : Package.t option
}

Expand Down Expand Up @@ -1514,6 +1514,7 @@ module Rule = struct
; ("locks", Field)
; ("fallback", Field)
; ("mode", Field)
; ("aliases", Field)
; ("alias", Field)
; ("enabled_if", Field)
]
Expand All @@ -1528,7 +1529,7 @@ module Rule = struct
; locks = []
; loc
; enabled_if = Blang.true_
; alias = None
; aliases = []
; package = None
}

Expand Down Expand Up @@ -1577,6 +1578,23 @@ module Rule = struct
and+ alias =
field_o "alias"
(Dune_lang.Syntax.since Stanza.syntax (2, 0) >>> Alias.Name.decode)
and+ aliases =
field_o "aliases"
(Dune_lang.Syntax.since Stanza.syntax (3, 5)
>>> repeat Alias.Name.decode)
in
let aliases =
match alias with
| None -> Option.value ~default:[] aliases
| Some alias -> (
match aliases with
| None -> [ alias ]
| Some _ ->
User_error.raise ~loc
[ Pp.text
"The 'alias' and 'aliases' fields are mutually exclusive. \
Please use only the 'aliases' field."
])
in
let mode, patch_back_source_tree =
match mode with
Expand All @@ -1602,7 +1620,7 @@ module Rule = struct
; locks
; loc
; enabled_if
; alias
; aliases
; package
; patch_back_source_tree
})
Expand Down Expand Up @@ -1672,7 +1690,7 @@ module Rule = struct
; locks = []
; loc
; enabled_if
; alias = None
; aliases = []
; package = None
})

Expand Down Expand Up @@ -1702,7 +1720,7 @@ module Rule = struct
; locks = []
; loc
; enabled_if
; alias = None
; aliases = []
; package = None
})
end
Expand Down
2 changes: 1 addition & 1 deletion src/dune_rules/dune_file.mli
Original file line number Diff line number Diff line change
Expand Up @@ -292,7 +292,7 @@ module Rule : sig
; locks : Locks.t
; loc : Loc.t
; enabled_if : Blang.t
; alias : Alias.Name.t option
; aliases : Alias.Name.t list
; package : Package.t option
}
end
Expand Down
46 changes: 25 additions & 21 deletions src/dune_rules/simple_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -37,17 +37,17 @@ let check_filename =
| Dir p -> not_in_dir ~kind ~error_loc (Path.to_string p)

type rule_kind =
| Alias_only of Alias.Name.t
| Alias_with_targets of Alias.Name.t * Path.Build.t
| Aliases_only of Alias.Name.t list
| Aliases_with_targets of Alias.Name.t list * Path.Build.t
| No_alias

let rule_kind ~(rule : Rule.t) ~(action : _ Action_builder.With_targets.t) =
match rule.alias with
| None -> No_alias
| Some alias -> (
match rule.aliases with
| [] -> No_alias
| aliases -> (
match Targets.head action.targets with
| None -> Alias_only alias
| Some target -> Alias_with_targets (alias, target))
| None -> Aliases_only aliases
| Some target -> Aliases_with_targets (aliases, target))

let interpret_and_add_locks ~expander locks action =
let+ locks = Expander.expand_locks expander ~base:`Of_expander locks in
Expand All @@ -66,13 +66,13 @@ let add_user_rule sctx ~dir ~(rule : Rule.t)

let user_rule sctx ?extra_bindings ~dir ~expander (rule : Rule.t) =
Expander.eval_blang expander rule.enabled_if >>= function
| false -> (
match rule.alias with
| None -> Memo.return None
| Some name ->
let alias = Alias.make ~dir name in
let+ () = Alias_rules.add_empty sctx ~alias ~loc:(Some rule.loc) in
None)
| false ->
let aliases = List.map rule.aliases ~f:(Alias.make ~dir) in
let+ () =
Memo.parallel_iter aliases ~f:(fun alias ->
Alias_rules.add_empty sctx ~loc:(Some rule.loc) ~alias)
in
None
| true -> (
let* targets =
match rule.targets with
Expand Down Expand Up @@ -120,18 +120,22 @@ let user_rule sctx ?extra_bindings ~dir ~expander (rule : Rule.t) =
| No_alias ->
let+ targets = add_user_rule sctx ~dir ~rule ~action ~expander in
Some targets
| Alias_with_targets (alias, alias_target) ->
| Aliases_with_targets (aliases, alias_target) ->
let* () =
let alias = Alias.make alias ~dir in
Rules.Produce.Alias.add_deps alias
(Action_builder.path (Path.build alias_target))
let aliases = List.map ~f:(Alias.make ~dir) aliases in
Memo.parallel_iter aliases ~f:(fun alias ->
Rules.Produce.Alias.add_deps alias
(Action_builder.path (Path.build alias_target)))
in
let+ targets = add_user_rule sctx ~dir ~rule ~action ~expander in
Some targets
| Alias_only name ->
let alias = Alias.make ~dir name in
| Aliases_only aliases ->
let aliases = List.map ~f:(Alias.make ~dir) aliases in
let* action = interpret_and_add_locks ~expander rule.locks action.build in
let+ () = Alias_rules.add sctx ~alias ~loc:(Some rule.loc) action in
let+ () =
Memo.parallel_iter aliases ~f:(fun alias ->
Alias_rules.add sctx ~alias ~loc:(Some rule.loc) action)
in
None)

let copy_files sctx ~dir ~expander ~src_dir (def : Copy_files.t) =
Expand Down
2 changes: 1 addition & 1 deletion src/dune_rules/test_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -105,7 +105,7 @@ let rules (t : Dune_file.Tests.t) ~sctx ~dir ~scope ~expander ~dir_contents =
; locks = t.locks
; loc
; enabled_if = t.enabled_if
; alias = None
; aliases = []
; package = t.package
}
in
Expand Down
105 changes: 105 additions & 0 deletions test/blackbox-tests/test-cases/alias-multiple.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,105 @@
Testing multiple aliases in rules stanza

First we start with a dune-project before alias was introduced:
$ cat > dune-project << EOF
> (lang dune 1.9)
> EOF

$ cat > dune << EOF
> (rule
> (alias a)
> (action (echo "I have run")))
> EOF

$ dune build @a
File "dune", line 2, characters 1-10:
2 | (alias a)
^^^^^^^^^
Error: 'alias' is only available since version 2.0 of the dune language.
Please update your dune-project file to have (lang dune 2.0).
[1]

Next we update the dune-project file to use dune 2.0:
$ cat > dune-project << EOF
> (lang dune 2.0)
> EOF

$ dune build @a
I have run

We now update the dune file to use multiple aliases
$ cat > dune << EOF
> (rule
> (alias a b)
> (action (echo "I have run")))
> EOF

$ dune build @a
File "dune", line 2, characters 10-11:
2 | (alias a b)
^
Error: Too many argument for alias
[1]

That doesn't work so we use the aliases field
$ cat > dune << EOF
> (rule
> (aliases a b)
> (action (echo "I have run")))
> EOF

$ dune build @a @b
File "dune", line 2, characters 1-14:
2 | (aliases a b)
^^^^^^^^^^^^^
Error: 'aliases' is only available since version 3.5 of the dune language.
Please update your dune-project file to have (lang dune 3.5).
[1]

Updating the dune-project file to use dune 3.5 allows the build to succeed:
$ cat > dune-project << EOF
> (lang dune 3.5)
> EOF

$ dune build @a
I have run
$ dune build @b
I have run

Also note having both the alias and aliases fields in the same rule stanza is
not allowed

$ cat > dune << EOF
> (rule
> (alias a)
> (aliases b)
> (action (echo "I have run")))
> EOF

$ dune build @a
File "dune", line 1, characters 0-60:
1 | (rule
2 | (alias a)
3 | (aliases b)
4 | (action (echo "I have run")))
Error: The 'alias' and 'aliases' fields are mutually exclusive. Please use
only the 'aliases' field.
[1]

Even if the aliases list is empty
$ cat > dune << EOF
> (rule
> (alias a)
> (aliases)
> (action (echo "I have run")))
> EOF

$ dune build @a
File "dune", line 1, characters 0-58:
1 | (rule
2 | (alias a)
3 | (aliases)
4 | (action (echo "I have run")))
Error: The 'alias' and 'aliases' fields are mutually exclusive. Please use
only the 'aliases' field.
[1]

0 comments on commit 91357bb

Please sign in to comment.