Skip to content

Commit

Permalink
Attach stack traces to library resolution errors (#5079)
Browse files Browse the repository at this point in the history
Thanks to #5075 and #5047, we can now easily provide more information for some library
resolution errors. I think it's pretty helpful to tell the user why the problematic library was required.
In fact, in one of the tests, this was suggested as a future improvement.

We could only do this for a subset of errors in this module, but after studying the new error
messages, I think all of them got better.

Signed-off-by: Andrey Mokhov <[email protected]>
  • Loading branch information
snowleopard authored Nov 2, 2021
1 parent 60bceb4 commit b3089db
Show file tree
Hide file tree
Showing 16 changed files with 56 additions and 7 deletions.
6 changes: 4 additions & 2 deletions src/dune_rules/lib.ml
Original file line number Diff line number Diff line change
Expand Up @@ -92,7 +92,9 @@ module Error = struct
consider the library that triggered the error. *)

let make ?loc ?hints paragraphs =
Resolve.Build.fail (User_error.make ?loc ?hints paragraphs)
Resolve.Build.fail
(User_error.make ?loc ?hints paragraphs
~annots:[ User_message.Annot.Needs_stack_trace.make () ])

let pp_lib info =
let name = Lib_info.name info in
Expand Down Expand Up @@ -1193,7 +1195,7 @@ end = struct
[ Pp.textf
"default implementation belongs to package %s \
while virtual library belongs to package %s. \
This is impossible\n"
This is impossible."
(Package.Name.to_string p)
(Package.Name.to_string p')
])))
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -24,6 +24,9 @@ A default implementation of a library must belong to the same package
6 | (default_implementation def_i))
^^^^^
Error: default implementation belongs to package dummyfoo2 while virtual
library belongs to package dummyfoo1. This is impossible

library belongs to package dummyfoo1. This is impossible.
-> required by _build/default/dummyfoo1.dune-package
-> required by _build/install/default/lib/dummyfoo1/dune-package
-> required by _build/default/dummyfoo1.install
-> required by alias install
[1]
Original file line number Diff line number Diff line change
Expand Up @@ -95,6 +95,7 @@ that wasn't found:
1 | (executable (name prog) (libraries a))
^
Error: Library "a" not found.
-> required by _build/default/c/prog.exe
[1]

Test that we can migrate top-level libraries
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -34,6 +34,7 @@ dune >= 2.8
18 | (libraries bar))
^^^
Error: Library "bar" in _build/default is hidden (unsatisfied 'enabled_if').
-> required by _build/default/bar_exe.exe
[1]

+ The actual context
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -10,4 +10,5 @@ This one is disabled (version too low)
^^^^^^^^^^
Error: Library "futurecaml" in _build/default is hidden (unsatisfied
'enabled_if').
-> required by _build/default/main2.exe
[1]
6 changes: 3 additions & 3 deletions test/blackbox-tests/test-cases/enabled_if/eif-simple.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ Test the enabled_if field for libraries:
35 | (libraries foo))
^^^
Error: Library "foo" in _build/default is hidden (unsatisfied 'enabled_if').
-> required by library "bar" in _build/default
-> required by executable main in dune:44
-> required by _build/default/main.exe
[1]

Ideally, the above message should mention the dependency path between
the requested target and the unsatisfied `enabled_if`.
1 change: 1 addition & 0 deletions test/blackbox-tests/test-cases/exec-missing.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -5,4 +5,5 @@ When using dune exec, the external-lib-deps command refers to the executable:
3 | (libraries does-not-exist))
^^^^^^^^^^^^^^
Error: Library "does-not-exist" not found.
-> required by _build/default/x.exe
[1]
2 changes: 2 additions & 0 deletions test/blackbox-tests/test-cases/forbidden_libraries.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -23,4 +23,6 @@ Test the `forbidden_libraries` feature
Error: Library "a" was pulled in.
-> required by library "b" in _build/default
-> required by library "c" in _build/default
-> required by executable main in dune:5
-> required by _build/default/main.exe
[1]
3 changes: 3 additions & 0 deletions test/blackbox-tests/test-cases/foreign-library.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -768,6 +768,9 @@ Testsuite for the (foreign_library ...) stanza.
4 | (include_dirs (lib answer) (lib unknown_lib))
^^^^^^^^^^^
Error: Library "unknown_lib" not found.
-> required by _build/default/some/dir/src.o
-> required by _build/default/some/dir/libclib.a
-> required by _build/default/some/dir/main.exe
[1]

----------------------------------------------------------------------------------
Expand Down
4 changes: 4 additions & 0 deletions test/blackbox-tests/test-cases/github1541.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,8 @@ for libraries:
1 | (rule (with-stdout-to dummy (echo "%{lib:fakelib:bar.ml}")))
^^^^^^^^^^^^^^^^^^^^^
Error: Library "fakelib" not found.
-> required by %{lib:fakelib:bar.ml} at dune:1
-> required by _build/default/dummy
[1]

