Skip to content

Commit

Permalink
Ignore ESC K VT code emitted by GCC
Browse files Browse the repository at this point in the history
GCC emits coloured output when it's printing to a tty, and coloured
output is disabled e.g., when the output is piped.
When GCC is called by Dune, it doesn't output ANSI sequences.

However, that behaviour can be forced with the
`-fdiagnostics-color=always` flag. GCC has the particularity that
after each color sequence, it will also emit a ESC K "erase from the
cursor the end of line".

Dune did not support this sequence, and this messes up the output. The
sequence does not seem important; clang doesn't use it, and it
clearing the line means that it would already have been written to,
which seems unlikely. So, this patch simply ignores that sequence.

Closes #3263.

Signed-off-by: Antonin Décimo <antonin@tarides.com>
  • Loading branch information
MisterDA committed Jan 15, 2021
1 parent a7ab861 commit a56cbce
Show file tree
Hide file tree
Showing 2 changed files with 14 additions and 0 deletions.
8 changes: 8 additions & 0 deletions src/stdune/ansi_color.ml
Original file line number Diff line number Diff line change
Expand Up @@ -83,6 +83,12 @@ module Style = struct
Printf.sprintf "\027[%sm" (String.concat l ~sep:";")
end

module Codes = struct
type t = char

let erase_from_cursor_to_eol = 'K'
end

let term_supports_color =
lazy
( match Stdlib.Sys.getenv "TERM" with
Expand Down Expand Up @@ -165,6 +171,8 @@ let parse_line str styles =
let seq_start = seq_start + 2 in
if seq_start >= len || str.[seq_start - 1] <> '[' then
(styles, acc)
else if str.[seq_start] = Codes.erase_from_cursor_to_eol then
loop styles (seq_start + 1) acc
else
match String.index_from str seq_start 'm' with
| None -> (styles, acc)
Expand Down
6 changes: 6 additions & 0 deletions src/stdune/ansi_color.mli
Original file line number Diff line number Diff line change
Expand Up @@ -79,6 +79,12 @@ module Style : sig
val escape_sequence : t list -> string
end

module Codes : sig
type t

val erase_from_cursor_to_eol : t
end

(** Print to [Format.std_formatter] *)
val print : Style.t list Pp.t -> unit

Expand Down

0 comments on commit a56cbce

Please sign in to comment.