Skip to content

Commit 0cbfa09

Browse files
committed
tui: add more features
We add more features to Dune's TUI. Using Lwd and Nottui we expand on the Notty TUI by creating an interactive UI for dune_console. - The user can now view all the messages and scroll in the console. - Each message can be minimized or expanded by clicking. - There is a help screen showing which buttons can be pressed. - The build status is printed in a status bar at the top. - And more. Signed-off-by: Ali Caglayan <alizter@gmail.com>
1 parent ca625ad commit 0cbfa09

File tree

20 files changed

+989
-137
lines changed

20 files changed

+989
-137
lines changed

boot/libs.ml

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -74,9 +74,11 @@ let local_libraries =
7474
None)
7575
; ("src/dune_vcs", Some "Dune_vcs", false, None)
7676
; ("src/dune_threaded_console", Some "Dune_threaded_console", false, None)
77+
; ("vendor/lwd/lwd", None, false, None)
7778
; ("vendor/notty/src", None, true, None)
7879
; ("vendor/notty/src-unix", None, true, None)
79-
; ("src/dune_tui", Some "Dune_tui", false, None)
80+
; ("vendor/lwd/nottui", None, false, None)
81+
; ("src/dune_tui", Some "Dune_tui", true, None)
8082
; ("src/dune_config_file", Some "Dune_config_file", false, None)
8183
; ("src/dune_shared_cache", Some "Dune_shared_cache", false, None)
8284
; ("src/scheme", Some "Scheme", false, None)

doc/changes/8429.md

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,4 @@
1+
- Added experimental `--display tui` option for Dune that opens an interactive
2+
Terminal User Interface (TUI) when Dune is running. Press '?' to open up a
3+
help screen when running for more information. (#8429, @Alizter and
4+
@rgrinberg)

otherlibs/stdune/src/ansi_color.ml

Lines changed: 132 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,7 @@ module RGB8 : sig
44
val to_dyn : t -> Dyn.t
55
val of_int : int -> t
66
val to_int : t -> int
7+
val compare : t -> t -> Ordering.t
78

89
(** This is only used internally. *)
910
val write_to_buffer : Buffer.t -> t -> unit
@@ -13,6 +14,7 @@ end = struct
1314
let to_dyn t = Dyn.Int (int_of_char t)
1415
let of_int t = char_of_int (t land 0xFF)
1516
let to_int t = int_of_char t
17+
let compare t1 t2 = Char.compare t1 t2
1618

1719
let write_to_buffer buf c =
1820
Buffer.add_string buf "38;5;";
@@ -24,6 +26,7 @@ module RGB24 : sig
2426
type t
2527

2628
val to_dyn : t -> Dyn.t
29+
val compare : t -> t -> Ordering.t
2730
val red : t -> int
2831
val green : t -> int
2932
val blue : t -> int
@@ -34,6 +37,7 @@ module RGB24 : sig
3437
end = struct
3538
type t = int
3639

