Skip to content

Commit

Permalink
Merge pull request #4048 from rgrinberg/subst-debug-backtrace
Browse files Browse the repository at this point in the history
Fix dune subst not to initialize root
  • Loading branch information
rgrinberg authored Jan 6, 2021
2 parents f728993 + 0bc5c25 commit 967719b
Show file tree
Hide file tree
Showing 3 changed files with 19 additions and 8 deletions.
12 changes: 7 additions & 5 deletions bin/common.ml
Original file line number Diff line number Diff line change
Expand Up @@ -118,6 +118,12 @@ let footer =

let copts_sect = "COMMON OPTIONS"

let debug_backtraces =
Arg.(
value & flag
& info [ "debug-backtraces" ] ~docs:copts_sect
~doc:{|Always print exception backtraces.|})

let examples = function
| [] -> `Blocks []
| _ :: _ as examples ->
Expand Down Expand Up @@ -475,11 +481,7 @@ let term =
Arg.(
value & flag
& info [ "debug-findlib" ] ~docs ~doc:{|Debug the findlib sub-system.|})
and+ debug_backtraces =
Arg.(
value & flag
& info [ "debug-backtraces" ] ~docs
~doc:{|Always print exception backtraces.|})
and+ debug_backtraces = debug_backtraces
and+ debug_artifact_substitution =
Arg.(
value & flag
Expand Down
2 changes: 2 additions & 0 deletions bin/common.mli
Original file line number Diff line number Diff line change
Expand Up @@ -60,6 +60,8 @@ val footer : Cmdliner.Manpage.block

val term : t Cmdliner.Term.t

val debug_backtraces : bool Cmdliner.Term.t

val config_term : Dune_engine.Config.t Cmdliner.Term.t

val display_term : Dune_engine.Config.Display.t option Cmdliner.Term.t
Expand Down
13 changes: 10 additions & 3 deletions bin/subst.ml
Original file line number Diff line number Diff line change
Expand Up @@ -58,9 +58,16 @@ let man =
let info = Term.info "subst" ~doc ~man

let term =
let+ common = Common.term in
Common.set_common ~log_file:No_log_file common ~targets:[];
let config = Common.config common in
let+ () = Common.build_info
and+ debug_backtraces = Common.debug_backtraces in
let config : Config.t =
{ Config.default with display = Quiet; concurrency = Fixed 1 }
in
Dune_engine.Clflags.debug_backtraces debug_backtraces;
Path.set_root (Path.External.cwd ());
Path.Build.set_build_dir (Path.Build.Kind.of_string Common.default_build_dir);
Config.init config;
Log.init_disabled ();
Dune_engine.Scheduler.go ~config Watermarks.subst

let command = (term, info)

0 comments on commit 967719b

Please sign in to comment.