Skip to content

Commit

Permalink
fix: expand %{deps} in (cat) properly
Browse files Browse the repository at this point in the history
Signed-off-by: Ali Caglayan <[email protected]>
  • Loading branch information
Alizter committed Jul 13, 2023
1 parent ff9b6f9 commit cb18441
Show file tree
Hide file tree
Showing 2 changed files with 17 additions and 8 deletions.
19 changes: 17 additions & 2 deletions src/dune_rules/action_unexpanded.ml
Original file line number Diff line number Diff line change
Expand Up @@ -68,6 +68,9 @@ module Action_expander : sig
(* Evaluate a path in a position of dependency, such as in [(cat <dep>)] *)
val dep : String_with_vars.t -> Path.t t

(* Evaluate paths in the position of dependencies, such as in [(cat <deps>)] *)
val deps : String_with_vars.t -> Path.t list t

(* Evaluate a path in a position of optional dependency, such as in [(diff
<dep_if_exists> ...)] *)
val dep_if_exists : String_with_vars.t -> Path.t t
Expand Down Expand Up @@ -241,6 +244,14 @@ end = struct
Value.to_path_in_build_or_external v
~error_loc:(String_with_vars.loc sw) ~dir:t.dir

let expand_paths t sw =
let+ v, vs = expand t ~mode:At_least_one sw in
List.map
~f:
(Value.to_path_in_build_or_external
~error_loc:(String_with_vars.loc sw) ~dir:t.dir)
(v :: vs)

let expand_string env sw =
let+ v = expand env ~mode:Single sw in
Value.to_string v ~dir:(Path.build env.dir)
Expand Down Expand Up @@ -304,6 +315,10 @@ end = struct
let fn = Expander.expand_path env sw in
register_dep fn ~f:Option.some env acc

let deps sw env acc =
let fn = Expander.expand_paths env sw in
register_dep fn ~f:(fun _ -> None) env acc

let dep_if_exists sw env acc =
Memo.return
(let fn = Expander.expand_path env sw in
Expand Down Expand Up @@ -427,8 +442,8 @@ let rec expand (t : Dune_lang.Action.t) ~context : Action.t Action_expander.t =
let l = List.concat l in
O.Echo l
| Cat xs ->
let+ xs = A.all (List.map xs ~f:E.dep) in
O.Cat xs
let+ xs = A.all (List.map xs ~f:E.deps) in
O.Cat (List.concat xs)
| Copy (x, y) ->
let+ x = E.dep x
and+ y = E.target y in
Expand Down
6 changes: 0 additions & 6 deletions test/blackbox-tests/test-cases/quoting/cat.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -13,9 +13,3 @@ arguments.
> EOF

$ dune build @foo
File "dune", line 5, characters 7-14:
5 | (cat %{deps})))
^^^^^^^
Error: Variable %{deps} expands to 2 values, however a single value is
expected here. Please quote this atom.
[1]

0 comments on commit cb18441

Please sign in to comment.