Skip to content

Commit

Permalink
When there are extra parentheses, display the exn
Browse files Browse the repository at this point in the history
Dune tries to be helpful when there are extra parentheses, but sometimes
it is a bit too eager. This wraps the exception so that the original one
is displayed.

Closes #1173
Closes #1181

Signed-off-by: Etienne Millon <me@emillon.org>
  • Loading branch information
emillon committed Aug 30, 2018
1 parent 561edb9 commit 6276240
Show file tree
Hide file tree
Showing 6 changed files with 51 additions and 14 deletions.
6 changes: 6 additions & 0 deletions src/report_error.ml
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,12 @@ let make_printer ?(backtrace=false) ?hint ?loc pp =
; backtrace
}

let set_loc p ~loc =
{p with loc = Some loc}

let set_hint p ~hint =
{p with hint = Some hint}

let builtin_printer = function
| Dsexp.Of_sexp.Of_sexp (loc, msg, hint') ->
let loc =
Expand Down
9 changes: 8 additions & 1 deletion src/report_error.mli
Original file line number Diff line number Diff line change
Expand Up @@ -20,8 +20,15 @@ val make_printer :
(Format.formatter -> unit) ->
printer

(** Register an error reporter. *)
val set_loc : printer -> loc:Loc.t -> printer

val set_hint : printer -> hint:string -> printer

(** Register an error printer. *)
val register : (exn -> printer option) -> unit

(** Find an error printer *)
val find_printer : exn -> printer option

(**/**)
val map_fname : (string -> string) ref
22 changes: 13 additions & 9 deletions src/stanza.ml
Original file line number Diff line number Diff line change
Expand Up @@ -27,18 +27,22 @@ let file_kind () =
module Of_sexp = struct
include Dsexp.Of_sexp

exception Parens_no_longer_necessary of Loc.t
exception Parens_no_longer_necessary of Loc.t * exn

let () =
Report_error.register
(function
| Parens_no_longer_necessary loc ->
let pp ppf =
Format.fprintf ppf
"These parentheses are no longer necessary with dune, \
please remove them.@\n"
| Parens_no_longer_necessary (loc, exn) ->
let hint =
"in dune files, these parentheses are no longer necessary. \
Try removing them."
in
Some (Report_error.make_printer ~loc pp)
Option.map (Report_error.find_printer exn)
~f:(fun printer ->
printer
|> Report_error.set_loc ~loc
|> Report_error.set_hint ~hint
)
| _ -> None)

let switch_file_kind ~jbuild ~dune =
Expand All @@ -61,12 +65,12 @@ module Of_sexp = struct
(if is_record then
peek >>= function
| Some (List _) ->
raise (Parens_no_longer_necessary loc)
raise (Parens_no_longer_necessary (loc, exn))
| _ -> t
else
t)
>>= fun _ ->
raise (Parens_no_longer_necessary loc)))
raise (Parens_no_longer_necessary (loc, exn))))
(function
| Parens_no_longer_necessary _ as exn -> raise exn
| _ -> raise exn))
Expand Down
5 changes: 5 additions & 0 deletions test/blackbox-tests/test-cases/too-many-parens/e/dune
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
(alias
(name a)
(deps (glob *)) ; this form doesn't exist
(action (echo test))
)
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
(lang dune 1.0)
22 changes: 18 additions & 4 deletions test/blackbox-tests/test-cases/too-many-parens/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -8,25 +8,39 @@ are readable.
3: (public_name hello)
4: (libraries (lib))
5: ))
These parentheses are no longer necessary with dune, please remove them.
Error: Atom expected
Hint: try: in dune files, these parentheses are no longer necessary. Try removing them.
[1]

$ dune build --root b
File "dune", line 4, characters 12-17:
(libraries (lib)))
^^^^^
These parentheses are no longer necessary with dune, please remove them.
Error: 'select' expected
Hint: try: in dune files, these parentheses are no longer necessary. Try removing them.
[1]

$ dune build --root c
File "dune", line 3, characters 7-14:
(deps (x y z)))
^^^^^^^
These parentheses are no longer necessary with dune, please remove them.
Error: Unknown constructor x
Hint: try: in dune files, these parentheses are no longer necessary. Try removing them.
[1]

Checking that extra long stanzas (over 10 lines) are not printed
$ dune build --root d
File "dune", line 3, characters 13-192:
These parentheses are no longer necessary with dune, please remove them.
Error: 'select' expected
Hint: try: in dune files, these parentheses are no longer necessary. Try removing them.
[1]

When the inner syntax is wrong, do not warn about the parens:

$ dune build --root e
File "dune", line 3, characters 7-15:
(deps (glob *)) ; this form doesn't exist
^^^^^^^^
Error: Unknown constructor glob
Hint: try: in dune files, these parentheses are no longer necessary. Try removing them.
[1]

0 comments on commit 6276240

Please sign in to comment.