Skip to content

Commit

Permalink
Hiding the status line means also to forget it
Browse files Browse the repository at this point in the history
Otherwise hiding then printing user message would show back the old status line
  • Loading branch information
bobot committed Jul 9, 2019
1 parent 96bc305 commit 5606d47
Show file tree
Hide file tree
Showing 3 changed files with 20 additions and 14 deletions.
4 changes: 2 additions & 2 deletions src/scheduler.ml
Original file line number Diff line number Diff line change
Expand Up @@ -534,7 +534,7 @@ let update_status_line () =
let gen_status_line = !status_line_generator () in
match gen_status_line with
| { message = None; _ } ->
Console.hide_status_line ();
Console.clear_status_line ();
| { message = Some status_line; show_jobs } ->
let status_line =
if show_jobs then
Expand Down Expand Up @@ -667,7 +667,7 @@ end = struct
let* () = Fiber.yield () in
let count = Event.pending_jobs () in
if count = 0 then begin
Console.hide_status_line ();
Console.clear_status_line ();
Fiber.return Done
end else begin
update_status_line ();
Expand Down
21 changes: 12 additions & 9 deletions src/stdune/console.ml
Original file line number Diff line number Diff line change
Expand Up @@ -25,8 +25,9 @@ module T = struct
if t.status_line_len > 0 then
Printf.eprintf "\r%*s\r" t.status_line_len ""

let show_status_line s =
Ansi_color.prerr s
let show_status_line t =
if t.status_line_len > 0 then
Ansi_color.prerr t.status_line

let update_status_line t status_line =
if t.display = Progress then begin
Expand All @@ -37,27 +38,29 @@ module T = struct
String.length (Format.asprintf "%a" Pp.render_ignore_tags status_line)
in
hide_status_line t;
show_status_line status_line;
flush stderr;
t.status_line <- status_line;
t.status_line_len <- status_line_len
t.status_line_len <- status_line_len;
show_status_line t;
flush stderr;
end

let print t msg =
hide_status_line t;
prerr_string msg;
show_status_line t.status_line;
show_status_line t;
flush stderr

let print_user_message t ?config msg =
hide_status_line t;
Option.iter msg.User_message.loc ~f:(Loc.print Format.err_formatter);
User_message.prerr ?config { msg with loc = None };
show_status_line t.status_line;
show_status_line t;
flush stderr

let hide_status_line t =
let clear_status_line t =
hide_status_line t;
t.status_line <- Pp.nop;
t.status_line_len <- 0;
flush stderr

end
Expand All @@ -77,7 +80,7 @@ let t () =
let display () = (t ()).display

let update_status_line status_line = T.update_status_line (t ()) status_line
let hide_status_line () = T.hide_status_line (t ())
let clear_status_line () = T.clear_status_line (t ())
let print msg =
match !t_var with
| None -> Printf.eprintf "%s%!" msg
Expand Down
9 changes: 6 additions & 3 deletions src/stdune/console.mli
Original file line number Diff line number Diff line change
@@ -1,3 +1,6 @@
(** Manage printing user message and keeping progress information in the status line *)


module Display : sig

type t =
Expand All @@ -23,9 +26,9 @@ val init : Display.t -> unit
(** Everything below this line requires [init] to have been called earlier. *)

val update_status_line : User_message.Style.t Pp.t -> unit
(** Update the status line if the display is in progress mode *)
(** Update the status line if the display is in progress mode. *)

val hide_status_line : unit -> unit
(** Hide the status line *)
val clear_status_line : unit -> unit
(** Clear the status line *)

val display : unit -> Display.t

0 comments on commit 5606d47

Please sign in to comment.