File 0297-erts-Fix-ttsl-driver-xn-followed-by-nl.patch of Package erlang

From d6c2adf927f4917eb851d8e29df71a5efe1890f7 Mon Sep 17 00:00:00 2001
From: Lukas Larsson <lukas@erlang.org>
Date: Tue, 11 Jan 2022 17:19:49 +0100
Subject: [PATCH] erts: Fix ttsl driver xn followed by nl

The terminal would incorrectly emit " \b" when the next
wrapping character was a \r|\n.

I think this is the correct behaviour, but it is hard to
test on all terminals.

Closes #5403
---
 erts/emulator/drivers/unix/ttsl_drv.c       | 33 +++++++++++++------
 lib/kernel/test/interactive_shell_SUITE.erl | 36 +++++++++++++++++++--
 2 files changed, 58 insertions(+), 11 deletions(-)

diff --git a/erts/emulator/drivers/unix/ttsl_drv.c b/erts/emulator/drivers/unix/ttsl_drv.c
index 7108b8bb07..eb477763b4 100644
--- a/erts/emulator/drivers/unix/ttsl_drv.c
+++ b/erts/emulator/drivers/unix/ttsl_drv.c
@@ -152,7 +152,7 @@ static int ins_chars(byte *,int);
 static int del_chars(int);
 static int step_over_chars(int);
 static int insert_buf(byte*,int);
-static int write_buf(Uint32 *,int);
+static int write_buf(Uint32 *,int,int);
 static int outc(int c);
 static int move_cursor(int,int);
 static int cp_pos_to_col(int cp_pos);
@@ -942,7 +942,7 @@ static int put_chars(byte *s, int l)
     if (lpos > llen)
         llen = lpos;
     if (n > 0)
-      write_buf(lbuf + lpos - n, n);
+        write_buf(lbuf + lpos - n, n, 0);
     return TRUE;
 }
 
@@ -981,7 +981,7 @@ static int ins_chars(byte *s, int l)
 	driver_free(tbuf);
     }
     llen += n;
-    write_buf(lbuf + (lpos - n), llen - (lpos - n));
+    write_buf(lbuf + (lpos - n), llen - (lpos - n), 0);
     move_cursor(llen, lpos);
     return TRUE;
 }
@@ -1011,7 +1011,7 @@ static int del_chars(int n)
 	    memmove(lbuf + lpos, lbuf + pos, r * sizeof(Uint32));
 	llen -= l;
 	/* Write out characters after, blank the tail and jump back to lpos. */
-	write_buf(lbuf + lpos, r);
+	write_buf(lbuf + lpos, r, 0);
 	for (i = gcs ; i > 0; --i)
 	  outc(' ');
 	if (xn && COL(cp_pos_to_col(llen)+gcs) == 0)
@@ -1031,7 +1031,7 @@ static int del_chars(int n)
 	lpos -= l;
 	llen -= l;
 	/* Write out characters after, blank the tail and jump back to lpos. */
-	write_buf(lbuf + lpos, r);
+	write_buf(lbuf + lpos, r, 0);
 	for (i = gcs ; i > 0; --i)
           outc(' ');
         if (xn && COL(cp_pos_to_col(llen)+gcs) == 0)
