Skip to content

Commit

Permalink
Cleanup the status line at the end of the build (#3767)
Browse files Browse the repository at this point in the history
Fixes #3737

Signed-off-by: Alan Hu <[email protected]>
Signed-off-by: Jeremie Dimino <[email protected]>
  • Loading branch information
alan-j-hu authored Sep 23, 2020
1 parent b8f51bc commit f51136f
Show file tree
Hide file tree
Showing 3 changed files with 19 additions and 15 deletions.
3 changes: 3 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,9 @@ Unreleased

- Add (enabled_if ...) to (copy_files ...) (#3756, @nojb)

- Make sure Dune cleans up the status line before exiting (#3767,
fixes #3737, @dosaylazy)

2.7.1 (2/09/2020)
-----------------

Expand Down
12 changes: 6 additions & 6 deletions bootstrap.ml
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ open Printf
(* This program performs version checking of the compiler and switches to the
secondary compiler if necessary. The script should execute in OCaml 4.02! *)

let min_supported_natively = (4, 08)
let min_supported_natively = (4, 08, 0)

let verbose, keep_generated_files, debug =
let anon s = raise (Arg.Bad (sprintf "don't know what to do with %s\n" s)) in
Expand Down Expand Up @@ -65,7 +65,7 @@ let read_file fn =
s

let () =
let v = Scanf.sscanf Sys.ocaml_version "%d.%d" (fun a b -> (a, b)) in
let v = Scanf.sscanf Sys.ocaml_version "%d.%d.%d" (fun a b c -> (a, b, c)) in
let compiler, which =
if v >= min_supported_natively then
("ocamlc", None)
Expand All @@ -77,15 +77,15 @@ let () =
prerr_endline s;
if n <> 0 || s <> "" then (
Format.eprintf "@[%a@]@." Format.pp_print_text
(sprintf
(let a, b, _ = min_supported_natively in
sprintf
"The ocamlfind's secondary toolchain does not seem to be \
correctly installed.\n\
Dune requires OCaml %d.%02d or later to compile.\n\
Please either upgrade your compile or configure a secondary \
OCaml compiler (in opam, this can be done by installing the \
ocamlfind-secondary package)."
(fst min_supported_natively)
(snd min_supported_natively));
a b);
exit 2
);
(compiler, Some "--secondary")
Expand All @@ -94,7 +94,7 @@ let () =
(runf "%s %s -w -24 -g -o %s -I boot unix.cma %s" compiler
(* Make sure to produce a self-contained binary as dlls tend to cause
issues *)
( if v < (4, 10) then
( if v < (4, 10, 1) then
"-custom"
else
"-output-complete-exe" )
Expand Down
19 changes: 10 additions & 9 deletions src/dune_engine/scheduler.ml
Original file line number Diff line number Diff line change
Expand Up @@ -702,7 +702,6 @@ end = struct
let fiber =
Fiber.Var.set t_var t (fun () -> Fiber.with_error_handler f ~on_error)
in
Console.Status_line.set (Fun.const None);
match Fiber.run fiber ~iter with
| res ->
assert (Event.pending_jobs () = 0);
Expand All @@ -712,14 +711,16 @@ end = struct

let run_and_cleanup t f =
let res = run t f in
( match res with
| Error Files_changed ->
Console.Status_line.set (fun () ->
Some
(Pp.seq
(Pp.tag User_message.Style.Error (Pp.verbatim "Had errors"))
(Pp.verbatim ", killing current build...")))
| _ -> () );
let status_line =
match res with
| Error Files_changed ->
Some
(Pp.seq
(Pp.tag User_message.Style.Error (Pp.verbatim "Had errors"))
(Pp.verbatim ", killing current build..."))
| _ -> None
in
Console.Status_line.set (Fun.const status_line);
match kill_and_wait_for_all_processes t () with
| Got_signal -> Error Got_signal
| Ok -> res
Expand Down

0 comments on commit f51136f

Please sign in to comment.