for binaries:
Expand All @@ -31,6 +33,8 @@ for libraries in the deps field:
1 | (rule (deps %{lib:fakelib:bar.ml}) (target dummy) (action (with-stdout-to %{target} (echo foo))))
^^^^^^^^^^^^^^^^^^^^^
Error: Library "fakelib" not found.
-> required by %{lib:fakelib:bar.ml} at dune:1
-> required by _build/default/dummy
[1]

for binaries in the deps field:
Expand Down
5 changes: 5 additions & 0 deletions test/blackbox-tests/test-cases/lib.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -251,4 +251,9 @@ But will fail when we release it, as it will need to run with -p:
5 | (with-stdout-to lib2.ml (echo "let _ = {|%{lib-private:lib1:lib1.ml}|}")))
^^^^^^^^^^^^^^^^^^^^^^^^^^^
Error: Library "lib1" not found.
-> required by %{lib-private:lib1:lib1.ml} at lib2/dune:5
-> required by _build/default/lib2/lib2.ml
-> required by _build/install/default/lib/public_lib2/lib2.ml
-> required by _build/default/public_lib2.install
-> required by alias install
[1]
6 changes: 6 additions & 0 deletions test/blackbox-tests/test-cases/libexec.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -313,4 +313,10 @@ But will fail when we release it, as it will need to run with -p:
5 | (with-stdout-to lib2.ml (echo "let _ = {|%{libexec-private:lib1:lib1.ml}|}")))
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Error: Library "lib1" not found.
-> required by %{libexec-private:lib1:lib1.ml} at lib2/dune:5
-> required by _build/target/lib2/lib2.ml
-> required by _build/install/target/lib/public_lib2/lib2.ml
-> required by _build/target/public_lib2.install
-> required by alias install (context target)
-> required by alias target (context target) in dune:5
[1]
13 changes: 13 additions & 0 deletions test/blackbox-tests/test-cases/optional-executable.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -26,13 +26,18 @@ Test optional executable
3 | (libraries does-not-exist)
^^^^^^^^^^^^^^
Error: Library "does-not-exist" not found.
-> required by _build/default/x.exe
-> required by alias all
[1]

$ dune build @run-x
File "dune", line 3, characters 12-26:
3 | (libraries does-not-exist)
^^^^^^^^^^^^^^
Error: Library "does-not-exist" not found.
-> required by _build/default/x.exe
-> required by %{exe:x.exe} at dune:8
-> required by alias run-x in dune:6
[1]

Reproduction case for a bug in dune < 2.4 where all executables where
Expand All @@ -51,6 +56,10 @@ The following command should fail because the executable is not optional:
3 | (libraries does-not-exist))
^^^^^^^^^^^^^^
Error: Library "does-not-exist" not found.
-> required by _build/default/x.exe
-> required by _build/install/default/bin/x
-> required by _build/default/x.install
-> required by alias install
[1]

A strange behavior discovered in #4786. Dune would ignore an executable if any
Expand Down Expand Up @@ -130,6 +139,10 @@ present even if the binary is not optional.
3 | (libraries doesnotexistatall)
^^^^^^^^^^^^^^^^^
Error: Library "doesnotexistatall" not found.
-> required by _build/default/exe/bar.exe
-> required by _build/install/default/bin/dunetestbar
-> required by %{bin:dunetestbar} at dune:3
-> required by alias run-x in dune:1
[1]

Optional on the executable should be respected:
Expand Down
5 changes: 5 additions & 0 deletions test/blackbox-tests/test-cases/optional.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -46,4 +46,9 @@ The following command should fail because the executable is not optional:
4 | (libraries lib_that_doesn't_exist))
^^^^^^^^^^^^^^^^^^^^^^
Error: Library "lib_that_doesn't_exist" not found.
-> required by library "foo" in _build/default
-> required by _build/default/META.foo
-> required by _build/install/default/lib/foo/META
-> required by _build/default/foo.install
-> required by alias install
[1]
Original file line number Diff line number Diff line change
Expand Up @@ -115,6 +115,7 @@ not been marked with (kind ppx_rewriter).
^
Error: Ppx dependency on a non-ppx library "b". If "b" is in fact a ppx
rewriter library, it should have (kind ppx_rewriter) in its dune file.
-> required by _build/default/bin/main.exe
[1]

----------------------------------------------------------------------------------
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -5,4 +5,5 @@ appropriate error message.
3 | (implements lib))
^^^
Error: Library "lib" is not virtual. It cannot be implemented by "impl".
-> required by alias default in dune:1
[1]

0 comments on commit b3089db

Please sign in to comment.