Skip to content

Commit

Permalink
move context annot in user errors to report_error
Browse files Browse the repository at this point in the history
Signed-off-by: Javier Chávarri <javier.chavarri@gmail.com>
  • Loading branch information
jchavarri committed Apr 12, 2024
1 parent a1d6e84 commit 63f17d1
Show file tree
Hide file tree
Showing 6 changed files with 30 additions and 33 deletions.
7 changes: 5 additions & 2 deletions src/dune_engine/action_runner.ml
Original file line number Diff line number Diff line change
Expand Up @@ -70,7 +70,10 @@ end = struct
let annots =
match with_directory with
| Some annot ->
User_message.Annots.set annots Process.with_directory_annot annot
User_message.Annots.set
annots
Dune_util.Report_error.with_directory_annot
annot
| None -> annots
in
User
Expand Down Expand Up @@ -108,7 +111,7 @@ end = struct
in
let diff_promotion = User_message.Annots.find annots Diff_promotion.Annot.annot in
let with_directory =
User_message.Annots.find annots Process.with_directory_annot
User_message.Annots.find annots Dune_util.Report_error.with_directory_annot
in
User_with_annots
{ message
Expand Down
4 changes: 3 additions & 1 deletion src/dune_engine/build_system_error.ml
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,9 @@ let of_exn (exn : Exn_with_backtrace.t) =
in
match exn.exn with
| User_error.E main ->
let dir = User_message.Annots.find main.annots Process.with_directory_annot in
let dir =
User_message.Annots.find main.annots Dune_util.Report_error.with_directory_annot
in
let promotion = User_message.Annots.find main.annots Diff_promotion.Annot.annot in
(match User_message.Annots.find main.annots Compound_user_error.annot with
| None ->
Expand Down
35 changes: 7 additions & 28 deletions src/dune_engine/process.ml
Original file line number Diff line number Diff line change
Expand Up @@ -6,10 +6,6 @@ module Timestamp = Event.Timestamp
module Action_output_on_success = Execution_parameters.Action_output_on_success
module Action_output_limit = Execution_parameters.Action_output_limit

let with_directory_annot =
User_message.Annots.Key.create ~name:"with-directory" Path.to_dyn
;;

let limit_output = Dune_output_truncation.limit_output ~message:"TRUNCATED BY DUNE"

module Failure_mode = struct
Expand Down Expand Up @@ -488,7 +484,6 @@ module Handle_exit_status : sig
-> output:string
-> command_line:User_message.Style.t Pp.t
-> dir:Path.t option
-> context:string option
-> 'a

val non_verbose
Expand All @@ -501,7 +496,6 @@ module Handle_exit_status : sig
-> dir:Path.t option
-> has_unexpected_stdout:bool
-> has_unexpected_stderr:bool
-> context:string option
-> 'a
end = struct
open Exit_status
Expand Down Expand Up @@ -534,7 +528,9 @@ end = struct
let get_loc_and_annots ~dir ~metadata ~output =
let { loc; annots; _ } = metadata in
let dir = Option.value dir ~default:Path.root in
let annots = User_message.Annots.set annots with_directory_annot dir in
let annots =
User_message.Annots.set annots Dune_util.Report_error.with_directory_annot dir
in
let annots =
match output with
| No_output -> annots
Expand All @@ -552,14 +548,14 @@ end = struct
loc, annots
;;

let fail ~loc ~annots ~context paragraphs =
let fail ~loc ~annots paragraphs =
(* We don't use [User_error.make] as it would add the "Error: " prefix. We
don't need this prefix as it is already included in the output of the
command. *)
raise (User_error.E (User_message.make ?loc ~annots ?context paragraphs))
raise (User_error.E (User_message.make ?loc ~annots paragraphs))
;;

let verbose t ~id ~metadata ~output ~command_line ~dir ~context =
let verbose t ~id ~metadata ~output ~command_line ~dir =
let open Pp.O in
let output = parse_output output in
match t with
Expand All @@ -585,7 +581,6 @@ end = struct
fail
~loc
~annots
~context
((Pp.tag User_message.Style.Kwd (Pp.verbatim "Command")
++ Pp.space
++ pp_id id
Expand All @@ -606,7 +601,6 @@ end = struct
~dir
~has_unexpected_stdout
~has_unexpected_stderr
~context
=
let output = parse_output output in
let show_command =
Expand Down Expand Up @@ -662,7 +656,7 @@ end = struct
| Signaled signame ->
[ Pp.textf "Command got signal %s." (Signal.name signame) ]))
in
fail ~loc ~annots ~context paragraphs
fail ~loc ~annots paragraphs
;;
end

Expand Down Expand Up @@ -990,18 +984,6 @@ let run_internal
| None -> dir
| Some p -> if Path.is_root p then None else Some p
in
let context =
let build_context =
match dir with
| None -> None
| Some path ->
(match Path.as_in_build_dir path with
| None -> None
| Some path -> Build_context.of_build_path path)
in
Option.map build_context ~f:(fun build_context ->
Context_name.to_string build_context.name)
in
let id = Running_jobs.Id.gen () in
let prog_str = Path.reach_for_running ?from:dir prog in
let command_line =
Expand All @@ -1016,7 +998,6 @@ let run_internal
in
Console.print_user_message
(User_message.make
?context
[ Pp.tag User_message.Style.Kwd (Pp.verbatim "Running")
++ pp_id id
++ Pp.verbatim ": "
Expand Down Expand Up @@ -1087,7 +1068,6 @@ let run_internal
~dir
~command_line:fancy_command_line
~output
~context
| _ ->
Handle_exit_status.non_verbose
result.exit_status
Expand All @@ -1099,7 +1079,6 @@ let run_internal
~verbosity:display
~has_unexpected_stdout:result.stdout.unexpected_output
~has_unexpected_stderr:result.stderr.unexpected_output
~context
in
Result.close result;
res, times)
Expand Down
2 changes: 0 additions & 2 deletions src/dune_engine/process.mli
Original file line number Diff line number Diff line change
Expand Up @@ -4,8 +4,6 @@ open Import
module Action_output_on_success := Execution_parameters.Action_output_on_success
module Action_output_limit := Execution_parameters.Action_output_limit

val with_directory_annot : Path.t User_message.Annots.Key.t

module Failure_mode : sig
(** How to handle sub-process failures *)
type ('a, 'b) t =
Expand Down
13 changes: 13 additions & 0 deletions src/dune_util/report_error.ml
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,10 @@ type error =
; needs_stack_trace : bool
}

let with_directory_annot =
User_message.Annots.Key.create ~name:"with-directory" Path.to_dyn
;;

let code_error ~loc ~dyn_without_loc =
let open Pp.O in
{ responsible = Developer
Expand Down Expand Up @@ -63,6 +67,15 @@ let get_error_from_exn = function
| User_error.E msg ->
let has_embedded_location = User_message.has_embedded_location msg in
let needs_stack_trace = User_message.needs_stack_trace msg in
let dir = User_message.Annots.find msg.annots with_directory_annot in
let msg =
match dir with
| None -> msg
| Some path ->
(match Path.extract_build_context path with
| None -> msg
| Some (ctxt, _) -> { msg with context = Some ctxt })
in
{ responsible = User; msg; has_embedded_location; needs_stack_trace }
| Code_error.E e ->
code_error ~loc:e.loc ~dyn_without_loc:(Code_error.to_dyn_without_loc e)
Expand Down
2 changes: 2 additions & 0 deletions src/dune_util/report_error.mli
Original file line number Diff line number Diff line change
Expand Up @@ -24,3 +24,5 @@ val print_memo_stacks : bool ref

(** Format a list of Memo stack frames into a user-friendly presentation *)
val format_memo_stack : 'a Pp.t list -> 'a Pp.t option

val with_directory_annot : Path.t User_message.Annots.Key.t

0 comments on commit 63f17d1

Please sign in to comment.