Skip to content

Commit

Permalink
Print a new line between error messages
Browse files Browse the repository at this point in the history
Signed-off-by: Benoît Montagu <benoit.montagu@inria.fr>
  • Loading branch information
esope committed Jan 13, 2023
1 parent 620b98b commit 4a3c95d
Show file tree
Hide file tree
Showing 4 changed files with 147 additions and 0 deletions.
16 changes: 16 additions & 0 deletions bin/common.ml
Original file line number Diff line number Diff line change
Expand Up @@ -522,6 +522,7 @@ module Builder = struct
; workspace_config : Dune_rules.Workspace.Clflags.t
; cache_debug_flags : Dune_engine.Cache_debug_flags.t
; report_errors_config : Dune_engine.Report_errors_config.t
; separate_error_messages : bool
; require_dune_project_file : bool
; insignificant_changes : [ `React | `Ignore ]
; build_dir : string
Expand Down Expand Up @@ -805,6 +806,14 @@ module Builder = struct
~doc:
"react to insignificant file system changes; this is only useful \
for benchmarking dune")
and+ separate_error_messages =
Arg.(
value & flag
& info
[ "separate-error-messages" ]
~doc:
"Separate error messages with a blank line. This feature is \
always disabled when watch mode is enabled.")
in
{ debug_dep_path
; debug_findlib
Expand Down Expand Up @@ -840,6 +849,11 @@ module Builder = struct
}
; cache_debug_flags
; report_errors_config
; separate_error_messages =
(* this flag is ALWAYS DISABLED when dune works in watch mode *)
(match watch with
| Yes _ -> false
| No -> separate_error_messages)
; require_dune_project_file
; insignificant_changes =
(if react_to_insignificant_changes then `React else `Ignore)
Expand Down Expand Up @@ -1031,6 +1045,8 @@ let init ?log_file c =
[ Pp.textf "Workspace root: %s"
(Path.to_absolute_filename Path.root |> String.maybe_quoted)
];
Dune_util.Report_error.separate_error_messages
c.builder.separate_error_messages;
config

let footer =
Expand Down
32 changes: 32 additions & 0 deletions src/dune_util/report_error.ml
Original file line number Diff line number Diff line change
Expand Up @@ -135,6 +135,37 @@ let format_memo_stack pps =
(Pp.seq (Pp.verbatim "-> ")
(Pp.seq (Pp.text "required by ") pp))))))

(* flag that controls whether error messages should be separated by a
blank line *)
let separate_error_messages_flag = ref false

let separate_error_messages b = separate_error_messages_flag := b

(* If the flag [separate_error_messages] is off, then [print_separator
()] does nothing. If the flag [separate_error_messages] is on, then
[print_separator ()] does nothing the first time it is called,
whereas subsequent calls print a new line. *)
let print_separator =
let first_error = ref true
and msg =
{ User_message.paragraphs = [ Pp.cut ]
; hints = []
; annots = User_message.Annots.empty
; loc = None
}
in
fun () ->
if !separate_error_messages_flag (* only do something when the flag is on *)
then
if !first_error then
(* do not print anything the first time the function is
called, but remember it has been called at least once *)
first_error := false
else
(* if the function has already been called at least once,
print a blank line *)
Console.print_user_message msg

let report { Exn_with_backtrace.exn; backtrace } =
let exn, memo_stack =
match exn with
Expand Down Expand Up @@ -194,4 +225,5 @@ let report { Exn_with_backtrace.exn; backtrace } =
| User -> msg
| Developer -> append msg (i_must_not_crash ())
in
print_separator ();
Console.print_user_message msg
4 changes: 4 additions & 0 deletions src/dune_util/report_error.mli
Original file line number Diff line number Diff line change
@@ -1,6 +1,10 @@
(** Error reporting *)
open Stdune

(** [separate_error_messages b] changes the behavior of [report], so that it
separates error messages with a blank line when [b = true]. *)
val separate_error_messages : bool -> unit

(** Reports an error.
Because dune doesn't stop at the first error, it might end up reporting the
Expand Down
95 changes: 95 additions & 0 deletions test/blackbox-tests/test-cases/error_messages_separated.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,95 @@
Tests for how error messages are displayed
==========================================

The purpose of these tests is to check that errors are displayed with
a separating blank line (issue #6158, PR #6823).

Test setup
----------

$ cat >dune-project <<EOF
> (lang dune 2.3)
> EOF

$ cat >dune <<EOF
> (library
> (name lib))
> EOF

$ cat >a.ml <<EOF
> let f x y z = ()
> (* this should produce 3 warnings for unused variables *)
> EOF

$ cat >b.ml <<EOF
> let () = 1
> (* this should produce a type error *)
> EOF

$ cat >c.ml <<EOF
> let x = +
> (* this should produce a syntax error *)
> EOF

Actual tests
------------

We check that the errors reported for different files are separated by
blank lines. If a file generates several errors (which is the case for
the `a.ml` file, then no blank lines are inserted between them,
because this is the exact message that is reported by the Ocaml
compiler, and we do not parse or modify such messages.

Without the --separate-error-messages flag, no blank line is put
between error messages for different files, as expected.

$ dune build
File "c.ml", line 3, characters 0-0:
Error: Syntax error
File "a.ml", line 1, characters 6-7:
1 | let f x y z = ()
^
Error (warning 27 [unused-var-strict]): unused variable x.
File "a.ml", line 1, characters 8-9:
1 | let f x y z = ()
^
Error (warning 27 [unused-var-strict]): unused variable y.
File "a.ml", line 1, characters 10-11:
1 | let f x y z = ()
^
Error (warning 27 [unused-var-strict]): unused variable z.
File "b.ml", line 1, characters 9-10:
1 | let () = 1
^
Error: This expression has type int but an expression was expected of type
unit
[1]

Wit the --separate-error-messages flag, a blank line is put between
error messages for different files. No blank line is inserted before
the forst message, and no blank line is inserted after the last
message either.

$ dune build --separate-error-messages
File "c.ml", line 3, characters 0-0:
Error: Syntax error

File "a.ml", line 1, characters 6-7:
1 | let f x y z = ()
^
Error (warning 27 [unused-var-strict]): unused variable x.
File "a.ml", line 1, characters 8-9:
1 | let f x y z = ()
^
Error (warning 27 [unused-var-strict]): unused variable y.
File "a.ml", line 1, characters 10-11:
1 | let f x y z = ()
^
Error (warning 27 [unused-var-strict]): unused variable z.

File "b.ml", line 1, characters 9-10:
1 | let () = 1
^
Error: This expression has type int but an expression was expected of type
unit
[1]

0 comments on commit 4a3c95d

Please sign in to comment.