@@ -1101,7 +1101,7 @@ static int insert_buf(byte *s, int n)
 	    DEBUGLOG(("insert_buf: ANSI Escape: \\e"));
 	    lbuf[lpos++] = (CONTROL_TAG | ((Uint32) ch));
 	} else if (ch == '\n' || ch == '\r') {
-	    write_buf(lbuf + buffpos, lpos - buffpos);
+	    write_buf(lbuf + buffpos, lpos - buffpos, 1);
                 outc('\r');
                 if (ch == '\n')
                     outc('\n');
@@ -1128,7 +1128,7 @@ static int insert_buf(byte *s, int n)
  * occur normally.
  */
 
-static int write_buf(Uint32 *s, int n)
+static int write_buf(Uint32 *s, int n, int next_char_is_crnl)
 {
     byte ubuf[4];
     int ubytes = 0, i;
@@ -1136,6 +1136,8 @@ static int write_buf(Uint32 *s, int n)
 
     update_cols();
 
+    DEBUGLOG(("write_buf(%d, %d)",n,next_char_is_crnl));
+
     while (n > 0) {
 	if (!(*s & TAG_MASK) ) {
 	    if (utf8_mode) {
@@ -1199,9 +1201,22 @@ static int write_buf(Uint32 *s, int n)
 	    --s;
 	}
     }
-    /* Check landed in first column of new line and have 'xn' bug. */
+    /* Check landed in first column of new line and have 'xn' bug.
+     *   https://www.gnu.org/software/termutils/manual/termcap-1.3/html_node/termcap_27.html
+     *
+     * The 'xn' bugs (from what I understand) is that the terminal cursor does
+     * not wrap to the next line when the current line is full. For example:
+     *
+     * If the terminal column size is 20 and we output 20 'a' the cursor will be
+     * on row 1, column 21. While we actually want it at row 2 column 0. So to
+     * achieve this the code below emits " \b", which will move the cursor to the
+     * correct place.
+     *
+     * We should not apply this 'xn' workaround if we know that the next character
+     * to be emitted is a cr|nl as that will wrap by itself.
+     */
     n = s - lbuf;
-    if (xn && n != 0 && COL(cp_pos_to_col(n)) == 0) {
+    if (!next_char_is_crnl && xn && n != 0 && COL(cp_pos_to_col(n)) == 0) {
 	if (n >= llen) {
 	    outc(' ');
 	} else if (lastput == 0) { /* A multibyte UTF8 character */
diff --git a/lib/kernel/test/interactive_shell_SUITE.erl b/lib/kernel/test/interactive_shell_SUITE.erl
index 14b48313b6..c480f0d87a 100644
--- a/lib/kernel/test/interactive_shell_SUITE.erl
+++ b/lib/kernel/test/interactive_shell_SUITE.erl
@@ -24,7 +24,7 @@
          init_per_group/2, end_per_group/2,
          init_per_testcase/2, end_per_testcase/2,
 	 get_columns_and_rows/1, exit_initial/1, job_control_local/1,
-	 job_control_remote/1,stop_during_init/1,
+	 job_control_remote/1,stop_during_init/1,wrap/1,
          shell_history/1, shell_history_resize/1, shell_history_eaccess/1,
          shell_history_repair/1, shell_history_repair_corrupt/1,
          shell_history_corrupt/1,
@@ -46,7 +46,7 @@ all() ->
     [get_columns_and_rows_escript,get_columns_and_rows,
      exit_initial, job_control_local,
      job_control_remote, job_control_remote_noshell,
-     ctrl_keys, stop_during_init,
+     ctrl_keys, stop_during_init, wrap,
      {group, shell_history},
      {group, remsh}].
 
@@ -295,6 +295,38 @@ stop_during_init(Config) when is_list(Config) ->
             ok
     end.
 
+%% This testcase tests that the correct wrapping characters are added
+%% When a terminal has the xn flag set, it means that wrapping may not
+%% work as expected and historically the ttysl driver has always inserted
+%% a " \b" (i.e. space + backspace) when an output string ends on that line
+%% in order for the cursor to be at col 0 on the next line instead of col max
+%% on the current line.
+%%
+%% This caused problems when a string was `columns` long and then ended in "\r\n"
+%% as it would first wrap due to " \b" and then output "\r\n" that cause a double
+%% newline to happen.
+%%
+%% This testcase tests that we get a " \b" when we should and we get a "\r\n" when
+%% we should.
+wrap(Config) when is_list(Config) ->
+    case proplists:get_value(default_shell, Config) of
+        new ->
+            As = lists:duplicate(20,"a"),
+            rtnode([{putline, "io:columns()."},
+                    {expect, "{ok,20}\r\n"},
+                    {putline, ["io:format(\"~s\",[lists:duplicate(20,\"a\")])."]},
+                    {expect, As ++ " \b"},
+                    {putline, ["io:format(\"~s~n~s\",[lists:duplicate(20,\"a\"),lists:duplicate(20,\"a\")])."]},
+                    {expect, As ++ "\r\n" ++ As ++ " \b"}
+                   ],
+                   [],
+                   "stty rows 40; stty columns 20; ",
+                   [""]);
+        _ ->
+            ok
+    end,
+    ok.
+
 %% This testcase tests that shell_history works as it should.
 %% We use Ctrl + P = Cp=[$\^p] in order to navigate up
 %% We use Ctrl + N = Cp=[$\^n] in order to navigate down
-- 
2.31.1

openSUSE Build Service is sponsored by