40+
let compare = Int.compare
3741
let red t = Int.shift_right t 16 land 0xFF
3842
let green t = Int.shift_right t 8 land 0xFF
3943
let blue t = t land 0xFF
@@ -186,6 +190,134 @@ module Style = struct
186190
| `Underline -> Dyn.variant "Underline" []
187191
;;
188192

193+
let compare (t1 : t) (t2 : t) : Ordering.t =
194+
match t1, t2 with
195+
| `Fg_default, `Fg_default -> Eq
196+
| `Fg_default, _ -> Lt
197+
| _, `Fg_default -> Gt
198+
| `Fg_black, `Fg_black -> Eq
199+
| `Fg_black, _ -> Lt
200+
| _, `Fg_black -> Gt
201+
| `Fg_red, `Fg_red -> Eq
202+
| `Fg_red, _ -> Lt
203+
| _, `Fg_red -> Gt
204+
| `Fg_green, `Fg_green -> Eq
205+
| `Fg_green, _ -> Lt
206+
| _, `Fg_green -> Gt
207+
| `Fg_yellow, `Fg_yellow -> Eq
208+
| `Fg_yellow, _ -> Lt
209+
| _, `Fg_yellow -> Gt
210+
| `Fg_blue, `Fg_blue -> Eq
211+
| `Fg_blue, _ -> Lt
212+
| _, `Fg_blue -> Gt
213+
| `Fg_magenta, `Fg_magenta -> Eq
214+
| `Fg_magenta, _ -> Lt
215+
| _, `Fg_magenta -> Gt
216+
| `Fg_cyan, `Fg_cyan -> Eq
217+
| `Fg_cyan, _ -> Lt
218+
| _, `Fg_cyan -> Gt
219+
| `Fg_white, `Fg_white -> Eq
220+
| `Fg_white, _ -> Lt
221+
| _, `Fg_white -> Gt
222+
| `Fg_bright_black, `Fg_bright_black -> Eq
223+
| `Fg_bright_black, _ -> Lt
224+
| _, `Fg_bright_black -> Gt
225+
| `Fg_bright_red, `Fg_bright_red -> Eq
226+
| `Fg_bright_red, _ -> Lt
227+
| _, `Fg_bright_red -> Gt
228+
| `Fg_bright_green, `Fg_bright_green -> Eq
229+
| `Fg_bright_green, _ -> Lt
230+
| _, `Fg_bright_green -> Gt
231+
| `Fg_bright_yellow, `Fg_bright_yellow -> Eq
232+
| `Fg_bright_yellow, _ -> Lt
233+
| _, `Fg_bright_yellow -> Gt
234+
| `Fg_bright_blue, `Fg_bright_blue -> Eq
235+
| `Fg_bright_blue, _ -> Lt
236+
| _, `Fg_bright_blue -> Gt
237+
| `Fg_bright_magenta, `Fg_bright_magenta -> Eq
238+
| `Fg_bright_magenta, _ -> Lt
239+
| _, `Fg_bright_magenta -> Gt
240+
| `Fg_bright_cyan, `Fg_bright_cyan -> Eq
241+
| `Fg_bright_cyan, _ -> Lt
242+
| _, `Fg_bright_cyan -> Gt
243+
| `Fg_bright_white, `Fg_bright_white -> Eq
244+
| `Fg_bright_white, _ -> Lt
245+
| _, `Fg_bright_white -> Gt
246+
| `Fg_8_bit_color c1, `Fg_8_bit_color c2 -> RGB8.compare c1 c2
247+
| `Fg_8_bit_color _, _ -> Lt
248+
| _, `Fg_8_bit_color _ -> Gt
249+
| `Fg_24_bit_color c1, `Fg_24_bit_color c2 -> RGB24.compare c1 c2
250+
| `Fg_24_bit_color _, _ -> Lt
251+
| _, `Fg_24_bit_color _ -> Gt
252+
| `Bg_default, `Bg_default -> Eq
253+
| `Bg_default, _ -> Lt
254+
| _, `Bg_default -> Gt
255+
| `Bg_black, `Bg_black -> Eq
256+
| `Bg_black, _ -> Lt
257+
| _, `Bg_black -> Gt
258+
| `Bg_red, `Bg_red -> Eq
259+
| `Bg_red, _ -> Lt
260+
| _, `Bg_red -> Gt
261+
| `Bg_green, `Bg_green -> Eq
262+
| `Bg_green, _ -> Lt
263+
| _, `Bg_green -> Gt
264+
| `Bg_yellow, `Bg_yellow -> Eq
265+
| `Bg_yellow, _ -> Lt
266+
| _, `Bg_yellow -> Gt
267+
| `Bg_blue, `Bg_blue -> Eq
268+
| `Bg_blue, _ -> Lt
269+
| _, `Bg_blue -> Gt
270+
| `Bg_magenta, `Bg_magenta -> Eq
271+
| `Bg_magenta, _ -> Lt
272+
| _, `Bg_magenta -> Gt
273+
| `Bg_cyan, `Bg_cyan -> Eq
274+
| `Bg_cyan, _ -> Lt
275+
| _, `Bg_cyan -> Gt
276+
| `Bg_white, `Bg_white -> Eq
277+
| `Bg_white, _ -> Lt
278+
| _, `Bg_white -> Gt
279+
| `Bg_bright_black, `Bg_bright_black -> Eq
280+
| `Bg_bright_black, _ -> Lt
281+
| _, `Bg_bright_black -> Gt
282+
| `Bg_bright_red, `Bg_bright_red -> Eq
283+
| `Bg_bright_red, _ -> Lt
284+
| _, `Bg_bright_red -> Gt
285+
| `Bg_bright_green, `Bg_bright_green -> Eq
286+
| `Bg_bright_green, _ -> Lt
287+
| _, `Bg_bright_green -> Gt
288+
| `Bg_bright_yellow, `Bg_bright_yellow -> Eq
289+
| `Bg_bright_yellow, _ -> Lt
290+
| _, `Bg_bright_yellow -> Gt
291+
| `Bg_bright_blue, `Bg_bright_blue -> Eq
292+
| `Bg_bright_blue, _ -> Lt
293+
| _, `Bg_bright_blue -> Gt
294+
| `Bg_bright_magenta, `Bg_bright_magenta -> Eq
295+
| `Bg_bright_magenta, _ -> Lt
296+
| _, `Bg_bright_magenta -> Gt
297+
| `Bg_bright_cyan, `Bg_bright_cyan -> Eq
298+
| `Bg_bright_cyan, _ -> Lt
299+
| _, `Bg_bright_cyan -> Gt
300+
| `Bg_bright_white, `Bg_bright_white -> Eq
301+
| `Bg_bright_white, _ -> Lt
302+
| _, `Bg_bright_white -> Gt
303+
| `Bg_8_bit_color c1, `Bg_8_bit_color c2 -> RGB8.compare c1 c2
304+
| `Bg_8_bit_color _, _ -> Lt
305+
| _, `Bg_8_bit_color _ -> Gt
306+
| `Bg_24_bit_color c1, `Bg_24_bit_color c2 -> RGB24.compare c1 c2
307+
| `Bg_24_bit_color _, _ -> Lt
308+
| _, `Bg_24_bit_color _ -> Gt
309+
| `Bold, `Bold -> Eq
310+
| `Bold, _ -> Lt
311+
| _, `Bold -> Gt
312+
| `Dim, `Dim -> Eq
313+
| `Dim, _ -> Lt
314+
| _, `Dim -> Gt
315+
| `Italic, `Italic -> Eq
316+
| `Italic, _ -> Lt
317+
| _, `Italic -> Gt
318+
| `Underline, `Underline -> Eq
319+
;;
320+
189321
module Of_ansi_code = struct
190322
type code = t
191323

otherlibs/stdune/src/ansi_color.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -68,6 +68,7 @@ module Style : sig
6868
]
6969

7070
val to_dyn : t -> Dyn.t
71+
val compare : t -> t -> Ordering.t
7172

7273
(** Ansi escape sequence that set the terminal style to exactly these styles *)
7374
val escape_sequence : t list -> string

otherlibs/stdune/src/char.ml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -11,3 +11,4 @@ let is_lowercase_hex = function
1111
;;
1212

1313
let[@inline always] hash c = Int.hash (code c)
14+
let compare x y = Ordering.of_int (compare x y)

otherlibs/stdune/src/char.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -9,3 +9,4 @@ val is_digit : t -> bool
99
val is_lowercase_hex : t -> bool
1010

1111
val hash : t -> int
12+
val compare : t -> t -> Ordering.t

otherlibs/stdune/src/stdune.ml

Lines changed: 10 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -22,7 +22,16 @@ module Map = Map
2222
module Option = Option
2323
module Or_exn = Or_exn
2424
module Ordering = Ordering
25-
module Pp = Pp
25+
26+
module Pp = struct
27+
include Pp
28+
29+
(** This version of [Pp.compare] uses [Ordering.t] rather than returning an [int]. *)
30+
let compare ~compare x y =
31+
Ordering.of_int (Pp.compare (fun a b -> Ordering.to_int (compare a b)) x y)
32+
;;
33+
end
34+
2635
module Result = Result
2736
module Set = Set
2837
module Signal = Signal

otherlibs/stdune/src/user_message.ml

Lines changed: 38 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,44 @@ module Style = struct
1212
| Debug
1313
| Success
1414
| Ansi_styles of Ansi_color.Style.t list
15+
16+
let compare t1 t2 : Ordering.t =
17+
match t1, t2 with
18+
| Loc, Loc -> Eq
19+
| Loc, _ -> Lt
20+
| _, Loc -> Gt
21+
| Error, Error -> Eq
22+
| Error, _ -> Lt
23+
| _, Error -> Gt
24+
| Warning, Warning -> Eq
25+
| Warning, _ -> Lt
26+
| _, Warning -> Gt
27+
| Kwd, Kwd -> Eq
28+
| Kwd, _ -> Lt
29+
| _, Kwd -> Gt
30+
| Id, Id -> Eq
31+
| Id, _ -> Lt
32+
| _, Id -> Gt
33+
| Prompt, Prompt -> Eq
34+
| Prompt, _ -> Lt
35+
| _, Prompt -> Gt
36+
| Hint, Hint -> Eq
37+
| Hint, _ -> Lt
38+
| _, Hint -> Gt
39+
| Details, Details -> Eq
40+
| Details, _ -> Lt
41+
| _, Details -> Gt
42+
| Ok, Ok -> Eq
43+
| Ok, _ -> Lt
44+
| _, Ok -> Gt
45+
| Debug, Debug -> Eq
46+
| Debug, _ -> Lt
47+
| _, Debug -> Gt
48+
| Success, Success -> Eq
49+
| Success, _ -> Lt
50+
| _, Success -> Gt
51+
| Ansi_styles _, Ansi_styles _ -> Eq
52+
;;
1553
end
1654

1755
module Annots = struct

otherlibs/stdune/src/user_message.mli

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -21,6 +21,8 @@ module Style : sig
2121
| Debug
2222
| Success
2323
| Ansi_styles of Ansi_color.Style.t list
24+
25+
val compare : t -> t -> Ordering.t
2426
end
2527

2628
module Annots : sig

0 commit comments

Comments
 (0)