Skip to content

Commit

Permalink
Fix incorrect message "unknown macro"
Browse files Browse the repository at this point in the history
When using %{lib:..} in a non dynamic context should give us an error
straight away. Delaying the error doesn't make sense as we will not be
expanding these variables in a second step.

Signed-off-by: Rudi Grinberg <rudi.grinberg@gmail.com>
  • Loading branch information
rgrinberg committed Aug 30, 2019
1 parent 5c1f104 commit ebcfdb8
Show file tree
Hide file tree
Showing 2 changed files with 13 additions and 6 deletions.
13 changes: 9 additions & 4 deletions src/dune/expander.ml
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
open Stdune
open Import

type expanded =
| Static of Value.t list
Expand Down Expand Up @@ -333,6 +333,11 @@ let expand_and_record acc ~map_exe ~dep_kind ~expansion_kind
| Static -> fun _ -> User_error.raise ~loc [ cannot_be_used_here pform ]
| Dynamic -> Resolved_forms.add_ddep acc ~key
in
let add_fail =
match expansion_kind with
| Static -> fun _ (f : fail) -> f.fail ()
| Dynamic -> Resolved_forms.add_fail
in
let open Build.O in
match (expansion : Pform.Expansion.t) with
| Var
Expand Down Expand Up @@ -361,7 +366,7 @@ let expand_and_record acc ~map_exe ~dep_kind ~expansion_kind
| Macro (Dep, s) -> Some (path_exp (relative dir s))
| Macro (Bin, s) -> (
match resolve_binary ~loc:(Some loc) t ~prog:s with
| Error fail -> Resolved_forms.add_fail acc fail
| Error fail -> add_fail acc fail
| Ok path -> Some (path_exp path) )
| Macro (Lib, s) -> (
let lib_dep, file = parse_lib_file ~loc s in
Expand All @@ -370,14 +375,14 @@ let expand_and_record acc ~map_exe ~dep_kind ~expansion_kind
Artifacts.Public_libs.file_of_lib t.lib_artifacts ~loc ~lib:lib_dep ~file
with
| Ok path -> Some (path_exp path)
| Error e -> Resolved_forms.add_fail acc { fail = (fun () -> raise e) } )
| Error e -> add_fail acc { fail = (fun () -> raise e) } )
| Macro (Libexec, s) -> (
let lib_dep, file = parse_lib_file ~loc s in
Resolved_forms.add_lib_dep acc lib_dep dep_kind;
match
Artifacts.Public_libs.file_of_lib t.lib_artifacts ~loc ~lib:lib_dep ~file
with
| Error e -> Resolved_forms.add_fail acc { fail = (fun () -> raise e) }
| Error e -> add_fail acc { fail = (fun () -> raise e) }
| Ok path ->
if (not Sys.win32) || Filename.extension s = ".exe" then
Some (path_exp path)
Expand Down
6 changes: 4 additions & 2 deletions test/blackbox-tests/test-cases/github1541/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,8 @@ for libraries in the deps field:
File "dune", line 1, characters 14-33:
1 | (rule (deps %{lib:fakelib:bar.ml}) (target dummy) (action (with-stdout-to %{target} (echo foo))))
^^^^^^^^^^^^^^^^^^^
Error: Unknown macro %{lib:..}
Error: Library "fakelib" not found.
Hint: try: dune external-lib-deps --missing ./dummy
[1]

for binaries in the deps field:
Expand All @@ -41,5 +42,6 @@ for binaries in the deps field:
File "dune", line 1, characters 14-25:
1 | (rule (deps %{bin:foobar}) (target dummy) (action (with-stdout-to %{target} (echo foo))))
^^^^^^^^^^^
Error: Unknown macro %{bin:..}
Error: Program foobar not found in the tree or in PATH
(context: default)
[1]

0 comments on commit ebcfdb8

Please sign in to comment.