Skip to content

Commit

Permalink
Better stack traces
Browse files Browse the repository at this point in the history
Signed-off-by: Nicolás Ojeda Bär <n.oje.bar@gmail.com>
  • Loading branch information
nojb committed Jan 9, 2024
1 parent b2eaa63 commit 4d71aa2
Show file tree
Hide file tree
Showing 5 changed files with 18 additions and 11 deletions.
8 changes: 7 additions & 1 deletion src/dune_lang/ordered_set_lang.ml
Original file line number Diff line number Diff line change
Expand Up @@ -411,7 +411,13 @@ module Unexpanded = struct
let* sexp =
let* path = expand_template fn ~mode:Single in
let path = Value.to_path path ?error_loc:(Some loc) ~dir in
Action_builder.read_sexp path
Action_builder.push_stack_frame
~human_readable_description:(fun () ->
Pp.textf
"(:include %s) at %s"
(Path.to_string path)
(Loc.to_file_colon_line loc))
(fun () -> Action_builder.read_sexp path)
in
let t = Decoder.parse decode context sexp in
expand t.ast ~allow_include:false
Expand Down
5 changes: 5 additions & 0 deletions src/dune_lang/ordered_set_lang_intf.ml
Original file line number Diff line number Diff line change
Expand Up @@ -46,6 +46,11 @@ module type Action_builder = sig
val all : 'a t list -> 'a list t
val read_sexp : Path.t -> Dune_sexp.Ast.t t

val push_stack_frame
: human_readable_description:(unit -> User_message.Style.t Pp.t)
-> (unit -> 'a t)
-> 'a t

module O : sig
val ( let+ ) : 'a t -> ('a -> 'b) -> 'b t
val ( and+ ) : 'a t -> 'b t -> ('a * 'b) t
Expand Down
3 changes: 0 additions & 3 deletions src/dune_rules/ml_sources.ml
Original file line number Diff line number Diff line change
Expand Up @@ -469,9 +469,6 @@ let make
~include_subdirs:(loc_include_subdirs, (include_subdirs : Dune_file.Include_subdirs.t))
~dirs
=
Memo.push_stack_frame ~human_readable_description:(fun () ->
Pp.textf "Finding source files in directory %s" (Path.Build.to_string dir))
@@ fun () ->
let+ modules_of_stanzas =
let modules =
let dialects = Dune_project.dialects project in
Expand Down
2 changes: 1 addition & 1 deletion src/dune_rules/modules_field_evaluator.ml
Original file line number Diff line number Diff line change
Expand Up @@ -405,7 +405,7 @@ let eval
=
let open Memo.O in
Memo.push_stack_frame ~human_readable_description:(fun () ->
Pp.textf "Evaluating modules field in directory %s" (Path.Build.to_string src_dir))
Pp.textf "(modules) field at %s" (Loc.to_file_colon_line stanza_loc))
@@ fun () ->
let* modules0 =
eval0 ~expander ~loc:stanza_loc ~all_modules ~standard:all_modules settings.modules
Expand Down
11 changes: 5 additions & 6 deletions test/blackbox-tests/test-cases/modules-expansion.t
Original file line number Diff line number Diff line change
Expand Up @@ -151,10 +151,9 @@ Interaction with `(include_subdirs)` when the dependencies are in the subtree:
$ dune build --display short
Error: Dependency cycle between:
Finding source files in directory _build/default
(modules) field at dune:2
-> %{read-lines:gen/lst} at dune:4
-> Evaluating modules field in directory _build/default
-> Finding source files in directory _build/default
-> (modules) field at dune:2
[1]
Let's move the gen subdirectory out of the hierarchy:
Expand Down Expand Up @@ -197,9 +196,9 @@ appears. We need to handle this cycle gracefully and report it to the user.
$ dune exec ./mod.exe
Error: Dependency cycle between:
Finding source files in directory _build/default
-> Evaluating modules field in directory _build/default
-> Finding source files in directory _build/default
(modules) field at dune:2
-> (:include _build/default/lst) at dune:2
-> (modules) field at dune:2
[1]
Let's do one example with a generated source file:
Expand Down

0 comments on commit 4d71aa2

Please sign in to comment.