Skip to content

Commit

Permalink
Apply review suggestions
Browse files Browse the repository at this point in the history
Signed-off-by: Alpha DIALLO <moyodiallo@gmail.com>
  • Loading branch information
moyodiallo committed Oct 9, 2024
1 parent 9739339 commit 1702a2a
Show file tree
Hide file tree
Showing 4 changed files with 23 additions and 19 deletions.
4 changes: 0 additions & 4 deletions src/dune_engine/action.ml
Original file line number Diff line number Diff line change
Expand Up @@ -71,10 +71,6 @@ module Prog = struct
raise (User_error.E (Utils.program_not_found_message ?hint ~loc ~context program))
;;

let message { context; program; hint; loc } =
Utils.program_not_found_message ?hint ~loc ~context program
;;

let to_dyn { context; program; hint; loc = _ } =
let open Dyn in
record
Expand Down
1 change: 0 additions & 1 deletion src/dune_engine/action.mli
Original file line number Diff line number Diff line change
Expand Up @@ -67,7 +67,6 @@ module Prog : sig
-> unit
-> t

val message : t -> User_message.t
val raise : t -> _
end

Expand Down
34 changes: 21 additions & 13 deletions src/dune_rules/pkg_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -582,11 +582,13 @@ end
module Depexts = struct
type t = string list

let message (t : t) =
let pp (t : t) =
[ Pp.textf "You may want to verify the following depexts are installed:"
; Pp.enumerate ~f:Pp.verbatim t
]
;;

let message (t : t) = User_message.make (pp t)
end

module Run_with_path = struct
Expand Down Expand Up @@ -630,7 +632,7 @@ module Run_with_path = struct
let depexts_warning =
match t.depexts with
| [] -> []
| _ -> Depexts.message t.depexts
| _ :: _ -> Depexts.pp 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
Expand Down Expand Up @@ -709,11 +711,7 @@ module Run_with_path = struct
let open Fiber.O in
let display = !Clflags.display in
match prog with
| Error e ->
let _, loc = pkg in
let depexts_msg = if List.is_empty depexts then [] else Depexts.message depexts in
let error_msg = (Action.Prog.Not_found.message e).paragraphs in
raise (User_error.E (error_msg @ depexts_msg |> User_message.make ~loc))
| Error e -> Action.Prog.Not_found.raise e
| Ok prog ->
let args =
Array.Immutable.to_list_map args ~f:(fun arg ->
Expand Down Expand Up @@ -954,12 +952,22 @@ module Action_expander = struct
>>| (function
| Some p -> Ok p
| None ->
Error
(Action.Prog.Not_found.create
~program
~context:t.context
~loc:(Some loc)
()))))
if List.is_empty t.depexts
then
Error
(Action.Prog.Not_found.create
~program
~context:t.context
~loc:(Some loc)
())
else
Error
(Action.Prog.Not_found.create
~hint:(Depexts.message t.depexts |> User_message.to_string)
~program
~context:t.context
~loc:(Some loc)
()))))
in
Result.map prog ~f:(map_exe t)
;;
Expand Down
3 changes: 2 additions & 1 deletion test/blackbox-tests/test-cases/pkg/depexts/error-message.t
Original file line number Diff line number Diff line change
Expand Up @@ -73,6 +73,7 @@ the program is not found.
^^^^^^^^^^^^^^^
Error: Program unknown-program not found in the tree or in PATH
(context: default)
You may want to verify the following depexts are installed:
Hint: You may want to verify the following depexts are installed:
- unknown-package
[1]

0 comments on commit 1702a2a

Please sign in to comment.