Skip to content

Commit

Permalink
fix(pkg): print depexts message when a program is not found (#11005)
Browse files Browse the repository at this point in the history
* fix(pkg): print depexts message when a program is not found

Signed-off-by: Alpha DIALLO <[email protected]>
  • Loading branch information
moyodiallo authored Oct 9, 2024
1 parent 412a0f5 commit 9992794
Show file tree
Hide file tree
Showing 2 changed files with 35 additions and 21 deletions.
43 changes: 28 additions & 15 deletions src/dune_rules/pkg_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -579,6 +579,16 @@ module Substitute = struct
let action expander ~src ~dst = A.action { Spec.expander; src; dst }
end

let depexts_hint = function
| [] -> None
| depexts ->
[ Pp.textf "You may want to verify the following depexts are installed:"
; Pp.enumerate ~f:Pp.verbatim depexts
]
|> Pp.concat_map ~sep:Pp.cut ~f:(fun pp -> Pp.box pp)
|> Option.some
;;

module Run_with_path = struct
module Output : sig
type error
Expand Down Expand Up @@ -616,30 +626,28 @@ module Run_with_path = struct
;;

let to_paragraphs t error =
let pkg_name, loc = t.pkg in
let depexts_warning =
match t.depexts with
| [] -> []
| _ :: _ ->
[ Pp.textf "You may want to verify the following depexts are installed:"
; Pp.enumerate ~f:Pp.verbatim t.depexts
]
in
let pp_pkg = Pp.textf "Logs for package %s" (Package.Name.to_string pkg_name) in
[ pp_pkg; Pp.verbatim error ] @ depexts_warning, loc
let pp_pkg = Pp.textf "Logs for package %s" (Package.Name.to_string (fst t.pkg)) in
[ pp_pkg; Pp.verbatim error ]
;;

let prerr ~rc error =
let hints =
lazy
(match depexts_hint error.depexts with
| None -> []
| Some h -> [ h ])
in
let loc = snd error.pkg in
match Predicate.test error.accepted_exit_codes rc, error.display with
| false, _ ->
let paragraphs, loc = Stdune.Io.read_file error.filename |> to_paragraphs error in
User_warning.emit ~loc ~is_error:true paragraphs
let paragraphs = Stdune.Io.read_file error.filename |> to_paragraphs error in
User_warning.emit ~hints:(Lazy.force hints) ~loc ~is_error:true paragraphs
| true, Display.Verbose ->
let content = Stdune.Io.read_file error.filename in
if not (String.is_empty content)
then (
let paragraphs, loc = to_paragraphs error content in
User_warning.emit ~loc paragraphs)
let paragraphs = to_paragraphs error content in
User_warning.emit ~hints:(Lazy.force hints) ~loc paragraphs)
| true, _ -> ()
;;
end
Expand Down Expand Up @@ -943,8 +951,13 @@ module Action_expander = struct
>>| (function
| Some p -> Ok p
| None ->
let hint =
depexts_hint t.depexts
|> Option.map ~f:(fun pp -> Format.asprintf "%a" Pp.to_fmt pp)
in
Error
(Action.Prog.Not_found.create
?hint
~program
~context:t.context
~loc:(Some loc)
Expand Down
13 changes: 7 additions & 6 deletions test/blackbox-tests/test-cases/pkg/depexts/error-message.t
Original file line number Diff line number Diff line change
Expand Up @@ -37,8 +37,8 @@ Make dune.lock files with known program "dune".
> (checksum md5=$(md5sum foo.tar | cut -f1 -d' '))))
> EOF
Build the project, when it fails building 'foo' package, it shows
the depexts error message.
Build the project, when it fails building 'foo' package, it shows the depexts
error message.
$ dune build
File "dune.lock/foo.pkg", line 3, characters 6-10:
3 | (run dune build))
Expand All @@ -47,7 +47,7 @@ the depexts error message.
File "dune-project", line 1, characters 0-0:
Error: Invalid first line, expected: (lang <lang> <version>)

You may want to verify the following depexts are installed:
Hint: You may want to verify the following depexts are installed:
- unzip
- gnupg
[1]
Expand All @@ -65,13 +65,14 @@ Make dune.lock files with unknown program and unknown package.
> (checksum md5=$(md5sum foo.tar | cut -f1 -d' '))))
> EOF
Doing the same build which is supposed to show the depexts message at the end.
There is a bug at the moment, it shows the correct error message but without
depexts message.
Running the same build. It is supposed to show the depexts message at the end,
when the program is not found.
$ dune build
File "dune.lock/foo.pkg", line 3, characters 6-21:
3 | (run unknown-program))
^^^^^^^^^^^^^^^
Error: Program unknown-program not found in the tree or in PATH
(context: default)
Hint: You may want to verify the following depexts are installed:
- unknown-package
[1]

0 comments on commit 9992794

Please sign in to comment.