Skip to content

Commit

Permalink
fix: do not re-render unless needed (#7186)
Browse files Browse the repository at this point in the history
Previously, dune would re-render on every frame even when it wasn't
necessary.

Now, dune will make sure we have at least one modification before
re-rendering

Signed-off-by: Rudi Grinberg <me@rgrinberg.com>
  • Loading branch information
rgrinberg authored Feb 26, 2023
1 parent 89d73f2 commit 0c4504d
Show file tree
Hide file tree
Showing 3 changed files with 17 additions and 3 deletions.
3 changes: 3 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
@@ -1,6 +1,9 @@
Unreleased
----------

- Do not re-render UI on every frame if the UI doesn't change (#7186, fix
#7184, @rgrinberg)

- Fix preludes not being recorded as dependencies in the `(mdx)` stanza (#7109,
fixes #7077, @emillon).

Expand Down
16 changes: 13 additions & 3 deletions src/dune_threaded_console/dune_threaded_console.ml
Original file line number Diff line number Diff line change
Expand Up @@ -16,10 +16,12 @@ let make (module Base : S) : (module Dune_console.Backend) =
; status_line = None
; finished = false
; finish_requested = false
; dirty = true
}

let finish () =
Mutex.lock mutex;
state.dirty <- true;
state.finish_requested <- true;
while not state.finished do
Condition.wait finish_cv mutex
Expand All @@ -28,25 +30,29 @@ let make (module Base : S) : (module Dune_console.Backend) =

let print_user_message m =
Mutex.lock mutex;
state.dirty <- true;
Queue.push state.messages m;
Mutex.unlock mutex

let set_status_line sl =
Mutex.lock mutex;
state.dirty <- true;
state.status_line <- sl;
Mutex.unlock mutex

let print_if_no_status_line _msg = ()

let reset () =
Mutex.lock mutex;
state.dirty <- true;
Queue.clear state.messages;
state.status_line <- None;
Base.reset ();
Mutex.unlock mutex

let reset_flush_history () =
Mutex.lock mutex;
state.dirty <- true;
Queue.clear state.messages;
state.status_line <- None;
Base.reset_flush_history ();
Expand Down Expand Up @@ -84,9 +90,13 @@ let make (module Base : S) : (module Dune_console.Backend) =
events and sleep for the remaining time. *)
while true do
Mutex.lock mutex;
Base.render state;
let finish_requested = state.finish_requested in
if finish_requested then raise_notrace Exit;
(match state.dirty with
| false -> ()
| true ->
Base.render state;
let finish_requested = state.finish_requested in
if finish_requested then raise_notrace Exit;
state.dirty <- false);
Mutex.unlock mutex;
let now = Unix.gettimeofday () in
let elapsed = now -. !last in
Expand Down
1 change: 1 addition & 0 deletions src/dune_threaded_console/dune_threaded_console_intf.ml
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,7 @@ type state =
; mutable finish_requested : bool
; mutable finished : bool
; mutable status_line : User_message.Style.t Pp.t option
; mutable dirty : bool
}

(** [Threaded] is the interface for user interfaces that are rendered in a
Expand Down

0 comments on commit 0c4504d

Please sign in to comment.