Skip to content

Commit

Permalink
feature: new terminal persistence mode
Browse files Browse the repository at this point in the history
[clear-on-rebuild-and-flush-history] is added for situations where in
fact we do prefer to flush the terminal history. Note that some
emulators will maintain the history regardless.

Signed-off-by: Rudi Grinberg <[email protected]>

ps-id: 2ecb488c-d1ae-4ef8-947a-649091419b2f
  • Loading branch information
rgrinberg committed Aug 10, 2022
1 parent 1928439 commit 85102cd
Show file tree
Hide file tree
Showing 6 changed files with 35 additions and 3 deletions.
4 changes: 4 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
@@ -1,6 +1,10 @@
3.5.0 (unreleased)
------------------

- Add a terminal persistence mode that attempts to clear the terminal history.
It is enabled by setting terminal persistence to
`clear-on-rebuild-and-flush-history` (#6065, @rgrinberg)

- Disallow generating targets in sub direcories in inferred rules. The check to
forbid this was accidentally done only for manually specified targets (#6031,
@rgrinberg)
Expand Down
1 change: 1 addition & 0 deletions bin/import.ml
Original file line number Diff line number Diff line change
Expand Up @@ -79,6 +79,7 @@ module Scheduler = struct
| false -> (
match dune_config.terminal_persistence with
| Clear_on_rebuild -> Console.reset ()
| Clear_on_rebuild_and_flush_history -> Console.reset_flush_history ()
| Preserve ->
let message =
sprintf "********** NEW BUILD (%s) **********"
Expand Down
18 changes: 18 additions & 0 deletions otherlibs/stdune/console.ml
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,8 @@ module Backend = struct
val print_if_no_status_line : User_message.Style.t Pp.t -> unit

val reset : unit -> unit

val reset_flush_history : unit -> unit
end

type t = (module S)
Expand All @@ -26,6 +28,8 @@ module Backend = struct
(Pp.seq (Pp.map_tags msg ~f:User_message.Print_config.default) Pp.cut)

let reset () = prerr_string "\x1b[H\x1b[2J"

let reset_flush_history () = prerr_string "\x1bc"
end

module Dumb : S = struct
Expand All @@ -42,6 +46,10 @@ module Backend = struct
let reset () =
reset ();
flush stderr

let reset_flush_history () =
reset_flush_history ();
flush stderr
end

module Progress : S = struct
Expand Down Expand Up @@ -79,6 +87,8 @@ module Backend = struct
flush stderr

let reset () = Dumb.reset ()

let reset_flush_history () = Dumb.reset_flush_history ()
end

let dumb = (module Dumb : S)
Expand Down Expand Up @@ -106,6 +116,10 @@ module Backend = struct
let reset () =
A.reset ();
B.reset ()

let reset_flush_history () =
A.reset_flush_history ();
B.reset_flush_history ()
end : S)
end

Expand All @@ -129,6 +143,10 @@ let reset () =
let (module M : Backend.S) = !Backend.main in
M.reset ()

let reset_flush_history () =
let (module M : Backend.S) = !Backend.main in
M.reset_flush_history ()

module Status_line = struct
type t =
| Live of (unit -> User_message.Style.t Pp.t)
Expand Down
2 changes: 2 additions & 0 deletions otherlibs/stdune/console.mli
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,8 @@ module Backend : sig

(** Reset the log output *)
val reset : unit -> unit

val reset_flush_history : unit -> unit
end

type t = (module S)
Expand Down
12 changes: 9 additions & 3 deletions src/dune_config/dune_config.ml
Original file line number Diff line number Diff line change
Expand Up @@ -16,15 +16,21 @@ module Terminal_persistence = struct
type t =
| Preserve
| Clear_on_rebuild
| Clear_on_rebuild_and_flush_history

let all = [ ("preserve", Preserve); ("clear-on-rebuild", Clear_on_rebuild) ]
let all =
[ ("preserve", Preserve)
; ("clear-on-rebuild", Clear_on_rebuild)
; ("clear-on-rebuild-and-flush-history", Clear_on_rebuild_and_flush_history)
]

let to_dyn = function
| Preserve -> Dyn.Variant ("Preserve", [])
| Clear_on_rebuild -> Dyn.Variant ("Clear_on_rebuild", [])
| Clear_on_rebuild_and_flush_history ->
Variant ("Clear_on_rebuild_and_flush_history", [])

let decode =
enum [ ("perserve", Preserve); ("clear-on-rebuild", Clear_on_rebuild) ]
let decode = enum all
end

module Concurrency = struct
Expand Down
1 change: 1 addition & 0 deletions src/dune_config/dune_config.mli
Original file line number Diff line number Diff line change
Expand Up @@ -44,6 +44,7 @@ module Terminal_persistence : sig
type t =
| Preserve
| Clear_on_rebuild
| Clear_on_rebuild_and_flush_history

val all : (string * t) list
end
Expand Down

0 comments on commit 85102cd

Please sign in to comment.